The Trunk: Kernel-jcg.329.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Kernel-jcg.329.mcz

commits-2
Joshua Gargus uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-jcg.329.mcz

==================== Summary ====================

Name: Kernel-jcg.329
Author: jcg
Time: 17 December 2009, 11:59:29 am
UUID: 9ff6251d-dc4f-4f49-a1ed-476c4b0ba2f9
Ancestors: Kernel-ul.328

Support for using #future and #future: keywords to conveniently send asynchronous messages.

Core support is in the Kernel package, and the default behavior is defined by Project, in the System package.

=============== Diff against Kernel-ul.328 ===============

Item was added:
+ Object subclass: #Promise
+ instanceVariableNames: 'isResolved value resolvers mutex'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Kernel-Processes'!
+
+ !Promise commentStamp: 'jcg 12/17/2009 02:22' prior: 0!
+ I represent the result of an asynchronous message.  Once the message is processed, I will be resolved to a value.  I am typically instantiated by invocations of #futureSend:at:args: (and not by #futureDo:atArgs:).
+
+ See class-comment of FutureNode.!

Item was added:
+ ----- Method: Promise>>initialize (in category 'initialize') -----
+ initialize
+ isResolved := false.
+ resolvers := #().
+ mutex := Mutex new.!

Item was added:
+ ----- Method: Promise>>evaluateResolver: (in category 'private') -----
+ evaluateResolver: resolverBlock
+ resolverBlock numArgs = 0
+ ifTrue: [resolverBlock value]
+ ifFalse: [resolverBlock value: value].
+ !

Item was added:
+ ----- Method: Promise>>waitTimeoutSeconds: (in category 'waiting') -----
+ waitTimeoutSeconds: seconds
+ "Wait for at most the given number of seconds for this promise to resolve. Answer true if it is resolved, false otherwise."
+ ^self waitTimeoutMSecs: seconds*1000!

Item was added:
+ ----- Method: FutureMaker>>setTarget: (in category 'private') -----
+ setTarget: aTarget
+ myTarget := aTarget.!

Item was added:
+ ----- Method: FutureMaker>>isKindOf: (in category 'accessing') -----
+ isKindOf: aClass
+ "--- needed for debugging ---"
+ self class == aClass
+ ifTrue: [^true]
+ ifFalse: [^self class inheritsFrom: aClass]!

Item was added:
+ ----- Method: FutureMaker>>basicAt:put: (in category 'accessing') -----
+ basicAt: index put: value
+ "Primitive. Assumes receiver is indexable. Store the second argument
+ value in the indexable element of the receiver indicated by index. Fail
+ if the index is not an Integer or is out of bounds. Or fail if the value is
+ not of the right type for this kind of collection. Answer the value that
+ was stored. Essential. Do not override in a subclass. See Object
+ documentation whatIsAPrimitive."
+
+ <primitive: 61>
+ index isInteger
+ ifTrue: [(index >= 1 and: [index <= self size])
+ ifTrue: [self errorImproperStore]
+ ifFalse: [self errorSubscriptBounds: index]].
+ index isNumber
+ ifTrue: [^self basicAt: index asInteger put: value]
+ ifFalse: [self errorNonIntegerIndex]!

Item was added:
+ ----- Method: FutureMaker>>= (in category 'comparing') -----
+ = anObject
+ ^self == anObject!

Item was added:
+ ----- Method: FutureMaker>>instVarAt: (in category 'accessing') -----
+ instVarAt: index
+ "Primitive. Answer a fixed variable in an object. The numbering of the
+ variables corresponds to the named instance variables. Fail if the index
+ is not an Integer or is not the index of a fixed variable. Essential. See
+ Object documentation whatIsAPrimitive."
+
+ <primitive: 73>
+ "Access beyond fixed variables."
+ ^self basicAt: index - self class instSize !

Item was added:
+ ----- Method: Object>>future: (in category 'futures') -----
+ future: deltaMSecs
+ "See FutureMaker class comment.  In practice, this code is optimized away by the Compiler (see FutureNode)."
+ ^(FutureMaker new)
+ setDeltaMSecs: deltaMSecs target: self!

