[PATCH] first attempts at loading Seaside into GNU Smalltalk

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
6 messages Options
Reply | Threaded
Open this post in threaded view
|

[PATCH] first attempts at loading Seaside into GNU Smalltalk

Paolo Bonzini
I tried to load seaside into GST.  This was meant more as a stress test
than a porting attempt.  Indeed I had a few problems (mostly my bugs,
such as having more than 64 items in Undeclared and causing it to grow).
   It also reproduced the 2.95b x86-64 failures on my machine too, so I
fixed them (they were introduced by the copy-on-write patches from last
December).

The converter did not support extensions of undefined classes (bad) and
subclasses of undefined classes (not necessarily bad, e.g. subclassing
TestCase); now it does.

There are a few undeclared variables in the Seaside copy I'm using, and
that's bad for Seaside. :-)  For instance, I removed WAOnceTest because
there is no WAOnce in the distribution I was using.  So the port may fix
a few bogosities in Seaside too. :-)

Other things I changed (but might be fixed in newer versions):

1) symbols like #'?xml', #'!doctype', #'accept-charset', #'http-equiv'
have to be expressed with quotes, otherwise RBParser does not like them

2) in WATableReport there is an instance of "aNumber-1" that I had to
change to "aNumber - 1"

3) DateAndTime is called DateTime in GNU Smalltalk, and MessageSend is
called DirectedMessage.

4) I disabled a few classes, WAKom (there is no Comanche), parts of
WABrowser (there is no Browser), WAVersionUploader (there is no
Monticello), WAScreenshot, as well as references to ImageSegment.  I
also removed Exception>>#reactivateHandler.  Some of these should be
handled by the Exporter, IIUC.  Same for Continuation which is in GST's
basic image.

5) interesting one: WAInputDialog>>#renderContentOn: refers to a
non-existing variable "message".

I had to add to the basic image a few methods such as
#removeAllSuchThat: and #allButFirst, which is good.

However, there is a bigger problem, that is the infamous zero/one
argument clash on #ifNotNil:.  I can modify my compiler to automatically
convert a zero-argument block given to #ifNotNil: and make it
one-argument, but I'd really hate to do that.  Better, I can augment the
converter with the possibility to apply refactoring browser rewriting
rules, which would fix item 3 above.  I wonder though if Avi's exporter
could do the same instead?

(Or could Squeak fix this once and for all???...)

Paolo

2007-07-12  Paolo Bonzini  <[hidden email]>

        * Exporter.st: Do not call #environment when not filing out the
        complete class.  Indentation fixes.
        * STLoader.st: Create an UndefinedClass object if there is no
        namespace and the class is not found in the current namespace.
        * STLoaderObjs.st: Move methods variable up to PseudoBehavior.
        Make metaclass of ProxyClass a ProxyClass itself.  Add
        UndefinedClass and UndefinedMetaclass.  Turn subclasses of
        PseudoBehavior into an OrderedCollection.

        * scripts/Convert.st: Give error or warning on undefined classes.

* looking for [hidden email]--2004b/smalltalk--devo--2.2--patch-453 to compare with
* comparing to [hidden email]--2004b/smalltalk--devo--2.2--patch-453
M  packages/stinst/parser/Exporter.st
M  scripts/Convert.st
M  packages/stinst/parser/STLoader.st
M  packages/stinst/parser/STLoaderObjs.st

* modified files

