-- | Optimised decode function for OSC packets.
module Sound.OSC.Coding.Decode.Binary
    (get_packet
    ,decodeMessage
    ,decodeBundle
    ,decodePacket
    ,decodePacket_strict) where

import Control.Applicative {- base -}
import Control.Monad {- base -}
import Data.Int {- base -}
import Data.Word {- base -}

import qualified Data.Binary.Get as G {- binary -}
import qualified Data.Binary.IEEE754 as I {- data-binary-ieee754 -}
import qualified Data.ByteString.Char8 as S.C {- bytestring -}
import qualified Data.ByteString.Lazy as B {- bytestring -}
import qualified Data.ByteString.Lazy.Char8 as C {- bytestring -}

import qualified Sound.OSC.Coding.Byte as Byte {- hosc -}
import Sound.OSC.Coding.Convert {- hosc -}
import Sound.OSC.Datum {- hosc -}
import Sound.OSC.Packet {- hosc -}
import qualified Sound.OSC.Time as Time {- hosc -}

-- | Get a 32 bit integer in big-endian byte order.
getInt32be :: G.Get Int32
getInt32be :: Get Int32
getInt32be = (Word32 -> Int32) -> Get Word32 -> Get Int32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Int32
word32_to_int32 Get Word32
G.getWord32be

-- | Get a 64 bit integer in big-endian byte order.
getInt64be :: G.Get Int64
getInt64be :: Get Int64
getInt64be = (Word64 -> Int64) -> Get Word64 -> Get Int64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word64 -> Int64
word64_to_int64 Get Word64
G.getWord64be

-- | Get an aligned OSC string.
get_string :: G.Get String
get_string :: Get String
get_string = do
    ByteString
s <- Get ByteString
G.getLazyByteStringNul
    Int -> Get ()
G.skip (Int64 -> Int
int64_to_int (Int64 -> Int64
forall i. (Num i, Bits i) => i -> i
Byte.align (ByteString -> Int64
B.length ByteString
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1)))
    String -> Get String
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> String
C.unpack ByteString
s)

-- | Get an aligned OSC string.
get_ascii :: G.Get ASCII
get_ascii :: Get ASCII
get_ascii = do
    ByteString
s <- Get ByteString
G.getLazyByteStringNul
    Int -> Get ()
G.skip (Int64 -> Int
int64_to_int (Int64 -> Int64
forall i. (Num i, Bits i) => i -> i
Byte.align (ByteString -> Int64
B.length ByteString
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1)))
    ASCII -> Get ASCII
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ASCII
S.C.pack (ByteString -> String
C.unpack ByteString
s))

-- | Get binary data prefixed by byte count.
get_bytes :: Word32 -> G.Get B.ByteString
get_bytes :: Word32 -> Get ByteString
get_bytes Word32
n = do
    ByteString
b <- Int64 -> Get ByteString
G.getLazyByteString (Word32 -> Int64
word32_to_int64 Word32
n)
    if Word32
n Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Int64 -> Word32
int64_to_word32 (ByteString -> Int64
B.length ByteString
b)
        then String -> Get ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"get_bytes: end of stream"
        else Int -> Get ()
G.skip (Word32 -> Int
word32_to_int (Word32 -> Word32
forall i. (Num i, Bits i) => i -> i
Byte.align Word32
n))
    ByteString -> Get ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
b

-- | Get an OSC datum.
get_datum :: Datum_Type -> G.Get Datum
get_datum :: Datum_Type -> Get Datum
get_datum Datum_Type
ty =
    case Datum_Type
ty of
      Datum_Type
'i' -> (Int32 -> Datum) -> Get Int32 -> Get Datum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> Datum
Int32 Get Int32
getInt32be
      Datum_Type
'h' -> (Int64 -> Datum) -> Get Int64 -> Get Datum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> Datum
Int64 Get Int64
getInt64be
      Datum_Type
'f' -> (Float -> Datum) -> Get Float -> Get Datum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Float -> Datum
Float Get Float
I.getFloat32be
      Datum_Type
'd' -> (Double -> Datum) -> Get Double -> Get Datum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Double -> Datum
Double Get Double
I.getFloat64be
      Datum_Type
's' -> (ASCII -> Datum) -> Get ASCII -> Get Datum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ASCII -> Datum
ASCII_String Get ASCII
get_ascii
      Datum_Type
'b' -> (ByteString -> Datum) -> Get ByteString -> Get Datum
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
G.getWord32be)
      Datum_Type
't' -> (Word64 -> Datum) -> Get Word64 -> Get Datum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double -> Datum
TimeStamp (Double -> Datum) -> (Word64 -> Double) -> Word64 -> Datum
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Double
Time.ntpi_to_ntpr) Get Word64
G.getWord64be
      Datum_Type
'm' -> do Word8
b0 <- Get Word8
G.getWord8
                Word8
b1 <- Get Word8
G.getWord8
                Word8
b2 <- Get Word8
G.getWord8
                Word8
b3 <- Get Word8
G.getWord8
                Datum -> Get Datum
