ExternalInt.st
author Claus Gittinger <cg@exept.de>
Sat, 02 May 2020 21:40:13 +0200
changeset 5476 7355a4b11cb6
parent 4576 abbfe9f91ef1
permissions -rw-r--r--
#FEATURE by cg class: Socket class added: #newTCPclientToHost:port:domain:domainOrder:withTimeout: changed: #newTCPclientToHost:port:domain:withTimeout:

"
 COPYRIGHT (c) 2018 by eXept Software AG
              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:libbasic2' }"

"{ NameSpace: Smalltalk }"

ExternalBytes subclass:#ExternalInt
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'System-Support'
!

!ExternalInt class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2018 by eXept Software AG
              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.
"
!

documentation
"
    Instances of me can be used as container in which int values are returned from C-calls. 
    Notice that the size of these ints depends on the machine's (and compiler's) int-size
    (which is ExternalBytes sizeofInt).
"
! !

!ExternalInt class methodsFor:'instance creation'!

new
    "allocate some memory usable to hold a C-int;
     the memory is not controlled by the garbage collector.
     Return a corresponding ExternalBytes object or raise MallocFailure (if malloc fails).

     Use this, if you have to pass a pointer to an integer
     external destination (such as a C function) which does not copy the
     data, but instead keeps a reference to it.

     DANGER ALERT: the memory is NOT automatically freed until it is either
                   MANUALLY freed (see #free) or the returned externalBytes object
                   is unprotected or the classes releaseAllMemory method is called."

    ^ super new:(ExternalBytes sizeofInt)

    "
     ExternalInt new
    "
!

unprotectedNew
    "allocate some memory usable to hold a naitve C-int;
     the memory is under the control of the garbage collector.
     Return a corresponding ExternalBytes object or raise MallocFailure (if malloc fails).

     DANGER ALERT: the memory block as allocated will be automatically freed
                   as soon as the reference to the returned externalBytes object
                   is gone (by the next garbage collect).
                   If the memory has been passed to a C-function which
                   remembers this pointer, bad things may happen ...."

    ^ super unprotectedNew:(ExternalBytes sizeofInt)

    "
     ExternalInt new
    "
! !

!ExternalInt methodsFor:'accessing'!

asExternalBytes
    ^ ExternalBytes address:(self value)

    "
     (ExternalLong new value:10) asExternalBytes
     (ExternalLong new value:0) asExternalBytes
    "
!

asInteger
    "warning: retrieves a signed integer with the size of the native machine's
     pointer (i.e. either 32 or 64bit)"

    ExternalBytes sizeofInt == 8 ifTrue:[
        ^ self signedInt64At:1 MSB:IsBigEndian
    ] ifFalse:[
        ^ self signedInt32At:1 MSB:IsBigEndian
    ]

    "
     ExternalInt new value:10
     (ExternalInt new value:16rFFFFFF) asInteger
    "
!

asUnsignedInteger
    "warning: retrieves an integer with the size of the native machine's
     pointer (i.e. either 32 or 64bit)"

    ExternalBytes sizeofInt == 8 ifTrue:[
        ^ self unsignedInt64At:1 MSB:IsBigEndian
    ] ifFalse:[
        ^ self unsignedInt32At:1 MSB:IsBigEndian
    ]

    "
     (ExternalInt new value:10) asUnsignedInteger
    "

    "Created: / 22-12-2010 / 18:31:03 / cg"
!

value
    ExternalBytes sizeofInt == 8 ifTrue:[
        ^ self signedInt64At:1 MSB:IsBigEndian
    ] ifFalse:[
        ^ self signedInt32At:1 MSB:IsBigEndian
    ]

    "
     (ExternalInt new value:10) value
    "

    "Modified: / 30.3.1998 / 17:07:57 / cg"
!

value:anInteger
    ExternalBytes sizeofInt == 8 ifTrue:[
        self signedInt64At:1 put:anInteger MSB:IsBigEndian
    ] ifFalse:[
        self signedInt32At:1 put:anInteger MSB:IsBigEndian
    ]

    "
     (ExternalInt new value:10) value
    "
! !

!ExternalInt methodsFor:'printing & storing'!

printOn:aStream
    aStream nextPutAll:self className; nextPut:$(.
    self asInteger printOn:aStream.
    aStream nextPut:$)
! !

!ExternalInt class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !