Behavior.st
changeset 9639 ec0c8078671a
parent 9489 0ab599dd1ec0
child 9655 21818d93f71d
--- a/Behavior.st	Wed Aug 23 16:03:05 2006 +0200
+++ b/Behavior.st	Wed Aug 23 16:03:23 2006 +0200
@@ -1234,73 +1234,81 @@
     "Created: 16.4.1996 / 16:27:16 / cg"
 ! !
 
-!Behavior methodsFor:'binary storage'!
-
-binaryDefinitionFrom:stream manager:manager
-    "sent during a binary read by the input manager.
-     Read the definition on an empty instance (of my class) from stream.
-     All pointer instances are left nil, while all bits are read in here.
-     return the new object."
-
-    |obj t
-     basicSize "{ Class: SmallInteger }" |
-
-    self isPointers ifTrue: [
-        "/
-        "/ inst size not needed - if you uncomment the line below,
-        "/ also uncomment the corresponding line in
-        "/ Object>>storeBinaryDefinitionOn:manager:
-        "/
-        "/ stream next. "skip instSize"
-        self isVariable ifTrue: [
-            ^ self basicNew:(stream nextNumber:3)
-        ].
-        ^ self basicNew
-    ].
-
-    "
-     an object with bit-valued instance variables.
-     These are read here.
-    "
-    basicSize := stream nextNumber:4.
-    obj := self basicNew:basicSize.
-
-    self isBytes ifTrue: [
-        stream nextBytes:basicSize into:obj
-    ] ifFalse: [
-        self isWords ifTrue: [
-            1 to:basicSize do:[:i |
-                obj basicAt:i put:(stream nextNumber:2)
-            ]
-        ] ifFalse:[
-            self isLongs ifTrue: [
-                1 to:basicSize do:[:i |
-                    obj basicAt:i put:(stream nextNumber:4)
-                ]
-            ] ifFalse:[
-                self isFloats ifTrue: [
-                    "could do it in one big read on machines which use IEEE floats ..."
-                    t := ShortFloat basicNew.
-                    1 to:basicSize do:[:i |
-                        ShortFloat readBinaryIEEESingleFrom:stream into:t.
-                        obj basicAt:i put: t
-                    ]
-                ] ifFalse:[
-                    self isDoubles ifTrue: [
-                        "could do it in one big read on machines which use IEEE doubles ..."
-                        t := Float basicNew.
-                        1 to:basicSize do:[:i |
-                            Float readBinaryIEEEDoubleFrom:stream into:t.
-                            obj basicAt:i put: t
-                        ]
-                    ]
-                ]
-            ]
-        ]
-    ].
-    ^obj
+
+!Behavior methodsFor:'compiler interface'!
+
+browserClass
+    "return the browser to use for this class - 
+     this can be redefined in special classes, to get different browsers"
+
+    ^ self class browserClass.
+!
+
+compilerClass
+    "return the compiler to use for this class - 
+     this can be redefined in special classes, to compile classes with
+     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
+
+    ^ self class compilerClass.
+!
+
+evaluatorClass
+    "return the compiler to use for expression evaluation for this class - 
+     this can be redefined in special classes, to evaluate expressions with
+     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
+
+    ^ self class evaluatorClass.
+!
+
+formatterClass
+    "return the parser to use for formatting (prettyPrinting) this class - 
+     this can be redefined in special classes, to format classes with
+     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
+
+    ^ self class formatterClass.
 !
 
+parserClass
+    "return the parser to use for parsing this class - 
+     this can be redefined in special classes, to parse classes with
+     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
+
+    ^ self class parserClass.
+!
+
+subclassDefinerClass
+    "Answer an evaluator class appropriate for evaluating definitions of new 
+     subclasses of this class."
+
+    ^ self class subclassDefinerClass.
+!
+
+syntaxHighlighterClass
+    "return the class to use for syntaxHighlighting (prettyPrinting) this class - 
+     this can be redefined in special classes, to highlight classes with
+     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
+
+    ^ self class syntaxHighlighterClass.
+! !
+
+!Behavior methodsFor:'compiling'!
+
+compile:code notifying:requestor
+    "compile code, aString for this class; on any error, notify
+     requestor, anObject with the error reason.
+     Returns the new method or nil (on failure)."
+
+    ^ self compilerClass
+	compile:code
+	forClass:self
+	notifying:requestor
+
+    "Modified: 13.12.1995 / 11:02:40 / cg"
+    "Created: 1.4.1997 / 23:43:43 / stefan"
+! !
+
+!Behavior methodsFor:'copying'!
+
 canCloneFrom:anObject 
     "return true, if this class can clone an obsolete object as retrieved
      by a binary load. Subclasses which do not want to have obsolete objects
@@ -1380,183 +1388,6 @@
     "
 !
 
