src/JavaNativeMemory.st
branchjk_new_structure
changeset 1524 b74a62ba8cc1
parent 1520 94915020b92b
child 1525 4463b11f29f4
--- a/src/JavaNativeMemory.st	Tue Jul 10 09:24:58 2012 +0000
+++ b/src/JavaNativeMemory.st	Wed Jul 11 09:40:08 2012 +0000
@@ -21,17 +21,24 @@
 "{ Package: 'stx:libjava' }"
 
 Object subclass:#JavaNativeMemory
-	instanceVariableNames:'chunk free allocated'
-	classVariableNames:''
+	instanceVariableNames:'chunks defaultMallocatedMemoryChunkSize'
+	classVariableNames:'DefaultMallocatedMemoryChunkSize'
 	poolDictionaries:''
 	category:'Languages-Java-Support'
 !
 
-Link subclass:#ListEntry
+Object subclass:#MallocatedMemoryChunk
+	instanceVariableNames:'base size data flist alist'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:JavaNativeMemory
+!
+
+Link subclass:#FreeListEntry
 	instanceVariableNames:'start stop'
 	classVariableNames:''
 	poolDictionaries:''
-	privateIn:JavaNativeMemory
+	privateIn:JavaNativeMemory::MallocatedMemoryChunk
 !
 
 !JavaNativeMemory class methodsFor:'documentation'!
@@ -60,6 +67,18 @@
 "
 ! !
 
+!JavaNativeMemory class methodsFor:'initialization'!
+
+initialize
+    "Invoked at system start or when the class is dynamically loaded."
+
+    "/ please change as required (and remove this comment)
+
+    DefaultMallocatedMemoryChunkSize := 1024 * 1024"1MB"
+
+    "Modified: / 10-07-2012 / 18:54:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !JavaNativeMemory class methodsFor:'instance creation'!
 
 new
@@ -70,34 +89,219 @@
 
 !JavaNativeMemory methodsFor:'accessing'!
 
-byteAt:address
+defaultMallocatedMemoryChunkSize
+    ^ defaultMallocatedMemoryChunkSize
+!
+
+defaultMallocatedMemoryChunkSize:something
+    defaultMallocatedMemoryChunkSize := something.
+! !
+
+!JavaNativeMemory methodsFor:'accessing-tests'!
+
+chunks
+    "For tests only!!!!!!"
+    ^chunks
+
+    "Created: / 11-07-2012 / 09:13:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory methodsFor:'allocation'!
+
+free: address
+    (self chunkFor: address) free: address
+
+    "Created: / 10-07-2012 / 18:57:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    ^chunk at: address
+malloc: size
+    | address chunk |
+
+    chunks do:[:each|
+        address := each malloc: size.
+        address notNil ifTrue:[ ^ address ]
+    ].
+    size > defaultMallocatedMemoryChunkSize ifTrue:[
+        self breakPoint: #jv.
+        chunk := MallocatedMemoryChunk new: size.
+    ] ifFalse:[
+        chunk := MallocatedMemoryChunk new: defaultMallocatedMemoryChunkSize
+    ].
+    chunk base: (chunks isEmpty ifTrue:[0] ifFalse:[chunks last base + chunks last size]).
+    chunks add: chunk.
+    address := chunk malloc: size.
+    ^address
+
+    "Created: / 10-07-2012 / 18:45:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory methodsFor:'byte access'!
+
+byteAt:address
+    ^(self chunkFor: address) byteAt: address
 
     "Created: / 09-12-2010 / 17:32:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-longAt:address put:value 
-    chunk longLongAt: address put: value
+byteAt:address put: value
+    (self chunkFor: address) byteAt: address put: value
+
+    "Created: / 10-07-2012 / 19:01:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+doubleAt:address
+    ^(self chunkFor: address) doubleAt: address
+
+    "Created: / 11-07-2012 / 10:13:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+doubleAt:address put: value
+    (self chunkFor: address) doubleAt: address put: value
+
+    "Created: / 11-07-2012 / 10:13:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+longAt:address
+    ^(self chunkFor: address) longAt: address
+
+    "Created: / 10-07-2012 / 19:01:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+longAt:address put: value
+    (self chunkFor: address) longAt: address put: value
 
     "Created: / 09-12-2010 / 17:32:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory methodsFor:'byte transfer'!
