| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Sound.OSC.Type
Description
Alegbraic data types for OSC datum and packets.
- type Time = Double
- immediately :: Time
- type Datum_Type = Char
- type ASCII = ByteString
- ascii :: String -> ASCII
- ascii_to_string :: ASCII -> String
- data MIDI = MIDI Word8 Word8 Word8 Word8
- data Datum
- datum_tag :: Datum -> Datum_Type
- datum_integral :: Integral i => Datum -> Maybe i
- datum_floating :: Floating n => Datum -> Maybe n
- class Datem a where
- int32 :: Integral n => n -> Datum
- int64 :: Integral n => n -> Datum
- float :: Real n => n -> Datum
- double :: Real n => n -> Datum
- string :: String -> Datum
- midi :: (Word8, Word8, Word8, Word8) -> Datum
- type Address_Pattern = String
- data Message = Message {}
- message :: Address_Pattern -> [Datum] -> Message
- descriptor :: [Datum] -> ASCII
- descriptor_tags :: ASCII -> ASCII
- data Bundle = Bundle {- bundleTime :: Time
- bundleMessages :: [Message]
 
- bundle :: Time -> [Message] -> Bundle
- data Packet- = Packet_Message { }
- | Packet_Bundle { }
 
- p_bundle :: Time -> [Message] -> Packet
- p_message :: Address_Pattern -> [Datum] -> Packet
- packetTime :: Packet -> Time
- packetMessages :: Packet -> [Message]
- packet_to_bundle :: Packet -> Bundle
- packet_to_message :: Packet -> Maybe Message
- packet_is_immediate :: Packet -> Bool
- at_packet :: (Message -> a) -> (Bundle -> a) -> Packet -> a
- message_has_address :: Address_Pattern -> Message -> Bool
- bundle_has_address :: Address_Pattern -> Bundle -> Bool
- packet_has_address :: Address_Pattern -> Packet -> Bool
- type FP_Precision = Maybe Int
- floatPP :: RealFloat n => Maybe Int -> n -> String
- timePP :: FP_Precision -> Time -> String
- vecPP :: Show a => [a] -> String
- datumPP :: FP_Precision -> Datum -> String
- messagePP :: FP_Precision -> Message -> String
- bundlePP :: FP_Precision -> Bundle -> String
- packetPP :: FP_Precision -> Packet -> String
- readMaybe :: Read a => String -> Maybe a
- parse_datum :: Datum_Type -> String -> Maybe Datum
Time
Constant indicating a bundle to be executed immediately.
Datum
type Datum_Type = Char Source
Type enumerating Datum categories.
type ASCII = ByteString Source
Type for ASCII strings (strict Char8 ByteString).
ascii_to_string :: ASCII -> String Source
Type-specialised unpack.
Four-byte midi message.
The basic elements of OSC messages.
Constructors
| Int32 | |
| Int64 | |
| Float | |
| Double | |
| ASCII_String | |
| Fields | |
| Blob | |
| Fields 
 | |
| TimeStamp | |
| Fields 
 | |
| Midi | |
datum_tag :: Datum -> Datum_Type Source
Single character identifier of an OSC datum.
datum_integral :: Integral i => Datum -> Maybe i Source
datum_floating :: Floating n => Datum -> Maybe n Source
Class for translating to and from Datum.  There are instances
 for the direct Datum field types.
d_put (1::Int32) == Int32 1 d_put (1::Int64) == Int64 1 d_put (1::Float) == Float 1 d_put (1::Double) == Double 1 d_put (C.pack "str") == ASCII_String (C.pack "str") d_put (B.pack [37,37]) == Blob (B.pack [37,37]) d_put (MIDI 0 0 0 0) == Midi (MIDI 0 0 0 0)
There are also instances for standard Haskell types.
d_put (1::Int) == Int64 1 d_put (1::Integer) == Int64 1
int32 :: Integral n => n -> Datum Source
Type generalised Int32.
int32 (1::Int32) == int32 (1::Integer) d_int32 (int32 (maxBound::Int32)) == maxBound int32 (((2::Int) ^ (64::Int))::Int) == Int32 0
int64 :: Integral n => n -> Datum Source
Type generalised Int64.
int64 (1::Int32) == int64 (1::Integer) d_int64 (int64 (maxBound::Int64)) == maxBound
float :: Real n => n -> Datum Source
Type generalised Float.
float (1::Int) == float (1::Double) floatRange (undefined::Float) == (-125,128) isInfinite (d_float (float (encodeFloat 1 256 :: Double))) == True
double :: Real n => n -> Datum Source
Type generalised Double.
double (1::Int) == double (1::Double) double (encodeFloat 1 256 :: Double) == Double 1.157920892373162e77
string :: String -> Datum Source
ASCII_String of pack.
string "string" == ASCII_String (C.pack "string")
Message
type Address_Pattern = String Source
OSC address pattern.  This is strictly an ASCII value, but it is
 very common to pattern match on addresses and matching on
 ByteString requires OverloadedStrings.
An OSC message.
Constructors
| Message | |
| Fields | |
message :: Address_Pattern -> [Datum] -> Message Source
Message constructor.  It is an error if the Address_Pattern
 doesn't conform to the OSC specification.
descriptor :: [Datum] -> ASCII Source
Message argument types are given by a descriptor.
C.unpack (descriptor [Int32 1,Float 1,string "1"]) == ",ifs"
descriptor_tags :: ASCII -> ASCII Source
Descriptor tags are comma prefixed.
Bundle
An OSC bundle.
Constructors
| Bundle | |
| Fields 
 | |
Packet
Constructors
| Packet_Message | |
| Fields | |
| Packet_Bundle | |
| Fields | |
p_message :: Address_Pattern -> [Datum] -> Packet Source
packetTime :: Packet -> Time Source
The Time of Packet, if the Packet is a Message this is
 immediately.
packet_to_bundle :: Packet -> Bundle Source
If Packet is a Message add immediately timestamp, else id.
packet_is_immediate :: Packet -> Bool Source
Is Packet immediate, ie. a Bundle with timestamp
 immediately, or a plain Message.
Address Query
message_has_address :: Address_Pattern -> Message -> Bool Source
Does Message have the specified Address_Pattern.
bundle_has_address :: Address_Pattern -> Bundle -> Bool Source
Do any of the Messages at Bundle have the specified
 Address_Pattern.
packet_has_address :: Address_Pattern -> Packet -> Bool Source
Does Packet have the specified Address_Pattern, ie.
 message_has_address or bundle_has_address.
Pretty printing
type FP_Precision = Maybe Int Source
Perhaps a precision value for floating point numbers.
floatPP :: RealFloat n => Maybe Int -> n -> String Source
Variant of showFFloat that deletes trailing zeros.
map (floatPP (Just 4)) [1,pi] == ["1.0","3.1416"]
timePP :: FP_Precision -> Time -> String Source
Pretty printer for Time.
timePP (Just 4) (1/3) == "0.3333"
datumPP :: FP_Precision -> Datum -> String Source
Pretty printer for Datum.
let d = [Int32 1,Float 1.2,string "str",midi (0,0x90,0x40,0x60)] in map datumPP d == ["1","1.2","\"str\"","<0,144,64,96>"]
Parser
parse_datum :: Datum_Type -> String -> Maybe Datum Source
Given Datum_Type attempt to parse Datum at String.
parse_datum 'i' "42" == Just (Int32 42) parse_datum 'h' "42" == Just (Int64 42) parse_datum 'f' "3.14159" == Just (Float 3.14159) parse_datum 'd' "3.14159" == Just (Double 3.14159) parse_datum 's' "\"pi\"" == Just (string "pi") parse_datum 'b' "[112,105]" == Just (Blob (B.pack [112,105])) parse_datum 'm' "(0,144,60,90)" == Just (midi (0,144,60,90))