module Sound.OSC.Datum where
import Data.Int 
import Data.List 
import Data.Maybe 
import Data.Word 
import Numeric 
import Text.Printf 
import Text.Read 
import qualified Data.ByteString.Lazy as Lazy 
import qualified Data.ByteString.Char8 as Char8 
import qualified Sound.OSC.Time as Time 
type Datum_Type = Char
type ASCII = Char8.ByteString
ascii :: String -> ASCII
ascii = Char8.pack
ascii_to_string :: ASCII -> String
ascii_to_string = Char8.unpack
type BLOB = Lazy.ByteString
blob_pack ::  [Word8] -> BLOB
blob_pack = Lazy.pack
blob_unpack :: BLOB -> [Word8]
blob_unpack = Lazy.unpack
data MIDI = MIDI !Word8 !Word8 !Word8 !Word8
    deriving (Eq,Show,Read)
data Datum = Int32 {d_int32 :: !Int32}
           | Int64 {d_int64 :: !Int64}
           | Float {d_float :: !Float}
           | Double {d_double :: !Double}
           | ASCII_String {d_ascii_string :: !ASCII}
           | Blob {d_blob :: !BLOB}
           | TimeStamp {d_timestamp :: !Time.Time} 
           | Midi {d_midi :: !MIDI}
             deriving (Eq,Read,Show)
osc_types_required :: [(Datum_Type,String)]
osc_types_required =
    [('i',"Int32")
    ,('f',"Float")
    ,('s',"ASCII_String") 
    ,('b',"ByteArray") 
    ]
osc_types_optional :: [(Datum_Type,String)]
osc_types_optional =
    [('h',"Int64")
    ,('t',"TimeStamp")
    ,('d',"Double")
    
    
    
    ,('m',"MIDI")
    
    
    
    
    
    
    ]
osc_types :: [(Datum_Type,String)]
osc_types = osc_types_required ++ osc_types_optional
osc_type_name :: Datum_Type -> Maybe String
osc_type_name c = lookup c osc_types
osc_type_name_err :: Datum_Type -> String
osc_type_name_err = fromMaybe (error "osc_type_name") . osc_type_name
datum_tag :: Datum -> Datum_Type
datum_tag d =
    case d of
      Int32 _ -> 'i'
      Int64 _ -> 'h'
      Float _ -> 'f'
      Double _ -> 'd'
      ASCII_String _ -> 's'
      Blob _ -> 'b'
      TimeStamp _ -> 't'
      Midi _ -> 'm'
datum_type_name :: Datum -> (Datum_Type,String)
datum_type_name d = let c = datum_tag d in (c,osc_type_name_err c)
datum_integral :: Integral i => Datum -> Maybe i
datum_integral d =
    case d of
      Int32 x -> Just (fromIntegral x)
      Int64 x -> Just (fromIntegral x)
      _ -> Nothing
datum_floating :: Floating n => Datum -> Maybe n
datum_floating d =
    case d of
      Int32 n -> Just (fromIntegral n)
      Int64 n -> Just (fromIntegral n)
      Float n -> Just (realToFrac n)
      Double n -> Just (realToFrac n)
      TimeStamp n -> Just (realToFrac n)
      _ -> Nothing
int32 :: Integral n => n -> Datum
int32 = Int32 . fromIntegral
int64 :: Integral n => n -> Datum
int64 = Int64 . fromIntegral
float :: Real n => n -> Datum
float = Float . realToFrac
double :: Real n => n -> Datum
double = Double . realToFrac
string :: String -> Datum
string = ASCII_String . Char8.pack
midi :: (Word8,Word8,Word8,Word8) -> Datum
midi (p,q,r,s) = Midi (MIDI p q r s)
descriptor :: [Datum] -> ASCII
descriptor l = Char8.pack (',' : map datum_tag l)
descriptor_tags :: ASCII -> ASCII
descriptor_tags = Char8.drop 1
type FP_Precision = Maybe Int
floatPP :: RealFloat n => Maybe Int -> n -> String
floatPP p n =
    let s = showFFloat p n ""
        s' = dropWhile (== '0') (reverse s)
    in case s' of
         '.':_ -> reverse ('0' : s')
         _ -> reverse s'
timePP :: FP_Precision -> Time.Time -> String
timePP = floatPP
vecPP :: Show a => [a] -> String
vecPP v = '<' : intercalate "," (map show v) ++ ">"
blobPP :: BLOB -> String
blobPP = unwords . map (printf "%02X") . Lazy.unpack
datumPP :: FP_Precision -> Datum -> String
datumPP p d =
    case d of
      Int32 n -> show n
      Int64 n -> show n
      Float n -> floatPP p n
      Double n -> floatPP p n
      ASCII_String s -> show (Char8.unpack s)
      Blob s -> blobPP s
      TimeStamp t -> timePP p t
      Midi (MIDI b1 b2 b3 b4) -> vecPP [b1,b2,b3,b4]
datum_pp_typed :: FP_Precision -> Datum -> String
datum_pp_typed fp d = datumPP fp d ++ ":" ++ snd (datum_type_name d)
parse_datum :: Datum_Type -> String -> Maybe Datum
parse_datum ty =
    case ty of
      'i' -> fmap Int32 . readMaybe
      'h' -> fmap Int64 . readMaybe
      'f' -> fmap Float . readMaybe
      'd' -> fmap Double . readMaybe
      's' -> fmap (ASCII_String . Char8.pack) . readMaybe
      'b' -> fmap (Blob . blob_pack) . readMaybe
      't' -> error "parse_datum: timestamp not implemented"
      'm' -> fmap midi . readMaybe
      _ -> error "parse_datum: unknown type"
parse_datum_err :: Datum_Type -> String -> Datum
parse_datum_err ty = fromMaybe (error "parse_datum") . parse_datum ty