Goods db

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

Goods db

Jonathan Kelly
Hi,

I thought I'd ask here first ... I got my BTree code working, so I
thought I'd try to use it with the Goods DB, but it seems it's only
storing and recovering the instance variables. My page class is

OrderedCollection variableSubclass: #BTreePageOuter
     instanceVariableNames: 'order count'
     classVariableNames: ''
     poolDictionaries: ''
     category: 'BTree'

db := KKDatabase onHost: 'localhost' port: 6543.
db root: (BTree withOrder: 2).
db root add: 'O1'.
db commit.
db logout.

When I reconnect, instance variables order and count are set, but array
(from the parent OrderedCollection) is nil.

Jonathan.
PS... squeaksource was down, so I downloaded the packages from the
spanish mirror into my local package cache, and loaded them from there.
I'm running 1.3 on COG (that came from the 1.2.1 single click).
Package versions are:
GOODS-cds.137.mcz
GOODSCollections-cds.1.mcz
GOODSPlatformSqueak-cds.6.mcz

Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Lukas Renggli
I do not see how BTreePageOuter is used? Is that your own class? What
does that have to do with BTree?

Generally it is a bad idea to subclass collections. I am not sure, but
it could be that GOODS optimizes OrderedCollection access (look for
class extension from GOODS in OrderedCollection and superclasses).

Some other random remarks:

- I am not aware that anybody has used GOODS in the past year on Pharo
or even on a  Cog VM. So there might be (subtle) bugs. Do the tests
pass?

- GOODS loads things lazily. So it might be that when you look at
things through reflection (like the inspector), they do not load
properly. Also you need to make sure not to not access your objects
with optimized messages like #== or #yourself, because these do not
trigger the loading of the object.

Lukas

On 22 October 2011 09:43, Jonathan Kelly <[hidden email]> wrote:

> Hi,
>
> I thought I'd ask here first ... I got my BTree code working, so I thought
> I'd try to use it with the Goods DB, but it seems it's only storing and
> recovering the instance variables. My page class is
>
> OrderedCollection variableSubclass: #BTreePageOuter
>    instanceVariableNames: 'order count'
>    classVariableNames: ''
>    poolDictionaries: ''
>    category: 'BTree'
>
> db := KKDatabase onHost: 'localhost' port: 6543.
> db root: (BTree withOrder: 2).
> db root add: 'O1'.
> db commit.
> db logout.
>
> When I reconnect, instance variables order and count are set, but array
> (from the parent OrderedCollection) is nil.
>
> Jonathan.
> PS... squeaksource was down, so I downloaded the packages from the spanish
> mirror into my local package cache, and loaded them from there. I'm running
> 1.3 on COG (that came from the 1.2.1 single click).
> Package versions are:
> GOODS-cds.137.mcz
> GOODSCollections-cds.1.mcz
> GOODSPlatformSqueak-cds.6.mcz
>
>



--
Lukas Renggli
www.lukas-renggli.ch

Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Mariano Martinez Peck


On Sat, Oct 22, 2011 at 10:09 AM, Lukas Renggli <[hidden email]> wrote:
I do not see how BTreePageOuter is used? Is that your own class? What
does that have to do with BTree?

Generally it is a bad idea to subclass collections. I am not sure, but
it could be that GOODS optimizes OrderedCollection access (look for
class extension from GOODS in OrderedCollection and superclasses).

Some other random remarks:

- I am not aware that anybody has used GOODS in the past year on Pharo
or even on a  Cog VM. So there might be (subtle) bugs. Do the tests
pass?

- GOODS loads things lazily. So it might be that when you look at
things through reflection (like the inspector), they do not load
properly. Also you need to make sure not to not access your objects
with optimized messages like #== or #yourself, because these do not
trigger the loading of the object.

Lukas