-fromBinaryStoreBytes:bytes
-    ^ self readBinaryFrom:(bytes readStream)
-
-    "
-     Object fromBinaryStoreBytes:
-        #[15 1 42 0 0 3 0 40 13 5 104 101 108 108 111 38 40 46 63 243 190 118 200 180 57 88]
-    "
-!
-
-readBinaryFrom:aStream
-    "read an objects binary representation from the argument,
-     aStream and return it. 
-     The read object must be a kind of myself, otherwise an error is raised. 
-     To get any object, use 'Object readBinaryFrom:...',
-     To get any number, use 'Number readBinaryFrom:...' and so on.
-     This is the reverse operation to 'storeBinaryOn:'. "
-
-    ^ self readBinaryFrom:aStream onError:[self error:('expected ' , self name)]
-
-    "
-     |s|
-     s := WriteStream on:(ByteArray new).
-     #(1 2 3 4) storeBinaryOn:s.
-     Object readBinaryFrom:(ReadStream on:s contents)  
-    "
-    "
-     |s|
-     s := 'testFile' asFilename writeStream binary.
-     #(1 2 3 4) storeBinaryOn:s.
-     'hello world' storeBinaryOn:s.
-     s close.
-
-     s := 'testFile' asFilename readStream binary.
-     Transcript showCR:(Object readBinaryFrom:s).
-     Transcript showCR:(Object readBinaryFrom:s).
-     s close.
-    "
-!
-
-readBinaryFrom:aStream onError:exceptionBlock
-    "read an objects binary representation from the argument,
-     aStream and return it. 
-     The read object must be a kind of myself, otherwise the value of
-     the exceptionBlock is returned.
-     To get any object, use 'Object readBinaryFrom:...',
-     To get any number, use 'Number readBinaryFrom:...' and so on.
-     This is the reverse operation to 'storeBinaryOn:'. "
-
-    |newObject|
-
-    newObject := (BinaryInputManager new) readFrom:aStream.
-    (self ~~ Object
-     and:[(newObject isKindOf:self) not]) ifTrue:[^ exceptionBlock value].
-    ^ newObject
-
-    "
-     |s|
-     s := WriteStream on:(ByteArray new).
-     #(1 2 3 4) storeBinaryOn:s.
-     Object readBinaryFrom:(ReadStream on:s contents) onError:['oops'] 
-    "
-    "
-     |s|
-     s := WriteStream on:(ByteArray new).
-     #[1 2 3 4] storeBinaryOn:s.
-     Array readBinaryFrom:(ReadStream on:s contents)  onError:['oops']  
-    "
-
-    "Modified: / 1.11.1997 / 16:53:36 / cg"
-!
-
-storeBinaryDefinitionOn: stream manager: manager
-    "binary store of a classes definition.
-     Classes will store the name only and restore by looking for
-     that name in the Smalltalk dictionary.
-     This is an internal interface for the binary storage mechanism."
-
-    | myName |
-
-    myName := self name.
-    stream nextNumber:4 put:self signature.
-    stream nextNumber:2 put:0.              "/ no instVarNames string here
-    stream nextNumber:2 put:myName size.
-    stream nextPutBytes:(myName size) from:myName startingAt:1.
-"/    myName do:[:c| 
-"/        stream nextPut:c asciiValue
-"/    ]
-
-    "
-     |s|
-     s := WriteStream on:ByteArray new.
-     #(1 2 3 4) storeBinaryOn:s.
-     Object readBinaryFrom:(ReadStream on:s contents)  
-
-     |s|
-     s := WriteStream on:ByteArray new.
-     Rectangle storeBinaryOn:s.
-     Object readBinaryFrom:(ReadStream on:s contents)  
-    "
-
-    "Modified: 19.3.1997 / 19:49:59 / cg"
-! !
-
-!Behavior methodsFor:'compiler interface'!
-
-browserClass
-    "return the browser to use for this class - 
-     this can be redefined in special classes, to get different browsers"
-
-    ^ self class browserClass.
-!
-
-compilerClass
-    "return the compiler to use for this class - 
-     this can be redefined in special classes, to compile classes with
-     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
-
-    ^ self class compilerClass.
-!
-
-evaluatorClass
-    "return the compiler to use for expression evaluation for this class - 
-     this can be redefined in special classes, to evaluate expressions with
-     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
-
-    ^ self class evaluatorClass.
-!
-
-formatterClass
-    "return the parser to use for formatting (prettyPrinting) this class - 
-     this can be redefined in special classes, to format classes with
-     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
-
-    ^ self class formatterClass.
-!
-
-parserClass
-    "return the parser to use for parsing this class - 
-     this can be redefined in special classes, to parse classes with
-     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
-
-    ^ self class parserClass.
-!
-
-subclassDefinerClass
-    "Answer an evaluator class appropriate for evaluating definitions of new 
-     subclasses of this class."
-
-    ^ self class subclassDefinerClass.
-!
-
-syntaxHighlighterClass
-    "return the class to use for syntaxHighlighting (prettyPrinting) this class - 
-     this can be redefined in special classes, to highlight classes with
-     Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
-
-    ^ self class syntaxHighlighterClass.
-! !
-
-!Behavior methodsFor:'compiling'!
-
-compile:code notifying:requestor
-    "compile code, aString for this class; on any error, notify
-     requestor, anObject with the error reason.
-     Returns the new method or nil (on failure)."
-
-    ^ self compilerClass
-	compile:code
-	forClass:self
-	notifying:requestor
-
-    "Modified: 13.12.1995 / 11:02:40 / cg"
-    "Created: 1.4.1997 / 23:43:43 / stefan"
-! !
-
-!Behavior methodsFor:'copying'!
-
 deepCopyUsing:aDictionary
     "return a deep copy of the receiver
      - return the receiver here - time will show if this is ok"
@@ -4470,5 +4301,5 @@
 !Behavior class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.258 2006-08-09 12:02:44 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.259 2006-08-23 14:03:23 cg Exp $'
 ! !