--- orig/packages/stinst/parser/Exporter.st
+++ mod/packages/stinst/parser/Exporter.st
@@ -135,22 +135,21 @@ Object subclass: FileOutExporter [
     ]
     
     fileOutDeclaration: aBlock [
-        outClass environment = self defaultNamespace
-        ifTrue: [ ^self fileOutClassBody: aBlock ].
+        (completeFileOut and: [ outClass environment ~= self defaultNamespace ])
+    ifFalse: [ ^self fileOutClassBody: aBlock ].
         
         outStream nextPutAll: 'Namespace current: ';
                   store: outClass environment;
                   nextPutAll: ' ['; nl; nl.
                   
-    self fileOutClassBody: aBlock.
-
+ self fileOutClassBody: aBlock.
         outStream nextPut: $]; nl; nl.
     ]
     
     fileOutClassBody: aBlock [
-    completeFileOut
-        ifTrue: [ self fileOutClassDeclaration: aBlock ]
-        ifFalse: [ self fileOutClassExtension: aBlock ].
+ completeFileOut
+    ifTrue: [ self fileOutClassDeclaration: aBlock ]
+    ifFalse: [ self fileOutClassExtension: aBlock ].
     ]
     
     fileOutClassExtension: aBlock [


--- orig/packages/stinst/parser/STLoader.st
+++ mod/packages/stinst/parser/STLoader.st
@@ -323,6 +323,12 @@ resolveName: node
     | current selectors |
     node isVariable
  ifTrue: [
+    (node name includes: $.) ifFalse: [
+ ^self currentNamespace at: node name asSymbol ifAbsent: [
+    defaultNamespace
+ at: node name asSymbol
+ put: (UndefinedClass name: node name asSymbol for: self) ]].
+
     ^(node name substrings: $.)
  inject: self currentNamespace
  into: [ :current :each | current at: each asSymbol ]


--- orig/packages/stinst/parser/STLoaderObjs.st
+++ mod/packages/stinst/parser/STLoaderObjs.st
@@ -32,7 +32,7 @@ STInST addSubspace: #STClassLoaderObject
 Namespace current: STClassLoaderObjects!
 
 Object subclass: #PseudoBehavior
-        instanceVariableNames: 'subclasses loader'
+        instanceVariableNames: 'subclasses methods loader'
         classVariableNames: ''
         poolDictionaries: ''
         category: 'System-Compiler'!
@@ -115,8 +115,30 @@ secondary: aDictionary
 ! !
 
 
+PseudoBehavior subclass: #UndefinedClass
+        instanceVariableNames: 'name class'
+        classVariableNames: ''
+        poolDictionaries: ''
+        category: 'System-Compiler'!
+
+UndefinedClass comment:
+'This class represent a proxy for a class that is found by an
+STClassLoader while parsing source code, but is not
+the system.  It is possible to handle subclasses and extension methods
+of such classes.'!
+
+PseudoBehavior subclass: #UndefinedMetaclass
+        instanceVariableNames: 'instanceClass'
+        classVariableNames: ''
+        poolDictionaries: ''
+        category: 'System-Compiler'!
+
+UndefinedMetaclass comment:
+'This class represent a proxy for the metaclass of a class that is found
+by an STClassLoader while parsing source code, but is not the system.'!
+
 PseudoBehavior subclass: #ProxyClass
-        instanceVariableNames: 'proxy methods'
+        instanceVariableNames: 'proxy otherSide'
         classVariableNames: ''
         poolDictionaries: ''
         category: 'System-Compiler'!
@@ -137,7 +159,7 @@ ProxyClass comment:
 'This class represent a proxy for the nil fake superclass.'!
 
 PseudoBehavior subclass: #LoadedBehavior
-        instanceVariableNames: 'instVars superclass methods comment '
+        instanceVariableNames: 'instVars superclass comment '
         classVariableNames: ''
         poolDictionaries: ''
         category: 'System-Compiler'!
@@ -153,7 +175,7 @@ LoadedBehavior subclass: #LoadedClass
         poolDictionaries: ''
         category: 'System-Compiler'!
 
-LoadedBehavior comment:
+LoadedClass comment:
 'This class represent a proxy for a class whose source code is parsed
 by an STClassLoader.'!
 
@@ -163,7 +185,7 @@ LoadedBehavior subclass: #LoadedMetaclas
         poolDictionaries: ''
         category: 'System-Compiler'!
 
-LoadedBehavior comment:
+LoadedMetaclass comment:
 'This class represent a proxy for a metaclass whose source code is parsed
 by an STClassLoader.'!
 
@@ -207,6 +229,12 @@ ProxyNamespace comment:
 'This class represent a proxy for a preexisting namespace that is
 referenced by the source code that an STClassLoader is parsing.'!
 
+!PseudoBehavior class methodsFor: 'initializing'!
+
+for: aSTClassLoader
+    ^self new initialize: aSTClassLoader
+! !
+
 !PseudoBehavior methodsFor: 'creating classes'!
 
 variableByteSubclass: s instanceVariableNames: ivn classVariableNames: cvn
@@ -452,6 +480,13 @@ nameIn: aNamespace
 ! !
 
 
+!PseudoBehavior methodsFor: 'testing'!
+
+isDefined
+    ^true
+!
+
+
 !PseudoBehavior methodsFor: 'abstract'!
 
 asClass
@@ -503,7 +538,12 @@ superclass
 !
 
 methodDictionary
-    self subclassResponsibility
+    methods isNil ifTrue: [ methods := LookupTable new ].
+    ^methods
+!
+
+methodDictionary: aDictionary
+    methods := aDictionary
 ! !
 
 !PseudoBehavior methodsFor: 'printing'!
@@ -523,90 +563,84 @@ storeOn: aStream
 !PseudoBehavior methodsFor: 'initializing'!
 
 initialize: aSTClassLoader
-    self setSubclasses: OrderedCollection new.
+    subclasses := OrderedCollection new.
     loader := aSTClassLoader
-!
-
-setSubclasses: classes
-    subclasses := classes
 ! !
 
 !ProxyClass class methodsFor: 'creating classes'!
 
 on: aClass for: aSTClassLoader
-    ^self new setProxy: aClass for: aSTClassLoader
+    ^(self for: aSTClassLoader) setProxy: aClass
 ! !
 
 !ProxyClass methodsFor: 'delegation'!
 
 = anObject
-    ^self asClass == anObject
+    ^proxy == anObject
  or: [ anObject class == self class
- and: [ self asClass == anObject asClass ]
- ]
+ and: [ proxy == anObject proxy ] ]
 !
 
 hash
     ^proxy hash
 !
 
+proxy
+   ^proxy
+!
+
 asClass
-    ^proxy
+    proxy isClass ifTrue: [ ^self ].
+    otherSide isNil
+ ifTrue: [ otherSide := ProxyClass on: proxy instanceClass for: self loader ].
+    ^otherSide
 !
 
 asMetaclass
-    ^self asClass asMetaclass
+    proxy isMetaclass ifTrue: [ ^self ].
+    otherSide isNil
+ ifTrue: [ otherSide := ProxyClass on: proxy class for: self loader ].
+    ^otherSide
 !
 
 isClass
-    ^true
+    ^proxy isClass
 !
 
-category
-    ^self asClass category
+isMetaclass
+    ^proxy isClass
 !
 
-category: aString
-    ^self asClass category: aString
+category
+    ^proxy category
 !
 
 comment
-    ^self asClass comment
-!
-
-comment: aString
-    ^self asClass comment: aString
+    ^proxy comment
 !
 
 environment
-    ^self asClass environment
+    ^proxy environment
 !
 
 kindOfSubclass
-    ^self asClass kindOfSubclass
+    ^proxy kindOfSubclass
 !
 
 superclass
-    ^self asClass superclass
-!
-
-methodDictionary
-    methods isNil ifTrue: [
-         methods := OverlayDictionary on: self asClass methodDictionary ].
-    ^methods
+    ^proxy superclass
 !
 
 doesNotUnderstand: aMessage
-    ^self asClass perform: aMessage
+    ^proxy perform: aMessage
 ! !
 
 
 !ProxyClass methodsFor: 'initializing'!
 
-setProxy: aClass for: aSTClassLoader
-    self initialize: aSTClassLoader.
+setProxy: aClass
     proxy := aClass.
-    self setSubclasses: OrderedCollection new.
+    self methodDictionary: (OverlayDictionary on: proxy methodDictionary)
 ! !
 
 !ProxyNilClass methodsFor: 'accessing'!
@@ -615,6 +649,101 @@ nameIn: aNamespace
     ^'nil'
 ! !
 
+!UndefinedClass class methodsFor: 'creating'!
+
+name: aSymbol for: aLoader
+    ^(self for: aLoader) setName: aSymbol
+! !
+
+!UndefinedClass methodsFor: 'testing'!
+
+isDefined
+    ^false
+! !
+
+!UndefinedClass methodsFor: 'accessing'!
+
+asMetaclass
+    ^class!
+
+asClass
+    ^self!
+
+name
+    ^name!
+
+nameIn: aNamespace
+    ^name asString!
+
+setName: aSymbol
+    name := aSymbol.
+    class := UndefinedMetaclass for: self.
+! !
+
+!UndefinedClass methodsFor: 'printing'!
+
+printOn: aStream
+    aStream nextPutAll: self name!
+! !
+
+!UndefinedMetaclass class methodsFor: 'creating'!
+
+for: aClass
+    ^(super for: aClass loader)
+ initializeFor: aClass! !
+
+!UndefinedMetaclass methodsFor: 'printing'!
+
+printOn: aStream
+    aStream
+ nextPutAll: self asClass name;
+ nextPutAll: ' class'!
+! !
+
+!UndefinedMetaclass methodsFor: 'initializing'!
+
+initializeFor: aClass
+    super initialize: aClass loader.
+    instanceClass := aClass! !
+
+!UndefinedMetaclass methodsFor: 'accessing'!
+
+isMetaclass
+    ^true
+!
+
+asClass
+    ^instanceClass
+!
+
+asMetaclass
+    ^self
+!
+
+shape
+    ^nil
+! !
+
+!UndefinedMetaclass methodsFor: 'testing'!
+
+isDefined
+    ^false
+! !
+
+!UndefinedMetaclass methodsFor: 'delegation'!
+
+name
+    ^self asClass name
+! !
+
+
+
+!LoadedMetaclass class methodsFor: 'creating'!
+
+for: aClass
+    ^(super for: aClass loader)
+ initializeFor: aClass! !
+
 !LoadedBehavior methodsFor: 'accessing'!
 
 instVarNames
@@ -629,11 +758,6 @@ instanceVariableNames: ivn
 
 superclass
     ^superclass
-!
-
-methodDictionary
-    methods isNil ifTrue: [ methods := LookupTable new ].
-    ^methods
 ! !
 
 !LoadedMetaclass methodsFor: 'printing'!
@@ -702,9 +826,15 @@ sharedPools
 
 
 
-!LoadedMetaclass methodsFor: 'initializing'!
+!LoadedMetaclass class methodsFor: 'initializing'!
 
 for: aClass
+    ^(super for: aClass loader)
+ initializeFor: aClass! !
+
+!LoadedMetaclass methodsFor: 'initializing'!
+
+initializeFor: aClass
     super initialize: aClass loader.
     instanceClass := aClass.
     instVars := Array new.
@@ -716,9 +846,9 @@ for: aClass
 
 superclass: sup name: s instanceVariableNames: ivn classVariableNames: cvn
  poolDictionaries: pd category: c shape: sh loader: loader
-    ^self new
+    ^(self for: loader)
  superclass: sup name: s instanceVariableNames: ivn classVariableNames: cvn
- poolDictionaries: pd category: c shape: sh loader: loader
+ poolDictionaries: pd category: c shape: sh
 ! !
 
 !LoadedClass methodsFor: 'accessing'!
@@ -810,14 +940,13 @@ import: aNamespace
 !LoadedClass methodsFor: 'initializing'!
 
 superclass: sup name: s instanceVariableNames: ivn classVariableNames: cvn
- poolDictionaries: pd category: c shape: sh loader: loader
-    self initialize: loader.
+ poolDictionaries: pd category: c shape: sh
     superclass := sup.
     name := s.
     category := c.
     shape := sh.
     environment := loader currentNamespace.
-    class := LoadedMetaclass new for: self.
+    class := LoadedMetaclass for: self.
     instVars := ivn subStrings.
     classVars := cvn subStrings.
     sharedPools := pd subStrings.


--- orig/scripts/Convert.st
+++ mod/scripts/Convert.st
@@ -61,14 +61,20 @@ EmittedEntity subclass: EmittedClass [
     by using a FormattingExporter.'>
     
     EmittedClass class >> forClass: aClass [        
-        ^super new initializeWithClass: aClass extension: true
+ aClass isDefined ifFalse: [ aClass printNl. self halt ].
+        ^super new initializeWithClass: aClass complete: true
     ]
     
     EmittedClass class >> forExtension: aClass [
-        ^super new initializeWithClass: aClass extension: false
+ aClass isDefined ifFalse: [
+    stderr
+ nextPutAll: 'warning: extensions for undefined class ';
+ print: aClass;
+ nl ].
+        ^super new initializeWithClass: aClass complete: false
     ]
     
-    initializeWithClass: aClass extension: aBoolean [
+    initializeWithClass: aClass complete: aBoolean [
         class := aClass.
         methodsToEmit := STInST.OrderedSet new.
  classMethodsToEmit := STInST.OrderedSet new.
@@ -266,7 +272,8 @@ STInST.STClassLoader subclass: SyntaxCon
  super doAddNamespace: receiver selector: selector arguments: argumentNodes.
 
         ns := (self resolveNamespace: receiver) at: argumentNodes first value.
- createdNamespaces add: ns
+ createdNamespaces add: ns.
+ ^false
     ]
 
     doEmitStuff [

2007-07-12  Paolo Bonzini  <[hidden email]>

        * libgst/oop.c: When compacting, do not discard grey pages from
        the loaded space.  Add _gst_print_grey_list.
        * libgst/oop.h: Add fields to delimit loaded space to
        struct memory_space.
        * libgst/save.c: Fill them in.

--- orig/libgst/oop.c
+++ mod/libgst/oop.c
@@ -998,7 +998,7 @@ void
 _gst_compact (size_t new_heap_limit)
 {
   OOP oop;
-  grey_area_node *node, *next;
+  grey_area_node *node, **next, *last;
   heap_data *new_heap = init_old_space (
     new_heap_limit ? new_heap_limit : _gst_mem.old->heap_limit);
 
@@ -1016,15 +1016,26 @@ _gst_compact (size_t new_heap_limit)
       update_stats (&stats.timeOfLastCompaction, NULL, NULL);
     }
 
-  /* Discard all the grey pages.  */
-  for (node = _gst_mem.grey_pages.head; node; node = next)
-    {
-      next = node->next;
-      xfree (node);
-    }
-  _gst_mem.grey_pages.head = _gst_mem.grey_pages.tail = NULL;
-  _gst_mem.rememberedTableEntries = 0;
+  /* Leave only pages from the loaded image in the grey table.  */
+  for (last = NULL, next = &_gst_mem.grey_pages.head; (node = *next); )
+    if (node->base >= (OOP *)_gst_mem.loaded_base
+        && node->base < _gst_mem.loaded_end)
+      {
+#ifdef MMAN_DEBUG_OUTPUT
+        printf ("  Remembered table entry left for loaded image: %p..%p\n",
+                node->base, node->base+node->n);
+#endif
+        last = node;
+        next = &(node->next);
+      }
+    else
+      {
+        _gst_mem.rememberedTableEntries--;
+        *next = node->next;
+        xfree (node);
+      }
 
+  _gst_mem.grey_pages.tail = last;
   _gst_fixup_object_pointers ();
 
   /* Now do the copying loop which will compact oldspace.  */
@@ -1704,26 +1715,52 @@ copy_oops (void)
 }
 
 void
-scan_grey_pages ()
+_gst_print_grey_list (mst_Boolean check_pointers)
 {
-  grey_area_node *node, **next, *last;
+  grey_area_node *node;
   OOP *pOOP, oop;
   int i, n;
 
-#if defined (MMAN_DEBUG_OUTPUT)
-  printf ("Pages on the grey list: ");
   for (n = 0, node = _gst_mem.grey_pages.head; node; node = node->next, n++)
     {
-      if (n & 3)
-        printf ("%12p ", node->base);
-      else
-        printf ("\n%12p ", node->base);
+      int new_pointers = 0;
+      if (check_pointers)
+        for (new_pointers = 0, pOOP = node->base, i = node->n; i--; pOOP++)
+          {
+            PREFETCH_LOOP (pOOP, PREF_READ | PREF_NTA);
+            oop = *pOOP;
+
+            /* Not all addresses are known to contain valid OOPs! */
+    if (!IS_OOP_ADDR (oop))
+      continue;
+
+            if (!IS_OOP_NEW (oop))
+      continue;
+
+    new_pointers++;
+  }
+
+      printf ("%11p%c ", node->base, new_pointers == 0 ? ' ' : '*');
+      if ((n & 3) == 3)
+ putchar ('\n');
     }
 
   if (_gst_mem.grey_pages.tail)
     printf ("  (tail = %12p)", _gst_mem.grey_pages.tail->base);
 
   printf ("\n");
+}
+
+void
+scan_grey_pages ()
+{
+  grey_area_node *node, **next, *last;
+  OOP *pOOP, oop;
+  int i, n;
+
+#if defined (MMAN_DEBUG_OUTPUT)
+  printf ("Pages on the grey list:\n");
+  _gst_print_grey_list (true);
 #endif
 
   for (last = NULL, next = &_gst_mem.grey_pages.head; (node = *next); )
@@ -1776,19 +1813,8 @@ scan_grey_pages ()
   _gst_mem.grey_pages.tail = last;
 
 #if defined (MMAN_DEBUG_OUTPUT)
-  printf ("Pages left on the grey list: ");
-  for (n = 0, node = _gst_mem.grey_pages.head; node; node = node->next, n++)
-    {
-      if (n & 3)
-        printf ("%12p ", node->base);
-      else
-        printf ("\n%12p ", node->base);
-    }
-
-  if (_gst_mem.grey_pages.tail)
-    printf ("  (tail = %12p)", _gst_mem.grey_pages.tail->base);
-
-  printf ("\n");
+  printf ("Pages left on the grey list:\n");
+  _gst_print_grey_list (false);
 #endif
 }
 


--- orig/libgst/oop.h
+++ mod/libgst/oop.h
@@ -217,6 +217,9 @@ struct memory_space
   /* The active survivor space */
   struct surv_space *active_half;
 
+  /* The beginning and end of the area mmap-ed directly from the image.  */
+  OOP *loaded_base, *loaded_end;
+
   /* The OOP flag corresponding to the active survivor space */
   int active_flag;
 


--- orig/libgst/save.c
+++ mod/libgst/save.c
@@ -149,9 +149,10 @@ static void buffer_write (int imageFd,
   PTR data,
   int numBytes);
 
-/* This function establishes a buffer of size NUMBYTES for reads.  */
-static void buffer_read_init (int imageFd,
-      int numBytes);
+/* This function establishes a buffer of size NUMBYTES for reads.  The
+   base of the buffer is returned if mmap was used.  */
+static char *buffer_read_init (int imageFd,
+       int numBytes);
 
 /* This function frees the buffer used for reads.  */
 static void buffer_read_free (int imageFd);
@@ -191,19 +192,19 @@ static inline void fixup_byte_order (PTR
 
 /* This function loads an OOP table made of OLDSLOTSUSED slots from
    the image file stored in the file whose descriptor is IMAGEFD.
-   The fixup gets handled by load_normal_oops */
+   The fixup gets handled by load_normal_oops.  */
 static void load_oop_table (int imageFd);
 
 /* This function loads OBJECTDATASIZE bytes of object data belonging
    to standard (i.e. non built-in OOPs) and fixes the endianness of
-   the objects, as well as converting to absolute the address of
-   their class.  Endianness conversion is done in two steps: first
+   the objects.  Endianness conversion is done in two steps: first
    the non-byte objects (identified by not having the F_BYTE flag),
    including the class objects which are necessary to fix the byte
    objects, then all the byte-objects which also have instance
    variables).
-   Object data is loaded from the IMAGEFD file descriptor.  */
-static void load_normal_oops (int imageFd);
+   Object data is loaded from the IMAGEFD file descriptor.  If
+   copy-on-write is used, return the end address of the loaded data.  */
+static char *load_normal_oops (int imageFd);
 
 /* This function stores the header, HEADERP, of the image file into the file
    whose descriptor is IMAGEFD.  */
@@ -455,8 +456,9 @@ load_snapshot (int imageFd)
 {
   save_file_header header;
   int prim_table_matches;
+  char *base, *end;
 
-  buffer_read_init (imageFd, READ_BUFFER_SIZE);
+  base = buffer_read_init (imageFd, READ_BUFFER_SIZE);
   if (!load_file_version (imageFd, &header))
     return false;
 
@@ -481,7 +483,12 @@ load_snapshot (int imageFd)
   printf ("After loading OOP table: %lld\n", file_pos + buf_pos);
 #endif /* SNAPSHOT_TRACE */
 
-  load_normal_oops (imageFd);
+  end = load_normal_oops (imageFd);
+  if (end)
+    {
+      _gst_mem.loaded_base = (OOP *) base;
+      _gst_mem.loaded_end = (OOP *) end;
+    }
 
 #ifdef SNAPSHOT_TRACE
   printf ("After loading objects: %lld\n", file_pos + buf_pos);
@@ -555,12 +562,14 @@ load_oop_table (int imageFd)
 }
 
 
-void
+char *
 load_normal_oops (int imageFd)
 {
   OOP oop;
-  gst_object object;
   int i;
+
+  gst_object object = NULL;
+  size_t size = 0;
   mst_Boolean use_copy_on_write
     = buf_used_mmap && ~wrong_endianness && ot_delta == 0;
 
@@ -571,7 +580,6 @@ load_normal_oops (int imageFd)
   PREFETCH_START (_gst_mem.ot, PREF_WRITE | PREF_NTA);
   for (oop = _gst_mem.ot, i = num_used_oops; i--; oop++)
     {
-      size_t size;
       intptr_t flags;
 
       PREFETCH_LOOP (oop, PREF_WRITE | PREF_NTA);
@@ -641,7 +649,12 @@ load_normal_oops (int imageFd)
  }
 
   if (!use_copy_on_write)
-    buffer_read_free (imageFd);
+    {
+      buffer_read_free (imageFd);
+      return NULL;
+    }
+  else
+    return ((char *)object) + size;
 }
 
 
@@ -805,7 +818,7 @@ buffer_fill (int imageFd)
   read (imageFd, buf, buf_size);
 }
 
-void
+char *
 buffer_read_init (int imageFd, int numBytes)
 {
   struct stat st;
@@ -820,7 +833,7 @@ buffer_read_init (int imageFd, int numBy
     {
       buf_size = file_size;
       buf_used_mmap = true;
-      return;
+      return buf;
     }
 #endif /* !WIN32 */
 
@@ -829,6 +842,7 @@ buffer_read_init (int imageFd, int numBy
   buf_size = numBytes;
   buf = xmalloc (buf_size);
   buffer_fill (imageFd);
+  return NULL;
 }
 
 void



_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH] first attempts at loading Seaside into GNU Smalltalk

Lukas Renggli
> I tried to load seaside into GST.  This was meant more as a stress test
> than a porting attempt.  Indeed I had a few problems (mostly my bugs,
> such as having more than 64 items in Undeclared and causing it to grow).

Great, lets get it started ;-)

> Other things I changed (but might be fixed in newer versions):

What version did you use?

> 1) symbols like #'?xml', #'!doctype', #'accept-charset', #'http-equiv'
> have to be expressed with quotes, otherwise RBParser does not like them

I can't find such symbols in my image. That probably has been fixed.

> 2) in WATableReport there is an instance of "aNumber-1" that I had to
> change to "aNumber - 1"

This is fixed in Seaside2.8a1-lr.408.

> 3) DateAndTime is called DateTime in GNU Smalltalk, and MessageSend is
> called DirectedMessage.