On 22 October 2011 09:43, Jonathan Kelly <[hidden email]> wrote:
> Hi,
>
> I thought I'd ask here first ... I got my BTree code working, so I thought
> I'd try to use it with the Goods DB, but it seems it's only storing and
> recovering the instance variables. My page class is
>
> OrderedCollection variableSubclass: #BTreePageOuter
>    instanceVariableNames: 'order count'
>    classVariableNames: ''
>    poolDictionaries: ''
>    category: 'BTree'
>
> db := KKDatabase onHost: 'localhost' port: 6543.
> db root: (BTree withOrder: 2).
> db root add: 'O1'.
> db commit.
> db logout.
>
> When I reconnect, instance variables order and count are set, but array
> (from the parent OrderedCollection) is nil.
>
> Jonathan.
> PS... squeaksource was down, so I downloaded the packages from the spanish
> mirror into my local package cache, and loaded them from there. I'm running
> 1.3 on COG (that came from the 1.2.1 single click).
> Package versions are:
> GOODS-cds.137.mcz
> GOODSCollections-cds.1.mcz
> GOODSPlatformSqueak-cds.6.mcz
>
>



--
Lukas Renggli
www.lukas-renggli.ch




--
Mariano
http://marianopeck.wordpress.com

Reply | Threaded
Open this post in threaded view
|

Re: Goods db

NorbertHartl


Am 22.10.2011 um 10:42 schrieb Mariano Martinez Peck <[hidden email]>:



On Sat, Oct 22, 2011 at 10:09 AM, Lukas Renggli <[hidden email]> wrote:
I do not see how BTreePageOuter is used? Is that your own class? What
does that have to do with BTree?

Generally it is a bad idea to subclass collections. I am not sure, but
it could be that GOODS optimizes OrderedCollection access (look for
class extension from GOODS in OrderedCollection and superclasses).

Some other random remarks:

- I am not aware that anybody has used GOODS in the past year on Pharo
or even on a  Cog VM. So there might be (subtle) bugs. Do the tests
pass?

- GOODS loads things lazily. So it might be that when you look at
things through reflection (like the inspector), they do not load
properly. Also you need to make sure not to not access your objects
with optimized messages like #== or #yourself, because these do not
trigger the loading of the object.

Exactly. Back then working with Glorp I learned it the hard way. And then I learned that Glorp provides a yourSelf message that can help. It is like yourself but yourSelf will make sure a proxy is resolved.

Norbert
 
Lukas

On 22 October 2011 09:43, Jonathan Kelly <[hidden email]> wrote:
> Hi,
>
> I thought I'd ask here first ... I got my BTree code working, so I thought
> I'd try to use it with the Goods DB, but it seems it's only storing and
> recovering the instance variables. My page class is
>
> OrderedCollection variableSubclass: #BTreePageOuter
>    instanceVariableNames: 'order count'
>    classVariableNames: ''
>    poolDictionaries: ''
>    category: 'BTree'
>
> db := KKDatabase onHost: 'localhost' port: 6543.
> db root: (BTree withOrder: 2).
> db root add: 'O1'.
> db commit.
> db logout.
>
> When I reconnect, instance variables order and count are set, but array
> (from the parent OrderedCollection) is nil.
>
> Jonathan.
> PS... squeaksource was down, so I downloaded the packages from the spanish
> mirror into my local package cache, and loaded them from there. I'm running
> 1.3 on COG (that came from the 1.2.1 single click).
> Package versions are:
> GOODS-cds.137.mcz
> GOODSCollections-cds.1.mcz
> GOODSPlatformSqueak-cds.6.mcz
>
>



--
Lukas Renggli
www.lukas-renggli.ch




--
Mariano
http://marianopeck.wordpress.com

Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Stéphane Ducasse
In reply to this post by Jonathan Kelly
I know that andy and johan fixed some bugs in goods and that david shaffer too.
Now I do not know if andy code has been published.
Andy?
Stef

On Oct 22, 2011, at 9:43 AM, Jonathan Kelly wrote:

