home *** CD-ROM | disk | FTP | other *** search
/ Really Useful CD 1 / ReallyUsefulCD1.iso / extras / languages / smalltalk / _smalltalk / prelude / object < prev    next >
Encoding:
Text File  |  1987-12-30  |  2.0 KB  |  87 lines

  1. Class Object
  2. [
  3.      == anObject
  4.           ^ <Equality self anObject >
  5. |
  6.        ~~ x
  7.                 ^ (self == x) not
  8. |
  9.      = x
  10.           ^ (self == x)
  11. |
  12.      ~= x
  13.           ^ (self = x) not
  14. |
  15.      asString
  16.           ^ self class printString
  17. |
  18.         asSymbol
  19.                 ^ self asString asSymbol
  20. |
  21.      class
  22.           ^ <Class self >
  23. |
  24.         copy
  25.                 ^ self shallowCopy
  26. |
  27.         deepCopy         | size newobj |
  28.           size <- <Size self>.
  29.           (size < 0) 
  30.                ifTrue: [^ self] "if special just copy object"
  31.                ifFalse: [ newobj <- self class new.
  32.                (1 to: size) do: [:i |
  33.                     <AtPut newobj i
  34.                          ( <At self i > copy ) > ].
  35.                     ^ newobj ]
  36. |
  37.      do: aBlock               | item |
  38.           item <- self first.
  39.           ^ [item notNil] whileTrue:
  40.                [aBlock value: item.  item <- self next]
  41. |
  42.      error: aString
  43.           <Error aString self>
  44. |
  45.         first
  46.                 ^ self
  47. |
  48.         isKindOf: aClass                | objectClass |
  49.                 objectClass <- self class.
  50.                 [objectClass notNil] whileTrue:
  51.                         [(objectClass == aClass) ifTrue: [^ true].
  52.                          objectClass <- objectClass superClass].
  53.                 ^ false
  54. |
  55.         isMemberOf: aClass
  56.                 ^ aClass == self class
  57.  
  58. |
  59.         isNil
  60.                 ^ false
  61. |
  62.         next
  63.                 ^ nil
  64. |
  65.         notNil
  66.                 ^ true
  67. |
  68.      print
  69.           <PrintWithReturn (self printString) >
  70. |
  71.      printString
  72.           ^ self asString
  73.  
  74. |       respondsTo: cmd
  75.                 ^ self class respondsTo: cmd
  76.  
  77. |       shallowCopy      | size newobj |
  78.           size <- <Size self>.
  79.           (size < 0) 
  80.                ifTrue: [^ self] "if special just copy object"
  81.                ifFalse: [ newobj <- self class new.
  82.                     (1 to: size) do: [:i |
  83.                          <AtPut newobj i
  84.                               <At self i > > ].
  85.                          ^ newobj ]
  86. ]
  87.