module Sound.Osc.Coding.Decode.Binary (
get_packet,
decodeMessage,
decodeBundle,
decodePacket,
decodePacket_strict,
decodeMessageOr,
decodeBundleOr,
decodePacketOr,
) where
import Control.Applicative
import Control.Monad
import Data.Word
import qualified Data.Binary.Get as Binary
import qualified Data.ByteString.Char8 as ByteString.Char8
import qualified Data.ByteString.Lazy as ByteString.Lazy
import qualified Data.ByteString.Lazy.Char8 as ByteString.Lazy.Char8
import qualified Sound.Osc.Coding.Byte as Byte
import qualified Sound.Osc.Coding.Convert as Convert
import Sound.Osc.Datum
import Sound.Osc.Packet
import qualified Sound.Osc.Time as Time
get_string :: Binary.Get String
get_string :: Get String
get_string = do
ByteString
s <- Get ByteString
Binary.getLazyByteStringNul
Int -> Get ()
Binary.skip (Int64 -> Int
Convert.int64_to_int (Int64 -> Int64
forall i. (Num i, Bits i) => i -> i
Byte.align (ByteString -> Int64
ByteString.Lazy.length ByteString
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1)))
String -> Get String
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> String
ByteString.Lazy.Char8.unpack ByteString
s)
get_ascii :: Binary.Get Ascii
get_ascii :: Get ByteString
get_ascii = do
ByteString
s <- Get ByteString
Binary.getLazyByteStringNul
Int -> Get ()
Binary.skip (Int64 -> Int
Convert.int64_to_int (Int64 -> Int64
forall i. (Num i, Bits i) => i -> i
Byte.align (ByteString -> Int64
ByteString.Lazy.length ByteString
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1)))
ByteString -> Get ByteString
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ByteString
ByteString.Char8.pack (ByteString -> String
ByteString.Lazy.Char8.unpack ByteString
s))
get_bytes :: Word32 -> Binary.Get ByteString.Lazy.ByteString
get_bytes :: Word32 -> Get ByteString
get_bytes Word32
n = do
ByteString
b <- Int64 -> Get ByteString
Binary.getLazyByteString (Word32 -> Int64
Convert.word32_to_int64 Word32
n)
if Word32
n Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Int64 -> Word32
Convert.int64_to_word32 (ByteString -> Int64
ByteString.Lazy.length ByteString
b)
then String -> Get ()
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"get_bytes: end of stream"
else Int -> Get ()
Binary.skip (Word32 -> Int
Convert.word32_to_int (Word32 -> Word32
forall i. (Num i, Bits i) => i -> i
Byte.align Word32
n))
ByteString -> Get ByteString
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
b
get_datum :: DatumType -> Binary.Get Datum
get_datum :: DatumType -> Get Datum
get_datum DatumType
ty =
case DatumType
ty of
DatumType
'i' -> (Int32 -> Datum) -> Get Int32 -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> Datum
Int32 Get Int32
Binary.getInt32be
DatumType
'h' -> (Int64 -> Datum) -> Get Int64 -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> Datum
Int64 Get Int64
Binary.getInt64be
DatumType
'f' -> (Float -> Datum) -> Get Float -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Float -> Datum
Float Get Float
Binary.getFloatbe
DatumType
'd' -> (Double -> Datum) -> Get Double -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> Datum
Double Get Double
Binary.getDoublebe
DatumType
's' -> (ByteString -> Datum) -> Get ByteString -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Datum
AsciiString Get ByteString
get_ascii
DatumType
'b' -> (ByteString -> Datum) -> Get ByteString -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Datum
Blob (Word32 -> Get ByteString
get_bytes (Word32 -> Get ByteString) -> Get Word32 -> Get ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word32
Binary.getWord32be)
DatumType
't' -> (Ntp64 -> Datum) -> Get Ntp64 -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double -> Datum
TimeStamp (Double -> Datum) -> (Ntp64 -> Double) -> Ntp64 -> Datum
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ntp64 -> Double
Time.ntpi_to_ntpr) Get Ntp64
Binary.getWord64be
DatumType
'm' -> (MidiData -> Datum) -> Get MidiData -> Get Datum
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MidiData -> Datum
Midi ((Word8 -> Word8 -> Word8 -> Word8 -> MidiData)
-> Get Word8 -> Get Word8 -> Get Word8 -> Get Word8 -> Get MidiData
forall (m :: * -> *) a1 a2 a3 a4 r.
Monad m =>
(a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
liftM4 Word8 -> Word8 -> Word8 -> Word8 -> MidiData
MidiData Get Word8
Binary.getWord8 Get Word8
Binary.getWord8 Get Word8
Binary.getWord8 Get Word8
Binary.getWord8)
DatumType
_ -> String -> Get Datum
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"get_datum: illegal type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ DatumType -> String
forall a. Show a => a -> String
show DatumType
ty)
get_message :: Binary.Get Message
get_message :: Get Message
get_message = do
String
cmd <- Get String
get_string
ByteString
dsc <- Get ByteString
get_ascii
case ByteString -> String
ByteString.Char8.unpack ByteString
dsc of
DatumType
',' : String
tags -> do
[Datum]
arg <- (DatumType -> Get Datum) -> String -> Get [Datum]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM DatumType -> Get Datum
get_datum String
tags
Message -> Get Message
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> [Datum] -> Message
Message String
cmd [Datum]
arg)
String
e -> String -> Get Message
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"get_message: invalid type descriptor string: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
e)
get_message_seq :: Binary.Get [Message]
get_message_seq :: Get [Message]
get_message_seq = do
Bool
b <- Get Bool
Binary.isEmpty
if Bool
b
then [Message] -> Get [Message]
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return []
else do
Message
p <- (Int -> Get Message -> Get Message)
-> Get Message -> Int -> Get Message
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Get Message -> Get Message
forall a. Int -> Get a -> Get a
Binary.isolate Get Message
get_message (Int -> Get Message) -> (Word32 -> Int) -> Word32 -> Get Message
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Int
Convert.word32_to_int (Word32 -> Get Message) -> Get Word32 -> Get Message
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word32
Binary.getWord32be
[Message]
ps <- Get [Message]
get_message_seq
[Message] -> Get [Message]
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (Message
p Message -> [Message] -> [Message]
forall a. a -> [a] -> [a]
: [Message]
ps)
get_bundle :: Binary.Get (BundleOf Message)
get_bundle :: Get (BundleOf Message)
get_bundle = do
ByteString
h <- Int -> Get ByteString
Binary.getByteString (ByteString -> Int
ByteString.Char8.length ByteString
Byte.bundleHeader_strict)
Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ByteString
h ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
/= ByteString
Byte.bundleHeader_strict) (String -> Get ()
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"get_bundle: not a bundle")
Double
t <- (Ntp64 -> Double) -> Get Ntp64 -> Get Double
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ntp64 -> Double
Time.ntpi_to_ntpr Get Ntp64
Binary.getWord64be
([Message] -> BundleOf Message)
-> Get [Message] -> Get (BundleOf Message)
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double -> [Message] -> BundleOf Message
forall t. Double -> [t] -> BundleOf t
Bundle Double
t) Get [Message]
get_message_seq
get_packet :: Binary.Get (PacketOf Message)
get_packet :: Get (PacketOf Message)
get_packet = (BundleOf Message -> PacketOf Message)
-> Get (BundleOf Message) -> Get (PacketOf Message)
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BundleOf Message -> PacketOf Message
forall t. BundleOf t -> PacketOf t
Packet_Bundle Get (BundleOf Message)
get_bundle Get (PacketOf Message)
-> Get (PacketOf Message) -> Get (PacketOf Message)
forall a. Get a -> Get a -> Get a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Message -> PacketOf Message)
-> Get Message -> Get (PacketOf Message)
forall a b. (a -> b) -> Get a -> Get b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Message -> PacketOf Message
forall t. Message -> PacketOf t
Packet_Message Get Message
get_message
{-# INLINE decodeMessage #-}
{-# INLINE decodeBundle #-}
{-# INLINE decodePacket #-}
{-# INLINE decodePacket_strict #-}
decodeMessage :: ByteString.Lazy.ByteString -> Message
decodeMessage :: ByteString -> Message
decodeMessage = Get Message -> ByteString -> Message
forall a. Get a -> ByteString -> a
Binary.runGet Get Message
get_message
decodeBundle :: ByteString.Lazy.ByteString -> BundleOf Message
decodeBundle :: ByteString -> BundleOf Message
decodeBundle = Get (BundleOf Message) -> ByteString -> BundleOf Message
forall a. Get a -> ByteString -> a
Binary.runGet Get (BundleOf Message)
get_bundle
runDecoder :: Binary.Get t -> ByteString.Lazy.Char8.ByteString -> Either String t
runDecoder :: forall t. Get t -> ByteString -> Either String t
runDecoder Get t
f ByteString
p =
case Get t
-> ByteString
-> Either (ByteString, Int64, String) (ByteString, Int64, t)
forall a.
Get a
-> ByteString
-> Either (ByteString, Int64, String) (ByteString, Int64, a)
Binary.runGetOrFail Get t
f ByteString
p of
Left (ByteString
_, Int64
_, String
err) -> String -> Either String t
forall a b. a -> Either a b
Left String
err
Right (ByteString
_, Int64
_, t
decoded) -> t -> Either String t
forall a b. b -> Either a b
Right t
decoded
decodePacket :: ByteString.Lazy.ByteString -> PacketOf Message
decodePacket :: ByteString -> PacketOf Message
decodePacket = Get (PacketOf Message) -> ByteString -> PacketOf Message
forall a. Get a -> ByteString -> a
Binary.runGet Get (PacketOf Message)
get_packet
decodePacket_strict :: ByteString.Char8.ByteString -> PacketOf Message
decodePacket_strict :: ByteString -> PacketOf Message
decodePacket_strict = Get (PacketOf Message) -> ByteString -> PacketOf Message
forall a. Get a -> ByteString -> a
Binary.runGet Get (PacketOf Message)
get_packet (ByteString -> PacketOf Message)
-> (ByteString -> ByteString) -> ByteString -> PacketOf Message
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ByteString] -> ByteString
ByteString.Lazy.fromChunks ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [])
decodeMessageOr :: ByteString.Lazy.ByteString -> Either String Message
decodeMessageOr :: ByteString -> Either String Message
decodeMessageOr = Get Message -> ByteString -> Either String Message
forall t. Get t -> ByteString -> Either String t
runDecoder Get Message
get_message
decodeBundleOr :: ByteString.Lazy.ByteString -> Either String Bundle
decodeBundleOr :: ByteString -> Either String (BundleOf Message)
decodeBundleOr = Get (BundleOf Message)
-> ByteString -> Either String (BundleOf Message)
forall t. Get t -> ByteString -> Either String t
runDecoder Get (BundleOf Message)
get_bundle
decodePacketOr :: ByteString.Lazy.ByteString -> Either String Packet
decodePacketOr :: ByteString -> Either String (PacketOf Message)
decodePacketOr = Get (PacketOf Message)
-> ByteString -> Either String (PacketOf Message)
forall t. Get t -> ByteString -> Either String t
runDecoder Get (PacketOf Message)
get_packet