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

127 lines
3.2 KiB
Smalltalk
Raw Normal View History

"
(C) 2010-2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
PackageLoader fileInPackage: 'Sockets'.
Integer extend [
swap16 [
| tmp |
<category: '*-OsmoCore-message'>
tmp := self bitAnd: 16rFFFF.
^ (tmp bitShift: -8) bitOr: ((tmp bitAnd: 16rFF) bitShift: 8)
]
swap32 [
| tmp |
"Certainly not the most effective way"
<category: '*-OsmoCore-message'>
tmp := 0.
tmp := tmp bitOr: ((self bitAnd: 16rFF000000) bitShift: -24).
tmp := tmp bitOr: ((self bitAnd: 16r00FF0000) bitShift: -8).
tmp := tmp bitOr: ((self bitAnd: 16r0000FF00) bitShift: 8).
tmp := tmp bitOr: ((self bitAnd: 16r000000FF) bitShift: 24).
^ tmp
]
]
Object extend [
toMessage [
| msg |
<category: '*-OsmoCore-message'>
msg := Osmo.MessageBuffer new.
self writeOn: msg.
^ msg
]
toMessageOrByteArray [
<category: '*-OsmoCore-message'>
^ self toMessage
]
]
ByteArray extend [
toMessageOrByteArray [
<category: '*-OsmoCore-message'>
^ self
]
]
"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: '*-OsmoCore-message'>
^self nextBytes: 2 signed: false
]
nextBytes: n signed: signed [
"Private - Get an integer out of the next anInteger bytes in the stream"
<category: '*-OsmoCore-message'>
| 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: '*-OsmoCore-message'>
| a |
a := self next.
^a isNil ifTrue: [a] ifFalse: [a asInteger]
]
]
ByteArray extend [
castTo: type [
<category: '*-OsmoCore-message'>
^ (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.
]
]