hosc-json-0.16: Haskell Open Sound Control JSON Serialisation

Safe HaskellNone
LanguageHaskell98

Sound.OSC.Type.JSON

Contents

Description

Encoding and decoding of OSC types as JSON values.

Synopsis

Library variant

type Value = Value Source #

The JSON value type.

String translation

encode_json_str :: Value -> String Source #

String variant of encode_json.

decode_json_str :: String -> Maybe Value Source #

String variant of decode_json.

import Sound.OSChar8.Type.JSON
let j = decode_json_str "[\"/n_set\",-1,\"c1\",66]"
fmap decode_message j

Encoding

type Number = Either Integer Double Source #

JSON numbers are Either Integer or Double.

encode_timestamp :: Time -> Value Source #

Encode TimeStamp data (Time), ie. the hosc real-valued NRT representation.

encode_midi :: MIDI -> Value Source #

Encode Midi data (Word8 tuple).

encode_datum :: Datum -> Value Source #

Datum encoder. The encoding is shallow, Int, Float and Double are all sent to Number. Blob, TimeStamp and Midi are tagged.

let {t = [(int32 0,"0")
         ,(int64 0,"0")
         ,(float 0.0,"0.0")
         ,(double 0.1,"0.1")
         ,(string "s","\"s\"")
         ,(Blob (Data.ByteString.Lazy.pack [0,1]),"{\"blob\":[0,1]}")
         ,(TimeStamp 0.0,"{\"timestamp\":0.0}")
         ,(midi (0,1,2,3),"{\"midi\":[0,1,2,3]}")]
    ;r = map (\(d,s) -> encode_json_str (encode_datum d) == s) t}
in all id r == True

encode_message :: Message -> Value Source #

Message encoder, the representation is a flat array of address and then arguments.

let m = message "/m" [Int32 0,Float 1,string "s"]
in encode_json_str (encode_message m)
import Sound.SC3
encode_json_str (encode_message (n_free [0])) == "[\"/n_free\",0]"

encode_bundle :: Bundle -> Value Source #

Bundle encoder, the representation is a flat array of #bundle tag, TimeStamp and then message arrays.

let b = bundle 0 [message "/m" []]
in encode_json_str (encode_bundle b)
let {b = bundle 0 [c_set1 3 4,n_free [0]]
    ;r = "[\"#bundle\",{\"timestamp\":0.0}" ++
         ",[\"/c_set\",3,4.0],[\"/n_free\",0]]"}
in encode_json_str (encode_bundle b) == r

encode_packet :: Packet -> Value Source #

Packet encoder.

Decoder

decode_message :: Value -> Maybe Message Source #

Decode Message.

let m = message "/m" [Int32 1,Float 1]
in decode_message (encode_message m) == Just m

decode_bundle :: Value -> Maybe Bundle Source #

Decode Bundle.

let b = bundle 0.0 [message "/m" [Int32 1,Float 1]]
in decode_bundle (encode_bundle b) == Just b
let {b = bundle 0 [c_set1 3 4,n_free [0]]
    ;j = encode_bundle b}
in (b,decode_bundle j)

decode_packet :: Value -> Maybe Packet Source #

Decode Packet.