aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--GSMEncoding.st58
-rw-r--r--Tests.st9
2 files changed, 67 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
diff --git a/Tests.st b/Tests.st
index c2be1d1..38cfa80 100644
--- a/Tests.st
+++ b/Tests.st
@@ -548,6 +548,15 @@ TestCase subclass: GSMEncodingTest [
self assert: res = wanted
]
+ test7BitDecode [
+ | wanted res |
+
+ wanted := 'Your remaining balance is:1704 min,expiring on:10-07-2010'.
+ res := #(16rD9 16r77 16r5D 16r0E 16r92 16r97 16rDB 16rE1 16rB4 16r3B 16rED 16r3E 16r83 16rC4 16r61 16r76 16rD8 16r3D 16r2E 16r83 16rD2 16r73 16r5D 16rEC 16r06 16rA3 16r81 16rDA 16r69 16r37 16rAB 16r8C 16r87 16rA7 16rE5 16r69 16rF7 16r19 16rF4 16r76 16rEB 16r62 16rB0 16r16 16rEC 16rD6 16r92 16rC1 16r62 16r30) asByteArray decodeGSM7Bit.
+
+ self assert: res = wanted.
+ ]
+
testUSSDEncode [
| wanted res |