aboutsummaryrefslogtreecommitdiffstats
path: root/GSMEncoding.st
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2011-04-01 01:14:46 +0200
committerHolger Hans Peter Freyther <zecke@selfish.org>2011-04-01 01:29:32 +0200
commit9ce4aebeb265b5f9ffe189b8dd1dad9cc2c196e8 (patch)
treea6beae6c129aba3dbc21db8f66b0e64a5ac6985a /GSMEncoding.st
parenta18ba2fb2e7b25d54633c8ea960ad0b282ff9cfc (diff)
GSM: Add basic decoding support to byte array
Diffstat (limited to 'GSMEncoding.st')
-rw-r--r--GSMEncoding.st58
1 files changed, 58 insertions, 0 deletions
diff --git a/GSMEncoding.st b/GSMEncoding.st
index f82575a..03cb44f 100644
--- a/GSMEncoding.st
+++ b/GSMEncoding.st
@@ -16,6 +16,13 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
+ByteArray extend [
+ decodeGSM7Bit [
+ <category: '*-osmo-gsm'>
+ ^ GSMDecoding decode: self.
+ ]
+]
+
String extend [
asGSM7Bit [
"I convert a string into a 7bit encoded string. I should
@@ -33,6 +40,57 @@ String extend [
]
]
+Object subclass: GSMDecoding [
+ <category: 'osmo-gsm'>
+ <comment: 'I am the base class for GSM Decoding as of GSM 03.38. I
+can be subclassed to deal with specifics for USSD and other systems.'>
+
+ GSMDecoding class >> decode: aByteArray [
+ | bits bytes |
+ bits := self convertFromBytes: aByteArray.
+ bytes := self convertToBytes: bits.
+ ^ self handleBytes: bytes from: bits
+ ]
+
+ GSMDecoding class >> handleBytes: bytes from: bits [
+ ^ bytes asString
+ ]
+
+ GSMDecoding class >> convertFromBytes: aByteArray [
+ | bits |
+ "We convert the stream into single bits. It is the
+ easiest to do it like this."
+
+ bits := OrderedCollection new.
+ aByteArray do: [:each |
+ 1 to: 8 do: [:pos | bits add: (each bitAt: pos)]
+ ].
+
+ ^ bits
+ ]
+
+ GSMDecoding class >> convertToBytes: bits [
+ | bytes |
+
+ bytes := ByteArray new: (bits size // 7).
+ 1 to: bits size by: 7 do: [:pos |
+ (pos + 6 <= bits size) ifTrue: [ | byte |
+ byte := 0.
+ byte := (byte bitShift: 1) bitOr: (bits at: pos + 6).
+ byte := (byte bitShift: 1) bitOr: (bits at: pos + 5).
+ byte := (byte bitShift: 1) bitOr: (bits at: pos + 4).
+ byte := (byte bitShift: 1) bitOr: (bits at: pos + 3).
+ byte := (byte bitShift: 1) bitOr: (bits at: pos + 2).
+ byte := (byte bitShift: 1) bitOr: (bits at: pos + 1).
+ byte := (byte bitShift: 1) bitOr: (bits at: pos + 0).
+ bytes at: (pos // 7) + 1 put: byte.
+ ].
+ ].
+
+ ^ bytes
+ ]
+]
+
Object subclass: GSMEncoding [
<category: 'osmo-gsm'>
<comment: 'I am the base class for GSM Encoding as of GSM 03.38. I