> Hi,
>
> I thought I'd ask here first ... I got my BTree code working, so I thought I'd try to use it with the Goods DB, but it seems it's only storing and recovering the instance variables. My page class is
>
> OrderedCollection variableSubclass: #BTreePageOuter
>    instanceVariableNames: 'order count'
>    classVariableNames: ''
>    poolDictionaries: ''
>    category: 'BTree'
>
> db := KKDatabase onHost: 'localhost' port: 6543.
> db root: (BTree withOrder: 2).
> db root add: 'O1'.
> db commit.
> db logout.
>
> When I reconnect, instance variables order and count are set, but array (from the parent OrderedCollection) is nil.
>
> Jonathan.
> PS... squeaksource was down, so I downloaded the packages from the spanish mirror into my local package cache, and loaded them from there. I'm running 1.3 on COG (that came from the 1.2.1 single click).
> Package versions are:
> GOODS-cds.137.mcz
> GOODSCollections-cds.1.mcz
> GOODSPlatformSqueak-cds.6.mcz
>


Reply | Threaded
Open this post in threaded view
|

Re: Goods db

jfabry
In reply to this post by Jonathan Kelly

I think you mean the Chilean mirror http://dsal.cl/squeaksource , unless there is a second mirror that I am not aware of? (And in that case, where is it and who is in charge? We should cooperate ...)

On 22 Oct 2011, at 04:43, Jonathan Kelly wrote:

> PS... squeaksource was down, so I downloaded the packages from the spanish mirror into my local package cache, and loaded them from there.



---> Save our in-boxes! http://emailcharter.org <---

Johan Fabry  
[hidden email] - http://dcc.uchile.cl/~jfabry
PLEIAD Lab - Computer Science Department (DCC) - University of Chile







Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Jonathan Kelly
In reply to this post by Lukas Renggli
Hi,

On 22/10/2011 7:09 PM, Lukas Renggli wrote:
> I do not see how BTreePageOuter is used? Is that your own class? What
> does that have to do with BTree?
I wrote my own BTree, mainly as a learning exercise. I had a look at the
other version, but it made my head hurt. Turns out mine is about 20%
faster than the version on squeaksource for adds, and nearly twice as
fast for deletes. I
> Generally it is a bad idea to subclass collections. I am not sure, but
Is that a general smalltalk principle, or just in regards to Goods??
> it could be that GOODS optimizes OrderedCollection access (look for
> class extension from GOODS in OrderedCollection and superclasses).
I couldn't find anything - but I'm quite new to smalltalk, so that's no
guarantee.
> Some other random remarks:
>
> - I am not aware that anybody has used GOODS in the past year on Pharo
> or even on a  Cog VM. So there might be (subtle) bugs. Do the tests
> pass?
Up until now. :) There were a couple of test failures
1.testFlushAllRemovesAllUnreferenced - this was failure
2.testTwoDifferentShapesInDatabase - this was error.

These seemed somewhat esoteric errors to me, so i kept going. All the DB
sort of tests passed, which is what i was interested in.

So ... I massaged my implementation to move from subclass to component
(another learning experience :) and now GOODS is working. I'll do some
more testing/playing/learning and report back.

I picked GOODS because I wanted to get my brain into OO thinking, and it
seemed more OO that other alternatives, but I'll look at GLORP as well.
Another learning experience.

> - GOODS loads things lazily. So it might be that when you look at
> things through reflection (like the inspector), they do not load
> properly. Also you need to make sure not to not access your objects
> with optimized messages like #== or #yourself, because these do not
> trigger the loading of the object.
Um, I'm not upto optimization tricks yet, so no. :)

Jonathan.

Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Lukas Renggli
>> I do not see how BTreePageOuter is used? Is that your own class? What
>> does that have to do with BTree?
>
> I wrote my own BTree, mainly as a learning exercise. I had a look at the
> other version, but it made my head hurt. Turns out mine is about 20% faster
> than the version on squeaksource for adds, and nearly twice as fast for
> deletes. I

