Initial revision
authorclaus
Sat, 18 Feb 1995 00:50:56 +0100
changeset 62 a759b5c72c98
parent 61 13d2435bc955
child 63 7dd3d5b7877e
Initial revision
Future.st
Iterator.st
Lazy.st
OrderedDictionary.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/Future.st	Sat Feb 18 00:50:56 1995 +0100
@@ -0,0 +1,266 @@
+"       NAME            Parallelism
+        AUTHOR          tph@cs.man.ac.uk
+        FUNCTION throttled Futures; lazy eval; explicit pa'l'l procs 
+        ST-VERSIONS     stx
+        PREREQUISITES    
+        CONFLICTS       
+        DISTRIBUTION    world
+        VERSION         1.1
+        DATE    22 Jan 1989
+        SUMMARY 
+Parallelism contains a number of explicitly parallel constructs,
+including a new version of Future, Lazy evaluation, and explicit
+parallel processes.  Lots of code in here.  Contains an early
+version (read: doesn't work) of a ""throttled"" future mechanism.
+New version RSN.(2.2).TPH
+
+claus: I have separated the original Parallelism package into
+       individual ones: Lazy, Future, ThrottledFuture and ParallelEvaluation
+"!
+
+'From Smalltalk-80, version 2, of April 1, 1983 on 29 March 1987 at 5:13:27 pm'!
+
+!Object methodsFor: 'parallel evaluation'!
+
+touch
+        "Simply returns self.  If the receiver is an uncompleted
+         Future or Lazy, this forces complete evaluation."
+
+        ^self
+! !
+
+Object subclass: #Future
+        instanceVariableNames: 'result semaphore '
+        classVariableNames: ''
+        poolDictionaries: ''
+        category: 'Kernel-Processes'
+!
+
+Future comment:
+'I represent an execution in progress.  Any messages sent to me are delayed until
+ execution has completed.'
+!
+
+!Future methodsFor: 'synchronising'!
+
+doesNotUnderstand: aMessage
+        "Any message to a Future will end up here."
+
+        semaphore wait.     "Wait for evaluation to complete"
+                            "(if not already completed)"
+        semaphore signal.   "Wake up anything else that might be waiting"
+        ^result perform: aMessage selector 
+                withArguments: aMessage arguments
+! !
+
+!Future methodsFor: 'evaluating'!
+
+block: aBlock
+        "Execute aBlock in parallel with whatever called me, but
+         ensure that any messages sent to me before execution
+         of the block has terminated are suspended until it has terminated."
+
+        semaphore _ Semaphore new.
+        [result _ aBlock value.  semaphore signal] fork
+!
+
+block: aBlock value: aValue
+        "Execute aBlock in parallel with whatever called me, but
+         ensure that any messages sent to me before execution
+         of the block has terminated are suspended until it has terminated."
+
+        semaphore _ Semaphore new.
+        [result _ aBlock value: aValue.  semaphore signal] fork
+!
+
+block: aBlock value: value1 value: value2
+        "Execute aBlock in parallel with whatever called me, but
+         ensure that any messages sent to me before execution
+         of the block has terminated are suspended until it has terminated."
+
+        semaphore _ Semaphore new.
+        [result _ aBlock value: value1 value: value2.
+         semaphore signal] fork
+!
+
+block: aBlock value: value1 value: value2 value: value3
+        "Execute aBlock in parallel with whatever called me, but
+         ensure that any messages sent to me before execution
+         of the block has terminated are suspended until it has terminated."
+
+        semaphore _ Semaphore new.
+        [result _ aBlock value: value1 value: value2 value: value3.
+         semaphore signal] fork
+!
+
+block: aBlock valueWithArguments: anArray
+        "Execute aBlock in parallel with whatever called me, but
+         ensure that any messages sent to me before execution
+         of the block has terminated are suspended until it has terminated."
+
+        semaphore _ Semaphore new.
+        [result _ aBlock valueWithArguments: anArray.
+         semaphore signal] fork
+! !
+
+!Future class methodsFor: 'examples'!
+
+example1
+        "Starts evaluating the factorial immediately, but waits until
+         the result is available before printing the answer!!"
+
+        | fac |
+        fac _ [100 factorial] futureValue.
+        Transcript showCr: 'evaluating factorial...'.
+        Transcript showCr: fac printString
+
+        "Future example1"
+!
+
+example2
+        "An example illustrating the use of multiple futures and
+         explicit resynchronisation."
+
+        "Starts evaluating both factorials immediately, but waits until
+         both blocks have finished before continuing."
+
+        | fac1 fac2 |
+        fac1 _ [Transcript showCr: 'Starting fac1.. '. 1000 factorial] futureValue.
+        fac2 _ [Transcript showCr: 'Starting fac2.. '. 2000 factorial] futureValue.
+        fac2 touch.
+        fac1 touch.
+        Transcript showCr: 'both completed.'.
+
+        "Future example2"
+!
+
+example3
+        "Example showing how arguments may be passed to futures."
+
+        | temp |
+        temp _ [:x :y | 10 * x * y] futureValue: 3 value: 4.
+        Transcript  showCr: temp printString.
+
+        "Future example3"
+! !
+
+!Future class methodsFor: 'class initialization'!
+
+initialize
+        "must avoid the checks"
+
+        superclass _ nil
+
+        "Future initialize."
+! !
+
+Future initialize!
+
+!Block methodsFor: 'parallel evaluation'!
+
+futureValue
+        "Fork a synchronised evaluation of myself. Starts the
+         evaluation in parallel immediately."
+
+        ^Future new block: self
+!
+
+futureValue: aValue
+        "Fork a synchronised evaluation of myself. Starts the
+         evaluation in parallel immediately."
+
+        ^Future new block: self value: aValue
+!
+
+futureValue: aValue value: anotherValue
+        "Fork a synchronised evaluation of myself. Starts the
+         evaluation in parallel immediately."
+
+        ^Future new block: self value: aValue value: anotherValue
+!
+
+futureValue: aValue value: anotherValue value: bValue
+        "Fork a synchronised evaluation of myself. Starts the
+         evaluation in parallel immediately."
+
+        ^Future new block: self value: aValue value: anotherValue value: bValue
+!
+
+futureValueWithArguments: anArray
+        "Fork a synchronised evaluation of myself. Starts the
+         evaluation in parallel immediately."
+
+        ^Future new block: self valueWithArguments: anArray
+! 
+
+parallelAnd: aBlock 
+        "Executes the receiver in parallel with aBlock. Once both   
+         have completed, perform a logical AND operation."
+
+        | first second |
+        first _ self futureValue.
+        second _ aBlock futureValue.
+        ^first touch & second touch!
+
+parallelEqv: aBlock 
+        "Executes the receiver in parallel with aBlock. Once both   
+         have completed, perform a logical equivalence (exclusive-NOR)
+         operation."
+
+        | first second |
+        first _ self futureValue.
+        second _ aBlock futureValue.
+        ^first touch eqv: second touch!
+
+parallelOr: aBlock 
+        "Executes the receiver in parallel with aBlock. Once both   
+         have completed, perform a logical OR operation."
+
+        | first second |
+        first _ self futureValue.
+        second _ aBlock futureValue.
+        ^first touch | second touch!
+
+parallelPerform: aSymbol with: aBlock 
+        "Executes the receiver in parallel with aBlock. Once both  
+         have completed, perform the operation given by aSymbol."
+
+        | first second |
+        first _ self futureValue.
+        second _ aBlock futureValue.
+        ^first touch perform: aSymbol with: second touch!
+
+parallelXor: aBlock 
+        "Executes the receiver in parallel with aBlock. Once both   
+         have completed, perform a logical equivalence (exclusive-NOR)
+         operation."
+
+        | first second |
+        first _ self futureValue.
+        second _ aBlock futureValue.
+        ^first touch xor: second touch
+! !
+
+
+"COPYRIGHT.
+ The above file is a Manchester Goodie protected by copyright.
+ These conditions are imposed on the whole Goodie, and on any significant
+ part of it which is separately transmitted or stored:
+        * You must ensure that every copy includes this notice, and that
+          source and author(s) of the material are acknowledged.
+        * These conditions must be imposed on anyone who receives a copy.
+        * The material shall not be used for commercial gain without the prior
+          written consent of the author(s).
+ Further information on the copyright conditions may be obtained by
+ sending electronic mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: copyright
+ or by writing to The Smalltalk Goodies Library Manager, Dept of
+ Computer Science, The University, Manchester M13 9PL, UK
+
+ (C) Copyright 1992 University of Manchester
+ For more information about the Manchester Goodies Library (from which 
+ this file was distributed) send e-mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: help 
+"!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/Iterator.st	Sat Feb 18 00:50:56 1995 +0100
@@ -0,0 +1,187 @@
+"       NAME            Iterator
+        AUTHOR          miw@cs.man.ac.uk (Mario Wolczko)
+        FUNCTION        a wrapper for blocks that iterate over collections
+        ST-VERSION      4.0 4.1
+        PREREQUISITES   
+        CONFLICTS
+        DISTRIBUTION    world
+        VERSION         1
+        DATE    18 Jun 1991
+        SUMMARY
+ Occasionally you may have a block that when evaluated can be
+treated as a collection -- ie it takes another block as parameter,
+then applies that to a sequence of values.
+
+This goodie wraps the block into an object -- an iterator -- which is
+part of the collection hierarchy, and therefore inherits a variety of
+useful collection-related methods.
+
+Mario Wolczko
+
+Dept. of Computer Science   Internet:      mario@cs.man.ac.uk
+The University              uucp:        uknet!!man.cs!!mario
+Manchester M13 9PL          JANET:         mario@uk.ac.man.cs
+U.K.                        Tel: +44-61-275 6146  (FAX: 6236)
+______the mushroom project___________________________________
+
+"
+'From Objectworks(r)\Smalltalk, Release 4 of 25 October 1990 on 18 June 1991 at 7:48:59 pm'!
+
+Collection subclass: #Iterator
+        instanceVariableNames: 'block '
+        classVariableNames: ''
+        poolDictionaries: ''
+        category: 'Collections-Sequenceable'
+!
+
+Iterator comment:
+'An Iterator is a read-only collection that evaluates a block to yield the elements
+ of the collection.'
+!
+
+!Iterator methodsFor: 'removing'!
+
+remove: oldObject ifAbsent: anExceptionBlock 
+        "Iterators are read-only."
+        self shouldNotImplement
+! !
+
+!Iterator methodsFor: 'adding'!
+
+add: anObject
+        "Iterators are read-only"
+        self shouldNotImplement
+! !
+
+!Iterator methodsFor: 'enumerating'!
+
+do: aBlock
+        block value: aBlock
+!
+
+findFirst: aBlock
+        "Answer the index of the first element of the receiver
+        for which aBlock evaluates as true."
+
+        | index |
+        index := 1.
+        self do: [ :el | (aBlock value: el) ifTrue: [^index].  index := index + 1].
+
+        ^0
+!
+
+findLast: aBlock
+        "Answer the index of the last element of the receiver
+        for which aBlock evaluates as true."
+
+        | index last |
+        index := 1.
+        last := 0.
+        self do: [ :el | (aBlock value: el) ifTrue: [last := index].  index := index + 1].
+        ^last
+!
+
+keysAndValuesDo: aBlock  
+        "Evaluate aBlock with each of the receiver's key/value pairs
+        (e.g. indexes and elements) as the arguments."
+
+        | index |
+        index := 1.
+        self do: [:el | aBlock value: index value: el.  index := index + 1]
+! !
+
+!Iterator methodsFor: 'accessing'!
+
+identityIndexOf: anElement 
+        "Answer the identity index of anElement within the receiver.  
+         If the receiver does not contain anElement, answer 0."
+
+        ^self identityIndexOf: anElement ifAbsent: [0]
+!
+
+identityIndexOf: anElement ifAbsent: exceptionBlock 
+        "Answer the identity index of anElement within the receiver.  
+         If the receiver does not contain anElement, answer the result 
+         of evaluating the exceptionBlock."
+
+        | index |
+        index := 1.
+        self do: [ :el | el == anElement ifTrue: [^index].  index := index + 1].
+        ^exceptionBlock value
+!
+
+indexOf: anElement 
+        "Answer the index of anElement within the receiver.  If the receiver does
+        not contain anElement, answer 0."
+
+        ^self indexOf: anElement ifAbsent: [0]
+!
+
+indexOf: anElement ifAbsent: exceptionBlock 
+        "Answer the index of anElement within the receiver.  If the receiver does
+        not contain anElement, answer the result of evaluating the exceptionBlock."
+
+
+        | index |
+        index := 1.
+        self do: [ :el | el = anElement ifTrue: [^index].  index := index + 1].
+        ^exceptionBlock value
+! !
+
+!Iterator methodsFor: 'private'!
+
+block: aBlock
+        block := aBlock
+!
+
+species
+        ^OrderedCollection
+! !
+
+!Iterator methodsFor: 'converting'!
+
+asOrderedCollection
+        "Answer a new instance of OrderedCollection whose elements are the elements of
+        the receiver.  The order in which elements are added depends on the order in
+        which the receiver enumerates its elements.  In the case of unordered collections,
+        the ordering is not necessarily the same for multiple requests for the conversion."
+
+
+        | anOrderedCollection |
+        anOrderedCollection := OrderedCollection new.
+        self do: [:each | anOrderedCollection addLast: each].
+        ^anOrderedCollection
+! !
+
+!Iterator class methodsFor: 'instance creation'!
+
+on: aBlock
+        ^self new block: aBlock
+!
+
+on: collection msg: msg
+        ^self new block: [ :aBlock | collection perform: msg with: aBlock]
+! !
+
+"COPYRIGHT.
+ The above file is a Manchester Goodie protected by copyright.
+ These conditions are imposed on the whole Goodie, and on any significant
+ part of it which is separately transmitted or stored:
+        * You must ensure that every copy includes this notice, and that
+          source and author(s) of the material are acknowledged.
+        * These conditions must be imposed on anyone who receives a copy.
+        * The material shall not be used for commercial gain without the prior
+          written consent of the author(s).
+ Further information on the copyright conditions may be obtained by
+ sending electronic mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: copyright
+ or by writing to The Smalltalk Goodies Library Manager, Dept of
+ Computer Science, The University, Manchester M13 9PL, UK
+
+ (C) Copyright 1992 University of Manchester
+ For more information about the Manchester Goodies Library (from which 
+ this file was distributed) send e-mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: help 
+"!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/Lazy.st	Sat Feb 18 00:50:56 1995 +0100
@@ -0,0 +1,220 @@
+"       NAME            Parallelism
+        AUTHOR          tph@cs.man.ac.uk
+        FUNCTION throttled Futures; lazy eval; explicit pa'l'l procs 
+        ST-VERSIONS     stx
+        PREREQUISITES    
+        CONFLICTS       
+        DISTRIBUTION    world
+        VERSION         1.1
+        DATE    22 Jan 1989
+        SUMMARY 
+Parallelism contains a number of explicitly parallel constructs,
+including a new version of Future, Lazy evaluation, and explicit
+parallel processes.  Lots of code in here.  Contains an early
+version (read: doesn't work) of a ""throttled"" future mechanism.
+New version RSN.(2.2).TPH
+
+claus: I have separated the original Parallelism package into
+       individual ones: Lazy, Future, ThrottledFuture and ParallelEvaluation
+"!
+
+'From Smalltalk-80, version 2, of April 1, 1983 on 29 March 1987 at 5:13:27 pm'!
+
+!Object methodsFor: 'parallel evaluation'!
+
+touch
+        "Simply returns self.  If the receiver is an uncompleted
+         Future or Lazy, this forces complete evaluation."
+
+        ^self
+! !
+
+'From Smalltalk-80, version 2, of April 1, 1983 on 29 March 1987 at 5:09:10 pm'!
+
+Object subclass: #Lazy
+        instanceVariableNames: 'result startSemaphore endSemaphore '
+        classVariableNames: ''
+        poolDictionaries: ''
+        category: 'Kernel-Processes'!
+Lazy comment:
+'I represent an execution which may not be required.  I will
+not start execution until at least one message has been
+received.  The messages sent to me are delayed until execution
+has completed.'!
+
+
+!Lazy methodsFor: 'synchronising'!
+
+doesNotUnderstand: aMessage
+        "Any message to a Lazy will end up here."
+
+        startSemaphore signal.          "Start the evaluation."
+        endSemaphore wait.              "Wait until evaluation completed."
+        endSemaphore signal.            "Wake up anything else."
+        ^result perform: aMessage selector withArguments: aMessage arguments
+                "Perform the message, having re-synchronised."! !
+
+!Lazy methodsFor: 'evaluating'!
+
+block: aBlock
+        "Execute aBlock in parallel, but ensure that any messages sent
+         to me before execution of the block has terminated are
+         suspended until it has terminated. Do not start the evaluation
+         until at least one message has been sent to the receiver."
+
+        startSemaphore _ Semaphore new.
+        endSemaphore _ Semaphore new.
+        [startSemaphore wait.
+         result _ aBlock value.
+         endSemaphore signal] fork!
+
+block: aBlock value: aValue
+        "Execute aBlock in parallel, but ensure that any messages sent
+         to me before execution of the block has terminated are
+         suspended until it has terminated. Do not start the evaluation
+         until at least one message has been sent to the receiver."
+
+        startSemaphore _ Semaphore new.
+        endSemaphore _ Semaphore new.
+        [startSemaphore wait.
+         result _ aBlock value: aValue.
+         endSemaphore signal] fork!
+
+block: aBlock value: value1 value: value2
+        "Execute aBlock in parallel, but ensure that any messages sent
+         to me before execution of the block has terminated are
+         suspended until it has terminated. Do not start the evaluation
+         until at least one message has been sent to the receiver."
+
+        startSemaphore _ Semaphore new.
+        endSemaphore _ Semaphore new.
+        [startSemaphore wait.
+         result _ aBlock value: value1 value: value2.
+         endSemaphore signal] fork!
+
+block: aBlock value: value1 value: value2 value: value3
+        "Execute aBlock in parallel, but ensure that any messages sent
+         to me before execution of the block has terminated are
+         suspended until it has terminated. Do not start the evaluation
+         until at least one message has been sent to the receiver."
+
+        startSemaphore _ Semaphore new.
+        endSemaphore _ Semaphore new.
+        [startSemaphore wait.
+         result _ aBlock value: value1 value: value2 value: value3.
+         endSemaphore signal] fork!
+
+block: aBlock valueWithArguments: anArray
+        "Execute aBlock in parallel, but ensure that any messages sent
+         to me before execution of the block has terminated are
+         suspended until it has terminated. Do not start the evaluation
+         until at least one message has been sent to the receiver."
+
+        startSemaphore _ Semaphore new.
+        endSemaphore _ Semaphore new.
+        [startSemaphore wait.
+         result _ aBlock valueWithArguments: anArray.
+         endSemaphore signal] fork! !
+
+!Lazy class methodsFor: 'class initialization'!
+
+initialize
+        "must avoid the checks"
+
+        superclass _ nil
+
+        "Lazy initialize."! !
+
+!Lazy class methodsFor: 'examples'!
+
+example1
+        "Evaluates the factorial, starting only when the
+         result is actually required (when printString is sent)."
+
+        | fac |
+        fac _ [100 factorial] futureValue.
+        Transcript showCr: 'Doing nothing. '.
+        (Delay forSeconds: 2) wait.
+        Transcript showCr: fac printString
+
+        "Lazy example1"!
+
+example2
+        "Starts evaluating both factorials only when required (by the touch),
+         and waits until both blocks have finished before continuing."
+
+        | fac1 fac2 |
+        fac1 _ [Transcript showCr: 'Starting fac1.. '. 100 factorial] lazyValue.
+        fac2 _ [Transcript showCr: 'Starting fac2.. '. 120 factorial] lazyValue.
+        fac2 touch.
+        fac1 touch.
+        Transcript showCr: 'both completed.'.
+
+        "Lazy example2"!
+
+example3
+        "Demonstrates how to pass arguments to a lazy evaluation block."
+
+        | temp |
+        temp _ [:x :y :z | x * y * z] lazyValueWithArguments: #(2 3 4).
+        Transcript  showCr: temp printString.
+
+        "Lazy example3"! !
+
+Lazy initialize!
+
+!Block methodsFor: 'parallel evaluation'!
+
+lazyValue
+        "Fork a synchronised evaluation of myself. Only starts
+         the evaluation when the result is requested."
+
+        ^Lazy new block: self!
+
+lazyValue: aValue
+        "Fork a synchronised evaluation of myself. Only starts
+         the evaluation when the result is requested."
+
+        ^Lazy new block: self value: aValue!
+
+lazyValue: aValue value: anotherValue
+        "Fork a synchronised evaluation of myself. Only starts
+         the evaluation when the result is requested."
+
+        ^Lazy new block: self value: aValue value: anotherValue!
+
+lazyValue: aValue value: anotherValue value: bValue
+        "Fork a synchronised evaluation of myself. Only starts
+         the evaluation when the result is requested."
+
+        ^Lazy new block: self value: aValue value: anotherValue value: bValue!
+
+lazyValueWithArguments: anArray
+        "Fork a synchronised evaluation of myself. Only starts
+         the evaluation when the result is requested."
+
+        ^Lazy new block: self valueWithArguments: anArray
+! !
+
+"COPYRIGHT.
+ The above file is a Manchester Goodie protected by copyright.
+ These conditions are imposed on the whole Goodie, and on any significant
+ part of it which is separately transmitted or stored:
+        * You must ensure that every copy includes this notice, and that
+          source and author(s) of the material are acknowledged.
+        * These conditions must be imposed on anyone who receives a copy.
+        * The material shall not be used for commercial gain without the prior
+          written consent of the author(s).
+ Further information on the copyright conditions may be obtained by
+ sending electronic mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: copyright
+ or by writing to The Smalltalk Goodies Library Manager, Dept of
+ Computer Science, The University, Manchester M13 9PL, UK
+
+ (C) Copyright 1992 University of Manchester
+ For more information about the Manchester Goodies Library (from which 
+ this file was distributed) send e-mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: help 
+"!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/OrderedDictionary.st	Sat Feb 18 00:50:56 1995 +0100
@@ -0,0 +1,603 @@
+"       NAME            OrderedDictionary
+        AUTHOR          Ifor Wyn Williams <ifor@uk.ac.man.cs>
+        CONTRIBUTOR     Ifor Wyn Williams <ifor@uk.ac.man.cs>
+        FUNCTION        An ordered dictionary
+        ST-VERSIONS     2.3-5, 4.0
+        PREREQUISITES   
+        CONFLICTS       
+        DISTRIBUTION    global
+        VERSION         1.2
+        DATE            28.3.90
+SUMMARY         A dictionary that behaves like a SequencableCollection
+(except that associations cannot be removed). 
+"!
+
+'From Smalltalk-80, Version 2.4 of 28 January 1989 on 28 March 1990 at 11:32:50 am'!
+
+Dictionary subclass: #OrderedDictionary
+        instanceVariableNames: 'order '
+        classVariableNames: ''
+        poolDictionaries: ''
+        category: 'Collections-Sequenceable'
+!
+
+OrderedDictionary comment:
+'I am a subclass of Dictionary whose elements (associations) are ordered in a
+ similar fashion to OrderedCollection.
+
+I have one instance variable:
+
+order <OrderedCollection>       Ordered collection of keys reflecting the order of
+                                associations in the dictionary. '
+!
+
+!OrderedDictionary methodsFor: 'adding'!
+
+add: anAssociation 
+        "add anAssociation to the dictionary"
+
+        | key |
+
+        key := anAssociation key.
+        (super includesKey: key)
+                ifFalse: [order add: key].
+        super add: anAssociation
+!
+
+add: anAssociation after: oldAssociation 
+        "Add the argument, anAssociation, as an element of the dictionary. Put it 
+        in the position just succeeding oldAssociation. Return anAssociation."
+
+        | index |
+
+        index := self indexOfAssociation: oldAssociation 
+                                ifAbsent: [self error: 'association not found'].
+        self removeFromOrder: anAssociation key.
+        order add: anAssociation key after: (order at: index).
+        super add: anAssociation.
+        ^ anAssociation
+!
+
+add: anAssociation before: oldAssociation 
+        "Add the argument, anAssociation, as an element of the dictionary. Put it 
+        in the position just preceding oldAssociation. Return anAssociation."
+
+        | index |
+
+        index := self indexOfAssociation: oldAssociation 
+                                ifAbsent: [self error: 'association not found'].
+        self removeFromOrder: anAssociation key.
+        order add: anAssociation key before: (order at: index).
+        super add: anAssociation.
+        ^ anAssociation
+!
+
+add: anAssociation beforeIndex: spot 
+        "Add the argument, anAssociation, as an element of the receiver.  Put it
+        in the position just preceding the indexed position spot.  Return newObject."
+
+        self removeFromOrder: anAssociation key.
+        order insert: anAssociation key before: spot.
+        super add: anAssociation
+!
+
+addAll: aCollectionOfAssociations 
+        "Add each element of aCollectionOfAssociations at my end."
+
+        aCollectionOfAssociations associationsDo: [:elems | self add: elems]
+!
+
+addAllFirst: anOrderedCollectionOfAssociations 
+        "Add each element of anOrderedCollectionOfAssociations at the beginning 
+         of the receiver."
+
+        anOrderedCollectionOfAssociations reverseDo: [:each | self addFirst: each]
+!
+
+addAllLast: anOrderedCollectionOfAssociations 
+        "Add each element of anOrderedCollectionOfAssociations at the end of the 
+        receiver."
+
+        anOrderedCollectionOfAssociations do: [:each | self addLast: each]
+!
+
+addFirst: anAssociation 
+        "Add anAssociation to the beginning of the receiver."
+
+        self removeFromOrder: anAssociation key.
+        order addFirst: anAssociation key.
+        super add: anAssociation.
+!
+
+addLast: anAssociation 
+        "Add anAssociation to the end of the receiver."
+
+        self removeFromOrder: anAssociation key.
+        order addLast: anAssociation key.
+        super add: anAssociation.
+"/!
+"/
+"/grow
+"/        "Increase the number of elements in the dictionary"
+"/
+"/        ^ super grow
+"/
+"/        | newSelf |
+"/
+"/        newSelf := (self class) new: (self basicSize + self growSize).
+"/        order do: [:key | newSelf add: (self associationAt: key)].
+"/        self become: newSelf
+"/
+! !
+
+!OrderedDictionary methodsFor: 'enumerating'!
+
+associationsDo: aBlock 
+        "Evaluate aBlock for each of the dictionary's associations."
+
+        order do: [:key | aBlock value: (self associationAt: key)]
+!
+
+associationsDo: aBlock from: firstIndex to: secondIndex 
+        "Evaluate aBlock with each of the dictionary's associations from index 
+        firstIndex to index secondIndex as the argument."
+
+        firstIndex to: secondIndex do: [:index | 
+            aBlock value: (self associationAt: (order at: index))
+        ]
+!
+
+collect: aBlock 
+        "Evaluate aBlock with each of the associations of the dictionary as the 
+        argument. The block should return an association which will be added to the
+        new OrderedDictionary"
+
+        | newDict |
+
+        newDict := OrderedDictionary new.
+        1 to: order size do: [:index | 
+            newDict add: (aBlock value: (self associationAt: (order at: index)))
+        ].
+        ^ newDict
+!
+
+do: aBlock 
+        "Evaluate aBlock for each of the dictionary's values."
+
+        order do: [:key | aBlock value: (self at: key)]
+!
+
+do: aBlock from: firstIndex to: secondIndex 
+        "Evaluate aBlock with each of the dictionary's associations from index 
+        firstIndex to index secondIndex as the argument."
+
+        firstIndex to: secondIndex do: [:index | 
+            aBlock value: (self at: (order at: index))
+        ]
+!
+
+findFirst: aBlock 
+        "Return the index of the first association in the dictionary for which aBlock
+        evaluates as true. If the block does not evaluate to true, return 0"
+
+        1 to: order size do: [:index | 
+            (aBlock value: (self associationAt: (order at: index))) ifTrue: [^index]
+        ].
+        ^ 0
+!
+
+findLast: aBlock 
+        "Return the index of the last association in the dictionary for which aBlock
+
+        evaluates as true. If the block does not evaluate to true, return 0"
+
+        order size to: 1 by: -1 do: [:index | 
+            (aBlock value: (self associationAt: (order at: index))) ifTrue: [^index]
+        ].
+        ^ 0
+!
+
+reverse
+        "Return with a new OrderedDictionary with its associations in reverse order."
+
+
+        | newDict|
+
+        newDict _ OrderedDictionary new.
+        order size to: 1 by: -1 do:[:index | 
+            |key|
+
+            key _ order at: index.
+            newDict at: key put: (self at: key)
+        ].
+        ^newDict
+!
+
+reverseDo: aBlock 
+        "Evaluate aBlock with each of the dictionary's associations as the argument,
+        starting with the last element and taking each in sequence up to the first."
+
+        order size to: 1 by: -1 do: [:index | 
+            aBlock value: (self associationAt: (order at: index))
+        ]
+!
+
+select: aBlock 
+        "Evaluate aBlock with each of the dictionary's associations as the argument.
+        Collect into a new OrderedDictionary only those associations for which 
+        aBlock evaluates to true. Return the new OrderedDictionary."
+
+        | newDict|
+
+        newDict := OrderedDictionary new.
+        1 to: order size do:[:index | 
+            |key assoc|
+
+            key _ order at: index.
+            assoc := self associationAt: key.
+            (aBlock value: assoc) ifTrue: [
+                newDict add: assoc
+            ]
+        ].
+        ^newDict
+! !
+
+!OrderedDictionary methodsFor: 'accessing index'!
+
+identityIndexOfAssociation: anAssociation 
+        "Return the identity index of anAssociation within the receiver. If the receiver
+        does not contain anAssociation, return 0."
+
+        ^self identityIndexOfAssociation: anAssociation ifAbsent: [0]
+!
+
+identityIndexOfAssociation: anAssociation ifAbsent: exceptionBlock 
+        "Return the identity index of anAssociation within the receiver. 
+         If the receiver does not contain anAssociation, 
+         return the result of evaluating the exceptionBlock."
+
+        1 to: order size do: [:i | 
+            (self associationAt: (order at: i)) == anAssociation ifTrue: [^i]
+        ].
+        ^exceptionBlock value
+!
+
+identityIndexOfKey: aKey 
+        "Return the identity index of aKey within the receiver. If the receiver 
+        does not contain aKey, return 0."
+
+        ^self identityIndexOfKey: aKey ifAbsent: [0]
+!
+
+identityIndexOfKey: aKey ifAbsent: exceptionBlock 
+        "Return the identity index of aKey within the receiver.  If the receiver does
+        not contain aKey, return the result of evaluating the exceptionBlock."
+
+        1 to: order size do: [:i | (order at: i) == aKey ifTrue: [^i]].
+        ^exceptionBlock value
+!
+
+identityIndexOfValue: aValue 
+        "Return the identity index of aValue within the receiver. If the receiver 
+        does not contain aValue, return 0."
+
+        ^self identityIndexOfValue: aValue ifAbsent: [0]
+!
+
+identityIndexOfValue: aValue ifAbsent: exceptionBlock 
+        "Return the identity index of aValue within the receiver. If the receiver 
+        does not contain aValue, return the result of evaluating the exceptionBlock."
+
+        1 to: order size do: [:i | 
+            (self at: (order at: i)) == aValue ifTrue: [^i]].
+        ^exceptionBlock value
+!
+
+indexOfAssociation: anAssociation 
+        "Return the index of anAssociation within the receiver. If the receiver does
+        not contain anAssociation, return 0."
+
+        ^self indexOfAssociation: anAssociation ifAbsent: [0]
+!
+
+indexOfAssociation: anAssociation ifAbsent: exceptionBlock 
+        "Return the identity index of anAssociation within the receiver. If the receiver
+        does not contain anAssociation, return the result of evaluating the exceptionBlock."
+
+        1 to: order size do: [:i | 
+            (self associationAt: (order at: i)) = anAssociation ifTrue: [^i]
+        ].
+        ^exceptionBlock value
+!
+
+indexOfKey: aKey 
+        "Return the index of aKey within the receiver. If the receiver does 
+        not contain aKey, return 0."
+
+        ^self indexOfKey: aKey ifAbsent: [0]
+!
+
+indexOfKey: aKey ifAbsent: exceptionBlock 
+        "Return the identity index of aKey within the receiver.  If the receiver does
+        not contain aKey, return the result of evaluating the exceptionBlock."
+
+        1 to: order size do: [:i | (order at: i) = aKey ifTrue: [^i]].
+        ^exceptionBlock value
+!
+
+indexOfValue: aValue 
+        "Return the index of aValue within the receiver. If the receiver does 
+        not contain aValue, return 0."
+
+        ^self indexOfValue: aValue ifAbsent: [0]
+!
+
+indexOfValue: aValue ifAbsent: exceptionBlock 
+        "Return the identity index of aValue within the receiver. If the receiver 
+        does not contain aValue, return the result of evaluating the exceptionBlock."
+
+        1 to: order size do: [:i | 
+            (self at: (order at: i)) = aValue ifTrue: [^i]].
+        ^exceptionBlock value
+!
+
+nextIndexOfAssociation: aAssociation from: startIndex to: stopIndex 
+        "Return the next index of aAssociation within the receiver between startIndex
+        and stopIndex. If the receiver does not contain aAssociation, return nil"
+
+        startIndex to: stopIndex do: [:i | 
+            (self associationAt: (order at: i)) = aAssociation ifTrue: [^i]].
+        ^nil
+!
+
+nextIndexOfKey: aKey from: startIndex to: stopIndex 
+        "Return the next index of aKey within the receiver between startIndex and 
+        stopIndex.  If the receiver does not contain aKey, return nil"
+
+        startIndex to: stopIndex do: [:i | 
+            (order at: i) = aKey ifTrue: [^i]].
+        ^nil
+!
+
+nextIndexOfValue: aValue from: startIndex to: stopIndex 
+        "Return the next index of aValue within the receiver between startIndex and
+        stopIndex. If the receiver does not contain aValue, return nil"
+
+        startIndex to: stopIndex do: [:i | 
+            (self at: (order at: i)) = aValue ifTrue: [^i]].
+        ^nil
+!
+
+prevIndexOfAssociation: aAssociation from: startIndex to: stopIndex 
+        "Return the previous index of aAssociation within the receiver between 
+        startIndex 
+        and stopIndex working backwards through the receiver. If the receiver does 
+
+        not contain aAssociation, return nil"
+
+        startIndex
+                to: stopIndex
+                by: -1
+                do: [:i | (self associationAt: (order at: i))
+                                = aAssociation ifTrue: [^i]].
+        ^nil!
+
+prevIndexOfKey: aKey from: startIndex to: stopIndex 
+        "Return the previous index of aKey within the receiver between startIndex and
+
+        stopIndex working backwards through the receiver. If the receiver does not 
+
+        contain aKey, return nil"
+
+        startIndex
+                to: stopIndex
+                by: -1
+                do: [:i | (order at: i)
+                                = aKey ifTrue: [^i]].
+        ^nil!
+
+prevIndexOfValue: aValue from: startIndex to: stopIndex 
+        "Return the previous index of aValue within the receiver between startIndex
+
+        and stopIndex working backwards through the receiver. If the receiver does 
+
+        not contain aValue, return nil"
+
+        startIndex
+                to: stopIndex
+                by: -1
+                do: [:i | (self at: (order at: i))
+                                = aValue ifTrue: [^i]].
+        ^nil! !
+
+!OrderedDictionary methodsFor: 'testing'!
+
+occurrencesOfKey: aKey 
+        "Return how many of the dictionary's keys are equal to aKey."
+
+        | count |
+        count _ 0.
+        1 to: self size do: [:index | aKey = (order at: index) ifTrue: [count _ count
+ + 1]].
+        ^count!
+
+occurrencesOfValue: aValue 
+        "Return how many of the dictionary's values are equal to aValue."
+
+        | count |
+        count _ 0.
+        1 to: self size do: [:index | aValue = (self at: (order at: index)) ifTrue:
+ [count _ count + 1]].
+        ^count! !
+
+!OrderedDictionary methodsFor: 'accessing'!
+
+after: anAssociation 
+        "Return the association after anAssociation in the order. If anAssociation is
+ the 
+        last association in the order, return the undefined object. If anAssociation
+ is 
+        not found, invoke an error notifier"
+
+        1 to: order size - 1 do: [:index | (self associationAt: (order at: index))
+                        = anAssociation ifTrue: [^self associationAt: (order at: index + 1)]].
+        (self associationAt: (order last))
+                = anAssociation
+                ifTrue: [^nil]
+                ifFalse: [^self error: 'not found']!
+
+associations
+        "Return an OrderedCollection containing the receiver's associations."
+
+        | anOrderedCollection |
+        anOrderedCollection _ OrderedCollection new: order size.
+        order do: [:key | anOrderedCollection add: (self associationAt: key)].
+        ^anOrderedCollection!
+
+at: key put: anObject 
+        "Set the value at key to be anObject. If key is not found, create a new 
+        entry for key and set is value to anObject. Return anObject."
+
+        (order includes: key)
+                ifFalse: [order add: key].
+        super at: key put: anObject!
+
+atAll: anInterval put: anObject 
+        "Put anObject into the value field of every association specified by the interval"
+
+
+        anInterval do: [:index | self at: (order at: index)
+                        put: anObject]!
+
+atAllPut: anObject 
+        "Put anObject into the value field of every association in the dictionary"
+
+        order do: [:key|  self at: key put: anObject]!
+
+before: anAssociation 
+        "Return the association before anAssociation in the order. If anAssociation
+ is the 
+        first association in the order, return the undefined object. If anAssociation
+ is 
+        not found, invoke an error notifier"
+
+        2 to: order size do: [:index | (self associationAt: (order at: index))
+                        = anAssociation ifTrue: [^self associationAt: (order at: index - 1)]].
+        (self associationAt: order first)
+                = anAssociation
+                ifTrue: [^nil]
+                ifFalse: [^self error: 'not found']!
+
+first
+        "Return the first association of the receiver.  Provide an error 
+        notification if the receiver contains no elements."
+
+        order emptyCheck.
+        ^self associationAt: (order first)!
+
+keys
+        "Return a OrderedCollection containing the receiver's keys."
+
+        ^order copy.!
+
+last
+        "Return the last association of the receiver. Provide an error 
+        notification if the receiver contains no elements."
+
+        order emptyCheck.
+        ^self associationAt: (order last)!
+
+order
+        ^order!
+
+values
+        "Return a OrderedCollection containing the receiver's values."
+
+        | anOrderedCollection |
+        anOrderedCollection _ OrderedCollection new: order size.
+        order do: [:key | anOrderedCollection add: (self at: key)].
+        ^anOrderedCollection! !
+
+!OrderedDictionary methodsFor: 'private'!
+
+initialize
+        order _ OrderedCollection new!
+
+removeFromOrder: aKey 
+        order remove: aKey ifAbsent: []! !
+
+!OrderedDictionary methodsFor: 'copying'!
+
+copyEmpty
+        "Return a copy of the receiver that contains no elements."
+
+        ^(self class) new: 10!
+
+copyEmpty: aSize
+        "Return a copy of the receiver that contains no elements."
+
+        ^(self class) new: aSize!
+
+copyFrom: startIndex to: endIndex 
+        "Return a copy of the receiver that contains elements from 
+        position startIndex to endIndex."
+
+        | newDict |
+        endIndex < startIndex ifTrue: [^self copyEmpty].
+        (startIndex < 1 or: [endIndex > order size])
+                ifTrue: [^self error: 'No such element'].
+        newDict _ self copyEmpty: endIndex - startIndex + 1.
+        startIndex to: endIndex do: [:index | newDict add: (self associationAt: (order
+ at: index))].
+        ^newDict!
+
+copyWith: anAssociation 
+        "Return a copy of the dictionary that is 1 bigger than the receiver and 
+        includes the argument, anAssociation, at the end."
+
+        | newDict |
+        newDict _ self copy.
+        newDict add: anAssociation.
+        ^newDict!
+
+copyWithout: anAssociation 
+        "Return a copy of the dictionary that is 1 smaller than the receiver and does
+
+        not includes the argument, anAssociation"
+
+        | newDict |
+        newDict _ OrderedDictionary new: order size - 1.
+        self associationsDo: [:assoc | anAssociation = assoc ifFalse: [newDict add:
+ assoc]]! !
+
+
+!OrderedDictionary class methodsFor: 'instance creation'!
+
+new
+        ^super new initialize!
+
+new: anInteger
+        ^(super new: anInteger) initialize! !
+
+"COPYRIGHT.
+ The above file is a Manchester Goodie protected by copyright.
+ These conditions are imposed on the whole Goodie, and on any significant
+ part of it which is separately transmitted or stored:
+        * You must ensure that every copy includes this notice, and that
+          source and author(s) of the material are acknowledged.
+        * These conditions must be imposed on anyone who receives a copy.
+        * The material shall not be used for commercial gain without the prior
+          written consent of the author(s).
+ Further information on the copyright conditions may be obtained by
+ sending electronic mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: copyright
+ or by writing to The Smalltalk Goodies Library Manager, Dept of
+ Computer Science, The University, Manchester M13 9PL, UK
+
+ (C) Copyright 1992 University of Manchester
+ For more information about the Manchester Goodies Library (from which 
+ this file was distributed) send e-mail:
+        To: goodies-lib@cs.man.ac.uk
+        Subject: help 
+"!