Merge jv
authorMerge Script
Fri, 30 Oct 2015 06:59:59 +0100
branchjv
changeset 18883 765cf9dca720
parent 18873 ce58d469e583 (current diff)
parent 18882 bac8f901c000 (diff)
child 18885 c3cb64a1b826
Merge
Collection.st
EncodedStream.st
ExternalBytes.st
ObjectMemory.st
OrderedCollection.st
PeekableStream.st
SequenceableCollection.st
SmalltalkLanguage.st
UninterpretedBytes.st
--- a/Collection.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/Collection.st	Fri Oct 30 06:59:59 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
               All Rights Reserved
@@ -275,7 +277,6 @@
     ^ self newWithSize:n
 ! !
 
-
 !Collection class methodsFor:'Signal constants'!
 
 emptyCollectionSignal
@@ -337,15 +338,16 @@
     ^ self == Collection
 ! !
 
-
-!Collection methodsFor:'Compatibility-Dolphin'!
+!Collection methodsFor:'Compatibility-ANSI'!
 
 identityIncludes:anObject
     "return true, if the argument, anObject is in the collection.
-     Same as #includesIdentical for Dolphin compatibility."
+     Same as #includesIdentical for Dolphin/ANSI compatibility."
 
     ^ self includesIdentical:anObject.
-!
+! !
+
+!Collection methodsFor:'Compatibility-Dolphin'!
 
 includesAnyOf:aCollection
     "same as #includesAny for Dolphin compatibility."
@@ -527,7 +529,6 @@
     "Created: / 22-10-2008 / 21:29:27 / cg"
 ! !
 
-
 !Collection methodsFor:'accessing'!
 
 anElement
@@ -4125,7 +4126,7 @@
     aStream nextPut:$)
 
     "
-     #(1 2 3 'hello' $a $ü) printOn:Transcript
+     #(1 2 3 'hello' $a $ü) printOn:Transcript
      (Array new:100000) printOn:Transcript
      (Array new:100000) printOn:Stdout          
      (Array new:100000) printString size 
@@ -5767,7 +5768,6 @@
     ^ aVisitor visitCollection:self with:aParameter
 ! !
 
-
 !Collection class methodsFor:'documentation'!
 
 version
--- a/EncodedStream.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/EncodedStream.st	Fri Oct 30 06:59:59 2015 +0100
@@ -211,7 +211,7 @@
         ]
     ].
 