+
+bcopy: dstAddr length: length from: bytearray offset: offset
+    (self chunkFor: dstAddr) bcopy: dstAddr length: length from: bytearray offset: offset
+
+    "Created: / 11-07-2012 / 10:34:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+bcopy: srcAddr length: length into: bytearray offset: offset
+    (self chunkFor: srcAddr) bcopy: srcAddr length: length into: bytearray offset: offset
+
+    "Created: / 11-07-2012 / 10:32:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+bcopy: srcAddr to: dstAddr length: length
+    "The bcopy... method copies n bytes from src to dest.  The result is correct, 
+      even when both areas overlap."
+
+    | srcChunk dstChunk |
+    srcChunk := self chunkFor: srcAddr.
+    dstChunk := self chunkFor: dstAddr.
+
+    srcChunk == dstChunk ifTrue:[
+        "/Easy, same chunk
+        srcChunk bcopy: srcAddr to: dstAddr length: length.
+        ^self.
+    ].
+    "/ Worse, different chunks...
+    self breakPoint: #jv.
+    self shouldImplement.
+
+    "Created: / 11-07-2012 / 10:21:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-memory
-    ^chunk
+memset: s value: c length: n
+    "The memset() function fills the first n bytes of the memory area pointed to by s with 
+     the constant byte c"
+
+     (self chunkFor: s) memset: s value: c length: n
+
+    "Created: / 11-07-2012 / 10:27:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory methodsFor:'error reporting'!
+
+errorSegmentationViolation: message
+    self error: message
+
+    "Created: / 10-07-2012 / 18:59:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory methodsFor:'initialization'!
 
-    "Created: / 09-07-2012 / 12:44:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+initialize
+    "Invoked when a new instance is created."
+
+    "/ please change as required (and remove this comment)
+    chunks := OrderedCollection new.
+    defaultMallocatedMemoryChunkSize := DefaultMallocatedMemoryChunkSize
+    "/ super initialize.   -- commented since inherited method does nothing
+
+    "Modified: / 11-07-2012 / 09:11:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory methodsFor:'private'!
+
+chunkFor: address
+    ^chunks 
+        detect:[:chunk|address between: chunk base + 1 and: chunk base + chunk size]
+        ifNone:[ self errorSegmentationViolation: 'No chunk for address ', address printString ].
+
+    "Created: / 10-07-2012 / 18:57:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!JavaNativeMemory methodsFor:'allocation/deallocation'!
+!JavaNativeMemory::MallocatedMemoryChunk class methodsFor:'instance creation'!
+
+new
+    "return an initialized instance"
+
+    ^ self new: 1024 * 1024"1MB"
+
+    "Modified: / 10-07-2012 / 18:36:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+new: size
+    "return an initialized instance"
+
+    ^ self basicNew initializeWithSize: size
+
+    "Created: / 10-07-2012 / 18:36:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'accessing'!
+
+base
+    ^ base
+!
 
-free: address
+base:something
+    base := something.
+!
+
+size
+    ^ size
+!
+
+size:something
+    size := something.
+! !
+
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'accessing-tests'!
+
+data
+    "For tests only!!!!!!"
+    ^ data
+
+    "Modified (comment): / 11-07-2012 / 10:01:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'allocation'!
+
+free: gaddress
 
     "Frees the memory"
 
-    | aentry aentryPrev |
+    | address aentry aentryPrev |
 