Sounds cool, but IMHO correctness and customizability to different
database layers is more important than speed.

>> Generally it is a bad idea to subclass collections. I am not sure, but
>
> Is that a general smalltalk principle, or just in regards to Goods??

This is general to Smalltalk. Subclassing from concrete collections
inherits you way too much behavior that exposes way too much of the
internal structure. Subclassing introduces subtle bugs and hand hard
to detect dependencies.

For example, did you think of overriding #removeAllSuchThat: in your
OrderedCollection subclass? If not, I bet that soon somebody starts to
use it and completely breaks all constraints of a B-Tree.

>> - I am not aware that anybody has used GOODS in the past year on Pharo
>> or even on a  Cog VM. So there might be (subtle) bugs. Do the tests
>> pass?
>
> Up until now. :) There were a couple of test failures
> 1.testFlushAllRemovesAllUnreferenced - this was failure
> 2.testTwoDifferentShapesInDatabase - this was error.

I haven't used GOODS for a long time, but it seems to me that fixing
all tests is the first thing you would need to do. I doubt that any of
you own code works reliably if there are things broken in the core
code.

>> - GOODS loads things lazily. So it might be that when you look at
>> things through reflection (like the inspector), they do not load
>> properly. Also you need to make sure not to not access your objects
>> with optimized messages like #== or #yourself, because these do not
>> trigger the loading of the object.
>
> Um, I'm not upto optimization tricks yet, so no. :)

This has nothing to do with *your* optimization tricks. These are
optimization tricks that the VM and the compiler play on you. Below a
list of potentially dangerous selectors that might not cause the GOODS
proxy objects to load the object. You need to be aware of these
details to be able to write code that works with proxy objects:

ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue: and: or: whileFalse:
whileTrue: whileFalse whileTrue to:do: to:by:do: caseOf:
caseOf:otherwise: ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:
repeat + - < > <= >= = ~= * / \\ @ bitShift: // bitAnd: bitOr: at:
at:put: size next nextPut: atEnd == class blockCopy: value value: do:
new new: x y yourself

Lukas

--
Lukas Renggli
www.lukas-renggli.ch

Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Mariano Martinez Peck

>
> Um, I'm not upto optimization tricks yet, so no. :)

This has nothing to do with *your* optimization tricks. These are
optimization tricks that the VM and the compiler play on you. Below a
list of potentially dangerous selectors that might not cause the GOODS
proxy objects to load the object. You need to be aware of these
details to be able to write code that works with proxy objects:

ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue: and: or: whileFalse:
whileTrue: whileFalse whileTrue to:do: to:by:do: caseOf:
caseOf:otherwise: ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:
repeat + - < > <= >= = ~= * / \\ @ bitShift: // bitAnd: bitOr: at:
at:put: size next nextPut: atEnd == class blockCopy: value value: do:
new new: x y yourself


Just a small comment: not ALL those methods will be *never* executed.

All those that are optimized by the compiler:  MessageNode >> #initialize   (instVar MacroSelectors)
    ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:
            and: or:
            whileFalse: whileTrue: whileFalse whileTrue
            to:do: to:by:do:
            caseOf: caseOf:otherwise:
            ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:
            repeat


Those are never executed, hence you cannot intercept them.

Now, those special selectors that have associated bytecodes:  Smalltalk specialSelectors
-> #(#+ 1 #- 1 #< 1 #> 1 #'<=' 1 #'>=' 1 #= 1 #'~=' 1 #* 1 #/ 1 #'\\' 1 #@ 1 #bitShift: 1 #'//' 1 #bitAnd: 1 #bitOr: 1 #at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #'==' 1 #class 0 #blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0)

SOME of them are not executed.

