On 18 November 2012 11:16, Camillo Bruni <camillobr...@gmail.com> wrote:
> most probably this is fine, I would not know why mmap and munmap should use
> a different lookup...
>
the explanation is simple: i need to call mmap before finishing bootstrap phase
to allocate some memory for gate function and install it.
while for munmap it is no longer requirement, because gate is already there.
The gate function is needed to call any interpreter function which may
trigger GC (and therefore
relocate machine code).. like if function answers an address, which means
there is a call to instantiate fresh instance of NBExternalAddress,
which may trigger GC.

> On 2012-11-16, at 10:40, Max Leske <maxle...@gmail.com> wrote:
>
>> It seems I found a fix. I simply copied the code from the "mmap" call over 
>> to "munmap". Can somebody (Igor?) *please* confirm that this is ok to do? My 
>> tests are green but I'm really not sure about this…
>>
>> Here's the new code for NBMacExternalHeapManager>>unmap:length:
>>
>> NBMacExternalHeapManager >>unmap: addr  length: len
>>
>>       <primitive: #primitiveNativeCall module: #NativeBoostPlugin error: 
>> errorCode>
>>
>>       "unmap memory page"
>>
>>       ^ NBFFICallout
>>               cdecl: #( int (uint addr, ulong  len)  )
>>               emitCall:  [:gen | | munmap |
>>                       munmap := NativeBoost forCurrentPlatform 
>> getGlobalSymbolPointer: 'munmap'.
>>                       gen asm mov: munmap asUImm32 to: gen asm EAX.
>>                       gen asm call: gen asm EAX
>>                       ]
>>               options: #( - optDirectProxyFnAddress )
>>
>>
>> Cheers,
>> Max
>>
>>
>> On 16.11.2012, at 14:11, Max Leske <maxle...@gmail.com> wrote:
>>
>>> A followup on the munmap issue:
>>>
>>> I think it has something to do with how NativeBoost does the lookup. I 
>>> looked at the way that "mmap" is called and noticed that the selector 
>>> #getGlobalSymbolPointer: is being used. Resolving "munmap" with this 
>>> selector succeeds while doing
>>>
>>> NativeBoost loadSymbol: 'munmap' aName fromModule: -2
>>>
>>> (which is what happens when the heap manager tries to call "munmap") 
>>> results the stack trace shown below.
>>>
>>> I'll keep digging...
>>>
>>>
>>> On 15.11.2012, at 17:20, Max Leske <maxle...@gmail.com> wrote:
>>>
>>>> Hi
>>>>
>>>> When NativeBoost tries to call munmap to free a page (happens because a 
>>>> pointer I freed was the last reserved one in that page) it will throw a 
>>>> NBFFICalloutError (every time) because (I think) it can't find the symbol. 
>>>> I have absolutely no clue how to fix this so I'm in need of help.
>>>>
>>>> System: OS X 10.8.2
>>>> Image: 1.4
>>>> NativeBoost-Core: CamilloBruni.80 (Installed by using the latest 
>>>> NBInstaller)
>>>>
>>>> Cheers,
>>>> Max
>>>>
>>>> Here's the stack:
>>>>
>>>> 15 November 2012 5:04:23.895 pm
>>>>
>>>> VM: Mac OS - intel - 1082 - NBCoInterpreter 
>>>> NativeBoost-CogPlugin-IgorStasenko.14 uuid: 
>>>> da3a649c-e2b2-bd4c-aa2f-9c2ebdb2658a Oct 26 2012, 
>>>> StackToRegisterMappingCogit VMMaker-oscog-EstebanLorenzano.164 uuid: 
>>>> d77dee73-00f5-4d00-847b-00646b08329d Oct 26 2012, 
>>>> git://gitorious.org/cogvm/blessed.git Commit: 
>>>> 48af8595004fd0ec3a3ac6d44c3d7516a87981ca Date: 2012-10-24 16:56:20 +0200 
>>>> By: Igor Stasenko <siguc...@gmail.com> Jenkins build #131
>>>> Image: Pharo1.4 [Latest update: #14457]
>>>>
>>>> NBFFICallout class>>signalError:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             errorCode:      1
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NBFFICallout class(NBNativeCodeGen class)>>handleFailureIn:nativeCode:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aContext:       
>>>> NativeBoostMac32(NativeBoost)>>bootstrapLoadSymbol:ofLength:fromModul...etc...
>>>>             aBlock:         [:gen | gen useEmitCall; sender: sender; 
>>>> parseOptions: anOptions; cdecl...etc...
>>>>             method:         
>>>> (NativeBoost>>#bootstrapLoadSymbol:ofLength:fromModule:into: "a 
>>>> Compile...etc...
>>>>             lastError:      1
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NBFFICallout class>>cdecl:emitCall:options:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             functionSpec:   #(#NBBootstrapUlong #(#byte #* #symbolName #, 
>>>> #long #symbolLen #,...etc...
>>>>             aCallEmittingBlock:     [:gen | gen proxy callFn: 
>>>> #ioLoadSymbol:OfLength:FromModule...etc...
>>>>             anOptions:      #(#- #optDirectProxyFnAddress 
>>>> #optAllowExternalAddressPtr)
>>>>             sender:         
>>>> NativeBoostMac32(NativeBoost)>>bootstrapLoadSymbol:ofLength:fromModule:...etc...
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NativeBoostMac32(NativeBoost)>>bootstrapLoadSymbol:ofLength:fromModule:into:
>>>>     Receiver: a NativeBoostMac32
>>>>     Arguments and temporary variables:
>>>>             symbolName:     'munmap'
>>>>             symbolLen:      6
>>>>             moduleHandle:   -2
>>>>             returnValueBuffer:      #[0 0 0 0 0 0 0 0]
>>>>     Receiver's instance variables:
>>>>             bootstrapping:  false
>>>>             insideCallback:         nil
>>>>             callbackCounterAddr:    @ 16r5F74000
>>>>             extraRootsRegistry:     a NBExtraRootsRegistry
>>>>             rootsCell:      @ 16r5F7402A
>>>>             gateFunction:   @ 16r5F74004
>>>>             heap:   a NBMacExternalHeapManager
>>>>
>>>> NativeBoostMac32(NativeBoost)>>loadSymbol:fromModule:
>>>>     Receiver: a NativeBoostMac32
>>>>     Arguments and temporary variables:
>>>>             aSymbolName:    'munmap'
>>>>             moduleName:     -2
>>>>             bytes:  #[0 0 0 0 0 0 0 0]
>>>>             module:         -2
>>>>             handle:         nil
>>>>     Receiver's instance variables:
>>>>             bootstrapping:  false
>>>>             insideCallback:         nil
>>>>             callbackCounterAddr:    @ 16r5F74000
>>>>             extraRootsRegistry:     a NBExtraRootsRegistry
>>>>             rootsCell:      @ 16r5F7402A
>>>>             gateFunction:   @ 16r5F74004
>>>>             heap:   a NBMacExternalHeapManager
>>>>
>>>> NativeBoostMac32(NativeBoostLinux32)>>loadSymbol:fromModule:
>>>>     Receiver: a NativeBoostMac32
>>>>     Arguments and temporary variables:
>>>>             aSymbolName:    'munmap'
>>>>             moduleName:     -2
>>>>     Receiver's instance variables:
>>>>             bootstrapping:  false
>>>>             insideCallback:         nil
>>>>             callbackCounterAddr:    @ 16r5F74000
>>>>             extraRootsRegistry:     a NBExtraRootsRegistry
>>>>             rootsCell:      @ 16r5F7402A
>>>>             gateFunction:   @ 16r5F74004
>>>>             heap:   a NBMacExternalHeapManager
>>>>
>>>> NativeBoost class>>loadSymbol:fromModule:
>>>>     Receiver: NativeBoost
>>>>     Arguments and temporary variables:
>>>>             aSymbolName:    'munmap'
>>>>             moduleName:     -2
>>>>     Receiver's instance variables:
>>>>             superclass:     Object
>>>>             methodDict:     a 
>>>> MethodDictionary(#CLibrary->(NativeBoost>>#CLibrary "a CompiledMe...etc...
>>>>             format:         142
>>>>             instanceVariables:      #('bootstrapping' 'insideCallback' 
>>>> 'callbackCounterAddr' 'ex...etc...
>>>>             organization:   ('retrieving symbols' CLibrary VMModule 
>>>> ioLoadFunction:from: ioLo...etc...
>>>>             subclasses:     {NativeBoostLinux32. NativeBoostWin32}
>>>>             name:   #NativeBoost
>>>>             classPool:      a Dictionary(#Current->a NativeBoostMac32 
>>>> #NBAnnouncer->an Announcer...etc...
>>>>             sharedPools:    an OrderedCollection(AJx86Registers 
>>>> NativeBoostConstants)
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NBMacExternalHeapManager class(Object)>>nbGetSymbolAddress:module:
>>>>     Receiver: NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             aName:  'munmap'
>>>>             aModuleNameOrHandle:    -2
>>>>             addr:   nil
>>>>     Receiver's instance variables:
>>>>             superclass:     NBExternalHeapManager
>>>>             methodDict:     a 
>>>> MethodDictionary(#mapFlags->(NBMacExternalHeapManager>>#mapFlags ...etc...
>>>>             format:         138
>>>>             instanceVariables:      nil
>>>>             organization:   ('as yet unclassified' mapFlags 
>>>> mmapLength:prot:flags:into: primA...etc...
>>>>             subclasses:     nil
>>>>             name:   #NBMacExternalHeapManager
>>>>             classPool:      nil
>>>>             sharedPools:    an OrderedCollection(NBMacConstants)
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Mac'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> [:gen |
>>>> fnAddress := requestor nbGetSymbolAddress: fnSpec functionName module: 
>>>> aModuleNameOrHandle.
>>>>     fnAddress
>>>>             ifNil: [self error: 'function unavailable'].
>>>>     self optMayGC
>>>>             ifTrue: [asm push: fnAddress asUImm32;
>>>>                              mov: NativeBoost callgateFunctionAddress 
>>>> asUImm32 to: EAX;
>>>>                              call: EAX]
>>>>             ifFalse: [asm mov: fnAddress asUImm32 to: EAX;
>>>>                              call: EAX]] in 
>>>> NBFFICallout>>generateCall:module:
>>>>     Receiver: a NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aModuleNameOrHandle:    a NBFFICallout
>>>>             fnAddress:      -2
>>>>             gen:    #(nil)
>>>>     Receiver's instance variables:
>>>>             asm:    an AJx86Assembler
>>>>             proxy:  a NBInterpreterProxy
>>>>             options:        a Set(#optCdecl #optAllowByteArraysPtr 
>>>> #optUseStackPointer #optReturnP...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             fnSpec:         a NBFnSpec
>>>>             requestor:      NBMacExternalHeapManager
>>>>             methodArgs:     an OrderedCollection('addr' 'len')
>>>>             coercionMayFail:        true
>>>>             callInfo:       an AJCdeclCallInfo
>>>>
>>>> BlockClosure>>valueWithPossibleArgs:
>>>>     Receiver: [:gen |
>>>> fnAddress := requestor nbGetSymbolAddress: fnSpec functionName module: 
>>>> aModuleNam...etc...
>>>>     Arguments and temporary variables:
>>>>             anArray:        an Array(a NBFFICallout a NBInterpreterProxy 
>>>> an AJx86Assembler)
>>>>     Receiver's instance variables:
>>>>             outerContext:   NBFFICallout>>generateCall:module:
>>>>             startpc:        91
>>>>             numArgs:        1
>>>>
>>>> [aFunctionBodyBlock valueWithPossibleArgs: {self. proxy. asm}.
>>>>     (self optEmitCall
>>>>                     or: [self optNoCleanup])
>>>>             ifTrue: [call disableCleanup]] in [:call |
>>>> self optNoAlignment
>>>>             ifTrue: [call alignment: 1].
>>>>     self pushArguments.
>>>>     coercionMayFail
>>>>             ifTrue: [proxy ifFailedJumpTo: self failedLabel].
>>>>     asm
>>>>             decorateWith: 'FFI: performing a call'
>>>>             during: [aFunctionBodyBlock valueWithPossibleArgs: {self. 
>>>> proxy. asm}.
>>>>                     (self optEmitCall
>>>>                                     or: [self optNoCleanup])
>>>>                             ifTrue: [call disableCleanup]]] in 
>>>> NBFFICallout>>generateInstructions:
>>>>     Receiver: a NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aFunctionBodyBlock:     an AJCdeclCallInfo
>>>>             call:   [:gen |
>>>> fnAddress := requestor nbGetSymbolAddress: fnSpec functionName m...etc...
>>>>     Receiver's instance variables:
>>>>             asm:    an AJx86Assembler
>>>>             proxy:  a NBInterpreterProxy
>>>>             options:        a Set(#optCdecl #optAllowByteArraysPtr 
>>>> #optUseStackPointer #optReturnP...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             fnSpec:         a NBFnSpec
>>>>             requestor:      NBMacExternalHeapManager
>>>>             methodArgs:     an OrderedCollection('addr' 'len')
>>>>             coercionMayFail:        true
>>>>             callInfo:       an AJCdeclCallInfo
>>>>
>>>> BlockClosure>>ensure:
>>>>     Receiver: [aFunctionBodyBlock valueWithPossibleArgs: {self. proxy. 
>>>> asm}.
>>>>     (self optEmitCall
>>>>                     or: [...etc...
>>>>     Arguments and temporary variables:
>>>>             aBlock:         [level := level - 1.
>>>>     self
>>>>             addInstruction: (AJInstructionDecoration n...etc...
>>>>             complete:       nil
>>>>             returnValue:    nil
>>>>     Receiver's instance variables:
>>>>             outerContext:   [:call |
>>>> self optNoAlignment
>>>>             ifTrue: [call alignment: 1].
>>>>     sel...etc...
>>>>             startpc:        155
>>>>             numArgs:        0
>>>>
>>>> AJx86Assembler>>decorateWith:during:
>>>>     Receiver: an AJx86Assembler
>>>>     Arguments and temporary variables:
>>>>             annotation:     'FFI: performing a call'
>>>>             aBlock:         [aFunctionBodyBlock valueWithPossibleArgs: 
>>>> {self. proxy. asm}.
>>>>     (self o...etc...
>>>>     Receiver's instance variables:
>>>>             instructions:   <<error during printing>>
>>>>
>>>> [:call |
>>>> self optNoAlignment
>>>>             ifTrue: [call alignment: 1].
>>>>     self pushArguments.
>>>>     coercionMayFail
>>>>             ifTrue: [proxy ifFailedJumpTo: self failedLabel].
>>>>     asm
>>>>             decorateWith: 'FFI: performing a call'
>>>>             during: [aFunctionBodyBlock valueWithPossibleArgs: {self. 
>>>> proxy. asm}.
>>>>                     (self optEmitCall
>>>>                                     or: [self optNoCleanup])
>>>>                             ifTrue: [call disableCleanup]]] in 
>>>> NBFFICallout>>generateInstructions:
>>>>     Receiver: a NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aFunctionBodyBlock:     an AJCdeclCallInfo
>>>>             call:   [:gen |
>>>> fnAddress := requestor nbGetSymbolAddress: fnSpec functionName m...etc...
>>>>     Receiver's instance variables:
>>>>             asm:    an AJx86Assembler
>>>>             proxy:  a NBInterpreterProxy
>>>>             options:        a Set(#optCdecl #optAllowByteArraysPtr 
>>>> #optUseStackPointer #optReturnP...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             fnSpec:         a NBFnSpec
>>>>             requestor:      NBMacExternalHeapManager
>>>>             methodArgs:     an OrderedCollection('addr' 'len')
>>>>             coercionMayFail:        true
>>>>             callInfo:       an AJCdeclCallInfo
>>>>
>>>> AJx86Assembler>>performingCall:in:
>>>>     Receiver: an AJx86Assembler
>>>>     Arguments and temporary variables:
>>>>             ci:     an AJCdeclCallInfo
>>>>             aBlock:         [:call |
>>>> self optNoAlignment
>>>>             ifTrue: [call alignment: 1].
>>>>     self push...etc...
>>>>     Receiver's instance variables:
>>>>             instructions:   <<error during printing>>
>>>>
>>>> NBFFICallout>>foreignCall:
>>>>     Receiver: a NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aBlock:         [:call |
>>>> self optNoAlignment
>>>>             ifTrue: [call alignment: 1].
>>>>     self push...etc...
>>>>     Receiver's instance variables:
>>>>             asm:    an AJx86Assembler
>>>>             proxy:  a NBInterpreterProxy
>>>>             options:        a Set(#optCdecl #optAllowByteArraysPtr 
>>>> #optUseStackPointer #optReturnP...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             fnSpec:         a NBFnSpec
>>>>             requestor:      NBMacExternalHeapManager
>>>>             methodArgs:     an OrderedCollection('addr' 'len')
>>>>             coercionMayFail:        true
>>>>             callInfo:       an AJCdeclCallInfo
>>>>
>>>> NBFFICallout>>generateInstructions:
>>>>     Receiver: a NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aFunctionBodyBlock:     [:gen |
>>>> fnAddress := requestor nbGetSymbolAddress: fnSpec ...etc...
>>>>             instructions:   nil
>>>>     Receiver's instance variables:
>>>>             asm:    an AJx86Assembler
>>>>             proxy:  a NBInterpreterProxy
>>>>             options:        a Set(#optCdecl #optAllowByteArraysPtr 
>>>> #optUseStackPointer #optReturnP...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             fnSpec:         a NBFnSpec
>>>>             requestor:      NBMacExternalHeapManager
>>>>             methodArgs:     an OrderedCollection('addr' 'len')
>>>>             coercionMayFail:        true
>>>>             callInfo:       an AJCdeclCallInfo
>>>>
>>>> NBFFICallout>>generate:
>>>>     Receiver: a NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aFunctionBodyBlock:     [:gen |
>>>> fnAddress := requestor nbGetSymbolAddress: fnSpec ...etc...
>>>>             generatedCode:  nil
>>>>     Receiver's instance variables:
>>>>             asm:    an AJx86Assembler
>>>>             proxy:  a NBInterpreterProxy
>>>>             options:        a Set(#optCdecl #optAllowByteArraysPtr 
>>>> #optUseStackPointer #optReturnP...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             fnSpec:         a NBFnSpec
>>>>             requestor:      NBMacExternalHeapManager
>>>>             methodArgs:     an OrderedCollection('addr' 'len')
>>>>             coercionMayFail:        true
>>>>             callInfo:       an AJCdeclCallInfo
>>>>
>>>> NBFFICallout>>generateCall:module:
>>>>     Receiver: a NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             functionSpec:   #(#int #munmap #(#uint #addr #, #ulong #len))
>>>>             aModuleNameOrHandle:    -2
>>>>             fnAddress:      #(nil)
>>>>     Receiver's instance variables:
>>>>             asm:    an AJx86Assembler
>>>>             proxy:  a NBInterpreterProxy
>>>>             options:        a Set(#optCdecl #optAllowByteArraysPtr 
>>>> #optUseStackPointer #optReturnP...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             fnSpec:         a NBFnSpec
>>>>             requestor:      NBMacExternalHeapManager
>>>>             methodArgs:     an OrderedCollection('addr' 'len')
>>>>             coercionMayFail:        true
>>>>             callInfo:       an AJCdeclCallInfo
>>>>
>>>> [:gen | gen sender: sender;
>>>>              cdecl;
>>>>              generateCall: functionSpec module: aModuleName] in 
>>>> NBFFICallout class>>cdecl:module:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             functionSpec:   a NBFFICallout
>>>>             aModuleName:    #(#int #munmap #(#uint #addr #, #ulong #len))
>>>>             sender:         -2
>>>>             gen:    NBMacExternalHeapManager>>unmap:length:
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> [bytes := aBlock
>>>>                             value: (self newForMethod: method)] in 
>>>> NBFFICallout class(NBNativeCodeGen class)>>generateCode:andRetry:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aBlock:         [:gen | gen sender: sender;
>>>>              cdecl;
>>>>              generateCall: functionSpec mod...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             bytes:  #(nil)
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> BlockClosure>>on:do:
>>>>     Receiver: [bytes := aBlock
>>>>                             value: (self newForMethod: method)]
>>>>     Arguments and temporary variables:
>>>>             exception:      NBRecursionDetect
>>>>             handlerAction:  [:ex | ex check: aMethod]
>>>>             handlerActive:  true
>>>>     Receiver's instance variables:
>>>>             outerContext:   NBFFICallout class(NBNativeCodeGen 
>>>> class)>>generateCode:andRetry:...etc...
>>>>             startpc:        96
>>>>             numArgs:        0
>>>>
>>>> NBRecursionDetect class>>in:during:
>>>>     Receiver: NBRecursionDetect
>>>>     Arguments and temporary variables:
>>>>             aMethod:        (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)...etc...
>>>>             aBlock:         [bytes := aBlock
>>>>                             value: (self newForMethod: method)]
>>>>     Receiver's instance variables:
>>>>             superclass:     Notification
>>>>             methodDict:     a 
>>>> MethodDictionary(#check:->(NBRecursionDetect>>#check: "a Compiled...etc...
>>>>             format:         144
>>>>             instanceVariables:      #('method')
>>>>             organization:   ('as yet unclassified' check: defaultAction 
>>>> method signalForMetho...etc...
>>>>             subclasses:     nil
>>>>             name:   #NBRecursionDetect
>>>>             classPool:      nil
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-Errors'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NBFFICallout class(NBNativeCodeGen class)>>generateCode:andRetry:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aBlock:         [:gen | gen sender: sender;
>>>>              cdecl;
>>>>              generateCall: functionSpec mod...etc...
>>>>             retryCtx:       NBMacExternalHeapManager>>unmap:length:
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             newMethod:      nil
>>>>             args:   nil
>>>>             bytes:  #(nil)
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NBFFICallout class(NBNativeCodeGen class)>>handleFailureIn:nativeCode:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             aContext:       NBMacExternalHeapManager>>unmap:length:
>>>>             aBlock:         [:gen | gen sender: sender;
>>>>              cdecl;
>>>>              generateCall: functionSpec mod...etc...
>>>>             method:         (NBMacExternalHeapManager>>#unmap:length: "a 
>>>> CompiledMethod(355205120)"...etc...
>>>>             lastError:      502
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NBFFICallout class>>cdecl:module:
>>>>     Receiver: NBFFICallout
>>>>     Arguments and temporary variables:
>>>>             functionSpec:   #(#int #munmap #(#uint #addr #, #ulong #len))
>>>>             aModuleName:    -2
>>>>             sender:         NBMacExternalHeapManager>>unmap:length:
>>>>     Receiver's instance variables:
>>>>             superclass:     NBNativeCodeGen
>>>>             methodDict:     a 
>>>> MethodDictionary(#aliasForType:->(NBFFICallout>>#aliasForType: "a...etc...
>>>>             format:         148
>>>>             instanceVariables:      #('fnSpec' 'requestor' 'methodArgs' 
>>>> 'coercionMayFail' 'callI...etc...
>>>>             organization:   ('type aliases' aliasForType:)
>>>> ('accessing' anonSpec: callType: c...etc...
>>>>             subclasses:     {NBNativeFunctionGen}
>>>>             name:   #NBFFICallout
>>>>             classPool:      a Dictionary(#CustomErrorCodes->a 
>>>> Dictionary(600->'An instance of NB...etc...
>>>>             sharedPools:    nil
>>>>             environment:    a SystemDictionary(lots of globals)
>>>>             category:       #'NativeBoost-Core-FFI'
>>>>             traitComposition:       {}
>>>>             localSelectors:         nil
>>>>
>>>> NBMacExternalHeapManager>>unmap:length:
>>>>     Receiver: a NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             addr:   7380992
>>>>             len:    32768
>>>>             errorCode:      502
>>>>     Receiver's instance variables:
>>>>             pages:  a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>             freeBlocks:     an IdentitySet(a NBMemoryBlock( @ 16r17D302E, 
>>>> 17, free) a NBMemoryB...etc...
>>>>             reservedBlocks:         a Dictionary(24981504->a 
>>>> NBMemoryBlock( @ 16r17D3000, 38) 24981...etc...
>>>>             sema:   a Semaphore()
>>>>
>>>> NBMacExternalHeapManager>>primFreePage:
>>>>     Receiver: a NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             aMemoryPage:    a NBMemoryPage
>>>>             res:    nil
>>>>     Receiver's instance variables:
>>>>             pages:  a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>             freeBlocks:     an IdentitySet(a NBMemoryBlock( @ 16r17D302E, 
>>>> 17, free) a NBMemoryB...etc...
>>>>             reservedBlocks:         a Dictionary(24981504->a 
>>>> NBMemoryBlock( @ 16r17D3000, 38) 24981...etc...
>>>>             sema:   a Semaphore()
>>>>
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>freePage:
>>>>     Receiver: a NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             aMemoryPage:    a NBMemoryPage
>>>>     Receiver's instance variables:
>>>>             pages:  a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>             freeBlocks:     an IdentitySet(a NBMemoryBlock( @ 16r17D302E, 
>>>> 17, free) a NBMemoryB...etc...
>>>>             reservedBlocks:         a Dictionary(24981504->a 
>>>> NBMemoryBlock( @ 16r17D3000, 38) 24981...etc...
>>>>             sema:   a Semaphore()
>>>>
>>>> [:page |
>>>> page length = aMemoryBlock length
>>>>             ifTrue: [self freePage: page.
>>>>                     ^ true].
>>>>     nil] in 
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>checkForFreePage:
>>>>     Receiver: a NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             aMemoryBlock:   a NBMemoryPage
>>>>             page:   a NBMemoryBlock( @ 16r70A000, 32768, free)
>>>>     Receiver's instance variables:
>>>>             pages:  a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>             freeBlocks:     an IdentitySet(a NBMemoryBlock( @ 16r17D302E, 
>>>> 17, free) a NBMemoryB...etc...
>>>>             reservedBlocks:         a Dictionary(24981504->a 
>>>> NBMemoryBlock( @ 16r17D3000, 38) 24981...etc...
>>>>             sema:   a Semaphore()
>>>>
>>>> BlockClosure>>cull:
>>>>     Receiver: [:page |
>>>> page length = aMemoryBlock length
>>>>             ifTrue: [self freePage: page.
>>>>                     ^ true].
>>>>     n...etc...
>>>>     Arguments and temporary variables:
>>>>             anArg:  a NBMemoryPage
>>>>     Receiver's instance variables:
>>>>             outerContext:   
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>checkForFreePage...etc...
>>>>             startpc:        41
>>>>             numArgs:        1
>>>>
>>>> Dictionary>>at:ifPresent:
>>>>     Receiver: a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>     Arguments and temporary variables:
>>>>             key:    7380992
>>>>             aBlock:         [:page |
>>>> page length = aMemoryBlock length
>>>>             ifTrue: [self freePage: p...etc...
>>>>             assoc:  7380992->a NBMemoryPage
>>>>     Receiver's instance variables:
>>>>             tally:  2
>>>>             array:  an Array(nil 100089856->a NBMemoryPage nil nil 
>>>> 24981504->a NBMemoryPage)...etc...
>>>>
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>checkForFreePage:
>>>>     Receiver: a NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             aMemoryBlock:   a NBMemoryBlock( @ 16r70A000, 32768, free)
>>>>     Receiver's instance variables:
>>>>             pages:  a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>             freeBlocks:     an IdentitySet(a NBMemoryBlock( @ 16r17D302E, 
>>>> 17, free) a NBMemoryB...etc...
>>>>             reservedBlocks:         a Dictionary(24981504->a 
>>>> NBMemoryBlock( @ 16r17D3000, 38) 24981...etc...
>>>>             sema:   a Semaphore()
>>>>
>>>> NBMemoryBlock>>makeFreeFor:
>>>>     Receiver: a NBMemoryBlock( @ 16r70A030, 32720, free)
>>>>     Arguments and temporary variables:
>>>>             heapManager:    a NBMacExternalHeapManager
>>>>     Receiver's instance variables:
>>>>             left:   a NBMemoryBlock( @ 16r70A000, 32768, free)
>>>>             right:  nil
>>>>             address:        7381040
>>>>             length:         32720
>>>>             free:   true
>>>>
>>>> [| block |
>>>> block := reservedBlocks
>>>>                             removeKey: address
>>>>                             ifAbsent: [self error: 'Unable to find a 
>>>> memory block with given address'].
>>>>     block makeFreeFor: self] in 
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>free:
>>>>     Receiver: a NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             address:        7381040
>>>>             block:  a NBMemoryBlock( @ 16r70A030, 32720, free)
>>>>     Receiver's instance variables:
>>>>             pages:  a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>             freeBlocks:     an IdentitySet(a NBMemoryBlock( @ 16r17D302E, 
>>>> 17, free) a NBMemoryB...etc...
>>>>             reservedBlocks:         a Dictionary(24981504->a 
>>>> NBMemoryBlock( @ 16r17D3000, 38) 24981...etc...
>>>>             sema:   a Semaphore()
>>>>
>>>> [caught := true.
>>>>     self wait.
>>>>     blockValue := mutuallyExcludedBlock value] in Semaphore>>critical:
>>>>     Receiver: a Semaphore()
>>>>     Arguments and temporary variables:
>>>> <<error during printing>
>>>>     Receiver's instance variables:
>>>>             firstLink:      nil
>>>>             lastLink:       nil
>>>>             excessSignals:  0
>>>>
>>>> BlockClosure>>ensure:
>>>>     Receiver: [caught := true.
>>>>     self wait.
>>>>     blockValue := mutuallyExcludedBlock value]
>>>>     Arguments and temporary variables:
>>>>             aBlock:         [caught
>>>>             ifTrue: [self signal]]
>>>>             complete:       nil
>>>>             returnValue:    nil
>>>>     Receiver's instance variables:
>>>>             outerContext:   Semaphore>>critical:
>>>>             startpc:        42
>>>>             numArgs:        0
>>>>
>>>> Semaphore>>critical:
>>>>     Receiver: a Semaphore()
>>>>     Arguments and temporary variables:
>>>> <<error during printing>
>>>>     Receiver's instance variables:
>>>>             firstLink:      nil
>>>>             lastLink:       nil
>>>>             excessSignals:  0
>>>>
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>free:
>>>>     Receiver: a NBMacExternalHeapManager
>>>>     Arguments and temporary variables:
>>>>             address:        7381040
>>>>     Receiver's instance variables:
>>>>             pages:  a Dictionary(24981504->a NBMemoryPage 100089856->a 
>>>> NBMemoryPage )
>>>>             freeBlocks:     an IdentitySet(a NBMemoryBlock( @ 16r17D302E, 
>>>> 17, free) a NBMemoryB...etc...
>>>>             reservedBlocks:         a Dictionary(24981504->a 
>>>> NBMemoryBlock( @ 16r17D3000, 38) 24981...etc...
>>>>             sema:   a Semaphore()
>>>>
>>>>
>>>> --- The full stack ---
>>>> NBFFICallout class>>signalError:
>>>> NBFFICallout class(NBNativeCodeGen class)>>handleFailureIn:nativeCode:
>>>> NBFFICallout class>>cdecl:emitCall:options:
>>>> NativeBoostMac32(NativeBoost)>>bootstrapLoadSymbol:ofLength:fromModule:into:
>>>> NativeBoostMac32(NativeBoost)>>loadSymbol:fromModule:
>>>> NativeBoostMac32(NativeBoostLinux32)>>loadSymbol:fromModule:
>>>> NativeBoost class>>loadSymbol:fromModule:
>>>> NBMacExternalHeapManager class(Object)>>nbGetSymbolAddress:module:
>>>> [:gen |
>>>> fnAddress := requestor nbGetSymbolAddress: fnSpec functionName module: 
>>>> aModuleNameOrHandle.
>>>>     fnAddress
>>>>             ifNil: [self error: 'function unavailable'].
>>>>     self optMayGC
>>>>             ifTrue: [asm push: fnAddress asUImm32;
>>>>                              mov: NativeBoost callgateFunctionAddress 
>>>> asUImm32 to: EAX;
>>>>                              call: EAX]
>>>>             ifFalse: [asm mov: fnAddress asUImm32 to: EAX;
>>>>                              call: EAX]] in 
>>>> NBFFICallout>>generateCall:module:
>>>> BlockClosure>>valueWithPossibleArgs:
>>>> [aFunctionBodyBlock valueWithPossibleArgs: {self. proxy. asm}.
>>>>     (self optEmitCall
>>>>                     or: [self optNoCleanup])
>>>>             ifTrue: [call disableCleanup]] in [:call |
>>>> self optNoAlignment
>>>>             ifTrue: [call alignment: 1].
>>>>     self pushArguments.
>>>>     coercionMayFail
>>>>             ifTrue: [proxy ifFailedJumpTo: self failedLabel].
>>>>     asm
>>>>             decorateWith: 'FFI: performing a call'
>>>>             during: [aFunctionBodyBlock valueWithPossibleArgs: {self. 
>>>> proxy. asm}.
>>>>                     (self optEmitCall
>>>>                                     or: [self optNoCleanup])
>>>>                             ifTrue: [call disableCleanup]]] in 
>>>> NBFFICallout>>generateInstructions:
>>>> BlockClosure>>ensure:
>>>> AJx86Assembler>>decorateWith:during:
>>>> [:call |
>>>> self optNoAlignment
>>>>             ifTrue: [call alignment: 1].
>>>>     self pushArguments.
>>>>     coercionMayFail
>>>>             ifTrue: [proxy ifFailedJumpTo: self failedLabel].
>>>>     asm
>>>>             decorateWith: 'FFI: performing a call'
>>>>             during: [aFunctionBodyBlock valueWithPossibleArgs: {self. 
>>>> proxy. asm}.
>>>>                     (self optEmitCall
>>>>                                     or: [self optNoCleanup])
>>>>                             ifTrue: [call disableCleanup]]] in 
>>>> NBFFICallout>>generateInstructions:
>>>> AJx86Assembler>>performingCall:in:
>>>> NBFFICallout>>foreignCall:
>>>> NBFFICallout>>generateInstructions:
>>>> NBFFICallout>>generate:
>>>> NBFFICallout>>generateCall:module:
>>>> [:gen | gen sender: sender;
>>>>              cdecl;
>>>>              generateCall: functionSpec module: aModuleName] in 
>>>> NBFFICallout class>>cdecl:module:
>>>> [bytes := aBlock
>>>>                             value: (self newForMethod: method)] in 
>>>> NBFFICallout class(NBNativeCodeGen class)>>generateCode:andRetry:
>>>> BlockClosure>>on:do:
>>>> NBRecursionDetect class>>in:during:
>>>> NBFFICallout class(NBNativeCodeGen class)>>generateCode:andRetry:
>>>> NBFFICallout class(NBNativeCodeGen class)>>handleFailureIn:nativeCode:
>>>> NBFFICallout class>>cdecl:module:
>>>> NBMacExternalHeapManager>>unmap:length:
>>>> NBMacExternalHeapManager>>primFreePage:
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>freePage:
>>>> [:page |
>>>> page length = aMemoryBlock length
>>>>             ifTrue: [self freePage: page.
>>>>                     ^ true].
>>>>     nil] in 
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>checkForFreePage:
>>>> BlockClosure>>cull:
>>>> Dictionary>>at:ifPresent:
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>checkForFreePage:
>>>> NBMemoryBlock>>makeFreeFor:
>>>> [| block |
>>>> block := reservedBlocks
>>>>                             removeKey: address
>>>>                             ifAbsent: [self error: 'Unable to find a 
>>>> memory block with given address'].
>>>>     block makeFreeFor: self] in 
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>free:
>>>> [caught := true.
>>>>     self wait.
>>>>     blockValue := mutuallyExcludedBlock value] in Semaphore>>critical:
>>>> BlockClosure>>ensure:
>>>> Semaphore>>critical:
>>>> NBMacExternalHeapManager(NBExternalHeapManager)>>free:
>>>> - - - - - - - - - - - - - - -
>>>>                     - - - - - - - - - - - - - - - - - -
>>>> NativeBoostMac32(NativeBoostLinux32)>>free:
>>>> NativeBoost class>>free:
>>>> NBExternalAddress>>free
>>>> [:pointer | pointer value free] in LimboCommand>>freePointers
>>>> Set>>do:
>>>> LimboCommand>>freePointers
>>>> [self freePointers] in LimboCommand>>run
>>>> BlockClosure>>ensure:
>>>> LimboCommand>>run
>>>> Limbo>>run:arguments:
>>>> Limbo>>runSh:
>>>> Limbo class>>runSh:
>>>> [limbo := Limbo runSh: '/bin/echo ' , arg] in 
>>>> LimboTest>>testShellCommandWithNewLines
>>>> [aBlock value.
>>>>     false] in LimboTest(TestCase)>>executeShould:inScopeOf:
>>>> BlockClosure>>on:do:
>>>> LimboTest(TestCase)>>executeShould:inScopeOf:
>>>> LimboTest(TestCase)>>shouldnt:raise:
>>>> LimboTest>>testShellCommandWithNewLines
>>>> LimboTest(TestCase)>>performTest
>>>> [self setUp.
>>>>     self performTest] in LimboTest(TestCase)>>runCase
>>>> BlockClosure>>ensure:
>>>> LimboTest(TestCase)>>runCase
>>>> [(self class selector: testSelector) runCase] in LimboTest(TestCase)>>debug
>>>> BlockClosure>>ensure:
>>>> LimboTest(TestCase)>>debug
>>>> OBCmdRunTests>>execute
>>>> [:each |
>>>> (each isActive
>>>>                     and: [each isEnabled])
>>>>             ifTrue: [each execute.
>>>>                     ^ true].
>>>>     nil] in 
>>>> OBNodeCommandScan(OBCommandScan)>>processKeystroke:withNode:for:
>>>> OrderedCollection>>do:
>>>> OBNodeCommandScan(OBCommandScan)>>processKeystroke:withNode:for:
>>>> [:each |
>>>> (scan
>>>>                     processKeystroke: aCharacter asKeystroke
>>>>                     withNode: each
>>>>                     for: self)
>>>>             ifTrue: [^ self].
>>>>     nil] in OBColumn>>keystroke:from:
>>>> OrderedCollection>>reverseDo:
>>>> OBColumn>>keystroke:from:
>>>> OBPluggableListMorph(PluggableListMorph)>>modifierKeyPressed:
>>>> OBPluggableListMorph(PluggableListMorph)>>keyStroke:
>>>> OBPluggableListMorph(Morph)>>handleKeystroke:
>>>> KeyboardEvent>>sentTo:
>>>> OBPluggableListMorph(Morph)>>handleEvent:
>>>> MorphicEventDispatcher>>dispatchDefault:with:
>>>> MorphicEventDispatcher>>dispatchEvent:with:
>>>> OBPluggableListMorph(Morph)>>processEvent:using:
>>>> OBPluggableListMorph(Morph)>>processEvent:
>>>> OBPluggableListMorph(PluggableListMorph)>>handleFocusEvent:
>>>> [ActiveHand := self.
>>>>     ActiveEvent := anEvent.
>>>>     result := focusHolder
>>>>                             handleFocusEvent: (anEvent
>>>>                                             transformedBy: (focusHolder 
>>>> transformedFrom: self))] in HandMorph>>sendFocusEvent:to:clear:
>>>> [aBlock value] in PasteUpMorph>>becomeActiveDuring:
>>>> BlockClosure>>on:do:
>>>> PasteUpMorph>>becomeActiveDuring:
>>>> HandMorph>>sendFocusEvent:to:clear:
>>>> HandMorph>>sendEvent:focus:clear:
>>>> HandMorph>>sendKeyboardEvent:
>>>> HandMorph>>handleEvent:
>>>> HandMorph>>processEvents
>>>> [:h |
>>>> ActiveHand := h.
>>>>     h processEvents.
>>>>     ActiveHand := nil] in WorldState>>doOneCycleNowFor:
>>>> Array(SequenceableCollection)>>do:
>>>> WorldState>>handsDo:
>>>> WorldState>>doOneCycleNowFor:
>>>> WorldState>>doOneCycleFor:
>>>> PasteUpMorph>>doOneCycle
>>>> [[World doOneCycle.
>>>>     Processor yield.
>>>>     false] whileFalse.
>>>>     nil] in MorphicUIManager>>spawnNewProcess
>>>> [self value.
>>>>     Processor terminateActive] in BlockClosure>>newProcess
>>>>
>>>
>>
>>
>
>



-- 
Best regards,
Igor Stasenko.

Reply via email to