Class.st
changeset 54 06dbdeeed4f9
parent 48 9f68393bea3c
child 68 59faa75185ba
equal deleted inserted replaced
53:77ed1ef5c018 54:06dbdeeed4f9
    43 
    43 
    44 UpdatingChanges <Boolean>       true if the changes-file shall be updated
    44 UpdatingChanges <Boolean>       true if the changes-file shall be updated
    45 
    45 
    46 WARNING: layout known by compiler and runtime system
    46 WARNING: layout known by compiler and runtime system
    47 
    47 
    48 $Header: /cvs/stx/stx/libbasic/Class.st,v 1.9 1994-02-05 12:18:46 claus Exp $
    48 $Header: /cvs/stx/stx/libbasic/Class.st,v 1.10 1994-02-25 12:55:33 claus Exp $
    49 written Spring 89 by claus
    49 written Spring 89 by claus
    50 '!
    50 '!
    51 
    51 
    52 !Class class methodsFor:'initialization'!
    52 !Class class methodsFor:'initialization'!
    53 
    53 
   192         category:cat
   192         category:cat
   193         comment:nil
   193         comment:nil
   194         changed:false
   194         changed:false
   195 !
   195 !
   196 
   196 
   197 variableWordSubclass:t instanceVariableNames:f lassVariableNames:d oolDictionaries:s ategory:cat
   197 variableWordSubclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s category:cat
   198     "create a new class as a subclass of an existing class (the receiver) 
   198     "create a new class as a subclass of an existing class (the receiver) 
   199      in which the subclass has indexable word-sized nonpointer variables"
   199      in which the subclass has indexable word-sized nonpointer variables"
   200 
   200 
   201     self isVariable ifTrue:[
   201     self isVariable ifTrue:[
   202         self isWords ifFalse:[
   202         self isWords ifFalse:[
   494     "if I have no subclasses, all we have to flush is cached
   494     "if I have no subclasses, all we have to flush is cached
   495      data for myself ... (actually, in any case all that needs
   495      data for myself ... (actually, in any case all that needs
   496      to be flushed is info for myself and all of my subclasses)"
   496      to be flushed is info for myself and all of my subclasses)"
   497 "
   497 "
   498     problem: this is slower; since looking for all subclasses is (currently)
   498     problem: this is slower; since looking for all subclasses is (currently)
   499 	     a bit slow :-(
   499              a bit slow :-(
   500 
   500 
   501     self withAllSubclassesDo:[:aClass |
   501     self withAllSubclassesDo:[:aClass |
   502 	ObjectMemory flushInlineCachesFor:aClass withArgs:nargs.
   502         ObjectMemory flushInlineCachesFor:aClass withArgs:nargs.
   503 	ObjectMemory flushMethodCacheFor:aClass
   503         ObjectMemory flushMethodCacheFor:aClass
   504     ].
   504     ].
   505 "
   505 "
   506 
   506 
   507     "actually, we would do better with less flushing ..."
   507     "actually, we would do better with less flushing ..."
   508 
   508 
   893     ^ ClassCategoryReader class:self category:'ST/V methods'
   893     ^ ClassCategoryReader class:self category:'ST/V methods'
   894 ! !
   894 ! !
   895 
   895 
   896 !Class methodsFor:'fileOut'!
   896 !Class methodsFor:'fileOut'!
   897 
   897 
       
   898 fileOutCommentOn:aStream
       
   899     "print an expression on aStream to define my comment"
       
   900 
       
   901     aStream nextPutAll:name.
       
   902     aStream nextPutAll:' comment:'.
       
   903     comment isNil ifTrue:[
       
   904         aStream nextPutAll:''''''
       
   905     ] ifFalse:[
       
   906         aStream nextPutAll:(comment storeString)
       
   907     ].
       
   908     aStream cr
       
   909 !
       
   910 
       
   911 fileOutDefinitionOn:aStream
       
   912     "print an expression to define myself on aStream"
       
   913 
       
   914     |isVar line|
       
   915 
       
   916     superclass isNil ifTrue:[
       
   917         line := 'Object'
       
   918     ] ifFalse:[
       
   919         line := (superclass name)
       
   920     ].
       
   921     superclass isNil ifTrue:[
       
   922         isVar := self isVariable
       
   923     ] ifFalse:[
       
   924         "I cant remember what this is for ?"
       
   925         isVar := (self isVariable and:[superclass isVariable not])
       
   926     ].
       
   927     isVar ifTrue:[
       
   928         self isBytes ifTrue:[
       
   929             line := line , ' variableByteSubclass:#'
       
   930         ] ifFalse:[
       
   931             self isWords ifTrue:[
       
   932                 line := line , ' variableWordSubclass:#'
       
   933             ] ifFalse:[
       
   934                 self isLongs ifTrue:[
       
   935                     line := line , ' variableLongSubclass:#'
       
   936                 ] ifFalse:[
       
   937                     self isFloats ifTrue:[
       
   938                         line := line , ' variableFloatSubclass:#'
       
   939                     ] ifFalse:[
       
   940                         self isDoubles ifTrue:[
       
   941                             line := line , ' variableDoubleSubclass:#'
       
   942                         ] ifFalse:[
       
   943                             line := line , ' variableSubclass:#'
       
   944                         ]
       
   945                     ]
       
   946                 ]
       
   947             ]
       
   948         ]
       
   949     ] ifFalse:[
       
   950         line := line , ' subclass:#'
       
   951     ].
       
   952     line := line , name.
       
   953     aStream nextPutAll:line.
       
   954 
       
   955     aStream crTab. 
       
   956     aStream nextPutAll:' instanceVariableNames:'''.
       
   957     self printInstVarNamesOn:aStream indent:16.
       
   958     aStream nextPutAll:''''.
       
   959 
       
   960     aStream crTab.
       
   961     aStream nextPutAll:' classVariableNames:'''.
       
   962     self printClassVarNamesOn:aStream indent:16.
       
   963     aStream nextPutAll:''''.
       
   964 
       
   965     aStream crTab.
       
   966     aStream nextPutAll:' poolDictionaries:'''''.
       
   967 
       
   968     aStream crTab.
       
   969     aStream nextPutAll:' category:'.
       
   970     category isNil ifTrue:[
       
   971         aStream nextPutAll:''''''
       
   972     ] ifFalse:[
       
   973         aStream nextPutAll:(category asString storeString)
       
   974     ].
       
   975     aStream cr
       
   976 !
       
   977 
       
   978 fileOutClassInstVarDefinitionOn:aStream
       
   979     aStream nextPutAll:(name , ' class instanceVariableNames:''').
       
   980     self class printInstVarNamesOn:aStream indent:8.
       
   981     aStream nextPutAll:''''
       
   982 !
       
   983 
       
   984 fileOutCategory:aCategory on:aStream
       
   985     "file out all methods belonging to aCategory, aString onto aStream"
       
   986 
       
   987     |nMethods count|
       
   988 
       
   989     methods notNil ifTrue:[
       
   990         nMethods := 0.
       
   991         methods do:[:aMethod |
       
   992             (aCategory = aMethod category) ifTrue:[
       
   993                 nMethods := nMethods + 1
       
   994             ]
       
   995         ].
       
   996         (nMethods ~~ 0) ifTrue:[
       
   997             aStream nextPut:$!!.
       
   998             self printClassNameOn:aStream.
       
   999             aStream nextPutAll:' methodsFor:'''.
       
  1000             aCategory notNil ifTrue:[
       
  1001                 aStream nextPutAll:aCategory
       
  1002             ].
       
  1003             aStream nextPut:$'. aStream nextPut:$!!. aStream cr.
       
  1004             aStream cr.
       
  1005             count := 1.
       
  1006             methods do:[:aMethod |
       
  1007                 (aCategory = aMethod category) ifTrue:[
       
  1008                     aStream nextChunkPut:(aMethod source).
       
  1009                     (count ~~ nMethods) ifTrue:[
       
  1010                         aStream cr.
       
  1011                         aStream cr
       
  1012                     ].
       
  1013                     count := count + 1
       
  1014                 ]
       
  1015             ].
       
  1016             aStream space.
       
  1017             aStream nextPut:$!!.
       
  1018             aStream cr
       
  1019         ]
       
  1020     ]
       
  1021 !
       
  1022 
       
  1023 fileOutMethod:aMethod on:aStream
       
  1024     "file out the method, aMethod onto aStream"
       
  1025 
       
  1026     |cat|
       
  1027 
       
  1028     methods notNil ifTrue:[
       
  1029         aStream nextPut:$!!.
       
  1030         self printClassNameOn:aStream.
       
  1031         aStream nextPutAll:' methodsFor:'''.
       
  1032         cat := aMethod category.
       
  1033         cat notNil ifTrue:[
       
  1034             aStream nextPutAll:cat
       
  1035         ].
       
  1036         aStream nextPut:$'.
       
  1037         aStream nextPut:$!!.
       
  1038         aStream cr.
       
  1039         aStream cr.
       
  1040         aStream nextChunkPut:(aMethod source).
       
  1041         aStream space.
       
  1042         aStream nextPut:$!!.
       
  1043         aStream cr
       
  1044     ]
       
  1045 !
       
  1046 
       
  1047 fileOutOn:aStream
       
  1048     "file out all methods onto aStream"
       
  1049 
       
  1050     |collectionOfCategories|
       
  1051 
       
  1052     aStream nextPutAll:(Smalltalk timeStamp).
       
  1053     aStream nextPut:$!!. 
       
  1054     aStream cr.
       
  1055     aStream cr.
       
  1056     self fileOutDefinitionOn:aStream.
       
  1057     aStream nextPut:$!!. 
       
  1058     aStream cr.
       
  1059     aStream cr.
       
  1060     self class instanceVariableString isBlank ifFalse:[
       
  1061         self fileOutClassInstVarDefinitionOn:aStream.
       
  1062         aStream nextPut:$!!. 
       
  1063         aStream cr.
       
  1064         aStream cr
       
  1065     ].
       
  1066 
       
  1067     comment notNil ifTrue:[
       
  1068         aStream nextPutAll:name.
       
  1069         aStream nextPutAll:' comment:'.
       
  1070         aStream nextPutAll:(comment storeString).
       
  1071         aStream nextPut:$!!.
       
  1072         aStream cr.
       
  1073         aStream cr
       
  1074     ].
       
  1075     collectionOfCategories := self class categories.
       
  1076     collectionOfCategories notNil ifTrue:[
       
  1077         collectionOfCategories do:[:aCategory |
       
  1078             self class fileOutCategory:aCategory on:aStream.
       
  1079             aStream cr
       
  1080         ]
       
  1081     ].
       
  1082     collectionOfCategories := self categories.
       
  1083     collectionOfCategories notNil ifTrue:[
       
  1084         collectionOfCategories do:[:aCategory |
       
  1085             self fileOutCategory:aCategory on:aStream.
       
  1086             aStream cr
       
  1087         ]
       
  1088     ].
       
  1089     (self class implements:#initialize) ifTrue:[
       
  1090         aStream nextPutAll:(name , ' initialize').
       
  1091         aStream nextPut:$!!. 
       
  1092         aStream cr
       
  1093     ]
       
  1094 !
       
  1095 
       
  1096 fileOutCategory:aCategory
       
  1097     "create a file 'class-category.st' consisting of all methods in aCategory.
       
  1098      If the current project is not nil, create the file in the projects
       
  1099      directory."
       
  1100 
       
  1101     |aStream fileName project|
       
  1102 
       
  1103     fileName := name , '-' , aCategory , '.st'.
       
  1104     project := Project current.
       
  1105     project notNil ifTrue:[
       
  1106         fileName := project directory , Filename separator asString , fileName.
       
  1107     ].
       
  1108     aStream := FileStream newFileNamed:fileName.
       
  1109     self fileOutCategory:aCategory on:aStream.
       
  1110     aStream close
       
  1111 !
       
  1112 
       
  1113 fileOutMethod:aMethod
       
  1114     "create a file 'class-method.st' consisting of the method, aMethod.
       
  1115      If the current project is not nil, create the file in the projects
       
  1116      directory."
       
  1117 
       
  1118     |aStream fileName selector project|
       
  1119 
       
  1120     selector := self selectorForMethod:aMethod.
       
  1121     selector notNil ifTrue:[
       
  1122         fileName := name , '-' , selector, '.st'.
       
  1123         project := Project current.
       
  1124         project notNil ifTrue:[
       
  1125             fileName := project directory , Filename separator asString , fileName.
       
  1126         ].
       
  1127         aStream := FileStream newFileNamed:fileName.
       
  1128         self fileOutMethod:aMethod on:aStream.
       
  1129         aStream close
       
  1130     ]
       
  1131 !
       
  1132 
       
  1133 fileOut
       
  1134     "create a file 'class.st' consisting of all methods in myself.
       
  1135      If the current project is not nil, create the file in the projects
       
  1136      directory."
       
  1137 
       
  1138     |aStream fileName project|
       
  1139 
       
  1140     fileName := (Smalltalk fileNameForClass:self name) , '.st'.
       
  1141     project := Project current.
       
  1142     project notNil ifTrue:[
       
  1143         fileName := project directory , Filename separator asString , fileName.
       
  1144     ].
       
  1145     aStream := FileStream newFileNamed:fileName.
       
  1146     aStream isNil ifTrue:[
       
  1147         ^ self error:('cannot create source file:', fileName)
       
  1148     ].
       
  1149     self fileOutOn:aStream.
       
  1150     aStream close
       
  1151 !
       
  1152 
       
  1153 fileOutIn:aFileDirectory
       
  1154     "create a file 'class.st' consisting of all methods in self in
       
  1155      directory aFileDirectory"
       
  1156 
       
  1157     |aStream fileName|
       
  1158 
       
  1159     fileName := (Smalltalk fileNameForClass:self name) , '.st'.
       
  1160     aStream := FileStream newFileNamed:fileName
       
  1161                                     in:aFileDirectory.
       
  1162     aStream isNil ifTrue:[
       
  1163         ^ self error:('cannot create source file:', fileName)
       
  1164     ].
       
  1165     self fileOutOn:aStream.
       
  1166     aStream close
       
  1167 ! !
       
  1168 
       
  1169 !Class methodsFor:'obsolete binary fileOut'!
       
  1170 
       
  1171 binaryFileOutMethodsOn:aStream
       
  1172     "binary file out all methods onto aStream"
       
  1173 
       
  1174     |temporaryMethod index|
       
  1175 
       
  1176     methods notNil ifTrue:[
       
  1177         aStream nextPut:$!!.
       
  1178         self printClassNameOn:aStream.
       
  1179         aStream nextPutAll:' binaryMethods'.
       
  1180         aStream nextPut:$!!.
       
  1181         aStream cr.
       
  1182         index := 1.
       
  1183         methods do:[:aMethod |
       
  1184             (selectors at:index) storeOn:aStream.
       
  1185             aStream nextPut:$!!.
       
  1186 
       
  1187             aMethod byteCode isNil ifTrue:[
       
  1188                 temporaryMethod := self compiler compile:(aMethod source)
       
  1189                                                 forClass:self
       
  1190                                               inCategory:(aMethod category)
       
  1191                                                notifying:nil
       
  1192                                                  install:false.
       
  1193                 temporaryMethod binaryFileOutOn:aStream
       
  1194             ] ifFalse:[
       
  1195                 aMethod binaryFileOutOn:aStream
       
  1196             ].
       
  1197             aStream cr.
       
  1198             index := index + 1
       
  1199         ].
       
  1200         aStream nextPut:$!!.
       
  1201         aStream cr
       
  1202     ]
       
  1203 !
       
  1204 
       
  1205 binaryFileOutOn:aStream
       
  1206     "file out all methods onto aStream"
       
  1207 
       
  1208     aStream nextPut:$'.
       
  1209     aStream nextPutAll:('From Smalltalk/X, Version:'
       
  1210                         , (Smalltalk version)
       
  1211                         , ' on ').
       
  1212     aStream nextPutAll:(Date today printString , ' at ' , Time now printString).
       
  1213     aStream nextPut:$'.
       
  1214     aStream nextPut:$!!.
       
  1215     aStream cr.
       
  1216     self fileOutDefinitionOn:aStream.
       
  1217     aStream nextPut:$!!. 
       
  1218     aStream cr.
       
  1219     comment notNil ifTrue:[
       
  1220         aStream nextPutAll:name.
       
  1221         aStream nextPutAll:' comment:'.
       
  1222         aStream nextPutAll:(comment storeString).
       
  1223         aStream nextPut:$!!.
       
  1224         aStream cr
       
  1225     ].
       
  1226     self class binaryFileOutMethodsOn:aStream.
       
  1227     self binaryFileOutMethodsOn:aStream.
       
  1228     (self class implements:#initialize) ifTrue:[
       
  1229         aStream nextPutAll:(name , ' initialize').
       
  1230         aStream nextPut:$!!. 
       
  1231         aStream cr
       
  1232     ]
       
  1233 !
       
  1234 
       
  1235 binaryFileOut
       
  1236     "create a file 'class.sb' consisting of all methods in myself.
       
  1237      If the current project is not nil, create the file in the projects
       
  1238      directory."
       
  1239 
       
  1240     |aStream fileName project|
       
  1241 
       
  1242     fileName := (Smalltalk fileNameForClass:self name) , '.sb'.
       
  1243     project := Project current.
       
  1244     project notNil ifTrue:[
       
  1245         fileName := project directory , Filename separator asString , fileName.
       
  1246     ].
       
  1247     aStream := FileStream newFileNamed:fileName.
       
  1248     aStream isNil ifTrue:[
       
  1249         ^ self error:('cannot create class file:', fileName)
       
  1250     ].
       
  1251     self binaryFileOutOn:aStream.
       
  1252     aStream close
       
  1253 ! !
       
  1254 
       
  1255 !Class methodsFor:'printOut'!
       
  1256 
   898 printClassNameOn:aStream
  1257 printClassNameOn:aStream
   899     "helper for fileOut - print my name if I am not a Metaclass;
  1258     "helper for fileOut - print my name if I am not a Metaclass;
   900      otherwise my name without -class followed by space-class"
  1259      otherwise my name without -class followed by space-class"
   901 
  1260 
   902     (self isMeta "isMemberOf:Metaclass") ifTrue:[
  1261     self isMeta ifTrue:[
   903         aStream nextPutAll:(name copyFrom:1 to:(name size - 5)).
  1262         aStream nextPutAll:(name copyTo:(name size - 5)).
   904         aStream nextPutAll:' class'
  1263         aStream nextPutAll:' class'
   905     ] ifFalse:[
  1264     ] ifFalse:[
   906         name printOn:aStream
  1265         name printOn:aStream
   907     ]
  1266     ]
   908 !
  1267 !
   912      defines a lineLength, break when this limit is reached; indent
  1271      defines a lineLength, break when this limit is reached; indent
   913      every line; used to printOut instanve variable names"
  1272      every line; used to printOut instanve variable names"
   914 
  1273 
   915     |thisName nextName arraySize lenMax pos mustBreak line spaces|
  1274     |thisName nextName arraySize lenMax pos mustBreak line spaces|
   916 
  1275 
   917     arraySize := 0.
  1276     arraySize := anArray size.
   918     anArray notNil ifTrue:[
       
   919         arraySize := anArray size
       
   920     ].
       
   921     arraySize ~~ 0 ifTrue:[
  1277     arraySize ~~ 0 ifTrue:[
   922         pos := indent.
  1278         pos := indent.
   923         lenMax := aStream lineLength.
  1279         lenMax := aStream lineLength.
   924         thisName := anArray at:1.
  1280         thisName := anArray at:1.
   925         line := ''.
  1281         line := ''.
   980 
  1336 
   981     indent := 0.
  1337     indent := 0.
   982     (superclass notNil) ifTrue:[
  1338     (superclass notNil) ifTrue:[
   983         indent := (superclass printHierarchyAnswerIndentOn:aStream) + 2
  1339         indent := (superclass printHierarchyAnswerIndentOn:aStream) + 2
   984     ].
  1340     ].
   985     aStream nextPutAll:(String new:indent).
  1341     aStream spaces:indent.
   986     aStream nextPutAll:name.
  1342     aStream nextPutAll:name.
   987     aStream nextPutAll:' ('.
  1343     aStream nextPutAll:' ('.
   988     self printInstVarNamesOn:aStream indent:(indent + name size + 2).
  1344     self printInstVarNamesOn:aStream indent:(indent + name size + 2).
   989     aStream nextPutAll:')'.
  1345     aStream nextPutAll:')'.
   990     aStream cr.
  1346     aStream cr.
   991     ^ indent
  1347     ^ indent
   992 !
  1348 !
   993     
  1349 
   994 printFullHierarchyOn:aStream indent:indent
  1350 printFullHierarchyOn:aStream indent:indent
   995     "print myself and all subclasses on aStream.
  1351     "print myself and all subclasses on aStream.
   996      recursively calls itself to print subclasses. 
  1352      recursively calls itself to print subclasses. 
   997      Can be used to print hierarchy on the printer."
  1353      Can be used to print hierarchy on the printer."
   998 
  1354 
   999     aStream nextPutAll:(String new:indent).
  1355     aStream spaces:indent.
  1000     aStream bold.
  1356     aStream bold.
  1001     aStream nextPutAll:name.
  1357     aStream nextPutAll:name.
  1002     aStream normal.
  1358     aStream normal.
  1003     aStream nextPutAll:' ('.
  1359     aStream nextPutAll:' ('.
  1004     self printInstVarNamesOn:aStream indent:(indent + name size + 2).
  1360     self printInstVarNamesOn:aStream indent:(indent + name size + 2).
  1012     "|printStream|
  1368     "|printStream|
  1013      printStream := Printer new.
  1369      printStream := Printer new.
  1014      Object printFullHierarchyOn:printStream indent:0.
  1370      Object printFullHierarchyOn:printStream indent:0.
  1015      printStream close"
  1371      printStream close"
  1016 !
  1372 !
  1017 
       
  1018 fileOutCommentOn:aStream
       
  1019     "print an expression on aStream to define my comment"
       
  1020 
       
  1021     aStream nextPutAll:name.
       
  1022     aStream nextPutAll:' comment:'.
       
  1023     comment isNil ifTrue:[
       
  1024         aStream nextPutAll:''''''
       
  1025     ] ifFalse:[
       
  1026         aStream nextPutAll:(comment storeString)
       
  1027     ].
       
  1028     aStream cr
       
  1029 !
       
  1030 
       
  1031 fileOutDefinitionOn:aStream
       
  1032     "print an expression to define myself on aStream"
       
  1033 
       
  1034     |isVar line|
       
  1035 
       
  1036     superclass isNil ifTrue:[
       
  1037         line := 'Object'
       
  1038     ] ifFalse:[
       
  1039         line := (superclass name)
       
  1040     ].
       
  1041     superclass isNil ifTrue:[
       
  1042         isVar := self isVariable
       
  1043     ] ifFalse:[
       
  1044         "I cant remember what this is for ?"
       
  1045         isVar := (self isVariable and:[superclass isVariable not])
       
  1046     ].
       
  1047     isVar ifTrue:[
       
  1048         self isBytes ifTrue:[
       
  1049             line := line , ' variableByteSubclass:#'
       
  1050         ] ifFalse:[
       
  1051             self isWords ifTrue:[
       
  1052                 line := line , ' variableWordSubclass:#'
       
  1053             ] ifFalse:[
       
  1054                 self isLongs ifTrue:[
       
  1055                     line := line , ' variableLongSubclass:#'
       
  1056                 ] ifFalse:[
       
  1057                     self isFloats ifTrue:[
       
  1058                         line := line , ' variableFloatSubclass:#'
       
  1059                     ] ifFalse:[
       
  1060                         self isDoubles ifTrue:[
       
  1061                             line := line , ' variableDoubleSubclass:#'
       
  1062                         ] ifFalse:[
       
  1063                             line := line , ' variableSubclass:#'
       
  1064                         ]
       
  1065                     ]
       
  1066                 ]
       
  1067             ]
       
  1068         ]
       
  1069     ] ifFalse:[
       
  1070         line := line , ' subclass:#'
       
  1071     ].
       
  1072     line := line , name.
       
  1073     aStream nextPutAll:line.
       
  1074 
       
  1075     aStream crTab. 
       
  1076     aStream nextPutAll:' instanceVariableNames:'''.
       
  1077     self printInstVarNamesOn:aStream indent:16.
       
  1078     aStream nextPutAll:''''.
       
  1079 
       
  1080     aStream crTab.
       
  1081     aStream nextPutAll:' classVariableNames:'''.
       
  1082     self printClassVarNamesOn:aStream indent:16.
       
  1083     aStream nextPutAll:''''.
       
  1084 
       
  1085     aStream crTab.
       
  1086     aStream nextPutAll:' poolDictionaries:'''''.
       
  1087 
       
  1088     aStream crTab.
       
  1089     aStream nextPutAll:' category:'.
       
  1090     category isNil ifTrue:[
       
  1091         aStream nextPutAll:''''''
       
  1092     ] ifFalse:[
       
  1093         aStream nextPutAll:(category asString storeString)
       
  1094     ].
       
  1095     aStream cr
       
  1096 !
       
  1097 
       
  1098 fileOutClassInstVarDefinitionOn:aStream
       
  1099     aStream nextPutAll:(name , ' class instanceVariableNames:''').
       
  1100     self class printInstVarNamesOn:aStream indent:8.
       
  1101     aStream nextPutAll:''''
       
  1102 !
       
  1103 
       
  1104 fileOutCategory:aCategory on:aStream
       
  1105     "file out all methods belonging to aCategory, aString onto aStream"
       
  1106 
       
  1107     |nMethods count|
       
  1108 
       
  1109     methods notNil ifTrue:[
       
  1110         nMethods := 0.
       
  1111         methods do:[:aMethod |
       
  1112             (aCategory = aMethod category) ifTrue:[
       
  1113                 nMethods := nMethods + 1
       
  1114             ]
       
  1115         ].
       
  1116         (nMethods ~~ 0) ifTrue:[
       
  1117             aStream nextPut:$!!.
       
  1118             self printClassNameOn:aStream.
       
  1119             aStream nextPutAll:' methodsFor:'''.
       
  1120             aCategory notNil ifTrue:[
       
  1121                 aStream nextPutAll:aCategory
       
  1122             ].
       
  1123             aStream nextPut:$'. aStream nextPut:$!!. aStream cr.
       
  1124             aStream cr.
       
  1125             count := 1.
       
  1126             methods do:[:aMethod |
       
  1127                 (aCategory = aMethod category) ifTrue:[
       
  1128                     aStream nextChunkPut:(aMethod source).
       
  1129                     (count ~~ nMethods) ifTrue:[
       
  1130                         aStream cr.
       
  1131                         aStream cr
       
  1132                     ].
       
  1133                     count := count + 1
       
  1134                 ]
       
  1135             ].
       
  1136             aStream space.
       
  1137             aStream nextPut:$!!.
       
  1138             aStream cr
       
  1139         ]
       
  1140     ]
       
  1141 !
       
  1142 
       
  1143 fileOutMethod:aMethod on:aStream
       
  1144     "file out the method, aMethod onto aStream"
       
  1145 
       
  1146     |cat|
       
  1147 
       
  1148     methods notNil ifTrue:[
       
  1149         aStream nextPut:$!!.
       
  1150         self printClassNameOn:aStream.
       
  1151         aStream nextPutAll:' methodsFor:'''.
       
  1152         cat := aMethod category.
       
  1153         cat notNil ifTrue:[
       
  1154             aStream nextPutAll:cat
       
  1155         ].
       
  1156         aStream nextPut:$'.
       
  1157         aStream nextPut:$!!.
       
  1158         aStream cr.
       
  1159         aStream cr.
       
  1160         aStream nextChunkPut:(aMethod source).
       
  1161         aStream space.
       
  1162         aStream nextPut:$!!.
       
  1163         aStream cr
       
  1164     ]
       
  1165 !
       
  1166 
       
  1167 fileOutOn:aStream
       
  1168     "file out all methods onto aStream"
       
  1169 
       
  1170     |collectionOfCategories|
       
  1171 
       
  1172     aStream nextPutAll:(Smalltalk timeStamp).
       
  1173     aStream nextPut:$!!. 
       
  1174     aStream cr.
       
  1175     aStream cr.
       
  1176     self fileOutDefinitionOn:aStream.
       
  1177     aStream nextPut:$!!. 
       
  1178     aStream cr.
       
  1179     aStream cr.
       
  1180     self class instanceVariableString isBlank ifFalse:[
       
  1181         self fileOutClassInstVarDefinitionOn:aStream.
       
  1182         aStream nextPut:$!!. 
       
  1183         aStream cr.
       
  1184         aStream cr
       
  1185     ].
       
  1186 
       
  1187     comment notNil ifTrue:[
       
  1188         aStream nextPutAll:name.
       
  1189         aStream nextPutAll:' comment:'.
       
  1190         aStream nextPutAll:(comment storeString).
       
  1191         aStream nextPut:$!!.
       
  1192         aStream cr.
       
  1193         aStream cr
       
  1194     ].
       
  1195     collectionOfCategories := self class categories.
       
  1196     collectionOfCategories notNil ifTrue:[
       
  1197         collectionOfCategories do:[:aCategory |
       
  1198             self class fileOutCategory:aCategory on:aStream.
       
  1199             aStream cr
       
  1200         ]
       
  1201     ].
       
  1202     collectionOfCategories := self categories.
       
  1203     collectionOfCategories notNil ifTrue:[
       
  1204         collectionOfCategories do:[:aCategory |
       
  1205             self fileOutCategory:aCategory on:aStream.
       
  1206             aStream cr
       
  1207         ]
       
  1208     ].
       
  1209     (self class implements:#initialize) ifTrue:[
       
  1210         aStream nextPutAll:(name , ' initialize').
       
  1211         aStream nextPut:$!!. 
       
  1212         aStream cr
       
  1213     ]
       
  1214 !
       
  1215 
       
  1216 fileOutCategory:aCategory
       
  1217     "create a file 'class-category.st' consisting of all methods in aCategory"
       
  1218 
       
  1219     |aStream fileName|
       
  1220 
       
  1221     fileName := name , '-' , aCategory , '.st'.
       
  1222     aStream := FileStream newFileNamed:fileName.
       
  1223     self fileOutCategory:aCategory on:aStream.
       
  1224     aStream close
       
  1225 !
       
  1226 
       
  1227 fileOutMethod:aMethod
       
  1228     "create a file 'class-method.st' consisting of the method, aMethod"
       
  1229 
       
  1230     |aStream fileName selector|
       
  1231 
       
  1232     selector := self selectorForMethod:aMethod.
       
  1233     selector notNil ifTrue:[
       
  1234         fileName := name , '-' , selector, '.st'.
       
  1235         aStream := FileStream newFileNamed:fileName.
       
  1236         self fileOutMethod:aMethod on:aStream.
       
  1237         aStream close
       
  1238     ]
       
  1239 !
       
  1240 
       
  1241 fileOut
       
  1242     "create a file 'class.st' consisting of all methods in myself"
       
  1243 
       
  1244     |aStream fileName|
       
  1245 
       
  1246     fileName := (Smalltalk fileNameForClass:self name) , '.st'.
       
  1247     aStream := FileStream newFileNamed:fileName.
       
  1248     aStream isNil ifTrue:[
       
  1249         ^ self error:('cannot create source file:', fileName)
       
  1250     ].
       
  1251     self fileOutOn:aStream.
       
  1252     aStream close
       
  1253 !
       
  1254 
       
  1255 fileOutIn:aFileDirectory
       
  1256     "create a file 'class.st' consisting of all methods in self in
       
  1257      directory aFileDirectory"
       
  1258 
       
  1259     |aStream fileName|
       
  1260 
       
  1261     fileName := (Smalltalk fileNameForClass:self) , '.st'.
       
  1262     aStream := FileStream newFileNamed:fileName
       
  1263                                     in:aFileDirectory.
       
  1264     aStream isNil ifTrue:[
       
  1265         ^ self error:('cannot create source file:', fileName)
       
  1266     ].
       
  1267     self fileOutOn:aStream.
       
  1268     aStream close
       
  1269 !
       
  1270 
       
  1271 binaryFileOutMethodsOn:aStream
       
  1272     "binary file out all methods onto aStream"
       
  1273 
       
  1274     |temporaryMethod index|
       
  1275 
       
  1276     methods notNil ifTrue:[
       
  1277         aStream nextPut:$!!.
       
  1278         self printClassNameOn:aStream.
       
  1279         aStream nextPutAll:' binaryMethods'.
       
  1280         aStream nextPut:$!!.
       
  1281         aStream cr.
       
  1282         index := 1.
       
  1283         methods do:[:aMethod |
       
  1284             (selectors at:index) storeOn:aStream.
       
  1285             aStream nextPut:$!!.
       
  1286 
       
  1287             aMethod byteCode isNil ifTrue:[
       
  1288                 temporaryMethod := self compiler compile:(aMethod source)
       
  1289                                                 forClass:self
       
  1290                                               inCategory:(aMethod category)
       
  1291                                                notifying:nil
       
  1292                                                  install:false.
       
  1293                 temporaryMethod binaryFileOutOn:aStream
       
  1294             ] ifFalse:[
       
  1295                 aMethod binaryFileOutOn:aStream
       
  1296             ].
       
  1297             aStream cr.
       
  1298             index := index + 1
       
  1299         ].
       
  1300         aStream nextPut:$!!.
       
  1301         aStream cr
       
  1302     ]
       
  1303 !
       
  1304 
       
  1305 binaryFileOutOn:aStream
       
  1306     "file out all methods onto aStream"
       
  1307 
       
  1308     aStream nextPut:$'.
       
  1309     aStream nextPutAll:('From Smalltalk/X, Version:'
       
  1310                         , (Smalltalk version)
       
  1311                         , ' on ').
       
  1312     aStream nextPutAll:(Date today printString , ' at ' , Time now printString).
       
  1313     aStream nextPut:$'.
       
  1314     aStream nextPut:$!!.
       
  1315     aStream cr.
       
  1316     self fileOutDefinitionOn:aStream.
       
  1317     aStream nextPut:$!!. 
       
  1318     aStream cr.
       
  1319     comment notNil ifTrue:[
       
  1320         aStream nextPutAll:name.
       
  1321         aStream nextPutAll:' comment:'.
       
  1322         aStream nextPutAll:(comment storeString).
       
  1323         aStream nextPut:$!!.
       
  1324         aStream cr
       
  1325     ].
       
  1326     self class binaryFileOutMethodsOn:aStream.
       
  1327     self binaryFileOutMethodsOn:aStream.
       
  1328     (self class implements:#initialize) ifTrue:[
       
  1329         aStream nextPutAll:(name , ' initialize').
       
  1330         aStream nextPut:$!!. 
       
  1331         aStream cr
       
  1332     ]
       
  1333 !
       
  1334 
       
  1335 binaryFileOut
       
  1336     "create a file 'class.sb' consisting of all methods in myself"
       
  1337 
       
  1338     |aStream fileName|
       
  1339 
       
  1340     fileName := (Smalltalk fileNameForClass:self name) , '.sb'.
       
  1341     aStream := FileStream newFileNamed:fileName.
       
  1342     aStream isNil ifTrue:[
       
  1343         ^ self error:('cannot create class file:', fileName)
       
  1344     ].
       
  1345     self binaryFileOutOn:aStream.
       
  1346     aStream close
       
  1347 ! !
       
  1348 
       
  1349 !Class methodsFor:'printOut'!
       
  1350 
  1373 
  1351 printOutDefinitionOn:aPrintStream
  1374 printOutDefinitionOn:aPrintStream
  1352     "print out my definition"
  1375     "print out my definition"
  1353 
  1376 
  1354     aPrintStream nextPutAll:'class                '.
  1377     aPrintStream nextPutAll:'class                '.
  1527     ]
  1550     ]
  1528 !
  1551 !
  1529 
  1552 
  1530 printOutCategoryProtocol:aCategory on:aPrintStream
  1553 printOutCategoryProtocol:aCategory on:aPrintStream
  1531     |any|
  1554     |any|
       
  1555 
  1532     methods notNil ifTrue:[
  1556     methods notNil ifTrue:[
  1533         any := false.
  1557         any := false.
  1534         methods do:[:aMethod |
  1558         methods do:[:aMethod |
  1535             (aCategory = aMethod category) ifTrue:[
  1559             (aCategory = aMethod category) ifTrue:[
  1536                 any := true
  1560                 any := true