[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

api[apple,Foundation] definitions

"NSObject.st"

Coco8Implementation
 subclass: #NSObject
 category: #Foundation!

! NSObject class methodsFor: #instantiation !
instance
	" Return an instance of the receiver. "

	^self @ (self nativeClass basicAt: #instance)! !

! NSObject class methodsFor: #accessing !
classHandle
	" Return the objC class handle (of the native class) of the receiver.  "

	^self nativeClass basicAt: #class! !

! NSObject class methodsFor: #accessing !
description
	" Returns a string that represents the contents of the receiver.  "

	^self nativeClass basicAt: #description! !

! NSObject methodsFor: #query !
respondsToSelector: objCSelector

	^(self handle respondsToSelector: objCSelector) notNil! !

! NSObject methodsFor: #release !
releaseHandle
	" Release the handle (native objC object). "

	self handle release.
	^super releaseHandle! !

NSObject
	subclass: #Coco8Closure
	instanceVariableNames: #block
	category: #Foundation!
Coco8Closure buildAccessors!

! Coco8Closure class methodsFor: #objC !
implementation
	" Private - Return the implementation literal of the receiver. "

	^(#outlets -> #())
	,(#actions -> #())
	,(#methods -> #(
		#( #fire #void )
		#( #fireWithArguments: 'void id')
		))! !

! Coco8Closure methodsFor: #objC !
fireWithArguments: theArguments
	" Private - Evaluate the block with arguments. "

	<objC: method>
	self block evaluateWithArguments: theArguments! !

! Coco8Closure methodsFor: #objC !
fire
	" Private - Evaluate the block. "

	<objC: method>
	self block evaluate! !

! Coco8Closure class methodsFor: #instantiation !
block: action
	" Return an instance of the receiver that will evaluate action when fired. "

	^self new
		block: action;
		yourself! !

! Coco8Closure class methodsFor: #instantiation !
value: action withArguments: array after: milliSeconds
	" Return an instance of the receiver that will evaluate action with arguments array after specified time. "

	^self	value: action
		withArguments: array
		afterSeconds: milliSeconds / 1000! !

! Coco8Closure class methodsFor: #instantiation !
value: action withArguments: anArray afterSeconds: seconds
	" Return an instance of the receiver that will evaluate action with arguments anArray after specified time. "

	^(self block: [ action evaluateWithArguments: anArray ])
		performSelector: #fire withObject: nil
		afterDelay: seconds! !

! Coco8Closure class methodsFor: #instantiation !
value: action after: milliSeconds
	" Return an instance of the receiver that will evaluate action with arguments array after specified time. "

	^self	value: action
		withArguments: #()
		after: milliSeconds! !

! Coco8Closure class methodsFor: #instantiation !
value: action afterSeconds: seconds
	" Return an instance of the receiver that will evaluate action with arguments array after specified time. "

	^self	value: action
		withArguments: #()
		afterSeconds: seconds! !

! Coco8Closure methodsFor: #initialize !
initializeHandle
	" Private - Initialize the handle of the receiver. "

	handle := self nativeClass basicAt: #instance.
	self bindToHandle: handle.! !

! BlockClosure methodsFor: 'NSObject-timeout' !
valueWithTimeout: aNumber
	" Evaluate the receiver with time out. "

	Coco8Closure isInstalled ifTrue: [
		^Coco8Closure value: self after: aNumber
	].
	"if coco8 is not running, we will try with default impl."
	^# #setTimeout: self with: aNumber! !

! Coco8Closure class methodsFor: #instantiation !
value: action withArguments: anArray
	" Return an instance of the receiver that will evaluate action with arguments anArray in main thread. "

	^(self block: [ action evaluateWithArguments: anArray ])
		performSelectorOnMainThread: #fire
		withObject: nil waitUntilDone: false! !

! BlockClosure methodsFor: 'NSObject-timeout' !
valueOnMainThreadWithArguments: args
	" Evaluate the receiver in the main thread. "

	Coco8Closure isInstalled ifTrue: [
		^Coco8Closure value: self withArguments: args
	].
	"if coco8 is not running, we simulate the evaluation."
	^self valueWithArguments: args! !

! BlockClosure methodsFor: 'NSObject-timeout' !
valueOnMainThread
	" Evaluate the receiver in the main thread. "

	^self valueOnMainThreadWithArguments: #()! !