~smalltalkers/squeak/base-4.0-dev

« back to all changes in this revision

Viewing changes to Kernel/0--bootstrap.updates/0004-M6426-ifNotNil-monadic.1.0.st

  • Committer: Keith Hodges
  • Date: 2010-03-14 20:00:50 UTC
  • Revision ID: keith_hodges@yahoo.co.uk-20100314200050-8yh9wuvlln8qsbqr
Squeak4.0 ready to rock

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
'
 
 
b'Mantis 6426 - ifNotNil: [ :acceptsMonadicBlocik | ]'
 
 
b"'!"
 
 
b"!MessageNode methodsFor: 'code generation' stamp: 'vb 4/16/2007 11:40'!emitIfNil: stack on: strm value: forValue"
 
 
b'\t"Emits both ifNil: and ifNotNil: code."'
 
 
b'\t"vb: The comment seems out of date; #ifNotNil: is expanded to #ifNil:ifNotNil: in 3.9 so this method only handles the ifNil: case."'
 
 
b'\t| theNode theSize ifNotNilSelector |'
 
 
b'\ttheNode := arguments first.'
 
 
b'\ttheSize := sizes at: 1.'
 
 
b'\tifNotNilSelector := #ifNotNil:.'
 
 
b'\treceiver emitForValue: stack on: strm.'
 
 
b'\tforValue ifTrue: [strm nextPut: Dup. stack push: 1].'
 
 
b'\tstrm nextPut: LdNil. stack push: 1.'
 
 
b'\tequalNode emit: stack args: 1 on: strm.'
 
 
b'\tself '
 
 
b'\t\temitBranchOn: (selector key == ifNotNilSelector)'
 
 
b'\t\tdist: theSize '
 
 
b'\t\tpop: stack '
 
 
b'\t\ton: strm.'
 
 
b'\tpc := strm position.'
 
 
b'\tforValue '
 
 
b'\t\tifTrue: '
 
 
b'\t\t\t[strm nextPut: Pop. stack pop: 1.'
 
 
b'\t\t\ttheNode emitForEvaluatedValue: stack on: strm]\t'
 
 
b'\t\tifFalse: [theNode emitForEvaluatedEffect: stack on: strm].! !'
 
 
b"!MessageNode methodsFor: 'macro transformations' stamp: 'vb 4/16/2007 11:42'!transformIfNil: encoder"
 
 
b'\t"vb: Removed the original transformBoolean: which amounds to a test we perform in each of the branches below."'
 
 
b'\t(MacroSelectors at: special) = #ifNotNil:'
 
 
b'\tifTrue:'
 
 
b"\t\t[(self checkBlock: arguments first as: 'ifNotNil arg' from: encoder maxArgs: 1) ifFalse: [^ false]."
 
 
b'\t\t\t"Transform \'ifNotNil: [stuff]\' to \'ifNil: [nil] ifNotNil: [stuff]\'.'
 
 
b'\t\t\tSlightly better code and more consistent with decompilation."'
 
 
b'\t\tself noteSpecialSelector: #ifNil:ifNotNil:.'
 
 
b'\t\tselector := SelectorNode new key: (MacroSelectors at: special) code: #macro.'
 
 
b'\t\targuments := {BlockNode withJust: NodeNil. arguments first}.'
 
 
b"\t\t(self transform: encoder) ifFalse: [self error: 'compiler logic error']."
 
 
b'\t\t^ true]'
 
 
b'\tifFalse:'
 
 
b"\t\t[^ self checkBlock: arguments first as: 'ifNil arg' from: encoder]"
 
 
b'! !'
 
 
b"!MessageNode methodsFor: 'macro transformations' stamp: 'vb 4/16/2007 11:44'!transformIfNilIfNotNil: encoder"
 
 
b'\t"vb: Changed to support one-argument ifNotNil: branch. In the 1-arg case we transform the receiver to'
 
 
b'\t\t(var := receiver)'
 
 
b'\twhich is further transformed to'
 
 
b'\t\t(var := receiver) == nil ifTrue: .... ifFalse: ...'
 
 
b'\tThis does not allow the block variable to shadow an existing temp, but it\'s no different from how to:do: is done."'
 
 
b'\t| ifNotNilArg blockVar |'
 
 
b'\tifNotNilArg := arguments at: 2.'
 
 
b"\t((self checkBlock: (arguments at: 1) as: 'Nil arg' from: encoder)"
 
 
b"\t\tand: [self checkBlock: ifNotNilArg as: 'NotNil arg' from: encoder maxArgs: 1])"
 
 
b'\t\t\tifFalse: [^false].'
 
 
b'\tifNotNilArg numberOfArguments = 1 ifTrue:'
 
 
b'\t\t[blockVar := ifNotNilArg firstArgument.'
 
 
b'\t\treceiver := AssignmentNode new variable: blockVar value: receiver].'
 
 
b'\tselector := SelectorNode new key: #ifTrue:ifFalse: code: #macro.'
 
 
b'\treceiver := MessageNode new'
 
 
b'\t\treceiver: receiver'
 
 
b'\t\tselector: #=='
 
 
b'\t\targuments: (Array with: NodeNil)'
 
 
b'\t\tprecedence: 2'
 
 
b'\t\tfrom: encoder.'
 
 
b'\t^true! !'
 
 
b"!MessageNode methodsFor: 'macro transformations' stamp: 'vb 4/16/2007 11:44'!transformIfNotNilIfNil: encoder"
 
 
b'\t"vb: Changed to support one-argument ifNotNil: branch. In the 1-arg case we transform the receiver to'
 
 
b'\t\t(var := receiver)'
 
 
b'\twhich is further transformed to'
 
 
b'\t\t(var := receiver) == nil ifTrue: .... ifFalse: ...'
 
 
b'\tThis does not allow the block variable to shadow an existing temp, but it\'s no different from how to:do: is done."'
 
 
b'\t| ifNotNilArg blockVar |'
 
 
b'\tifNotNilArg := arguments at: 1.'
 
 
b"\t((self checkBlock: ifNotNilArg as: 'NotNil arg' from: encoder maxArgs: 1)"
 
 
b"\t\tand: [self checkBlock: (arguments at: 2) as: 'Nil arg' from: encoder])"
 
 
b'\t\t\tifFalse: [^false].'
 
 
b'\t\t'
 
 
b'\tifNotNilArg numberOfArguments = 1 ifTrue:'
 
 
b'\t\t[blockVar := ifNotNilArg firstArgument.'
 
 
b'\t\treceiver := AssignmentNode new variable: blockVar value: receiver].'
 
 
b'\tselector := SelectorNode new key: #ifTrue:ifFalse: code: #macro.'
 
 
b'\treceiver := MessageNode new'
 
 
b'\t\treceiver: receiver'
 
 
b'\t\tselector: #=='
 
 
b'\t\targuments: (Array with: NodeNil)'
 
 
b'\t\tprecedence: 2'
 
 
b'\t\tfrom: encoder.'
 
 
b'\targuments swap: 1 with: 2.'
 
 
b'\t^true'
 
 
b'! !'
 
 
b"!MessageNode methodsFor: 'private' stamp: 'vb 4/16/2007 11:39'!checkBlock: node as: nodeName from: encoder maxArgs: maxArgs"
 
 
b'\t"vb: #canBeSpecialArgument for blocks hardcodes 0 arguments as the requirement for special blocks. We work around that here by further checking the number of arguments for blocks.."'
 
 
b'\tnode canBeSpecialArgument ifTrue: '
 
 
b'\t\t[^node isMemberOf: BlockNode].'
 
 
b'\t(node isKindOf: BlockNode)'
 
 
b'\t\tifTrue:'
 
 
b'\t\t\t[node numberOfArguments <= maxArgs'
 
 
b'\t\t\t\tifTrue: [^true]'
 
 
b"\t\t\t\tifFalse: [^encoder notify: '<- ', nodeName , ' of ' ,"
 
 
b"\t\t\t\t\t(MacroSelectors at: special) , ' has too many arguments']]"
 
 
b'\t\tifFalse:'
 
 
b"\t\t\t[^encoder notify: '<- ', nodeName , ' of ' ,"
 
 
b"\t\t\t\t\t(MacroSelectors at: special) , ' must be a block or variable']! !"
 
 
b"!MessageNode methodsFor: 'private' stamp: 'vb 4/15/2007 09:10'!checkBlock: node as: nodeName from: encoder"
 
 
b'\t^self checkBlock: node as: nodeName from: encoder maxArgs: 0! !'
 
 
b'Smalltalk at: #Squeak40Parity ifAbsent: [ '
 
 
b'\tObject subclass: #Squeak40Parity'
 
 
b"\t\tinstanceVariableNames: '' "
 
 
b"\t\tclassVariableNames: '' "
 
 
b"\t\tpoolDictionaries: '' "
 
 
b"\t\tcategory: 'Progress-Squeak4.0' ]. !"
 
 
b"!Squeak40Parity class methodsFor: 'as yet unclassified' stamp: 'kph 3/14/2010 18:24'!bootstrap0004M6426MonadicIfNotNil"
 
 
b"\t<update:  'M6426-ifNotNil-monadic' version: '1.0'>"
 
 
b"\t<project: 'Kernel' level: 0 series: #bootstrap number: 4>"
 
 
b'"'
 
 
b'Mantis 6426 - ifNotNil: [ :acceptsMonadicBlocik | ]'
 
 
b'"'
 
 
b'\t'
 
 
b'\t^  [ :pkg |'
 
 
b'\t\t'
 
 
b'\t\tpkg stampComment.'
 
 
b'\t\t \t\t\t'
0
2
                pkg systemAllImplementorsOf: #(ifNil:ifNotNil: ifNotNil:ifNil:).
1
3
                pkg class: MessageNode selectors: #(
 
 
b'\t\t\temitIfNil:on:value: '
 
 
b'\t\t\ttransformIfNil: '
 
 
b'\t\t\ttransformIfNilIfNotNil: '
 
 
b'\t\t\ttransformIfNotNilIfNil:'
 
 
b'\t\t\tcheckBlock:as:from:maxArgs:'
 
 
b'\t\t\tcheckBlock:as:from:'
 
 
b'\t\t).'
 
 
b'\t].  ! !'
 
 
b'\\ No newline at end of file'