1) Some are ALWAYS executed
For example, the bytecode for #atEnd  does nothing more than a small optimization, but it is always executed at the end:
StackInterpreter >> bytecodePrimAtEnd
    messageSelector := self specialSelector: 21.
    argumentCount := 0.
    self normalSend.

2) Some are SOMETIMES executed.
Example, #+, #>=, etc.  All those math bytecode usually work if the receiver and argument are numbers. But if they are not, like in the case of a proxy, then the bytecode fails and hence, the method is executed. Example:
StackInterpreter >> bytecodePrimAdd
    | rcvr arg result |
    rcvr := self internalStackValue: 1.
    arg := self internalStackValue: 0.
    (self areIntegers: rcvr and: arg)
        ifTrue: [result := (objectMemory integerValueOf: rcvr) + (objectMemory integerValueOf: arg).
                (objectMemory isIntegerValue: result) ifTrue:
                    [self internalPop: 2 thenPush: (objectMemory integerObjectOf: result).
                    ^ self fetchNextBytecode "success"]]
        ifFalse: [self initPrimCall.
                self externalizeIPandSP.
                self primitiveFloatAdd: rcvr toArg: arg.
                self internalizeIPandSP.
                self successful ifTrue: [^ self fetchNextBytecode "success"]].

    messageSelector := self specialSelector: 0.
    argumentCount := 1.
    self normalSend

3) Some are NEVER executed. For example, #class and #==.
StackInterpreter >> bytecodePrimEquivalent

    | rcvr arg |
    rcvr := self internalStackValue: 1.
    arg := self internalStackValue: 0.
    self booleanCheat: rcvr = arg.


So, for a proxy I think the only problem is (apart from the already mentioned compiler inlining) point 3), that is #== and #class

Anyway, I have wirtten a paper about writting proxies in Smalltalk which you may find interesting.
http://rmod.lille.inria.fr/web/pier/software/Marea/GhostProxies
You can get the paper from there.

Cheers


 

Lukas

--
Lukas Renggli
www.lukas-renggli.ch




--
Mariano
http://marianopeck.wordpress.com

Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Lukas Renggli

>> > Um, I'm not upto optimization tricks yet, so no. :)
>>
>> This has nothing to do with *your* optimization tricks. These are
>> optimization tricks that the VM and the compiler play on you. Below a
>> list of potentially dangerous selectors that might not cause the GOODS
>> proxy objects to load the object. You need to be aware of these
>> details to be able to write code that works with proxy objects:
>>
>> ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue: and: or: whileFalse:
>> whileTrue: whileFalse whileTrue to:do: to:by:do: caseOf:
>> caseOf:otherwise: ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:
>> repeat + - < > <= >= = ~= * / \\ @ bitShift: // bitAnd: bitOr: at:
>> at:put: size next nextPut: atEnd == class blockCopy: value value: do:
>> new new: x y yourself
>
>
> Just a small comment: not ALL those methods will be *never* executed.

That's why I used the word "might" ;-)

Lukas