forall (m :: * -> *) a. Monad m => a -> m a
return (MIDI -> Datum
Midi (Word8 -> Word8 -> Word8 -> Word8 -> MIDI
MIDI Word8
b0 Word8
b1 Word8
b2 Word8
b3))
      Datum_Type
_ -> String -> Get Datum
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"get_datum: illegal type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Datum_Type -> String
forall a. Show a => a -> String
show Datum_Type
ty)

-- | Get an OSC 'Message', fail if type descriptor is invalid.
get_message :: G.Get Message
get_message :: Get Message
get_message = do
    String
cmd <- Get String
get_string
    ASCII
dsc <- Get ASCII
get_ascii
    case ASCII -> String
S.C.unpack ASCII
dsc of
        Datum_Type
',':String
tags -> do
            [Datum]
arg <- (Datum_Type -> Get Datum) -> String -> Get [Datum]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Datum_Type -> Get Datum
get_datum String
tags
            Message -> Get Message
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> [Datum] -> Message
Message String
cmd [Datum]
arg)
        String
e -> String -> Get Message
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 a sequence of OSC 'Message's, each one headed by its length.
get_message_seq :: G.Get [Message]
get_message_seq :: Get [Message]
get_message_seq = do
    Bool
b <- Get Bool
G.isEmpty
    if Bool
b
        then [Message] -> Get [Message]
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
G.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
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
G.getWord32be
            [Message]
ps <- Get [Message]
get_message_seq
            [Message] -> Get [Message]
forall (m :: * -> *) a. Monad m => a -> m a
return (Message
pMessage -> [Message] -> [Message]
forall a. a -> [a] -> [a]
:[Message]
ps)

-- | Get a bundle. Fail if bundle header is not found in packet.
get_bundle :: G.Get Bundle
get_bundle :: Get Bundle
get_bundle = do
    ASCII
h <- Int -> Get ASCII
G.getByteString (ASCII -> Int
S.C.length ASCII
Byte.bundleHeader_strict)
    Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (ASCII
h ASCII -> ASCII -> Bool
forall a. Eq a => a -> a -> Bool
/= ASCII
Byte.bundleHeader_strict) (String -> Get ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"get_bundle: not a bundle")
    Double
t <- (Word64 -> Double) -> Get Word64 -> Get Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word64 -> Double
Time.ntpi_to_ntpr Get Word64
G.getWord64be
    ([Message] -> Bundle) -> Get [Message] -> Get Bundle
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Double -> [Message] -> Bundle
Bundle Double
t) Get [Message]
get_message_seq

-- | Get an OSC 'Packet'.
get_packet :: G.Get Packet
get_packet :: Get Packet
get_packet = (Bundle -> Packet) -> Get Bundle -> Get Packet
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bundle -> Packet
Packet_Bundle Get Bundle
get_bundle Get Packet -> Get Packet -> Get Packet
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Message -> Packet) -> Get Message -> Get Packet
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Message -> Packet
Packet_Message Get Message
get_message

{-# INLINE decodeMessage #-}
{-# INLINE decodeBundle #-}
{-# INLINE decodePacket #-}
{-# INLINE decodePacket_strict #-}

{- | Decode an OSC 'Message' from a lazy ByteString.

> let b = B.pack [47,103,95,102,114,101,101,0,44,105,0,0,0,0,0,0]
> decodeMessage b == Message "/g_free" [Int32 0]
-}
decodeMessage :: B.ByteString -> Message
decodeMessage :: ByteString -> Message
decodeMessage = Get Message -> ByteString -> Message
forall a. Get a -> ByteString -> a
G.runGet Get Message
get_message

-- | Decode an OSC 'Bundle' from a lazy ByteString.
decodeBundle :: B.ByteString -> Bundle
decodeBundle :: ByteString -> Bundle
decodeBundle = Get Bundle -> ByteString -> Bundle
forall a. Get a -> ByteString -> a
G.runGet Get Bundle
get_bundle

{- | Decode an OSC packet from a lazy ByteString.

> let b = B.pack [47,103,95,102,114,101,101,0,44,105,0,0,0,0,0,0]
> decodePacket b == Packet_Message (Message "/g_free" [Int32 0])
-}
decodePacket :: B.ByteString -> Packet
decodePacket :: ByteString -> Packet
decodePacket = Get Packet -> ByteString -> Packet
forall a. Get a -> ByteString -> a
G.runGet Get Packet
get_packet

-- | Decode an OSC packet from a strict Char8 ByteString.
decodePacket_strict :: S.C.ByteString -> Packet
decodePacket_strict :: ASCII -> Packet
decodePacket_strict = Get Packet -> ByteString -> Packet
forall a. Get a -> ByteString -> a
G.runGet Get Packet
get_packet (ByteString -> Packet) -> (ASCII -> ByteString) -> ASCII -> Packet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ASCII] -> ByteString
B.fromChunks ([ASCII] -> ByteString)
-> (ASCII -> [ASCII]) -> ASCII -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ASCII -> [ASCII] -> [ASCII]
forall a. a -> [a] -> [a]
:[])