-    Smalltalk::Compiler isNil ifTrue:[
+    (Smalltalk at:#Compiler) isNil ifTrue:[
         self isFileStream ifTrue:[
             Transcript show:('[' , self pathName , '] ').
         ].
--- a/ExternalBytes.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/ExternalBytes.st	Fri Oct 30 06:59:59 2015 +0100
@@ -682,6 +682,17 @@
     "
 !
 
+sizeofNativeInt
+    "return the number of bytes used by the machine's SmallInteger native values"
+
+%{  /* NOCONTEXT */
+    RETURN (__mkSmallInteger( sizeof(INT)));
+%}
+    "
+     ExternalBytes sizeofNativeInt
+    "
+!
+
 sizeofPointer
     "return the number of bytes used by the machine's native pointer"
 
--- a/ObjectMemory.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/ObjectMemory.st	Fri Oct 30 06:59:59 2015 +0100
@@ -1,16 +1,3 @@
-"{ Encoding: utf8 }"
-
-"
- COPYRIGHT (c) 1992 by Claus Gittinger
-	      All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: Smalltalk }"
@@ -5560,10 +5547,12 @@
 !
 
 nameForChanges
-    "return a reasonable filename to store the changes into.
+    "return a reasonable filename string to store the changes into.
      By default, this is the basename of the current image with '.img' replaced
      by '.chg', or, if not running from an image, the default name 'st.chg'.
-     However, it can be overwritten via the nameForChanges: setter"
+     However, it can be overwritten via the nameForChanges: setter.
+     For now, this returns a string (for backward compatibility);
+     senders should be prepared to get a filename in the future."
 
     |userPrefs localName nm wd|
 
@@ -5571,17 +5560,20 @@
     userPrefs := UserPreferences current.
     
     "/ if the prefs provide a full, explicit name
-    (nm := userPrefs changeFileName) notNil ifTrue:[ ^ nm ].
-
-    "/ if there is a workspace, create it there
-    ((wd := userPrefs workspaceDirectory) notNil and:[wd exists]) ifTrue:[
-        ^ wd / (localName asFilename baseName)
-    ].
-
-    "/ if it was set by a startup file
-    ChangeFileName notNil ifTrue:[^ ChangeFileName].
-    "/ finally, fall back to a default.
-    ^ localName
+    (nm := userPrefs changeFileName) isNil ifTrue:[ 
+
+        "/ if there is a workspace, create it there
+        ((wd := userPrefs workspaceDirectory) notNil and:[wd exists]) ifTrue:[
+            nm := wd / (localName asFilename baseName)
+        ] ifFalse:[
+            "/ if it was set by a startup file
+            (nm := ChangeFileName) isNil ifTrue:[
+                "/ finally, fall back to a default.
+                nm := localName
+            ]
+        ]
+    ].    
+    ^ nm asFilename pathName.
 
     "
      ObjectMemory nameForChanges
--- a/OrderedCollection.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/OrderedCollection.st	Fri Oct 30 06:59:59 2015 +0100
@@ -15,7 +15,7 @@
 
 SequenceableCollection subclass:#OrderedCollection
 	instanceVariableNames:'contentsArray firstIndex lastIndex'
-	classVariableNames:''
+	classVariableNames:'MinContentsArraySize'
 	poolDictionaries:''
 	category:'Collections-Sequenceable'
 !
@@ -202,12 +202,35 @@
 "
 ! !
 
+!OrderedCollection class methodsFor:'initialization'!
+
+initialize
+    MinContentsArraySize := 3. "the minimum size of a non-empty contentsArray"
+! !
+
 !OrderedCollection class methodsFor:'instance creation'!
 
 new
     "create a new, empty OrderedCollection"
 
-    ^ (self basicNew) initContents:10
+    MinContentsArraySize isNil ifTrue:[
+        self initialize.
+    ].
+    ^ self basicNew initContents:0
+
+    "
+        self new
+
+        |nEmpty|
+        nEmpty := 0.
+        self allInstancesDo:[:e| e size == 0 ifTrue:[nEmpty := nEmpty + 1]].
+        nEmpty
+
+        |nEmpty|
+        nEmpty := OrderedCollection new.
+        self allInstancesDo:[:e| (e size == 0 and:[e contentsArray size ~~ 0]) ifTrue:[nEmpty add:e]].
+        nEmpty
+    "
 
     "Modified: 19.3.1996 / 17:53:12 / cg"
 !
@@ -223,7 +246,13 @@
      See also newWithSize:, which might do what you really want.        
      "
 
-    ^ (self basicNew) initContents:(size max:3)
+    |sz|
+
+    MinContentsArraySize isNil ifTrue:[
+        self initialize.
+    ].
+    sz := size.
+    ^ self basicNew initContents:sz
 
     "Modified: 19.3.1996 / 17:53:47 / cg"
 !
@@ -266,7 +295,10 @@
      This creates an initial contents array of size 0 in contrast to the default new:0,
      which preserves space for 3 elements."
 
-    ^ (self basicNew) initContents:0
+    MinContentsArraySize isNil ifTrue:[
+        self initialize.
+    ].
+    ^ self basicNew initContents:0
 
     "
      self newLikelyToRemainEmpty size
@@ -275,6 +307,7 @@
     "
 ! !
 
+
 !OrderedCollection methodsFor:'accessing'!
 
 at:anInteger
@@ -683,14 +716,7 @@
      Returns the receiver.
      Destructive: modifies the receiver."
 
-    contentsArray size <= 20 ifTrue:[
-        "/ reuse the contents array
-        contentsArray atAllPut:nil.
-        firstIndex := 1.
-        lastIndex := 0.
-    ] ifFalse:[
-        self initContents:10
-    ].
+    self initContents:0
 
     "Modified: 12.4.1996 / 13:34:19 / cg"
 !
@@ -1270,19 +1296,11 @@
 copyEmpty
     "return a copy of the receiver without any elements."
 
-    ^ self copyEmpty:10
-!
-
-copyFrom:start to:stop
-    "return a new OrderedCollection containing the elements
-     from start to stop."
+    ^ self copyEmpty:0
 
-    |newCollection sz|
-
-    sz := stop - start + 1.
-    newCollection := self copyEmptyAndGrow:sz.   "must grow, otherwise replace fails"
-    newCollection replaceFrom:1 to:sz with:self startingAt:start.
-    ^ newCollection
+    "
+        self new copyEmpty
+    "
 !
 
 postCopy
@@ -1579,7 +1597,7 @@
         newLast := firstIndex + newSize - 1.
         newSize < oldSize ifTrue:[
             newSize == 0 ifTrue:[
-                self initContents:10.
+                self initContents:0.
                 ^ self.
             ].
             oldLast := lastIndex.
@@ -1604,12 +1622,17 @@
 ! !
 
 
+
 !OrderedCollection methodsFor:'private'!
 
 initContents:size
     "setup the receiver-collection to hold size entries"
 
-    contentsArray := Array basicNew:size.
+    size == 0 ifTrue:[
+        contentsArray := #().   "save garbage"
+    ] ifFalse:[
+        contentsArray := Array basicNew:size.
+    ].
     firstIndex := 1.
     lastIndex := 0 
 !
@@ -1631,7 +1654,7 @@
     sz := lastIndex - firstIndex + 1.
 
     ((oldSize == 0) or:[sz == 0]) ifTrue:[ 
-        contentsArray := Array basicNew:3.
+        contentsArray := Array basicNew:MinContentsArraySize.
         firstIndex := 2. lastIndex := 1.
         ^ self
     ].
@@ -1654,7 +1677,6 @@
         ]
     ].
     newSize := oldSize * 2.