It is the easiest if you create a global that points to the right class names.

> 4) I disabled a few classes, WAKom (there is no Comanche), parts of
> WABrowser (there is no Browser), WAVersionUploader (there is no
> Monticello), WAScreenshot, as well as references to ImageSegment.  I
> also removed Exception>>#reactivateHandler.  Some of these should be
> handled by the Exporter, IIUC.  Same for Continuation which is in GST's
> basic image.

Code in the class and method-categories matching *-plattform or
*-squeak' are not supposed to be portable. What kind of exporting
mechanism are you using?

> 5) interesting one: WAInputDialog>>#renderContentOn: refers to a
> non-existing variable "message".

I think this has been fixed, I can't find it in my image. We try to
regularly run SLint on the code and this should catch that kind of
bugs.

> However, there is a bigger problem, that is the infamous zero/one
> argument clash on #ifNotNil:.  I can modify my compiler to automatically
> convert a zero-argument block given to #ifNotNil: and make it
> one-argument, but I'd really hate to do that.  Better, I can augment the
> converter with the possibility to apply refactoring browser rewriting
> rules, which would fix item 3 above.  I wonder though if Avi's exporter
> could do the same instead?

Of course this is almost a religious question. In my opinion the
compiler should accept both variations. Sometimes you want the
argument, sometimes not. VisualWorks also does it like this. The way
Squeak does it is certainly bad.

