module Sound.OSC.Coding.Decode.Base (decodeMessage
,decodeBundle
,decodePacket) where
import Data.Binary
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Lazy as B
import Data.List
import Data.Maybe
import Sound.OSC.Coding.Byte
import Sound.OSC.Coding.Convert
import Sound.OSC.Datum
import Sound.OSC.Packet
import Sound.OSC.Time
size :: Datum_Type -> B.ByteString -> Int
size ty b =
case ty of
'i' -> 4
'f' -> 4
'd' -> 8
't' -> 8
'm' -> 4
's' -> int64_to_int (fromMaybe
(error ("size: no terminating zero: " ++ show b))
(B.elemIndex 0 b))
'b' -> decode_i32 (B.take 4 b)
_ -> error "size: illegal type"
storage :: Datum_Type -> B.ByteString -> Int
storage ty b =
case ty of
's' -> let n = size 's' b + 1 in n + align n
'b' -> let n = size 'b' b in n + align n + 4
_ -> size ty B.empty
decode_datum :: Datum_Type -> B.ByteString -> Datum
decode_datum ty b =
case ty of
'i' -> Int32 (decode b)
'h' -> Int64 (decode b)
'f' -> Float (decode_f32 b)
'd' -> Double (decode_f64 b)
's' -> ASCII_String (decode_ascii (b_take (size 's' b) b))
'b' -> Blob (b_take (size 'b' b) (B.drop 4 b))
't' -> TimeStamp (ntpi_to_ntpr (decode_word64 b))
'm' -> let [b0,b1,b2,b3] = B.unpack (B.take 4 b)
in midi (b0,b1,b2,b3)
_ -> error ("decode_datum: illegal type (" ++ [ty] ++ ")")
decode_datum_seq :: ASCII -> B.ByteString -> [Datum]
decode_datum_seq cs b =
let swap (x,y) = (y,x)
cs' = C.unpack cs
f b' c = swap (B.splitAt (int_to_int64 (storage c b')) b')
in zipWith decode_datum cs' (snd (mapAccumL f b cs'))
decodeMessage :: B.ByteString -> Message
decodeMessage b =
let n = storage 's' b
(ASCII_String cmd) = decode_datum 's' b
m = storage 's' (b_drop n b)
(ASCII_String dsc) = decode_datum 's' (b_drop n b)
arg = decode_datum_seq (descriptor_tags dsc) (b_drop (n + m) b)
in Message (C.unpack cmd) arg
decode_message_seq :: B.ByteString -> [Message]
decode_message_seq b =
let s = decode_i32 b
m = decodeMessage (b_drop 4 b)
nxt = decode_message_seq (b_drop (4+s) b)
in if B.length b == 0 then [] else m:nxt
decodeBundle :: B.ByteString -> Bundle
decodeBundle b =
let h = storage 's' b
t = storage 't' (b_drop h b)
(TimeStamp timeStamp) = decode_datum 't' (b_drop h b)
ms = decode_message_seq (b_drop (h+t) b)
in Bundle timeStamp ms
decodePacket :: B.ByteString -> Packet
decodePacket b =
if bundleHeader `B.isPrefixOf` b
then Packet_Bundle (decodeBundle b)
else Packet_Message (decodeMessage b)
b_take :: Int -> B.ByteString -> B.ByteString
b_take = B.take . int_to_int64
b_drop :: Int -> B.ByteString -> B.ByteString
b_drop = B.drop . int_to_int64