>
> All those that are optimized by the compiler:  MessageNode >> #initialize   (instVar MacroSelectors)
>     ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:
>             and: or:
>             whileFalse: whileTrue: whileFalse whileTrue
>             to:do: to:by:do:
>             caseOf: caseOf:otherwise:
>             ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:
>             repeat
>
>
> Those are never executed, hence you cannot intercept them.
>
> Now, those special selectors that have associated bytecodes:  Smalltalk specialSelectors
> -> #(#+ 1 #- 1 #< 1 #> 1 #'<=' 1 #'>=' 1 #= 1 #'~=' 1 #* 1 #/ 1 #'\\' 1 #@ 1 #bitShift: 1 #'//' 1 #bitAnd: 1 #bitOr: 1 #at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #'==' 1 #class 0 #blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0)
>
> SOME of them are not executed.
>
> 1) Some are ALWAYS executed
> For example, the bytecode for #atEnd  does nothing more than a small optimization, but it is always executed at the end:
> StackInterpreter >> bytecodePrimAtEnd
>     messageSelector := self specialSelector: 21.
>     argumentCount := 0.
>     self normalSend.
>
> 2) Some are SOMETIMES executed.
> Example, #+, #>=, etc.  All those math bytecode usually work if the receiver and argument are numbers. But if they are not, like in the case of a proxy, then the bytecode fails and hence, the method is executed. Example:
> StackInterpreter >> bytecodePrimAdd
>     | rcvr arg result |
>     rcvr := self internalStackValue: 1.
>     arg := self internalStackValue: 0.
>     (self areIntegers: rcvr and: arg)
>         ifTrue: [result := (objectMemory integerValueOf: rcvr) + (objectMemory integerValueOf: arg).
>                 (objectMemory isIntegerValue: result) ifTrue:
>                     [self internalPop: 2 thenPush: (objectMemory integerObjectOf: result).
>                     ^ self fetchNextBytecode "success"]]
>         ifFalse: [self initPrimCall.
>                 self externalizeIPandSP.
>                 self primitiveFloatAdd: rcvr toArg: arg.
>                 self internalizeIPandSP.
>                 self successful ifTrue: [^ self fetchNextBytecode "success"]].
>
>     messageSelector := self specialSelector: 0.
>     argumentCount := 1.
>     self normalSend
>
> 3) Some are NEVER executed. For example, #class and #==.
> StackInterpreter >> bytecodePrimEquivalent
>
>     | rcvr arg |
>     rcvr := self internalStackValue: 1.
>     arg := self internalStackValue: 0.
>     self booleanCheat: rcvr = arg.
>
>
> So, for a proxy I think the only problem is (apart from the already mentioned compiler inlining) point 3), that is #== and #class
>
> Anyway, I have wirtten a paper about writting proxies in Smalltalk which you may find interesting.
> http://rmod.lille.inria.fr/web/pier/software/Marea/GhostProxies
> You can get the paper from there.

>
> Cheers
>
>
>  
>>
>> Lukas
>>
>> --
>> Lukas Renggli
>> www.lukas-renggli.ch
>>
>
>
>
> --
> Mariano
> http://marianopeck.wordpress.com
>
>

--
Lukas Renggli
www.lukas-renggli.ch
Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Stéphane Ducasse
In reply to this post by Mariano Martinez Peck
this is why we need a solid proxy.

Stef

On Oct 23, 2011, at 12:13 PM, Mariano Martinez Peck wrote:

>
> >
> > Um, I'm not upto optimization tricks yet, so no. :)
>
> This has nothing to do with *your* optimization tricks. These are
> optimization tricks that the VM and the compiler play on you. Below a
> list of potentially dangerous selectors that might not cause the GOODS
> proxy objects to load the object. You need to be aware of these
> details to be able to write code that works with proxy objects:
>
> ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue: and: or: whileFalse:
> whileTrue: whileFalse whileTrue to:do: to:by:do: caseOf:
> caseOf:otherwise: ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:
> repeat + - < > <= >= = ~= * / \\ @ bitShift: // bitAnd: bitOr: at:
> at:put: size next nextPut: atEnd == class blockCopy: value value: do:
> new new: x y yourself
>
>
> Just a small comment: not ALL those methods will be *never* executed.
>
> All those that are optimized by the compiler:  MessageNode >> #initialize   (instVar MacroSelectors)
>     ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:
>             and: or:
>             whileFalse: whileTrue: whileFalse whileTrue
>             to:do: to:by:do:
>             caseOf: caseOf:otherwise:
>             ifNil: ifNotNil:  ifNil:ifNotNil: ifNotNil:ifNil:
>             repeat
>
>
> Those are never executed, hence you cannot intercept them.
>
> Now, those special selectors that have associated bytecodes:  Smalltalk specialSelectors
> -> #(#+ 1 #- 1 #< 1 #> 1 #'<=' 1 #'>=' 1 #= 1 #'~=' 1 #* 1 #/ 1 #'\\' 1 #@ 1 #bitShift: 1 #'//' 1 #bitAnd: 1 #bitOr: 1 #at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #'==' 1 #class 0 #blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0)
>
> SOME of them are not executed.
>
> 1) Some are ALWAYS executed
> For example, the bytecode for #atEnd  does nothing more than a small optimization, but it is always executed at the end:
> StackInterpreter >> bytecodePrimAtEnd
>     messageSelector := self specialSelector: 21.
>     argumentCount := 0.
>     self normalSend.
>
> 2) Some are SOMETIMES executed.
> Example, #+, #>=, etc.  All those math bytecode usually work if the receiver and argument are numbers. But if they are not, like in the case of a proxy, then the bytecode fails and hence, the method is executed. Example:
> StackInterpreter >> bytecodePrimAdd
>     | rcvr arg result |
>     rcvr := self internalStackValue: 1.
>     arg := self internalStackValue: 0.
>     (self areIntegers: rcvr and: arg)
>         ifTrue: [result := (objectMemory integerValueOf: rcvr) + (objectMemory integerValueOf: arg).
>                 (objectMemory isIntegerValue: result) ifTrue:
>                     [self internalPop: 2 thenPush: (objectMemory integerObjectOf: result).
>                     ^ self fetchNextBytecode "success"]]
>         ifFalse: [self initPrimCall.
>                 self externalizeIPandSP.
>                 self primitiveFloatAdd: rcvr toArg: arg.
>                 self internalizeIPandSP.
>                 self successful ifTrue: [^ self fetchNextBytecode "success"]].
>
>     messageSelector := self specialSelector: 0.
>     argumentCount := 1.
>     self normalSend
>
> 3) Some are NEVER executed. For example, #class and #==.
> StackInterpreter >> bytecodePrimEquivalent
>
>     | rcvr arg |
>     rcvr := self internalStackValue: 1.
>     arg := self internalStackValue: 0.
>     self booleanCheat: rcvr = arg.
>
>
> So, for a proxy I think the only problem is (apart from the already mentioned compiler inlining) point 3), that is #== and #class
>
> Anyway, I have wirtten a paper about writting proxies in Smalltalk which you may find interesting.
> http://rmod.lille.inria.fr/web/pier/software/Marea/GhostProxies
> You can get the paper from there.
>
> Cheers
>
>
>  
>
> Lukas
>
> --
> Lukas Renggli
> www.lukas-renggli.ch
>
>
>
>
> --
> Mariano
> http://marianopeck.wordpress.com
>


Reply | Threaded
Open this post in threaded view
|

Re: Goods db

Jonathan Kelly
In reply to this post by Lukas Renggli
On 23/10/2011 7:45 PM, Lukas Renggli wrote:

>>> I do not see how BTreePageOuter is used? Is that your own class? What
>>> does that have to do with BTree?
>> I wrote my own BTree, mainly as a learning exercise. I had a look at the
>> other version, but it made my head hurt. Turns out mine is about 20% faster
>> than the version on squeaksource for adds, and nearly twice as fast for
>> deletes. I
> Sounds cool, but IMHO correctness and customizability to different
> database layers is more important than speed.
>
>>> Generally it is a bad idea to subclass collections. I am not sure, but
>> Is that a general smalltalk principle, or just in regards to Goods??
> This is general to Smalltalk. Subclassing from concrete collections
> inherits you way too much behavior that exposes way too much of the
> internal structure. Subclassing introduces subtle bugs and hand hard
> to detect dependencies.
>
> For example, did you think of overriding #removeAllSuchThat: in your
> OrderedCollection subclass? If not, I bet that soon somebody starts to
> use it and completely breaks all constraints of a B-Tree.
>

Um, sub-classed or in a variable, what's to stop them doing that either way?

J