> (Or could Squeak fix this once and for all???...)

This will probably never happen. Multiple fixes have been posted and
nothing has ever happened: http://bugs.squeak.org/view.php?id=6426.
Also keep in mind that we have to keep portability with Squeak 3.7,
3.8, 3.9 and 3.10.

Lukas

--
Lukas Renggli
http://www.lukas-renggli.ch


_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH] first attempts at loading Seaside into GNU Smalltalk

Paolo Bonzini
In reply to this post by Paolo Bonzini

> What version did you use?

Just the one that was supplied together with VW.  I was offline and that
was what I found on my hard drive.  I used the Squeak version, not an
exported one.

Paolo


_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH] first attempts at loading Seaside into GNU Smalltalk

Markus Fritsche
In reply to this post by Paolo Bonzini
Paolo Bonzini wrote:
> I tried to load seaside into GST.  This was meant more as a stress test
> than a porting attempt.  Indeed I had a few problems (mostly my bugs,
> such as having more than 64 items in Undeclared and causing it to grow).
>   It also reproduced the 2.95b x86-64 failures on my machine too, so I
> fixed them (they were introduced by the copy-on-write patches from last
> December).

I don't wand to FUD, but... well, I once was curious if gst would be
capable of loading seaside. That was when I started to make the
continuation tests work, which were working fine, even without me having
a good idea how I managed to. I was quite confident that the whole
system would work, if somebody contributes a couple of days to it. But
then...