Item was added:
+ ----- Method: FutureMaker>>doesNotUnderstand: (in category 'accessing') -----
+ doesNotUnderstand: aMessage
+ "Package up the message and send it"
+ ^myTarget futureSend: aMessage selector at: deltaMSecs args: aMessage arguments!

Item was added:
+ ----- Method: FutureMaker>>printString (in category 'printing') -----
+ printString
+ "Answer a String whose characters are a description of the receiver.
+ If you want to print without a character limit, use fullPrintString."
+ ^ self printStringLimitedTo: 50000!

Item was added:
+ ----- Method: FutureMaker>>isMemberOf: (in category 'accessing') -----
+ isMemberOf: aClass
+ "Answer whether the receiver is an instance of the class, aClass."
+ ^self class == aClass!

Item was added:
+ ----- Method: FutureMaker>>instVarAt:put: (in category 'accessing') -----
+ instVarAt: anInteger put: anObject
+ "Primitive. Store a value into a fixed variable in the receiver. The
+ numbering of the variables corresponds to the named instance variables.
+ Fail if the index is not an Integer or is not the index of a fixed variable.
+ Answer the value stored as the result. Using this message violates the
+ principle that each object has sovereign control over the storing of
+ values into its instance variables. Essential. See Object documentation
+ whatIsAPrimitive."
+
+ <primitive: 74>
+ "Access beyond fixed fields"
+ ^self basicAt: anInteger - self class instSize put: anObject!

Item was added:
+ ----- Method: FutureMaker>>isText (in category 'testing') -----
+ isText
+ ^false!

Item was added:
+ ----- Method: Promise>>waitTimeoutMSecs: (in category 'waiting') -----
+ waitTimeoutMSecs: msecs
+ "Wait for at most the given number of milliseconds for this promise to resolve. Answer true if it is resolved, false otherwise."
+ | sema delay |
+ sema := Semaphore new.
+ self whenComplete:[sema signal].
+ delay := Delay timeoutSemaphore: sema afterMSecs: msecs.
+ [sema wait] ensure: [delay unschedule].
+ ^isResolved!

Item was added:
+ ----- Method: FutureMaker>>basicAt: (in category 'accessing') -----
+ basicAt: index
+ "Primitive. Assumes receiver is indexable. Answer the value of an
+ indexable element in the receiver. Fail if the argument index is not an
+ Integer or is out of bounds. Essential. Do not override in a subclass. See
+ Object documentation whatIsAPrimitive."
+
+ <primitive: 60>
+ index isInteger ifTrue: [self errorSubscriptBounds: index].
+ index isNumber
+ ifTrue: [^self basicAt: index asInteger]
+ ifFalse: [self errorNonIntegerIndex]!

Item was added:
+ ----- Method: FutureMaker>>setDeltaMSecs:target: (in category 'private') -----
+ setDeltaMSecs: delta target: futureTarget
+ deltaMSecs := delta.
+ myTarget := futureTarget.!

Item was added:
+ ----- Method: Promise>>whenResolved: (in category 'resolving') -----
+ whenResolved: aBlock
+ "Evaluate aBlock when I am resolved"
+ aBlock numArgs <= 1 ifFalse:[self error: 'Must be 0- or 1-argument block'].
+ mutex critical: [
+ resolvers := resolvers copyWith: aBlock.
+ self isResolved ifTrue:[self evaluateResolver: aBlock].
+ ]!

Item was added:
+ ----- Method: Object>>future (in category 'futures') -----
+ future
+ "See FutureMaker class comment.  In practice, this code is optimized away by the Compiler (see FutureNode)."
+ ^(FutureMaker new)
+ setDeltaMSecs: 0.0 target: self!

