2010/9/21 Henrik Sperre Johansen <henrik.s.johan...@veloxit.no>

>  On 21.09.2010 20:47, Mariano Martinez Peck wrote:
>
>
>
> On Tue, Apr 27, 2010 at 1:19 PM, Adrian Lienhard <a...@netstyle.ch> wrote:
>
>> Its a simple method in Object:
>>
>> Object>>sizeInMemory
>>        "Returns the number of bytes used by this object in memory
>> (including its header)"
>>
>>        | headerSize instanceSize |
>>        headerSize := (self class indexIfCompact > 0 ifTrue: [ 4 ] ifFalse:
>> [ 8 ]).
>>        instanceSize := (self class isVariable
>>                ifFalse: [ self class instSize * Smalltalk wordSize ]
>>                ifTrue: [ (self basicSize * (self class isBytes
>>                        ifTrue: [ 1 ] ifFalse: [ Smalltalk wordSize ])) ]).
>>        ^ headerSize + instanceSize
>>
>>
       ^ headerSize + contentBytes

:)

Thanks Henry....so do you think we can integrate this?

Adrian?



>
> Hi Adrian. Sorry for returning to this thread. I am trying to contemplate
> all the cases.
>
> I was looking at SpaceTally and I found that maybe a better implementation
> could be something like this:
>
> Object >> sizeInMemory
>     "Answer the number of bytes consumed by this instance including object
> header."
>
>     | isCompact instVarBytes bytesPerElement headerBytes total contentBytes
> |
>     isCompact := self class indexIfCompact > 0.
>     instVarBytes := self class instSize * 4.
>     self class isVariable
>         ifTrue: [
>             bytesPerElement := self class isBytes ifTrue: [1] ifFalse: [4].
>             total := 0.
>             contentBytes := instVarBytes + (self basicSize *
> bytesPerElement).
>                 headerBytes :=
>                     contentBytes > 255
>                         ifTrue: [12]
>                         ifFalse: [isCompact ifTrue: [4] ifFalse: [8]].
>                 total :=  headerBytes + contentBytes.
>             ^ total]
>         ifFalse: [
>             headerBytes :=
>                 instVarBytes > 255
>                     ifTrue: [12]
>                     ifFalse: [isCompact ifTrue: [4] ifFalse: [8]].
>             ^ headerBytes + instVarBytes ].
>
>
>
> I guess I did some mistake but if we can arrive to a good implementation it
> would be really cool.
>
> Thanks
>
> mariano
>
>
> Please, at least do some refactoring :)
>
> Object >> sizeInMemory
>     "Answer the number of bytes consumed by this instance including object
> header."
>     | isCompact headerBytes contentBytes |
>
>     isCompact := self class indexIfCompact > 0.
>     contentBytes := self class instSize * Smalltalk wordSize. "inst vars"
>
>     self class isVariable ifTrue:
>         [ |bytesPerElement|
>             bytesPerElement := self class isBytes ifTrue: [1] ifFalse: [4].
>             contentBytes := contentBytes + (self basicSize *
> bytesPerElement)].
>
>       headerBytes :=
>                     contentBytes > 255
>                         ifTrue: [12]
>                         ifFalse: [isCompact ifTrue: [4] ifFalse: [8]].
>             ^ headerBytes + instVarBytes
>
> Also, in a 64-bit image, I suspect you may have to make a distinction
> between class isWords as well.
> ie:
> self class isBytes ifTrue: [1] ifFalse: [self class isWords ifTrue: [4]
> ifFalse: [Smalltalk wordSize]]
>
> Cheers,
> Henry
>
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>
_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to