hosc-0.21: 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).

>>> map escapeString ["str", "str ", "st r", "s\tr", "s\\tr", "\nstr"]
["str","str\\ ","st\\ r","s\\\tr","s\\\\tr","\\\nstr"]

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

Printer for Datum.

>>> let 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.

>>> let 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
"/addr ,ihfdsbm 1 2 3.0 4.0 five 0607 08090a0b"
>>> let 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
["/c_set ,if 1 2.3","/s_new ,siii sine -1 1 1"]

showBundle :: FpPrecision -> BundleOf Message -> String Source #

Printer for Bundle

>>> let 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
"#bundle 4294967296 2 /c_set ,ifhd 1 2.3 4 5.6 /memset ,sb addr 0708"

showPacket :: FpPrecision -> PacketOf Message -> 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 (BundleOf Message) Source #

Bundle parser.

packetP :: P (PacketOf Message) Source #

Packet parser.

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

Run parser.

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

Run datum parser.

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

parseMessage :: String -> Message Source #

Run message parser.

>>> let 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
True

parseBundle :: String -> BundleOf Message Source #

Run bundle parser.

>>> let 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
True

parsePacket :: String -> PacketOf Message Source #

Run packet parser.

>>> let 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
True