Item was added:
+ ----- Method: Promise>>resolveWith: (in category 'resolving') -----
+ resolveWith: arg
+ "Resolve this promise"
+ mutex critical: [
+ isResolved ifTrue: [self error: 'Promise was already resolved'].
+ value := arg.
+ isResolved := true.
+ resolvers ifNotNil: [resolvers do: [:r | self evaluateResolver: value]].
+ ].!

Item was added:
+ ----- Method: FutureMaker>>inspectorClass (in category 'debug') -----
+ inspectorClass
+ "Answer the class of the inspector to be used on the receiver.  Called by inspect;
+ use basicInspect to get a normal (less useful) type of inspector."
+
+ ^ Inspector!

Item was added:
+ ----- Method: Object>>futureSend:at:args: (in category 'futures') -----
+ futureSend: aSelector at: deltaMSecs args: args
+ "Send a message deltaSeconds into the future (some implementations may requires 'deltaMSecs' to be zero).  Answers a Promise that will be resolved at some time in the future.  See comment in class FutureNode."
+ ^Project current future: self send: aSelector at: deltaMSecs args: args.!

Item was added:
+ ----- Method: Promise>>wait (in category 'waiting') -----
+ wait
+ "Wait unconditionally for this promise to resolve."
+ | sema |
+ sema := Semaphore new.
+ self whenResolved:[sema signal].
+ sema wait.
+ ^value!

Item was added:
+ ----- Method: Promise>>value (in category 'accessing') -----
+ value
+ ^value!

Item was added:
+ ----- Method: FutureMaker>>defaultLabelForInspector (in category 'debug') -----
+ defaultLabelForInspector
+ "Answer the default label to be used for an Inspector window on the receiver."
+ ^self class name!

Item was added:
+ ----- Method: FutureMaker>>printOn: (in category 'printing') -----
+ printOn: aStream
+ "Append to the argument, aStream, a sequence of characters that  
+ identifies the receiver."
+ | title |
+ title := self class name.
+ aStream
+ nextPutAll: (title first isVowel ifTrue: ['an '] ifFalse: ['a ']);
+ nextPutAll: title!

Item was added:
+ ----- Method: FutureMaker>>basicSize (in category 'accessing') -----
+ basicSize
+ "Primitive. Answer the number of indexable variables in the receiver.
+ This value is the same as the largest legal subscript. Essential. Do not
+ override in any subclass. See Object documentation whatIsAPrimitive."
+
+ <primitive: 62>
+ "The number of indexable fields of fixed-length objects is 0"
+ ^0!

Item was added:
+ ----- Method: FutureMaker>>hash (in category 'comparing') -----
+ hash
+ ^self identityHash!

Item was added:
+ ----- Method: Promise>>isResolved (in category 'testing') -----
+ isResolved
+ ^isResolved!

Item was added:
+ ----- Method: FutureMaker>>printStringLimitedTo: (in category 'printing') -----
+ printStringLimitedTo: limit
+ "Answer a String whose characters are a description of the receiver.
+ If you want to print without a character limit, use fullPrintString."
+ | limitedString |
+ limitedString := String streamContents: [:s | self printOn: s] limitedTo: limit.
+ limitedString size < limit ifTrue: [^ limitedString].
+ ^ limitedString , '...etc...'!

Item was added:
+ ProtoObject subclass: #FutureMaker
+ instanceVariableNames: 'myTarget deltaMSecs'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Kernel-Processes'!
+
+ !FutureMaker commentStamp: 'jcg 12/17/2009 23:24' prior: 0!
+ Uses #doesNotUnderstand: to transform messages into future messages.  In practice, this class is never used; for efficiency, the Compiler has been modified to use FutureNode to transform code at compile-time to directly send #futureSend:at:args:.  However, this is simply an optimization... the semantics are unchanged.!

Item was added:
+ ----- Method: Object>>futureDo:at:args: (in category 'futures') -----
+ futureDo: aSelector at: deltaMSecs args: args
+ "Send a message deltaMSecs into the future (some implementations may requires 'deltaMSecs' to be zero).  No response is expected.  See comment in class FutureNode."
+ Project current future: self do: aSelector at: deltaMSecs args: args.
+ ^nil!