1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-network/Extensions.st

74 lines
1.6 KiB
Smalltalk
Raw Normal View History

"Copyright Header"
PackageLoader fileInPackage: 'Sockets'.
Integer extend [
swap16 [
| tmp |
tmp := self bitAnd: 16rFFFF.
^ (tmp bitShift: -8) bitOr: ((tmp bitAnd: 16rFF) bitShift: 8)
]
]
"Code from FileDescriptor, GST license"
Sockets.Socket extend [
nextUshort [
"Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int"
<category: 'binary I/O'>
^self nextBytes: 2 signed: false
]
nextBytes: n signed: signed [
"Private - Get an integer out of the next anInteger bytes in the stream"
<category: 'private'>
| int msb |
int := 0.
0 to: n * 8 - 16
by: 8
do: [:i | int := int + (self nextByte bitShift: i)].
msb := self nextByte.
(signed and: [msb > 127]) ifTrue: [msb := msb - 256].
^int + (msb bitShift: n * 8 - 8)
]
nextByte [
"Return the next byte in the file, or nil at eof"
<category: 'basic'>
| a |
a := self next.
^a isNil ifTrue: [a] ifFalse: [a asInteger]
]
]
ByteArray extend [
castTo: type [
<category: 'private'>
^ (CObject new storage: self) castTo: type
]
]
CCompound subclass: CPackedStruct [
<shape: #word>
<category: 'Language-C interface'>
<comment: nil>
CPackedStruct class >> declaration: array [
"Compile methods that implement the declaration in array."
<category: 'subclass creation'>
self
declaration: array
inject: self superclass sizeof
into: [:oldOffset :alignment | oldOffset]
]
CPackedStruct class >> compileSize: size align: alignment [
<category: 'private'>
^ super compileSize: size align: 1.
]
]