home *** CD-ROM | disk | FTP | other *** search
/ The CDPD Public Domain Collection for CDTV 3 / CDPDIII.bin / pd / programming / gnusmalltalk / dictionary.st < prev    next >
Text File  |  1992-02-15  |  11KB  |  399 lines

  1. "======================================================================
  2. |
  3. |   Dictionary Method Definitions
  4. |
  5.  ======================================================================"
  6.  
  7.  
  8. "======================================================================
  9. |
  10. | Copyright (C) 1990, 1991, 1992 Free Software Foundation, Inc.
  11. | Written by Steve Byrne.
  12. |
  13. | This file is part of GNU Smalltalk.
  14. |
  15. | GNU Smalltalk is free software; you can redistribute it and/or modify it
  16. | under the terms of the GNU General Public License as published by the Free
  17. | Software Foundation; either version 1, or (at your option) any later version.
  18. | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
  19. | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
  20. | FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
  21. | details.
  22. | You should have received a copy of the GNU General Public License along with
  23. | GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
  24. | Foundation, 675 Mass Ave, Cambridge, MA 02139, USA.  
  25. |
  26.  ======================================================================"
  27.  
  28.  
  29. "
  30. |     Change Log
  31. | ============================================================================
  32. | Author       Date       Change 
  33. | sbb         28 Jul 91      Fixed #= to check argument class.  Also fixed
  34. |              printing and storing to use cascaded messages.
  35. |
  36. | sbb         16 Mar 91      Class creation now separate statement.
  37. |
  38. | sbb         16 Feb 91      Override the #new method from builtins when this file
  39. |              is loaded so that subclasses of Dictionary have a
  40. |              proper #new method instead of the built-in one that
  41. |              only creates Dictionary instances.
  42. |
  43. | sbb         21 Sep 90      Changed printOn: to print the associations directly.
  44. |
  45. | sbyrne      6 May 90      Fixed grow method to preserve associations in use in
  46. |              the dictionary instead of making new ones.  This
  47. |              should be faster, and doesn't break compiled methods
  48. |              that reference global variables when Smalltalk grows.
  49. |
  50. | sbyrne     24 Apr 90      Fix at:ifAbsent: to deal with failure better (and be
  51. |              a tad more efficient).  Kudos (or BarNone's,
  52. |              depending on preference) to Andy Valencia.
  53. |
  54. | sbyrne      7 Apr 90      Modified at:put: to resuse the existing Association
  55. |              if there is one, rather than create a new one all the
  56. |              time.  This was causing lossage when setting global
  57. |              variables in Smalltalk that previous usages weren't
  58. |              being changed.
  59. |
  60. | sbyrne     25 Apr 89      created.
  61. |
  62. "
  63.  
  64. Set variableSubclass: #Dictionary
  65.     instanceVariableNames: ''
  66.     classVariableNames: ''
  67.     poolDictionaries: ''
  68.     category: nil
  69. !
  70.  
  71. Dictionary comment: 
  72. 'I implement a dictionary, which is an object that is indexed by
  73. unique objects (typcially instances of Symbol), and associates another
  74. object with that index.  I use the equality operator = to determine
  75. equality of indices.' !
  76.  
  77. "### The initblocks variable should not be globally visible, I think"
  78. "This is a HACK HACK HACK.  We want to reference the InitBlocks global variable
  79. from within some methods in System Dictionary.  However, after this file
  80. redefines at:put: from the built-in one, and until UndefinedObject.st is 
  81. loaded, defining isNil for nil, at:put: for dictionaries does not work
  82. properly.  So we do it here.  The basic problem is that InitBlocks should
  83. maybe be kept elsewhere, and not be globally visible."
  84. Smalltalk at: #InitBlocks put: nil!
  85.  
  86. !Dictionary class methodsFor: 'instance creation'!
  87.  
  88. new
  89.     "Builtins defines a #new method, so that during bootstrap there is a way
  90.      to create dictionaries.  Unfortunately, this #new method only creates
  91.      dictionaries, so subclasses when trying to use this method, lose big.
  92.      This fixes the problem."
  93.     ^self new: 32
  94. ! !
  95.  
  96.  
  97.  
  98. !Dictionary methodsFor: 'accessing'!
  99.  
  100. add: anAssociation
  101.     | index |
  102.     index _ self findKeyIndex: anAssociation key.
  103.     (self basicAt: index) isNil
  104.     ifTrue: [ tally _ tally + 1].
  105.     self basicAt: index put: anAssociation.
  106.     ^anAssociation
  107. !
  108.  
  109. at: key put: value
  110.     | index assoc |
  111.     index _ self findKeyIndex: key.
  112.     (assoc _ self basicAt: index) isNil
  113.     ifTrue: [ self basicAt: index
  114.                put: (Association key: key value: value).
  115.           tally _ tally + 1 ]
  116.     ifFalse: [ assoc value: value ].
  117.     ^value
  118. !
  119.  
  120. at: key
  121.     ^self at: key ifAbsent: [ ^self error: 'key not found' ]
  122. !
  123.  
  124. at: key ifAbsent: aBlock
  125.     | assoc |
  126.     assoc _ self basicAt: (self findKeyIndex: key).
  127.     assoc isNil
  128.             ifTrue: [ ^aBlock value ]
  129.             ifFalse: [ ^assoc value ]
  130. !
  131.     
  132. associationAt: key
  133.     ^self associationAt: key ifAbsent: [ ^self error: 'key not found' ]
  134. !
  135.  
  136. associationAt: key ifAbsent: aBlock
  137.     | index assoc|
  138.     index _ self findKeyIndex: key.
  139.     assoc _ self basicAt: index.
  140.     assoc isNil ifTrue: [ ^aBlock value ]
  141.                 ifFalse: [ ^assoc ]
  142. !
  143.  
  144. keyAtValue: value ifAbsent: exceptionBlock
  145.     self associationsDo:
  146.         [ :assoc | value = assoc value
  147.                  ifTrue: [ ^assoc key ] ].
  148.     ^exceptionBlock value
  149. !
  150.  
  151. keyAtValue: value
  152.     ^self keyAtValue: value ifAbsent: []
  153. !
  154.  
  155. keys
  156.     | aSet |
  157.     aSet _ Set new: tally.
  158.     self keysDo: [ :aKey | aSet add: aKey ].
  159.     ^aSet
  160. !
  161.  
  162. values
  163.     | aBag |
  164.     aBag _ Bag new.
  165.     self do: [ :aValue | aBag add: aValue ].
  166.     ^aBag
  167. !!
  168.  
  169.  
  170.  
  171. !Dictionary methodsFor: 'dictionary testing'!
  172.  
  173. includesAssociation: anAssociation
  174.     | assoc |
  175.     assoc _ self associationAt: anAssociation key ifAbsent: [ ^false ].
  176.     ^assoc value = anAssociation value
  177. !
  178.  
  179. includesKey: key
  180.     self associationAt: key ifAbsent: [ ^false ].
  181.     ^true
  182. !
  183.  
  184. includes: anObject
  185.     self do: [ :element | element = anObject ifTrue: [ ^true ] ].
  186.     ^false
  187. !
  188.  
  189. occurrencesOf: aValue
  190.     | count |
  191.     count _ 0.
  192.     self do: [ :element | element = aValue
  193.                     ifTrue: [ count _ count + 1] ].
  194.     ^count
  195. !!
  196.  
  197.  
  198.  
  199. !Dictionary methodsFor: 'dictionary removing'!
  200.  
  201. removeAssociation: anAssociation
  202.     "### does this check the value as well as the key?"
  203.     self removeKey: anAssociation key ifAbsent: [].
  204.     ^anAssociation
  205. !
  206.  
  207. removeKey: key
  208.     ^self removeKey: key ifAbsent: [ ^self error: 'key not found' ]
  209. !
  210.  
  211. removeKey: key ifAbsent: aBlock
  212.     | index assoc |
  213.     index _ self findKeyIndexNoGrow: key ifAbsent: [ ^aBlock value ].
  214.     assoc _ self basicAt: index.
  215.     self basicAt: index put: nil.
  216.     tally _ tally - 1.
  217.     self rehashObjectsAfter: index.
  218.     ^assoc value
  219. !
  220.  
  221. remove: anObject
  222.     self error: 'remove: not allowed in Dictionary'
  223. !
  224.  
  225. remove: anObject ifAbsent: aBlock
  226.     self error: 'remove:ifAbsent: not allowed in Dictionary'
  227. !!
  228.  
  229.  
  230.  
  231. !Dictionary methodsFor: 'dictionary enumerating'!
  232. associationsDo: aBlock
  233.     super do: [ :assoc | aBlock value: assoc ]
  234. !
  235.  
  236. "These could be implemented more efficiently by doing the super do
  237.  directly, or doing the explicit scanning of the dictionary by hand"
  238. keysDo: aBlock
  239.     self associationsDo: [ :assoc | aBlock value: assoc key ]
  240. !
  241.  
  242. do: aBlock
  243.     self associationsDo: [ :assoc | aBlock value: assoc value ]
  244. !
  245.  
  246. collect: aBlock
  247.     | aBag |
  248.     aBag _ Bag new.
  249.     self do: [ :element | aBag add: (aBlock value: element) ].
  250.     ^aBag
  251. !
  252.  
  253. select: aBlock
  254.     | newDict |
  255.     newDict _ self species new.
  256.     self associationsDo:
  257.         [ :assoc | (aBlock value: assoc value)
  258.              ifTrue: [ newDict add: assoc ] ].
  259.     ^newDict
  260. !
  261.  
  262. reject: aBlock
  263.     self shouldNotImplement
  264. !
  265.  
  266. inject: value into: aBlock
  267.     self shouldNotImplement
  268. !!
  269.  
  270.  
  271.  
  272. !Dictionary methodsFor: 'misc math methods'!
  273.  
  274. = aDictionary
  275.     self class == aDictionary class
  276.     ifFalse: [ ^false ].
  277.     tally ~= aDictionary size ifTrue: [ ^false ].
  278.     self associationsDo:
  279.         [ :assoc | assoc value ~= (aDictionary at: assoc key
  280.                                            ifAbsent: [ ^false ])
  281.                      ifTrue: [ ^false ] ].
  282.     ^true
  283. !
  284.  
  285. hash
  286.     | hashValue |
  287.     hashValue _ tally.
  288.     self associationsDo:
  289.         [ :assoc | hashValue _ hashValue + assoc hash ].
  290.     ^hashValue
  291. !!
  292.  
  293.  
  294.  
  295. !Dictionary methodsFor: 'printing'!
  296.  
  297. printOn: aStream
  298.     aStream nextPutAll: self class name , ' (' .
  299.     self associationsDo:
  300.         [ :assoc | aStream print: assoc;
  301.                nextPut: Character space ].
  302.     aStream nextPut: $)
  303. !!
  304.  
  305.  
  306.  
  307. !Dictionary methodsFor: 'storing'!
  308.  
  309. storeOn: aStream
  310.     | hasElements |
  311.     aStream nextPutAll: '(', self class name , ' new'.
  312.     hasElements _ false.
  313.     self associationsDo:
  314.         [ :assoc | aStream nextPutAll: ' at: ';
  315.                store: assoc key;
  316.                nextPutAll: ' put: ';
  317.                store: assoc value;
  318.                nextPut: $;.
  319.            hasElements _ true ].
  320.     hasElements ifTrue: [ aStream nextPutAll: ' yourself' ].
  321.     aStream nextPut: $)
  322. !!
  323.  
  324.  
  325.  
  326. !Dictionary methodsFor: 'private methods'!
  327.  
  328. rehashObjectsAfter: index
  329.     "Rehashes all the objects in the collection after index to see if any of
  330.     them hash to index.  If so, that object is copied to index, and the
  331.     process repeats with that object's index, until a nil is encountered."
  332.     | i size count assoc |
  333.     i _ index.
  334.     size _ self basicSize.
  335.     count _ size.
  336.     [ count > 0 ]
  337.         whileTrue:
  338.         [ i _ i \\ size + 1.
  339.               assoc _ self basicAt: i.
  340.           assoc isNil ifTrue: [ ^self ].
  341.               ((assoc key hash \\ size) + 1) = index
  342.               ifTrue: [ self basicAt: index put: assoc.
  343.                   self basicAt: i put: nil.  "Be tidy"
  344.               index _ i ].
  345.               count _ count - 1 ]
  346. !
  347.  
  348. findKeyIndex: aKey ifFull: aBlock
  349.     "Tries to see if aKey exists as the key of an indexed variable (which is an
  350.     association).  If it's searched the entire dictionary and the key is 
  351.     not to be found, aBlock is evaluated and it's value is returned."
  352.     | index count size assoc |
  353.     size _ self basicSize.
  354.     index _ aKey hash \\ size + 1.
  355.     count _ size.
  356.     [ count > 0 ]
  357.         whileTrue:
  358.         [ assoc _ self basicAt: index.
  359.               (assoc isNil or: [ assoc key = aKey ])
  360.             ifTrue: [ ^index ].
  361.           index _ index \\ size + 1.
  362.           count _ count - 1. ].
  363.     ^aBlock value
  364. !
  365.         
  366. findKeyIndex: aKey
  367.     "Finds an association with the given key in the dictionary and returns its
  368.     index.  If the dictionary doesn't contain the object and there is no nil
  369.     element, the dictionary is grown and then the index of where the object
  370.     would go is returned."
  371.     ^self findKeyIndex: aKey
  372.            ifFull: [ self grow.
  373.                 self findKeyIndexNoGrow: aKey
  374.                   ifAbsent: [ ^self error: 'failed to grow a new empty element!!!' ] ]
  375. !
  376.  
  377. findKeyIndexNoGrow: aKey ifAbsent: aBlock
  378.     | index |
  379.     index _ self findKeyIndex: aKey ifFull: [ 0 ].
  380.     (index = 0 )
  381.         ifTrue: [ ^aBlock value ]
  382.     ifFalse: [ ^index ]
  383. !
  384.  
  385. grow
  386.     | newDict |
  387.     newDict _ self species new: self basicSize + self growSize.
  388.     self associationsDo: [ :assoc | newDict add: assoc ].
  389.     ^self become: newDict
  390. !
  391.  
  392. growSize
  393.     ^32
  394.  
  395. !!
  396.  
  397.