Skip to content

Commit

Permalink
Fixes to correctly translate ifNotNil: [:arg & variants.
Browse files Browse the repository at this point in the history
	
This makes Cog compile and run.
  • Loading branch information
guillep committed Jul 2, 2019
1 parent 65b06d3 commit 4f6c87d
Show file tree
Hide file tree
Showing 3 changed files with 62 additions and 0 deletions.
Expand Up @@ -7,6 +7,12 @@ Class {
#category : #'VMMakerCompatibilityForPharo6-FileDirectoryToFileSystem'
}

{ #category : #accessing }
FileDirectory class >> baseNameFor: aString [

^ aString asFileReference basename
]

{ #category : #'instance creation' }
FileDirectory class >> default [

Expand Down
Expand Up @@ -12,6 +12,9 @@ RBBlockNode >> asTranslatorNodeIn: aTMethod [
newS isStmtList
ifTrue: [statementList addAll: newS statements]
ifFalse: [statementList add: newS]].
statementList ifEmpty: [
statementList add: (TVariableNode new setName: 'nil').
].
^TStmtListNode new
setArguments: (arguments asArray collect: [:arg | arg name])
statements: statementList;
Expand Down
Expand Up @@ -55,6 +55,59 @@ RBMessageNode >> asTranslatorNodeIn: aTMethod [
yourself)
].

"If in the form of ifNil: [ :obj | ], replace that by an assignment and an ifFalse"
((usedSelector == #ifNotNil:) and: [ args first args notEmpty ]) ifTrue: [
^ TStmtListNode new
setArguments: #();
setStatements: {
TAssignmentNode new
setVariable: (TVariableNode new setName: args first args first)
expression: rcvrOrNil.

TSendNode new
setSelector: #ifFalse:
receiver: (TSendNode new
setSelector: #==
receiver: (TVariableNode new setName: args first args first)
arguments: {(TVariableNode new setName: 'nil')};
yourself)
arguments: {args first}
};
yourself ].

(#(#ifNotNil:ifNil: #ifNil:ifNotNil:) includes: usedSelector) ifTrue: [ | comparand expression blockWithPossibleArgument |
"We turn it always to an ifTrueIfFalse"
usedSelector = #ifNotNil:ifNil:
ifTrue: [ args := args reversed ].
blockWithPossibleArgument := args second.
expression := rcvrOrNil.
comparand := blockWithPossibleArgument args
ifEmpty: [ expression ]
ifNotEmpty: [ (TVariableNode new setName: blockWithPossibleArgument args first) ].

usedSelector := #ifTrue:ifFalse:.
rcvrOrNil := TSendNode new
setSelector: #==
receiver: comparand
arguments: { TVariableNode new setName: 'nil' }.

"If there is a variable we should epand the message as a statement"
blockWithPossibleArgument args notEmpty ifTrue: [
^ TStmtListNode new
setArguments: #();
setStatements: {
TAssignmentNode new
setVariable: (TVariableNode new setName: blockWithPossibleArgument args first)
expression: expression.

TSendNode new
setSelector: usedSelector
receiver: rcvrOrNil
arguments: args
};
yourself
] ].

(usedSelector == #ifNil:ifNotNil:) ifTrue: [
usedSelector := #ifTrue:ifFalse:.
rcvrOrNil := TSendNode new
Expand Down

0 comments on commit 4f6c87d

Please sign in to comment.