SnapShotImageMemory.st
changeset 1416 eec0911414fe
child 1417 28d6026fe30c
equal deleted inserted replaced
1415:77abca16cfa3 1416:eec0911414fe
       
     1 "{ Package: 'cg:private' }"
       
     2 
       
     3 Object subclass:#SnapShotImageMemory
       
     4 	instanceVariableNames:'stream msb ptrSize intSize intTag spaceInfos symbolEntries
       
     5 		globalEntries addrToObjectMapping'
       
     6 	classVariableNames:''
       
     7 	poolDictionaries:''
       
     8 	category:'System-Support'
       
     9 !
       
    10 
       
    11 Object subclass:#SpaceInfo
       
    12 	instanceVariableNames:'start end size flags imageBase'
       
    13 	classVariableNames:''
       
    14 	poolDictionaries:''
       
    15 	privateIn:SnapShotImageMemory
       
    16 !
       
    17 
       
    18 Object variableSubclass:#ImageObject
       
    19 	instanceVariableNames:'classRef size bits'
       
    20 	classVariableNames:''
       
    21 	poolDictionaries:''
       
    22 	privateIn:SnapShotImageMemory
       
    23 !
       
    24 
       
    25 SnapShotImageMemory::ImageObject variableSubclass:#ImageClassObject
       
    26 	instanceVariableNames:''
       
    27 	classVariableNames:''
       
    28 	poolDictionaries:''
       
    29 	privateIn:SnapShotImageMemory
       
    30 !
       
    31 
       
    32 
       
    33 !SnapShotImageMemory class methodsFor:'instance creation'!
       
    34 
       
    35 for:aFilename
       
    36     ^ self new for:aFilename
       
    37 ! !
       
    38 
       
    39 !SnapShotImageMemory class methodsFor:'private'!
       
    40 
       
    41 isNilOOP:anOOP
       
    42     ^ anOOP == 0
       
    43 !
       
    44 
       
    45 isPointerOOP:anOOP
       
    46     ^ (anOOP bitTest:1) not
       
    47 !
       
    48 
       
    49 isSmallIntegerOOP:anOOP
       
    50     ^ anOOP bitTest:1
       
    51 ! !
       
    52 
       
    53 !SnapShotImageMemory methodsFor:'accessing'!
       
    54 
       
    55 globalEntries
       
    56     "return the value of the instance variable 'globalEntries' (automatically generated)"
       
    57 
       
    58     ^ globalEntries!
       
    59 
       
    60 globalEntries:something
       
    61     "set the value of the instance variable 'globalEntries' (automatically generated)"
       
    62 
       
    63     globalEntries := something.! !
       
    64 
       
    65 !SnapShotImageMemory methodsFor:'object access'!
       
    66 
       
    67 fetchClassObjectAt:baseAddr
       
    68     |addr classPtr size bits o|
       
    69 
       
    70     o := addrToObjectMapping at:baseAddr ifAbsent:nil.
       
    71     o notNil ifTrue:[^ o].
       
    72 
       
    73     addr := baseAddr.
       
    74     classPtr := self fetchPointerAt:addr.
       
    75     addr := addr + ptrSize.
       
    76     size := self fetchUnboxedIntegerAt:addr.
       
    77     addr := addr + ptrSize.
       
    78     bits := self fetchUnboxedIntegerAt:addr.
       
    79     addr := addr + ptrSize.
       
    80 
       
    81     o := ImageClassObject new:(size - intSize - intSize - intSize).
       
    82     o classRef:classPtr.
       
    83     o size:size.
       
    84     o bits:bits.
       
    85 
       
    86     1 to:size // intSize do:[:idx |
       
    87         o at:idx put:(self fetchUnboxedIntegerAt:addr).
       
    88         addr := addr + 1.
       
    89     ].
       
    90 
       
    91     addrToObjectMapping at:baseAddr put:o.
       
    92     ^ o
       
    93 !
       
    94 
       
    95 fetchObjectAt:baseAddr
       
    96     |addr classPtr classRef size bits o|
       
    97 
       
    98     o := addrToObjectMapping at:baseAddr ifAbsent:nil.
       
    99     o notNil ifTrue:[^ o].
       
   100 
       
   101     addr := baseAddr.
       
   102     classPtr := self fetchPointerAt:addr.
       
   103     addr := addr + ptrSize.
       
   104     size := self fetchUnboxedIntegerAt:addr.
       
   105     addr := addr + ptrSize.
       
   106     bits := self fetchUnboxedIntegerAt:addr.
       
   107     addr := addr + ptrSize.
       
   108 
       
   109     (self class isPointerOOP:classPtr) ifFalse:[
       
   110         self halt
       
   111     ].
       
   112 
       
   113     classRef := self fetchClassObjectAt:classPtr.
       
   114     classRef isImageBehavior ifFalse:[
       
   115         self halt.
       
   116     ].
       
   117 
       
   118     o := ImageObject new:(size - intSize - intSize - intSize).
       
   119     o classRef:classRef.
       
   120     o size:size.
       
   121     o bits:bits.
       
   122 
       
   123     self halt.
       
   124 !
       
   125 
       
   126 fetchObjectHeaderAt:baseAddr
       
   127     |addr class size bits|
       
   128 
       
   129     addr := baseAddr.
       
   130     class := self fetchPointerAt:addr.
       
   131     addr := addr + ptrSize.
       
   132     size := self fetchUnboxedIntegerAt:addr.
       
   133     addr := addr + ptrSize.
       
   134     bits := self fetchUnboxedIntegerAt:addr.
       
   135     addr := addr + ptrSize.
       
   136 
       
   137     self halt.
       
   138 !
       
   139 
       
   140 fetchPointerAt:addr
       
   141     ^ self fetchUnboxedIntegerAt:addr
       
   142 !
       
   143 
       
   144 fetchUnboxedIntegerAt:addr
       
   145     spaceInfos do:[:eachSpace |
       
   146         |ptr imgAddr|
       
   147 
       
   148         addr >= eachSpace start ifTrue:[
       
   149             addr <= eachSpace end ifTrue:[
       
   150                 imgAddr := eachSpace imageBase + (addr - eachSpace start).
       
   151                 stream position:imgAddr.
       
   152                 ptr := stream nextUnsignedLongMSB:msb.
       
   153                 ^ ptr
       
   154             ]
       
   155         ].
       
   156     ].
       
   157     self halt:'image fetch error'.
       
   158 ! !
       
   159 
       
   160 !SnapShotImageMemory methodsFor:'private'!
       
   161 
       
   162 allClassesDo:aBlock
       
   163     self allGlobalKeysDo:[:eachKey |
       
   164         |val|
       
   165 
       
   166         val := self at:eachKey.
       
   167         val isBehavior ifTrue:[
       
   168             aBlock value:val
       
   169         ]
       
   170     ].
       
   171 !
       
   172 
       
   173 allGlobalKeysDo:aBlock
       
   174     globals isNil ifTrue:[
       
   175         self readHeader.
       
   176         self readGlobals.
       
   177     ].
       
   178 !
       
   179 
       
   180 for:aFilename
       
   181     stream := aFilename asFilename readStream binary.
       
   182     addrToObjectMapping := IdentityDictionary new.
       
   183 !
       
   184 
       
   185 readGlobalEntries
       
   186         |refPointer theSymbol theValue|
       
   187 
       
   188         globalEntries := OrderedCollection new.
       
   189         [
       
   190             refPointer := stream nextUnsignedLongMSB:msb.
       
   191             theSymbol := stream nextUnsignedLongMSB:msb.
       
   192             theValue := stream nextUnsignedLongMSB:msb.
       
   193             theSymbol ~~ 0
       
   194         ] whileTrue:[
       
   195             globalEntries add:(theSymbol -> theValue).
       
   196         ].
       
   197         globalEntries := globalEntries asArray
       
   198 !
       
   199 
       
   200 readHeader
       
   201         "
       
   202          (self for:'stmeas.img') readHeader
       
   203         "
       
   204 
       
   205         |order magic version timeStamp snapID last_util_addr hiText_addr flags 
       
   206          lowData hiData charSlots charTableSlots fixMemStart fixMemEnd 
       
   207          symMemStart symMemEnd vmDataAddr sharedMethodCode sharedBlockCode 
       
   208          nContexts contextSpace nRegistered symbolsSeqNr nSpaces 
       
   209          spaceFlags spaceBase spaceSize classNameSize|
       
   210 
       
   211         stream next:256.        "/ skip execCmd
       
   212 
       
   213         msb := false.
       
   214         order := stream nextUnsignedLongMSB:msb.        
       
   215         order = 16r076543210 ifTrue:[
       
   216         ] ifFalse:[
       
   217             order = 16r01234567 ifTrue:[
       
   218                 msb := true.
       
   219             ] ifFalse:[
       
   220                 self error:'unhandled byteorder'
       
   221             ].
       
   222         ].
       
   223         magic := (stream next:8) asString.
       
   224         magic ~= 'ST/X-IMG' ifTrue:[
       
   225             self error:'not an st/x image'
       
   226         ].
       
   227         version := stream nextUnsignedLongMSB:msb.        
       
   228         timeStamp := stream nextUnsignedLongMSB:msb.        
       
   229         ptrSize := stream nextByte.        
       
   230         ptrSize ~~ 4 ifTrue:[
       
   231             self error:'unhandled ptr format'
       
   232         ].
       
   233         stream next:7.    "/ filler    
       
   234         intSize := stream nextUnsignedLongMSB:msb.        
       
   235         intSize == 9 ifTrue:[
       
   236             intSize := 4.
       
   237             intTag := 1.
       
   238         ] ifFalse:[
       
   239             self error:'unhandled int format'
       
   240         ].
       
   241         
       
   242         snapID := stream nextUnsignedLongMSB:msb.        
       
   243         last_util_addr := stream next:intSize.        
       
   244         hiText_addr := stream next:intSize.        
       
   245         flags := stream next:intSize.        
       
   246         stream next:8.    "/ info, debug & filler    
       
   247 
       
   248         lowData := stream nextUnsignedLongMSB:msb.
       
   249         hiData := stream nextUnsignedLongMSB:msb.
       
   250 
       
   251         charSlots := stream nextUnsignedLongMSB:msb.
       
   252         charTableSlots := stream nextUnsignedLongMSB:msb.
       
   253 
       
   254         version >= 8 ifTrue:[
       
   255             fixMemStart := stream nextUnsignedLongMSB:msb.
       
   256             fixMemEnd := stream nextUnsignedLongMSB:msb.
       
   257             symMemStart := stream nextUnsignedLongMSB:msb.
       
   258             symMemEnd := stream nextUnsignedLongMSB:msb.
       
   259             vmDataAddr := stream nextUnsignedLongMSB:msb.
       
   260         ].
       
   261         stream next:(128 * intSize).    "/ skip sharedMethodCode ptrs
       
   262         stream next:(128 * intSize).    "/ skip sharedBlockCode ptrs
       
   263 
       
   264         nContexts := stream nextUnsignedLongMSB:msb.
       
   265         contextSpace := stream nextUnsignedLongMSB:msb.
       
   266         nRegistered := stream nextUnsignedLongMSB:msb.
       
   267 
       
   268         version >= 8 ifTrue:[
       
   269             version >= 9 ifTrue:[
       
   270                 symbolsSeqNr := stream nextUnsignedLongMSB:msb.
       
   271                 stream next:(intSize * 31).
       
   272             ] ifFalse:[
       
   273                 stream next:(intSize * 32).
       
   274             ]
       
   275         ].
       
   276 
       
   277         nSpaces := stream nextUnsignedLongMSB:msb.
       
   278         spaceInfos := (1 to:nSpaces) collect:[:idx | SpaceInfo new].
       
   279         
       
   280         spaceBase := Array new:nSpaces.
       
   281         spaceSize := Array new:nSpaces.
       
   282         1 to:nSpaces do:[:i |
       
   283             (spaceInfos at:i) flags:(stream nextUnsignedLongMSB:msb).
       
   284         ].
       
   285         nSpaces+1 to:32 do:[:i | stream nextUnsignedLongMSB:msb].
       
   286 
       
   287         1 to:nSpaces do:[:i |
       
   288             (spaceInfos at:i) start:(stream nextUnsignedLongMSB:msb).
       
   289         ].
       
   290         nSpaces+1 to:32 do:[:i | stream nextUnsignedLongMSB:msb].
       
   291 
       
   292         1 to:nSpaces do:[:i |
       
   293             (spaceInfos at:i) size:(stream nextUnsignedLongMSB:msb).
       
   294         ].
       
   295         nSpaces+1 to:32 do:[:i | stream nextUnsignedLongMSB:msb].
       
   296 
       
   297         version >= 8 ifTrue:[
       
   298             stream position:(stream class zeroPosition + 4096).
       
   299         ].
       
   300 
       
   301         1 to:nSpaces do:[:i |
       
   302             (spaceInfos at:i) end:((spaceInfos at:i) start + (spaceInfos at:i) size - 1).
       
   303         ].
       
   304         1 to:nSpaces do:[:i |
       
   305             (spaceInfos at:i) imageBase:(stream position).
       
   306             stream skip:((spaceInfos at:i) size).
       
   307         ].
       
   308 
       
   309         "/ registration
       
   310 
       
   311         self readRegistrationEntries.
       
   312         self readSymbolEntries.
       
   313         self readGlobalEntries.
       
   314         self readUGlobalEntries.
       
   315 
       
   316 
       
   317 "/struct basicImageHeader {
       
   318 "/        char            h_execCmd[256];
       
   319 "/
       
   320 "/        int             h_orderWord;
       
   321 "/        char            h_magic[8];
       
   322 "/        int             h_version;
       
   323 "/        int             h_timeStamp;
       
   324 "/        char            h_ptrSize;
       
   325 "/        char            h_filler1[7];
       
   326 "/        int             h_intSize;
       
   327 "/        int             h_snapID;
       
   328 "/        INT             h_last_util_addr;
       
   329 "/        INT             h_hiText_addr;
       
   330 "/        INT             h_flags;
       
   331 "/        char            h_infoPrinting;
       
   332 "/        char            h_debugPrinting;
       
   333 "/        char            h_filler2[6];
       
   334 "/
       
   335 "/        /*
       
   336 "/         * these are to verify compatibility of the image with
       
   337 "/         * myself ...
       
   338 "/         * this is now obsolete.
       
   339 "/         */
       
   340 "/        INT             h_lowData, h_hiData;
       
   341 "/
       
   342 "/        /*
       
   343 "/         * base address of character- and characterTable slots
       
   344 "/         */
       
   345 "/        INT             h_charSlots;
       
   346 "/        INT             h_charTableSlots;
       
   347 "/
       
   348 "/#if HEADER_VERSION >= 8
       
   349 "/        /*
       
   350 "/         * the fixBase (VMDATA address)
       
   351 "/         */
       
   352 "/        INT             h_fixMemStart;
       
   353 "/        INT             h_fixMemEnd;
       
   354 "/        INT             h_symMemStart;
       
   355 "/        INT             h_symMemEnd;
       
   356 "/
       
   357 "/        INT             h_vmDataAddr;
       
   358 "/#endif
       
   359 "/
       
   360 "/        INT             h_sharedMethodCode[128];
       
   361 "/        INT             h_sharedBlockCode[128];
       
   362 "/
       
   363 "/        /*      
       
   364 "/         * space needed to restore contexts
       
   365 "/         */
       
   366 "/        INT             h_nContexts;
       
   367 "/        INT             h_contextSpace;
       
   368 "/
       
   369 "/        /*
       
   370 "/         * number of class registration info records
       
   371 "/         */
       
   372 "/        INT             h_nRegistered;
       
   373 "/
       
   374 "/#if HEADER_VERSION >= 8
       
   375 "/        /*
       
   376 "/         * reserved slots, for future versions
       
   377 "/         * (can add additional info, without affecting position of following stuff)
       
   378 "/         * If you add slots, you MUST DECREMENT the fillcount.
       
   379 "/         */
       
   380 "/# if HEADER_VERSION >= 9
       
   381 "/        INT             h_symbolsSeqNr;
       
   382 "/        INT             h_reserved[31];
       
   383 "/# else
       
   384 "/        INT             h_reserved[32];
       
   385 "/# endif
       
   386 "/#endif
       
   387 "/
       
   388 "/        /*
       
   389 "/         * number of spaces, base and size of each
       
   390 "/         */
       
   391 "/        INT             h_nSpaces;
       
   392 "/        INT             h_spaceFlags[MAXSPACES];
       
   393 "/        INT             h_spaceBase[MAXSPACES];
       
   394 "/        INT             h_spaceSize[MAXSPACES];
       
   395 "/
       
   396 "/        /*
       
   397 "/         * here come nSpaces object spaces
       
   398 "/         */
       
   399 "/
       
   400 "/        /*
       
   401 "/         * here comes registration info
       
   402 "/         */
       
   403 "/
       
   404 "/        /*
       
   405 "/         * here come nSymbols symbolEntries
       
   406 "/         * followed by a zero/zero entry
       
   407 "/         */
       
   408 "/
       
   409 "/        /*
       
   410 "/         * here come nGlobal globalEntries
       
   411 "/         * followed by a zero/zero entry
       
   412 "/         */
       
   413 "/
       
   414 "/        /*
       
   415 "/         * here come nUnnamedGlobal globalEntries
       
   416 "/         * followed by a zero/zero entry
       
   417 "/         */
       
   418 "/
       
   419 "/        /*
       
   420 "/         * here come stack contexts
       
   421 "/         */
       
   422 "/};      
       
   423 !
       
   424 
       
   425 readRegistrationEntries
       
   426         |classNameSize|
       
   427 
       
   428         [
       
   429             classNameSize := stream nextUnsignedLongMSB:msb.
       
   430             classNameSize ~~ 0
       
   431         ] whileTrue:[
       
   432             |className flags moduleTimestamp signature nMethods nBlocks oldLitRefs nLitRefs
       
   433              oldConstTable nConsts|
       
   434 
       
   435             className := (stream next:classNameSize) asString.
       
   436             stream next. "/ 0-byte
       
   437             flags := stream nextUnsignedLongMSB:msb.
       
   438             moduleTimestamp := stream nextUnsignedLongMSB:msb.   
       
   439             signature := stream nextUnsignedLongMSB:msb.   
       
   440             nMethods := stream nextUnsignedLongMSB:msb.   
       
   441             nMethods timesRepeat:[ stream nextUnsignedLongMSB:msb ].
       
   442             nBlocks := stream nextUnsignedLongMSB:msb.   
       
   443             nBlocks timesRepeat:[ stream nextUnsignedLongMSB:msb ].
       
   444             oldLitRefs := stream nextUnsignedLongMSB:msb.  
       
   445             nLitRefs := stream nextUnsignedLongMSB:msb.
       
   446             nLitRefs timesRepeat:[ stream nextUnsignedLongMSB:msb ].
       
   447             stream nextUnsignedLongMSB:msb. "/ 0-litRef
       
   448             oldConstTable := stream nextUnsignedLongMSB:msb.  
       
   449             nConsts := stream nextUnsignedLongMSB:msb.
       
   450             nConsts timesRepeat:[ stream nextUnsignedLongMSB:msb ].
       
   451 
       
   452             Transcript showCR:className.
       
   453         ].
       
   454 !
       
   455 
       
   456 readSymbolEntries
       
   457         |refPointer theSymbol|
       
   458 
       
   459         symbolEntries := OrderedCollection new.
       
   460 
       
   461         [
       
   462             refPointer := stream nextUnsignedLongMSB:msb.
       
   463             theSymbol := stream nextUnsignedLongMSB:msb.
       
   464         
       
   465             theSymbol ~~ 0
       
   466         ] whileTrue:[
       
   467             symbolEntries add:(theSymbol -> refPointer).
       
   468         ].
       
   469         symbolEntries := symbolEntries asArray
       
   470 !
       
   471 
       
   472 readUGlobalEntries
       
   473         |refPointer theValue|
       
   474 
       
   475         [
       
   476             refPointer := stream nextUnsignedLongMSB:msb.
       
   477             theValue := stream nextUnsignedLongMSB:msb.
       
   478             refPointer ~~ 0
       
   479         ] whileTrue
       
   480 ! !
       
   481 
       
   482 !SnapShotImageMemory::SpaceInfo methodsFor:'accessing'!
       
   483 
       
   484 end
       
   485     "return the value of the instance variable 'end' (automatically generated)"
       
   486 
       
   487     ^ end!
       
   488 
       
   489 end:something
       
   490     "set the value of the instance variable 'end' (automatically generated)"
       
   491 
       
   492     end := something.!
       
   493 
       
   494 flags
       
   495     "return the value of the instance variable 'flags' (automatically generated)"
       
   496 
       
   497     ^ flags!
       
   498 
       
   499 flags:something
       
   500     "set the value of the instance variable 'flags' (automatically generated)"
       
   501 
       
   502     flags := something.!
       
   503 
       
   504 imageBase
       
   505     "return the value of the instance variable 'imageBase' (automatically generated)"
       
   506 
       
   507     ^ imageBase!
       
   508 
       
   509 imageBase:something
       
   510     "set the value of the instance variable 'imageBase' (automatically generated)"
       
   511 
       
   512     imageBase := something.!
       
   513 
       
   514 size
       
   515     "return the value of the instance variable 'size' (automatically generated)"
       
   516 
       
   517     ^ size!
       
   518 
       
   519 size:something
       
   520     "set the value of the instance variable 'size' (automatically generated)"
       
   521 
       
   522     size := something.!
       
   523 
       
   524 start
       
   525     "return the value of the instance variable 'start' (automatically generated)"
       
   526 
       
   527     ^ start!
       
   528 
       
   529 start:something
       
   530     "set the value of the instance variable 'start' (automatically generated)"
       
   531 
       
   532     start := something.! !
       
   533 
       
   534 !SnapShotImageMemory::ImageObject methodsFor:'accessing'!
       
   535 
       
   536 bits
       
   537     "return the value of the instance variable 'bits' (automatically generated)"
       
   538 
       
   539     ^ bits!
       
   540 
       
   541 bits:something
       
   542     "set the value of the instance variable 'bits' (automatically generated)"
       
   543 
       
   544     bits := something.!
       
   545 
       
   546 classRef
       
   547     "return the value of the instance variable 'classRef' (automatically generated)"
       
   548 
       
   549     ^ classRef!
       
   550 
       
   551 classRef:something
       
   552     "set the value of the instance variable 'classRef' (automatically generated)"
       
   553 
       
   554     classRef := something.!
       
   555 
       
   556 size
       
   557     "return the value of the instance variable 'size' (automatically generated)"
       
   558 
       
   559     ^ size!
       
   560 
       
   561 size:something
       
   562     "set the value of the instance variable 'size' (automatically generated)"
       
   563 
       
   564     size := something.! !
       
   565 
       
   566 !SnapShotImageMemory::ImageObject methodsFor:'queries'!
       
   567 
       
   568 isImageBehavior
       
   569     |flags|
       
   570 
       
   571     flags := self flagsSlot.
       
   572 
       
   573     (SnapShotImageMemory isSmallIntegerOOP:flags) ifFalse:[
       
   574         self halt
       
   575     ].
       
   576     flags := flags bitShift:-1.
       
   577     ^ flags bitTest:Behavior flagBehavior  
       
   578 !
       
   579 
       
   580 isImageBytes
       
   581     self halt.
       
   582 !
       
   583 
       
   584 isImageString
       
   585     self halt.
       
   586 !
       
   587 
       
   588 isImageSymbol
       
   589     self halt.
       
   590 ! !
       
   591 
       
   592 !SnapShotImageMemory::ImageClassObject methodsFor:'accessing - slots'!
       
   593 
       
   594 categorySlot
       
   595     ^ self at:8
       
   596 !
       
   597 
       
   598 classFilenameSlot
       
   599     ^ self at:12
       
   600 !
       
   601 
       
   602 classVarsSlot
       
   603     ^ self at:9
       
   604 !
       
   605 
       
   606 commentSlot
       
   607     ^ self at:10
       
   608 !
       
   609 
       
   610 flagsSlot
       
   611     ^ self at:2
       
   612 !
       
   613 
       
   614 flagsValue
       
   615     |flags|
       
   616 
       
   617     flags := self flagsSlot.
       
   618 
       
   619     (SnapShotImageMemory isSmallIntegerOOP:flags) ifFalse:[
       
   620         self halt
       
   621     ].
       
   622     ^ flags bitShift:-1.
       
   623 !
       
   624 
       
   625 instSizeSlot
       
   626     ^ self at:5
       
   627 !
       
   628 
       
   629 instVarsSlot
       
   630     ^ self at:6
       
   631 !
       
   632 
       
   633 methodDictionarySlot
       
   634     ^ self at:3
       
   635 !
       
   636 
       
   637 nameSlot
       
   638     ^ self at:7
       
   639 !
       
   640 
       
   641 packageSlot
       
   642     ^ self at:13
       
   643 !
       
   644 
       
   645 revisionSlot
       
   646     ^ self at:14
       
   647 !
       
   648 
       
   649 superClassSlot
       
   650     ^ self at:1
       
   651 ! !
       
   652 
       
   653 !SnapShotImageMemory class methodsFor:'documentation'!
       
   654 
       
   655 version
       
   656     ^ '$Header$'
       
   657 ! !