Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Data type for OSC datum.
Synopsis
- type Datum_Type = Char
- type ASCII = ByteString
- ascii :: String -> ASCII
- ascii_to_string :: ASCII -> String
- type BLOB = ByteString
- blob_pack :: [Word8] -> BLOB
- blob_unpack :: BLOB -> [Word8]
- data MIDI = MIDI !Word8 !Word8 !Word8 !Word8
- data Datum
- osc_types_required :: [(Datum_Type, String)]
- osc_types_optional :: [(Datum_Type, String)]
- osc_types :: [(Datum_Type, String)]
- osc_type_name :: Datum_Type -> Maybe String
- osc_type_name_err :: Datum_Type -> String
- datum_tag :: Datum -> Datum_Type
- datum_type_name :: Datum -> (Datum_Type, String)
- datum_integral :: Integral i => Datum -> Maybe i
- datum_floating :: Floating n => Datum -> Maybe n
- 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
- descriptor :: [Datum] -> ASCII
- descriptor_tags :: ASCII -> ASCII
- type FP_Precision = Maybe Int
- floatPP :: RealFloat n => Maybe Int -> n -> String
- timePP :: FP_Precision -> Time -> String
- vecPP :: Show a => [a] -> String
- blobPP :: BLOB -> String
- datumPP :: FP_Precision -> Datum -> String
- datum_pp_typed :: FP_Precision -> Datum -> String
- parse_datum :: Datum_Type -> String -> Maybe Datum
- parse_datum_err :: Datum_Type -> String -> Datum
Datum
type Datum_Type = Char Source #
Type enumerating Datum categories.
type ASCII = ByteString Source #
Type for ASCII strings (strict Lexeme
8 ByteString
).
Four-byte midi message: port-id, status-byte, data, data.
The basic elements of OSC messages.
Int32 | |
Int64 | |
Float | |
Double | |
ASCII_String | |
| |
Blob | |
TimeStamp | |
| |
Midi | |
Datum types
osc_types_required :: [(Datum_Type, String)] Source #
List of required data types (tag,name).
osc_types_optional :: [(Datum_Type, String)] Source #
List of optional data types (tag,name).
osc_types :: [(Datum_Type, String)] Source #
List of all data types (tag,name).
osc_type_name :: Datum_Type -> Maybe String Source #
Lookup name of type.
osc_type_name_err :: Datum_Type -> String Source #
Erroring variant.
datum_tag :: Datum -> Datum_Type Source #
Single character identifier of an OSC datum.
datum_type_name :: Datum -> (Datum_Type, String) Source #
Type and name of Datum
.
Generalised element access
Constructors
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 (Char8.pack "string")
Descriptor
descriptor :: [Datum] -> ASCII Source #
Message argument types are given by a descriptor.
descriptor [Int32 1,Float 1,string "1"] == ascii ",ifs"
descriptor_tags :: ASCII -> ASCII Source #
Descriptor tags are comma
prefixed.
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)] map (datumPP (Just 5)) d == ["1","1.2","\"str\"","<0,144,64,96>"]
datum_pp_typed :: FP_Precision -> Datum -> String Source #
Variant of datumPP
that appends the datum_type_name
.
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 (blob_pack [112,105])) parse_datum 'm' "(0,144,60,90)" == Just (midi (0,144,60,90))
parse_datum_err :: Datum_Type -> String -> Datum Source #
Erroring variant of parse_datum
.