module Sound.OSC.Coding.Decode.Binary
    (get_packet
    ,decodeMessage
    ,decodeBundle
    ,decodePacket
    ,decodePacket_strict) where
import Control.Applicative 
import Control.Monad 
import qualified Data.Binary.Get as G 
import qualified Data.Binary.IEEE754 as I 
import qualified Data.ByteString.Char8 as S.C 
import qualified Data.ByteString.Lazy as B 
import qualified Data.ByteString.Lazy.Char8 as C 
import Data.Int 
import Data.Word 
import qualified Sound.OSC.Coding.Byte as Byte 
import Sound.OSC.Coding.Convert 
import Sound.OSC.Datum 
import Sound.OSC.Packet 
import qualified Sound.OSC.Time as Time 
getInt32be :: G.Get Int32
getInt32be = word32_to_int32 <$> G.getWord32be
getInt64be :: G.Get Int64
getInt64be = word64_to_int64 <$> G.getWord64be
get_string :: G.Get String
get_string = do
    s <- G.getLazyByteStringNul
    G.skip (int64_to_int (Byte.align (B.length s + 1)))
    return $ C.unpack s
get_ascii :: G.Get ASCII
get_ascii = do
    s <- G.getLazyByteStringNul
    G.skip (int64_to_int (Byte.align (B.length s + 1)))
    return (S.C.pack (C.unpack s))
get_bytes :: Word32 -> G.Get B.ByteString
get_bytes n = do
    b <- G.getLazyByteString (word32_to_int64 n)
    if n /= int64_to_word32 (B.length b)
        then fail "get_bytes: end of stream"
        else G.skip (word32_to_int (Byte.align n))
    return b
get_datum :: Datum_Type -> G.Get Datum
get_datum ty =
    case ty of
      'i' -> Int32 <$> getInt32be
      'h' -> Int64 <$> getInt64be
      'f' -> Float <$> I.getFloat32be
      'd' -> Double <$> I.getFloat64be
      's' -> ASCII_String <$> get_ascii
      'b' -> Blob   <$> (get_bytes =<< G.getWord32be)
      't' -> TimeStamp <$> Time.ntpi_to_ntpr <$> G.getWord64be
      'm' -> do b0 <- G.getWord8
                b1 <- G.getWord8
                b2 <- G.getWord8
                b3 <- G.getWord8
                return $ Midi (MIDI b0 b1 b2 b3)
      _ -> fail ("get_datum: illegal type " ++ show ty)
get_message :: G.Get Message
get_message = do
    cmd <- get_string
    dsc <- get_ascii
    case S.C.unpack dsc of
        ',':tags -> do
            arg <- mapM get_datum tags
            return $ Message cmd arg
        e -> fail ("get_message: invalid type descriptor string: " ++ e)
get_message_seq :: G.Get [Message]
get_message_seq = do
    b <- G.isEmpty
    if b
        then return []
        else do
            p <- flip G.isolate get_message . word32_to_int =<< G.getWord32be
            ps <- get_message_seq
            return (p:ps)
get_bundle :: G.Get Bundle
get_bundle = do
    h <- G.getByteString (S.C.length Byte.bundleHeader_strict)
    when (h /= Byte.bundleHeader_strict) (fail "get_bundle: not a bundle")
    t <- Time.ntpi_to_ntpr <$> G.getWord64be
    ps <- get_message_seq
    return $ Bundle t ps
get_packet :: G.Get Packet
get_packet = (Packet_Bundle <$> get_bundle) <|> (Packet_Message <$> get_message)
{-# INLINE decodeMessage #-}
{-# INLINE decodeBundle #-}
{-# INLINE decodePacket #-}
{-# INLINE decodePacket_strict #-}
decodeMessage :: B.ByteString -> Message
decodeMessage = G.runGet get_message
decodeBundle :: B.ByteString -> Bundle
decodeBundle = G.runGet get_bundle
decodePacket :: B.ByteString -> Packet
decodePacket = G.runGet get_packet
decodePacket_strict :: S.C.ByteString -> Packet
decodePacket_strict = G.runGet get_packet . B.fromChunks . (:[])