Skip to content

Commit

Permalink
if we move #mustBeBoolean to ProtoObject, the mechanism to get #ifTru…
Browse files Browse the repository at this point in the history
…e: sends will work for subclasses of ProtoObject. As this is used often for proxies, having that mechanism in ProtoObject makes sense, I think.
  • Loading branch information
MarcusDenker committed Nov 21, 2019
1 parent 5e256b0 commit 2b3d79e
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 39 deletions.
36 changes: 0 additions & 36 deletions src/Kernel/Object.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1400,42 +1400,6 @@ Object >> longPrintStringLimitedTo: aLimitValue [
^ str isEmpty ifTrue: [self printString, String cr] ifFalse: [str]
]

{ #category : #'block support' }
Object >> mustBeBoolean [
"Catches attempts to test truth of non-Booleans. This message is sent from the VM. The sending context is rewound to just before the jump causing this exception."
^ Boolean mustBeBooleanDeOptimize
ifTrue: [ self mustBeBooleanDeOptimizeIn: thisContext sender ]
ifFalse: [ self mustBeBooleanIn: thisContext sender ]
]

{ #category : #'block support' }
Object >> mustBeBooleanIn: context [
"context is the where the non-boolean error occurred. Rewind context to before jump then raise error."

"Some constructs are optimized in the compiler :
#whileTrue:
#whileFalse:
#ifTrue:
#ifFalse:
#ifTrue:ifFalse:
#ifFalse:ifTrue:
So you cannot by default use them on non boolean objects."

"If you really need to use optimized constructs, you can enable Opal compiler and do one of the following :
- recompile your method with the pragma : <compilerOptions: #(+ optIlineNone)>
- recompile your class with the method : MyClass class>>compiler
^ super compiler options: #(+ optIlineNone)
- enable the option mustBeBooleanDeOptimize to call mustBeBooleanDeOptimizeIn: instead of this method "

| proceedValue |

context skipBackBeforeJump.
proceedValue := NonBooleanReceiver new
object: self;
signal: 'proceed for truth.'.
^ proceedValue ~~ false
]

{ #category : #dependencies }
Object >> myDependents [
"Private. Answer a list of all the receiver's dependents."
Expand Down
36 changes: 36 additions & 0 deletions src/Kernel/ProtoObject.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -212,6 +212,42 @@ ProtoObject >> modificationForbiddenFor: selector value: value [

]

{ #category : #'block support' }
ProtoObject >> mustBeBoolean [
"Catches attempts to test truth of non-Booleans. This message is sent from the VM. The sending context is rewound to just before the jump causing this exception."
^ Boolean mustBeBooleanDeOptimize
ifTrue: [ self mustBeBooleanDeOptimizeIn: thisContext sender ]
ifFalse: [ self mustBeBooleanIn: thisContext sender ]
]

{ #category : #'block support' }
ProtoObject >> mustBeBooleanIn: context [
"context is the where the non-boolean error occurred. Rewind context to before jump then raise error."

"Some constructs are optimized in the compiler :
#whileTrue:
#whileFalse:
#ifTrue:
#ifFalse:
#ifTrue:ifFalse:
#ifFalse:ifTrue:
So you cannot by default use them on non boolean objects."

"If you really need to use optimized constructs, you can enable Opal compiler and do one of the following :
- recompile your method with the pragma : <compilerOptions: #(+ optIlineNone)>
- recompile your class with the method : MyClass class>>compiler
^ super compiler options: #(+ optIlineNone)
- enable the option mustBeBooleanDeOptimize to call mustBeBooleanDeOptimizeIn: instead of this method "

| proceedValue |

context skipBackBeforeJump.
proceedValue := NonBooleanReceiver new
object: self;
signal: 'proceed for truth.'.
^ proceedValue ~~ false
]

{ #category : #'memory scanning' }
ProtoObject >> nextInstance [
"Primitive. Answer the next instance after the receiver in the
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Extension { #name : #Object }
Extension { #name : #ProtoObject }

{ #category : #'*OpalCompiler-Core' }
Object >> mustBeBooleanCompileExpression: context andCache: cache [
ProtoObject >> mustBeBooleanCompileExpression: context andCache: cache [
"Permits to redefine methods inlined by compiler.
Take the ast node corresponding to the mustBeBoolean error, compile it on the fly and executes it as a DoIt. Then resume the execution of the context."

Expand Down Expand Up @@ -34,7 +34,7 @@ Object >> mustBeBooleanCompileExpression: context andCache: cache [
]

{ #category : #'*OpalCompiler-Core' }
Object >> mustBeBooleanDeOptimizeIn: context [
ProtoObject >> mustBeBooleanDeOptimizeIn: context [
"Permits to redefine methods inlined by compiler.
Take the ast node corresponding to the mustBeBoolean error, compile it on the fly and executes it as a DoIt. Then resume the execution of the context.
the generated DoIts are cached in the calling method"
Expand Down

0 comments on commit 2b3d79e

Please sign in to comment.