Skip to content

Commit

Permalink
Merge pull request #2002 from estebanlm/22682-when-callback-fails-a-d…
Browse files Browse the repository at this point in the history
…efault-value-should-be-returned-to-prevent-crashes

22682-when-callback-fails-a-default-value-should-be-returned-to-prevent-crashes
  • Loading branch information
estebanlm committed Nov 19, 2018
2 parents 5665d4e + 536fead commit da608ce
Show file tree
Hide file tree
Showing 10 changed files with 107 additions and 5 deletions.
35 changes: 35 additions & 0 deletions src/UnifiedFFI/BlockClosure.extension.st
@@ -0,0 +1,35 @@
Extension { #name : #BlockClosure }

{ #category : #'*UnifiedFFI' }
BlockClosure >> on: exception fork: handlerAction return: answerAction [
"This is the same as #on:fork: but instead just fork and letting the flow continues, in
case of an error it also evaluates answerAction and returns its result."

^ self on: exception do: [:ex |
| onDoCtx handler bottom thisCtx |

onDoCtx := thisContext.
thisCtx := onDoCtx home.

"find the context on stack for which this method's is sender"

[ onDoCtx sender == thisCtx] whileFalse: [
onDoCtx := onDoCtx sender.
onDoCtx ifNil: [
"Can't find our home context. seems like we're already forked
and handling another exception in new thread. In this case, just pass it through handler."
^ handlerAction cull: ex ] ].

bottom := [ Processor terminateActive ] asContext.
onDoCtx privSender: bottom.

handler := [ handlerAction cull: ex ] asContext.
handler privSender: thisContext sender.

(Process forContext: handler priority: Processor activePriority) resume.

"cut the stack of current process"
thisContext privSender: thisCtx.
answerAction cull: exception ]

]
6 changes: 6 additions & 0 deletions src/UnifiedFFI/FFIBool.class.st
Expand Up @@ -33,6 +33,12 @@ FFIBool >> basicHandle: aHandle at: index put: value [
^ aHandle booleanAt: index put: value
]

{ #category : #accessing }
FFIBool >> defaultReturnOnError [

^ false
]

{ #category : #'stack parameter classification' }
FFIBool >> stackValueParameterClass [
^ #integer
Expand Down
24 changes: 19 additions & 5 deletions src/UnifiedFFI/FFICallback.class.st
Expand Up @@ -69,7 +69,7 @@ FFICallback class >> signature: aSignature block: aBlock [
^ self new signature: aSignature block: aBlock
]

{ #category : #'as yet unclassified' }
{ #category : #evaluation }
FFICallback >> argumentsFor: stackPointer context: callbackContext [
| index architecture intRegisterCount intRegisterSize intRegisterIndex floatRegisterCount floatRegisterSize floatRegisterIndex floatRegisters intRegisters structureRegisterLayout |
self flag: 'TODO: Refactor and improve this code.'.
Expand Down Expand Up @@ -130,6 +130,15 @@ FFICallback >> argumentsFor: stackPointer context: callbackContext [
value ].
]

{ #category : #evaluation }
FFICallback >> executeWithArguments: argumentValues [

^ [ block valueWithArguments: argumentValues ]
on: Error
fork: [ :e | e pass ]
return: [ self returnOnError ]
]

{ #category : #private }
FFICallback >> ffiBindingOf: aName [
^ self class ffiBindingOf: aName
Expand All @@ -153,6 +162,12 @@ FFICallback >> newParser [
yourself
]

{ #category : #private }
FFICallback >> returnOnError [

^ functionSpec returnType defaultReturnOnError
]

{ #category : #initialization }
FFICallback >> signature: signature "<String>" block: aBlock [ "<BlockClosure>"
functionSpec := self newParser parseAnonymousFunction: signature.
Expand All @@ -169,12 +184,11 @@ FFICallback >> thunk [
]

{ #category : #evaluation }
FFICallback >> valueWithContext: callbackContext sp: stackPointer [
FFICallback >> valueWithContext: callbackContext sp: stackPointer [
| argumentValues |

self flag: #todo. "This can be optimised in a shadow method"

argumentValues := self argumentsFor: stackPointer context: callbackContext.
^ functionSpec returnType
callbackReturnOn: callbackContext
for: (block valueWithArguments: argumentValues)
for: (self executeWithArguments: argumentValues)
]
6 changes: 6 additions & 0 deletions src/UnifiedFFI/FFICharacterType.class.st
Expand Up @@ -33,6 +33,12 @@ FFICharacterType >> basicHandle: aHandle at: index put: value [
^ aHandle signedCharAt: index put: value
]

{ #category : #acccessing }
FFICharacterType >> defaultReturnOnError [

^ Character null
]

{ #category : #testing }
FFICharacterType >> needsArityPacking [
">1 because it can be a 'char *', then just roll when is 'char**' or bigger"
Expand Down
6 changes: 6 additions & 0 deletions src/UnifiedFFI/FFIExternalReferenceType.class.st
Expand Up @@ -48,6 +48,12 @@ FFIExternalReferenceType >> basicHandle: aHandle at: index put: value [

]

{ #category : #accessing }
FFIExternalReferenceType >> defaultReturnOnError [

^ ExternalAddress null
]

{ #category : #'emitting code' }
FFIExternalReferenceType >> emitReturn: aBuilder resultTempVar: resultVar context: aContext [
^ aBuilder
Expand Down
6 changes: 6 additions & 0 deletions src/UnifiedFFI/FFIExternalString.class.st
Expand Up @@ -33,6 +33,12 @@ FFIExternalString >> basicHandle: aHandle at: index put: value [
self error: 'Not sure I want to do this.'
]

{ #category : #accessing }
FFIExternalString >> defaultReturnOnError [

^ ''
]

{ #category : #accessing }
FFIExternalString >> externalTypeSize [
^ self pointerSize "i am live and die as a pointer (a char*)"
Expand Down
11 changes: 11 additions & 0 deletions src/UnifiedFFI/FFIExternalType.class.st
Expand Up @@ -130,6 +130,17 @@ FFIExternalType >> callbackValueFor: anObject at: index [
^ self handle: anObject at: index
]

{ #category : #accessing }
FFIExternalType >> defaultReturnOnError [
"In case of a callback error, the image will try to show a debugger and that will most ot the
time crashes the VM (because it will break the process and will let a C function waiting and
and in incorrect state).
To prevent that, we use #on:fork:return: (look for senders) and, while forking the error to
allow user to debug his error, we also return a 'default' value, that may be also wrong."

^ self subclassResponsibility
]

{ #category : #'emitting code' }
FFIExternalType >> emitArgument: aBuilder context: aContext [
self basicEmitArgument: aBuilder context: aContext.
Expand Down
6 changes: 6 additions & 0 deletions src/UnifiedFFI/FFIFloatType.class.st
Expand Up @@ -12,6 +12,12 @@ FFIFloatType >> callbackReturnOn: callbackContext for: aFloat [
^ callbackContext floatResult: aFloat
]

{ #category : #accessing }
FFIFloatType >> defaultReturnOnError [

^ 0.0
]

{ #category : #'stack parameter classification' }
FFIFloatType >> stackValueParameterClass [
^ #float
Expand Down
6 changes: 6 additions & 0 deletions src/UnifiedFFI/FFIIntegerType.class.st
Expand Up @@ -7,6 +7,12 @@ Class {
#category : #'UnifiedFFI-Types'
}

{ #category : #accessing }
FFIIntegerType >> defaultReturnOnError [

^ 0
]

{ #category : #'stack parameter classification' }
FFIIntegerType >> stackValueParameterClass [
^ #integer
Expand Down
6 changes: 6 additions & 0 deletions src/UnifiedFFI/FFIVoid.class.st
Expand Up @@ -31,6 +31,12 @@ FFIVoid >> callbackReturnOn: callbackContext for: anObject [

]

{ #category : #accessing }
FFIVoid >> defaultReturnOnError [

^ nil
]

{ #category : #'emitting code' }
FFIVoid >> emitPointerReturn: aBuilder resultTempVar: resultVar context: aContext [
^ aBuilder
Expand Down

0 comments on commit da608ce

Please sign in to comment.