-    newSize == 0 ifTrue:[ newSize := 3].
     newContents := Array basicNew:newSize.
     newContents
         replaceFrom:(oldSize + 1) to:newSize
@@ -1745,36 +1767,42 @@
         ^ index
     ].
 
-    newSize := oldSize * 2.
-    newSize == 0 ifTrue:[ newSize := 3].
+    oldSize == 0 ifTrue:[
+        newSize := MinContentsArraySize
+    ] ifFalse:[
+        newSize := oldSize * 2.
+    ].
     newContents := Array basicNew:newSize.
     index == first ifTrue:[
         "/ if there is a lot at the end (> 50), make all new space at the beginning.
         "/ otherwise make 3/4 of the new space to the beginning, 1/4 to the end
-        (last < (oldSize - 50)) ifTrue:[
-            lastIndex := newSize - (oldSize-last).
-            firstIndex := lastIndex - (last - first).
-        ] ifFalse:[
-            firstIndex := oldSize * 3 // 4.
-            lastIndex := firstIndex + (last - first).
+        oldSize ~~ 0 ifTrue:[
+            (last < (oldSize - 50)) ifTrue:[
+                lastIndex := newSize - (oldSize-last).
+                firstIndex := lastIndex - (last - first).
+            ] ifFalse:[
+                firstIndex := oldSize * 3 // 4.
+                lastIndex := firstIndex + (last - first).
+            ].
+            newContents 
+                replaceFrom:firstIndex to:lastIndex
+                with:contentsArray startingAt:first.
         ].
-        newContents 
-            replaceFrom:firstIndex to:lastIndex
-            with:contentsArray startingAt:first.
-        
         contentsArray := newContents.
         firstIndex := firstIndex - 1.
 
         ^ firstIndex.
     ] ifFalse:[
-        newContents 
-            replaceFrom:1 to:(index - first)
-            with:contentsArray startingAt:first.
+        oldSize ~~ 0 ifTrue:[
+            newContents 
+                replaceFrom:1 to:(index - first)
+                with:contentsArray startingAt:first.
 
-        index <= last ifTrue:[
-            newContents
-                replaceFrom:(index - first + 2) to:(last - first + 2) 
-                with:contentsArray startingAt:index.
+            index <= last ifTrue:[
+                newContents
+                    replaceFrom:(index - first + 2) to:(last - first + 2) 
+                    with:contentsArray startingAt:index.
+            ].
         ].
         contentsArray := newContents.
         firstIndex := 1.
@@ -1816,7 +1844,6 @@
     shiftLeft := shiftRight := false.
     ((first > howMany) and:[first > oneFourthOfSize]) ifTrue:[
         "there is room (>25%) at the beginning"
-
         shiftLeft := true.
     ] ifFalse:[
         ((last + howMany) <= oldSize
@@ -1861,19 +1888,21 @@
     ].
 
     newContents := Array basicNew:newSize.
-    index > first ifTrue:[
-        newContents 
-            replaceFrom:1 
-            to:index - first
-            with:contentsArray
-            startingAt:first.
-    ].
-    index <= last ifTrue:[
-        newContents
-            replaceFrom:index - first + howMany + 1
-            to:(last - first + howMany + 1) 
-            with:contentsArray
-            startingAt:(index).
+    oldSize ~~ 0 ifTrue:[
+        index > first ifTrue:[
+            newContents 
+                replaceFrom:1 
+                to:index - first
+                with:contentsArray
+                startingAt:first.
+        ].
+        index <= last ifTrue:[
+            newContents
+                replaceFrom:index - first + howMany + 1
+                to:(last - first + howMany + 1) 
+                with:contentsArray
+                startingAt:(index).
+        ].
     ].
     contentsArray := newContents.
     firstIndex := 1.
@@ -1918,12 +1947,17 @@
         lastIndex := startIndex + sz - 1.
         ^ self
     ].
-    newSize := oldSize * 2.
-    newSize == 0 ifTrue:[newSize := 3].
+    oldSize == 0 ifTrue:[
+        newSize := MinContentsArraySize
+    ] ifFalse:[
+        newSize := oldSize * 2.
+    ].
     newContents := Array basicNew:newSize.
-    newContents 
-        replaceFrom:1 to:oldSize 
-        with:contentsArray startingAt:1.
+    oldSize ~~ 0 ifTrue:[
+        newContents 
+            replaceFrom:1 to:oldSize 
+            with:contentsArray startingAt:1.
+    ].
     contentsArray := newContents
 
     "Modified: / 22-10-2008 / 11:50:28 / cg"
@@ -2193,3 +2227,5 @@
     ^ '$Header$'
 ! !
 
+
+OrderedCollection initialize!
--- a/PeekableStream.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/PeekableStream.st	Fri Oct 30 06:59:59 2015 +0100
@@ -435,7 +435,7 @@
                 someone notNil ifTrue:[someone source:aString]
             ].
             someone perform:#reader: with:(SourceFileLoader::SourceFileReader new) ifNotUnderstood:[].
-            compiler := Smalltalk::Compiler new.
+            compiler := (Smalltalk at:#Compiler) new.
             compiler allowUndeclaredVariables:false.
 
             sawExcla ifFalse:[
@@ -443,7 +443,7 @@
                 rslt := compiler evaluate:aString receiver:someone notifying:someone compile:false.
             ] ifTrue:[
                 "/ methodsFor chunks, etc., which generate a reader
-                Smalltalk::Compiler emptySourceNotificationSignal handle:[:ex |
+                (Smalltalk at:#Compiler) emptySourceNotificationSignal handle:[:ex |
                     ^ nil
                 ] do:[
                     rslt := compiler 
--- a/SequenceableCollection.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/SequenceableCollection.st	Fri Oct 30 06:59:59 2015 +0100
@@ -400,8 +400,6 @@
     ^ self == SequenceableCollection
 ! !
 
-
-
 !SequenceableCollection methodsFor:'Compatibility-Squeak'!
 
 allButFirst
@@ -556,44 +554,6 @@
     ^ self from:startIndex to:stopIndex collect:aBlock
 !
 
-copyAfter: anElement
-	"Answer a copy of the receiver from after the first occurrence
-	of anElement up to the end. If no such element exists, answer
-	an empty copy."
-    |idx|
-
-    idx := self indexOf:anElement.
-    idx == 0 ifTrue:[idx := self size].
-    ^ self copyFrom:idx + 1
-
-    "
-     'hello world' copyAfter:$l
-     '123456123456' copyAfter:$2
-     #(1 2 3 4 1 2 3 3 4 5 6) copyAfter:3
-     #(1 2 3 4 2 3 3 4 5 6) copyAfter:1
-     #(1 2 3 4 1 2 3 3 4 5 6) copyAfter:7
-    "
-!
-
-copyAfterLast:element
-    "return a copy of the receiver from (but excluding) the last occurrence
-     of element to the end; uses = for comparison"
-
-    |idx|
-
-    idx := self lastIndexOf:element.
-    idx == 0 ifTrue:[idx := self size].
-    ^ self copyFrom:idx + 1
-
-    "
-     'hello world' copyAfterLast:$l
-     '123456123456' copyAfterLast:$2
-     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLast:3
-     #(1 2 3 4 2 3 3 4 5 6) copyAfterLast:1
-     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLast:7
-    "
-!
-
 copyUpToLast:element
     "return a copy of the receiver up to (but excluding) the last occurrence
      of element; uses = for comparison"
@@ -752,7 +712,6 @@
     ^ self replaceFrom:start to:stop with:anArray startingAt:repStart
 ! !
 
-
 !SequenceableCollection methodsFor:'accessing'!
 
 after:anObject
@@ -3645,6 +3604,45 @@
     "
 !
 
+copyAfter: anElement
+    "Answer a copy of the receiver from after the first occurrence
+    of anElement up to the end. If no such element exists, answer
+    an empty copy."
+
+    |idx|
+
+    idx := self indexOf:anElement.
+    idx == 0 ifTrue:[idx := self size].
+    ^ self copyFrom:idx + 1
+
+    "
+     'hello world' copyAfter:$l
+     '123456123456' copyAfter:$2
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfter:3
+     #(1 2 3 4 2 3 3 4 5 6) copyAfter:1
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfter:7
+    "
+!
+
+copyAfterLast:element
+    "return a copy of the receiver from (but excluding) the last occurrence
+     of element to the end; uses = for comparison"
+
+    |idx|
+
+    idx := self lastIndexOf:element.
+    idx == 0 ifTrue:[idx := self size].
+    ^ self copyFrom:idx + 1
+
+    "
+     'hello world' copyAfterLast:$l
+     '123456123456' copyAfterLast:$2
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLast:3
+     #(1 2 3 4 2 3 3 4 5 6) copyAfterLast:1
+     #(1 2 3 4 1 2 3 3 4 5 6) copyAfterLast:7
+    "
+!
+
 copyButFirst
     "return a new collection consisting of the receiver's elements
      except for the first element.
@@ -3974,6 +3972,29 @@
     "Modified (comment): / 27-07-2012 / 16:39:17 / cg"
 !
 
+copyReplaceFrom:startIndex to:endIndex withObject:anObject
+    "return a copy of the receiver, where the elements from startIndex to
+     endIndex have been replaced by anObject.
+     Returns a plain copy, if startIndex is beyond the receiver's size"
+
+    |newColl mySize|
+
+    mySize := self size.
+    startIndex > mySize ifTrue:[^ self copy].
+
+    newColl := self copyEmptyAndGrow:mySize.
+    newColl replaceFrom:1 to:(startIndex - 1) with:self.
+    newColl from:startIndex to:endIndex put:anObject.
+    newColl replaceFrom:(endIndex + 1) with:self startingAt:(endIndex + 1).
+    ^ newColl
+
+    "
+     #(1 2 3 4 5 6 7 8 9 0) copyReplaceFrom:3 to:6 withObject:#foo
+     'hello world' copyReplaceFrom:1 to:5 withObject:$*
+     'hello world' copyReplaceFrom:6 to:8 withObject:$*
+    "
+!
+
 copyReplaceFrom:startIndex with:aCollection
     "return a copy of the receiver, where the elements from startIndex to
      the end have been replaced by the elements of aCollection"
@@ -7643,7 +7664,6 @@
     "Created: 14.2.1997 / 16:13:03 / cg"
 ! !
 
-
 !SequenceableCollection methodsFor:'searching'!
 
 detect:aBlock startingAt:startIndex
--- a/SmalltalkLanguage.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/SmalltalkLanguage.st	Fri Oct 30 06:59:59 2015 +0100
@@ -41,6 +41,7 @@
     "Modified: / 16-08-2009 / 10:53:52 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
 
+
 !SmalltalkLanguage methodsFor:'accessing-classes'!
 
 codeGeneratorClass
@@ -54,7 +55,7 @@
 compilerClass
     "Answer a class suitable for compiling a source code in 'my' language"
 
-    ^ Smalltalk::Compiler
+    ^ Smalltalk at:#Compiler
 
     "Modified: / 21-08-2009 / 13:02:27 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
@@ -63,7 +64,7 @@
     "Answer a class suitable for compiling a source code with breakpoints
      in 'my' language"
 
-    ^ Smalltalk::ByteCodeCompilerWithBreakpointSupport
+    ^ ByteCodeCompilerWithBreakpointSupport
 
     "Created: / 22-07-2013 / 15:46:12 / cg"
 !
@@ -74,7 +75,7 @@
      nil, which means that there is no explainer for given language."
 
     "return nil by default"
-    ^ Smalltalk::Explainer
+    ^ Explainer
 
     "Created: / 21-08-2009 / 08:49:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
@@ -83,13 +84,13 @@
     "Answer a class suitable for prettyPrinting (indenting) code in 'my' language.
      It is ok to return nil, which means that the browser will not be able to prettyprint."
 
-    ^ Smalltalk::Parser
+    ^ Parser
 !
 
 parserClass
     "Answer a class suitable for parsing a source codein 'my' language"
 
-    ^ Smalltalk::Parser
+    ^ Parser
 
     "Modified: / 21-08-2009 / 13:02:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
@@ -115,7 +116,7 @@
      this can be redefined in special classes, to highlight classes with
      Lisp, Prolog, ASN1, Basic :-) or whatever syntax."
 
-    ^ Smalltalk::SyntaxHighlighter
+    ^ SyntaxHighlighter
 ! !
 
 !SmalltalkLanguage methodsFor:'mimicry'!
@@ -197,14 +198,14 @@
 !SmalltalkLanguage class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SmalltalkLanguage.st,v 1.25 2015-02-08 03:40:46 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/SmalltalkLanguage.st,v 1.25 2015-02-08 03:40:46 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
-    ^'$Id: SmalltalkLanguage.st,v 1.25 2015-02-08 03:40:46 cg Exp $'
+    ^'$Id$'
 ! !
 
--- a/UninterpretedBytes.st	Thu Oct 29 06:54:02 2015 +0100
+++ b/UninterpretedBytes.st	Fri Oct 30 06:59:59 2015 +0100
@@ -1704,6 +1704,115 @@
     "Modified: / 9.5.1998 / 01:13:34 / cg"
 !
 
+nativeIntAt:index
+    "return the 4- or 8-bytes (depending on the native integer/pointer size) starting at index as a signed Integer.
+     The index is a smalltalk index (i.e. 1-based).
+     The value is retrieved in the machines natural byte order,
+     therefore, this should only be used for byte-data which is
+     only used inside this machine."
+
+    |w|
+
+%{
+    /*
+     * handle the most common cases fast ...
+     */
+    if (__isSmallInteger(index)) {
+        unsigned char *cp;
+        INT sz;
+
+        __fetchBytePointerAndSize__(self, &cp, &sz);
+        if (cp) {
+            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;
+
+            if ((idx+(sizeof(INT)-1)) < sz) {
+                cp += idx;
+#if defined(__i386__)
+                /*
+                 * aligned or not, we dont care (i386 can do both)
+                 */
+                {
+                    INT iVal = ((INT *)cp)[0];
+
+                    RETURN (__MKINT(iVal));
+                }
+#else
+                /*
+                 * aligned
+                 */
+                if (((INT)cp & (sizeof(INT)-1)) == 0) {
+                    INT iVal = ((INT *)cp)[0];
+
+                    RETURN (__MKINT(iVal));
+                }
+#endif
+            }
+        }
+    }
+%}.
+
+    ^ self primitiveFailed.
+
+    "
+     |b|
+     b := ByteArray new:8.
+     b nativeIntAt:1 put:SmallInteger maxVal.
+     b nativeIntAt:1
+    "
+!
+
+nativeIntAt:index put:value
+    "set the 4- or 8-bytes (depending on INT-/pointer size) starting at index from the signed Integer value.
+     The index is a smalltalk index (i.e. 1-based).
+     The value is stored in the machines natural byte order."
+
+    |v|
+
+%{
+    /*
+     * handle the most common cases fast ...
+     */
+    if (__isSmallInteger(index)) {
+        unsigned char *cp;
+        INT sz;
+
+        __fetchBytePointerAndSize__(self, &cp, &sz);
+        if (cp) {
+            unsigned INT idx = ((unsigned INT)__intVal(index)) - 1;
+
+            if ((idx+(sizeof(INT)-1)) < sz) {
+                cp += idx;
+                /*
+                 * aligned
+                 */
+                if (((INT)cp & (sizeof(INT)-1)) == 0) {
+                    INT __v;
+
+                    if (__isSmallInteger(value)) {
+                        // how about a range check?
+                        ((INT *)cp)[0] = (INT)(__intVal(value));
+                        RETURN (value);
+                    }
+                    if ((__v = __signedLongIntVal(value)) != 0) {
+                        // how about a range check?
+                        ((INT *)cp)[0] = (INT)(__v);
+                        RETURN (value);
+                    }
+                }
+            }
+        }
+    }
+%}.
+    ^ self primitiveFailed.
+
+    "
+     |b|
+     b := ByteArray new:8.
+     b nativeIntAt:1 put:SmallInteger maxVal.
+     (b nativeIntAt:1) 
+    "
+!
+
 pointerAt:index
     "get a pointer starting at index as ExternalAddress.
      The index is a smalltalk index (i.e. 1-based).