-    aentry := allocated.
+    address := gaddress - base.
+    aentry := alist.
     aentryPrev := nil.
     [ aentry notNil and:[aentry start ~~ address ] ] whileTrue:[
         aentryPrev := aentry.
@@ -112,85 +316,173 @@
     aentryPrev notNil ifTrue:[
         aentryPrev next: aentry next.
     ] ifFalse:[
-        allocated := aentry next.
+        alist := aentry next.
     ].
 
-    free := self insert: aentry into: free join: true.
+    flist := self insert: aentry into: flist join: true.
 
     "/Insert free entry
 
     "Created: / 07-12-2010 / 23:33:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-malloc: size
+malloc: sz
 
     "Allocate new chunk of memory, size bytes long"
 
     | fentry aentry |
-    fentry := free.
-    [ fentry notNil and:[fentry size < size] ] whileTrue:[
+    fentry := flist.
+    [ fentry notNil and:[fentry size < sz] ] whileTrue:[
         fentry := fentry next.
     ].
     fentry isNil ifTrue:[
-        self errorOutOfMemory: 'Not enounh memory or too fragmented'.
-        ^self.
+        ^nil "Not enough memory in this chunk or too fragmented"
     ].
 
     "/ create allocation entry
-    aentry := ListEntry new 
+    aentry := FreeListEntry new 
                 start: fentry start;
-                stop:  fentry start + size - 1.
+                stop:  fentry start + sz - 1.
 
     "/Update free entry
-    fentry start: fentry start + size.
-
-
-
+    (fentry start + sz) > size ifTrue:[
+        "No more free memory in this chunk"
+        flist := nil
+    ] ifFalse:[
+        fentry start: fentry start + sz.
+    ].
+    alist := self insert: aentry into: alist join: false.
 
-
-    allocated := self insert: aentry into: allocated join: false.
-
-    ^aentry start.
+    ^aentry start + base
 
     "Created: / 07-12-2010 / 23:25:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!JavaNativeMemory methodsFor:'error reporting'!
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'byte access'!
+
+byteAt:address
+    ^data at: address - base
+
+    "Created: / 09-12-2010 / 17:32:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+byteAt:address put: value
+    data at: address - base put: value
+
+    "Created: / 10-07-2012 / 19:01:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+doubleAt:address 
+    ^data doubleAt: address - base
+
+    "Created: / 11-07-2012 / 10:12:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+doubleAt:address put: value
+    data doubleAt: address - base put: value
 
-errorAccessingUnallocatedMemory:arg
-    self shouldImplement
+    "Created: / 11-07-2012 / 10:12:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+longAt:address
+    ^data longAt: address - base
+
+    "Created: / 10-07-2012 / 19:01:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    "Created: / 07-12-2010 / 23:40:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+longAt:address put: value
+    data longAt: address - base put: value
+
+    "Created: / 09-12-2010 / 17:32:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'byte transfer'!
+
+bcopy: dstAddr length: length from: bytearray offset: offset
+
+    data replaceBytesFrom: dstAddr - base to: dstAddr - base + length - 1 with: bytearray startingAt: offset + 1
+
+    "Created: / 11-07-2012 / 10:36:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-errorFreeingUnallocatedMemory:arg
-    self shouldImplement
+bcopy: srcAddr length: length into: bytearray offset: offset
+
+    bytearray replaceBytesFrom: offset + 1 to: offset + length with: data startingAt: srcAddr - base
+
+    "Created: / 11-07-2012 / 10:33:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+bcopy: srcAddr to: dstAddr length: length
+    "The bcopy... method copies n bytes from src to dest.  The result is correct, 
+      even when both areas overlap."
 
-    "Created: / 09-07-2012 / 10:57:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    srcAddr == dstAddr ifTrue:[ ^ self ].
+    srcAddr < dstAddr ifTrue:[
+        (srcAddr + length - 1) < dstAddr ifTrue:[
+            "/No overlap"
+            data replaceBytesFrom: dstAddr - base to: dstAddr - base + length - 1
+                            with: data
+                      startingAt: srcAddr - base.
+        ] ifFalse:[
+            "/Overlap
+            self breakPoint: #jv.
+            self shouldImplement
+        ].
+    ] ifFalse:[
+        data replaceBytesFrom: dstAddr - base to: dstAddr - base + length - 1
+                        with: data
+                  startingAt: srcAddr - base.
+    ]
+
+    "Created: / 11-07-2012 / 10:22:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+memset: s value: c length: n
+    "The memset() function fills the first n bytes of the memory area pointed to by s with 
+     the constant byte c"
+
+     data from: s - base to: s - base + n - 1  put: c
+
+    "Created: / 11-07-2012 / 10:27:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'error reporting'!
+
+errorFreeingUnallocatedMemory: message
+    self error: message
+
+    "Created: / 10-07-2012 / 18:40:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 errorOutOfMemory: message
-    self shouldImplement
+    JavaVM throwOutOfMemoryError: message
+
+    "Created: / 10-07-2012 / 18:38:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-    "Created: / 09-07-2012 / 10:52:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+errorSegmentationViolation: message
+    self error: message
+
+    "Created: / 10-07-2012 / 19:00:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!JavaNativeMemory methodsFor:'initialization'!
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'initialization'!
 
-initialize
+initializeWithSize: sz
     "Invoked when a new instance is created."
 
-    chunk:= ByteArray new: 1024 * 1024.
-    free := ListEntry new start: 1; stop: chunk size.
-    allocated := nil.
+    size := sz.
+    data:= ByteArray new: sz.
+    flist := FreeListEntry new start: 1; stop: sz.
+    alist := nil.
 
 
     "/ super initialize.   -- commented since inherited method does nothing
 
-    "Modified: / 09-07-2012 / 11:54:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 10-07-2012 / 18:37:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!JavaNativeMemory methodsFor:'private'!
+!JavaNativeMemory::MallocatedMemoryChunk methodsFor:'private'!
 
 insert: entry into: list join: join
     "Inserts an entry into given list. Returns new
@@ -216,7 +508,7 @@
     "Created: / 09-07-2012 / 11:29:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!JavaNativeMemory::ListEntry methodsFor:'accessing'!
+!JavaNativeMemory::MallocatedMemoryChunk::FreeListEntry methodsFor:'accessing'!
 
 next
     ^nextLink
@@ -256,7 +548,7 @@
     stop := something.
 ! !
 
-!JavaNativeMemory::ListEntry methodsFor:'printing & storing'!
+!JavaNativeMemory::MallocatedMemoryChunk::FreeListEntry methodsFor:'printing & storing'!
 
 printOn:aStream
     "append a printed representation if the receiver to the argument, aStream"
@@ -271,7 +563,7 @@
     "Modified: / 09-07-2012 / 11:54:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!JavaNativeMemory::ListEntry methodsFor:'utilities'!
+!JavaNativeMemory::MallocatedMemoryChunk::FreeListEntry methodsFor:'utilities'!
 
 next: next join: join
     (join and:[next notNil]) ifTrue:[
@@ -294,3 +586,5 @@
 version_SVN
     ^ '$Id$'
 ! !
+
+JavaNativeMemory initialize!