Well, it involves (from my point of view, not really knowing what I did
that time) that there's a not a lot of code to be added, but many
different "small get-theres", which, for my experiments, I copied from
squeak. It worked, but I wasn't sure if there were license issues.

So, to put the long story short: to make seaside work on gst, one have
to implement the glue code by ones own, not "copying" the stuff from
squeak, right? Or am I completely wrong?

Once again, I don't want to interfere - just want to know if that would
be a manageable project for my vacation or not ;)

Kind regards,

Markus



_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: Re: [PATCH] first attempts at loading Seaside into GNU Smalltalk

Paolo Bonzini

> Well, it involves (from my point of view, not really knowing what I did
> that time) that there's a not a lot of code to be added, but many
> different "small get-theres", which, for my experiments, I copied from
> squeak. It worked, but I wasn't sure if there were license issues.

Sometimes you can figure out the code without even looking at -- for
example, #allButFirst.  But anyway Squeak is now MIT license, so the
license issue would be extremely minor.

Paolo


_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH] first attempts at loading Seaside into GNU Smalltalk

Markus Fritsche
Paolo Bonzini wrote:

> Sometimes you can figure out the code without even looking at -- for
> example, #allButFirst.  But anyway Squeak is now MIT license, so the
> license issue would be extremely minor.

Thanks for the update; I will dig deeper into that when it's the first
of december ;) (the time I did my first tries was when squeak was
released with this apple-thing-license, when I first ported  the
mysql-driver).

Btw, is it possible to update THANKS from [hidden email] to
[hidden email]? Should be my email-address for now-and-forever.

TY, Markus



_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk