hosc-0.20: Haskell Open Sound Control
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Osc.Text

Contents

Description

A simple and unambigous text encoding for Osc.

Synopsis

Documentation

type FpPrecision = Maybe Int Source #

Precision value for floating point numbers.

showFloatWithPrecision :: RealFloat n => FpPrecision -> n -> String Source #

Variant of showFFloat that deletes trailing zeros.

map (showFloatWithPrecision (Just 4)) [1, 2.0, pi] == ["1.0", "2.0", "3.1416"]

showBytes :: [Int] -> String Source #

Hex encoded byte sequence.

showBytes [0, 15, 16, 144, 255] == "000f1090ff"

escapeString :: String -> String Source #

Escape whites space (space, tab, newline) and the escape character (backslash).

mapM_ (putStrLn .  escapeString) ["str", "str ", "st r", "s\tr", "s\\tr", "\nstr"]

showDatum :: FpPrecision -> Datum -> String Source #

Printer for Datum.

aDatumSeq = [Int32 1,Float 1.2,string "str",midi (0,0x90,0x40,0x60),blob [12,16], TimeStamp 100.0]
map (showDatum (Just 5)) aDatumSeq == ["1","1.2","str","00904060","0c10","429496729600"]

showMessage :: FpPrecision -> Message -> String Source #

Printer for Message.

aMessage = Message "/addr" [Int32 1, Int64 2, Float 3, Double 4, string "five", blob [6, 7], midi (8, 9, 10, 11)]
showMessage (Just 4) aMessage
aMessageSeq = [Message "/c_set" [Int32 1, Float 2.3], Message "/s_new" [string "sine", Int32 (-1), Int32 1, Int32 1]]
map (showMessage (Just 4)) aMessageSeq

showBundle :: FpPrecision -> Bundle -> String Source #

Printer for Bundle

aBundle = Bundle 1 [Message "/c_set" [Int32 1, Float 2.3, Int64 4, Double 5.6], Message "/memset" [string "addr", blob [7, 8]]]
showBundle (Just 4) aBundle

showPacket :: FpPrecision -> Packet -> String Source #

Printer for Packet.

Parser

type P a = GenParser Char () a Source #

A character parser with no user state.

(>>~) :: Monad m => m t -> m u -> m t Source #

Run p then q, returning result of p.

lexemeP :: P t -> P t Source #

p as lexeme, i.e. consuming any trailing white space.

stringCharP :: P Char Source #

Any non-space character. Allow escaped space.

stringP :: P String Source #

Parser for string.

oscAddressP :: P String Source #

Parser for Osc address.

oscSignatureP :: P String Source #

Parser for Osc signature.

digitP :: P Char Source #

Parser for decimal digit.

allowNegativeP :: Num n => P n -> P n Source #

nonNegativeIntegerP :: (Integral n, Read n) => P n Source #

Parser for non-negative integer.

integerP :: (Integral n, Read n) => P n Source #

Parser for integer.

nonNegativeFloatP :: (Fractional n, Read n) => P n Source #

Parser for non-negative float.

floatP :: (Fractional n, Read n) => P n Source #

Parser for non-negative float.

hexdigitP :: P Char Source #

Parser for hexadecimal digit.

byteP :: (Integral n, Read n) => P n Source #

Byte parser.

byteSeqP :: (Integral n, Read n) => P [n] Source #

Byte sequence parser.

datumP :: Char -> P Datum Source #

Datum parser.

messageP :: P Message Source #

Message parser.

bundleTagP :: P String Source #

Bundle tag parser.

bundleP :: P Bundle Source #

Bundle parser.

packetP :: P Packet Source #

Packet parser.

runP :: P t -> String -> t Source #

Run parser.

parseDatum :: Char -> String -> Datum Source #

Run datum parser.

parseDatum 'i' "-1" == Int32 (-1)
parseDatum 'f' "-2.3" == Float (-2.3)

parseMessage :: String -> Message Source #

Run message parser.

aMessageSeq = [Message "/c_set" [Int32 1, Float 2.3, Int64 4, Double 5.6], Message "/memset" [string "addr", blob [7, 8]]]
map (parseMessage . showMessage (Just 4)) aMessageSeq  == aMessageSeq

parseBundle :: String -> Bundle Source #

Run bundle parser.

aBundle = Bundle 1 [Message "/c_set" [Int32 1, Float 2.3, Int64 4, Double 5.6], Message "/memset" [string "addr", blob [7, 8]]]
parseBundle (showBundle (Just 4) aBundle) == aBundle

parsePacket :: String -> Packet Source #

Run packet parser.

aPacket = Packet_Bundle (Bundle 1 [Message "/c_set" [Int32 1, Float 2.3, Int64 4, Double 5.6], Message "/memset" [string "addr", blob [7, 8]]])
parsePacket (showPacket (Just 4) aPacket) == aPacket