candid-0.1: Candid integration
Safe HaskellNone
LanguageHaskell2010

Codec.Candid

Description

This module provides preliminary Haskell supprot for decoding and encoding the Candid data format. See https://github.com/dfinity/candid/blob/master/spec/Candid.md for the official Candid specification.

Warning: The interface of this library is still in flux, as we are yet learning the best idioms around Candid and Haskell.

Synopsis

Tutorial

Candid is inherently typed, so before encoding or decoding, you have to indicate the types to use. In most cases, you can use Haskell types for that:

Haskell types

The easiest way is to use this library is to use the canonical Haskell types. Any type that is an instance of Candid can be used:

>>> encode ([True, False], Just 100)
"DIDL\STXm~n|\STX\NUL\SOH\STX\SOH\NUL\SOH\228\NUL"
>>> decode (encode ([True, False], Just 100)) == Right ([True, False], Just 100)
True

Here, no type annotations are needed, the library can infer them from the types of the Haskell values. You can see the Candid types used using typeDesc and seqDesc:

>>> :type +d ([True, False], Just 100)
([True, False], Just 100) :: ([Bool], Maybe Integer)
>>> :set -XTypeApplications
>>> pretty (tieKnot (seqDesc @([Bool], Maybe Integer)))
(vec bool, opt int)

This library is integrated with the row-types library, so you can use their records directly:

>>> :set -XOverloadedLabels
>>> import Data.Row
>>> encode (#foo .== [True, False] .+ #bar .== Just 100)
"DIDL\ETXl\STX\211\227\170\STX\SOH\134\142\183\STX\STXn|m~\SOH\NUL\SOH\228\NUL\STX\SOH\NUL"
>>> :set -XDataKinds -XTypeOperators
>>> pretty (typeDesc @(Rec ("bar" .== Maybe Integer .+ "foo" .== [Bool])))
record {bar : opt int; foo : vec bool}

Custom types

If you want to use your own types directly, you have to declare an instance of the Candid type class. In this instance, you indicate a canonical Haskel type to describe how your type should serialize, and provide conversion functions to the corresponding AsCandid.

>>> :set -XTypeFamilies
>>> newtype Age = Age Integer
>>> :{
instance Candid Age where
    type AsCandid Age = Integer
    toCandid (Age i) = i
    fromCandid = Age
:}
>>> encode (Age 42)
"DIDL\NUL\SOH|*"

This is more or less the only way to introduce recursive types:

>>> data Peano = N | S Peano deriving (Show, Eq)
>>> :{
instance Candid Peano where
    type AsCandid Peano = Maybe Peano
    toCandid N = Nothing
    toCandid (S p) = Just p
    fromCandid Nothing = N
    fromCandid (Just p) = S p
:}
>>> peano = S (S (S N))
>>> encode peano
"DIDL\SOHn\NUL\SOH\NUL\SOH\SOH\SOH\NUL"

Generic types

Especially for Haskell record types, you can use magic involving generic types to create the Candid instance automatically. The best way is using the DerivingVia langauge extension,using the AsRecord new type to indicate that this strategy should be used:

>>> :set -XDerivingVia -XDeriveGeneric -XUndecidableInstances
>>> import GHC.Generics (Generic)
>>> :{
data SimpleRecord = SimpleRecord { foo :: [Bool], bar :: Maybe Integer }
    deriving Generic
    deriving Candid via (AsRecord SimpleRecord)
:}
>>> pretty (typeDesc @SimpleRecord)
record {bar : opt int; foo : vec bool}
>>> encode (SimpleRecord { foo = [True, False], bar = Just 100 })
"DIDL\ETXl\STX\211\227\170\STX\SOH\134\142\183\STX\STXn|m~\SOH\NUL\SOH\228\NUL\STX\SOH\NUL"

Unfortunately, this feature requires UndecidableInstances.

This works for variants too:

>>> :{
data Shape = Point () | Sphere Double | Rectangle (Double, Double)
    deriving Generic
    deriving Candid via (AsVariant Shape)
:}
>>> pretty (typeDesc @Shape)
variant {Point; Rectangle : record {0 : float64; 1 : float64}; Sphere : float64}
>>> encode (Rectangle (100,100))
"DIDL\STXk\ETX\176\200\244\205\ENQ\DEL\143\232\190\218\v\SOH\173\198\172\140\SIrl\STX\NULr\SOHr\SOH\NUL\SOH\NUL\NUL\NUL\NUL\NUL\NULY@\NUL\NUL\NUL\NUL\NUL\NULY@"

Because data constructors are capitalized in Haskell, you cannot derive enums or variants with lower-case names. Also, nullary data constructors are not supported by row-types, and thus here, even though they would nicely map onto variants with arguments of type 'null.

Candid services

Very likely you want to either implement or use whole Candid interfaces. In order to apply the encoding/decoding in one go, you can use fromCandidService and toCandidService. These convert between a raw service (RawService, takes a method name and bytes, and return bytes), and a typed CandidService (expressed as an Rec record).

Let us create a simple service:

>>> :set -XOverloadedLabels
>>> import Data.Row
>>> import Data.Row.Internal
>>> import Data.IORef
>>> c <- newIORef 0
>>> let service = #get .== (\() -> readIORef c) .+ #inc .== (\d -> modifyIORef c (d +))
>>> service .! #get $ ()
0
>>> service .! #inc $ 5
>>> service .! #get $ ()
5

For convenience, we name its type

>>> :t service
service :: Rec ('R '[ "get" ':-> (() -> IO Integer), "inc" ':-> (Integer -> IO ())])
>>> :set -XTypeOperators -XDataKinds -XFlexibleContexts
>>> type Interface = 'R '[ "get" ':-> (() -> IO Integer), "inc" ':-> (Integer -> IO ())]

Now we can turn this into a raw service operating on bytes:

>>> let raw = fromCandidService (error . show) error service
>>> raw (T.pack "get") (BS.pack "DUDE")
*** Exception: Failed reading: Expected magic bytes "DIDL", got "DUDE"
...
>>> raw (T.pack "get") (BS.pack "DIDL\NUL\NUL")
"DIDL\NUL\SOH|\ENQ"
>>> raw (T.pack "inc") (BS.pack "DIDL\NUL\SOH|\ENQ")
"DIDL\NUL\NUL"
>>> service .! #get $ ()
10

And finally, we can turn this raw function back into a typed interface:

>>> let service' :: Rec Interface = toCandidService error raw
>>> service .! #get $ ()
10
>>> service .! #inc $ 5
>>> service .! #get $ ()
15

In a real application you would more likely pass some networking code to toCandidService.

Importing Candid

In the example above, we wrote the type of the service in Haskell. But very likely you want to talk to a service whose is given to you in the form of a .did files, like

service : {
  get : () -> (int);
  inc : (int) -> ();
}

You can parse such a description:

>>> either error pretty $ parseDid "service : { get : () -> (int); inc : (int) -> (); }"
service : {get : () -> (int); inc : (int) -> ();}

And you can even, using Template Haskell, turn this into a proper Haskell type. The candid antiquotation produces a type, and expects a free type variable m for the monad you want to use.

>>> :set -XQuasiQuotes
>>> import Data.Row.Internal
>>> type Counter m = [candid| service : { get : () -> (int); inc : (int) -> (); } |]
>>> :info Counter
type Counter :: (* -> *) -> Row *
type Counter m = ("get" .== (() -> m Integer)) .+ ("inc" .== (Integer -> m ())) :: Row *
...

You can then use this with toCandidService to talk to a service.

If you want to read the description from a .did file, you can use candidFile.

If this encounters a Candid type definition, it will just inline them. This means that cyclic type definitions are not supported.

Dynamic use

Sometimes one needs to interact with Candid in a dynamic way, without static type information.

This library allows the parsing and pretty-printing of candid values. The binary value was copied from above:

>>> import Data.Row
>>> :set -XDataKinds -XTypeOperators
>>> let bytes = encode (#bar .== Just 100 .+ #foo .== [True,False])
>>> let Right vs = decodeVals bytes
>>> pretty vs
(record {4895187 = opt +100; 5097222 = vec {true; false}})

As you can see, the binary format does not preserve the field names. Future versions of this library will allow you to specify the (dynamic) Type at which you want to decode these values, to overcome that problem.

Conversely, you can encode from the textual representation:

>>> let Right bytes = encodeTextual "record { foo = vec { true; false }; bar = opt 100 }"
>>> bytes
"DIDL\ETXl\STX\211\227\170\STX\STX\134\142\183\STX\SOHm~n}\SOH\NUL\SOHd\STX\SOH\NUL"
>>> decode @(Rec ("bar" .== Maybe Integer .+ "foo" .== [Bool])) bytes
Right (#bar .== Just 100 .+ #foo .== [True,False])

This function does not support the full textual format yet; in particular type annotation can only be used around number literals.

Missing features

  • Generating interface descriptions (.did files) from Haskell functions
  • Service and function types
  • Future types
  • Parsing the textual representation dynamically against an expected type
  • Method annotations in service types

Reference

Encoding and decoding

encode :: CandidArg a => a -> ByteString Source #

Encode based on Haskell type

encodeBuilder :: forall a. CandidArg a => a -> Builder Source #

Encode to a Builder based on Haskell type

decode :: forall a. CandidArg a => ByteString -> Either String a Source #

Decode to Haskell type

Type classes

class (Typeable a, CandidVal (AsCandid a)) => Candid a where Source #

The class of Haskell types that can be converted to Candid.

You can create intances of this class for your own types, see the tutorial above for examples. The default instance is mostly for internal use.

Minimal complete definition

Nothing

Associated Types

type AsCandid a Source #

type AsCandid a = a

Methods

toCandid :: a -> AsCandid a Source #

default toCandid :: a ~ AsCandid a => a -> AsCandid a Source #

fromCandid :: AsCandid a -> a Source #

default fromCandid :: a ~ AsCandid a => AsCandid a -> a Source #

Instances

Instances details
Candid Bool Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Bool Source #

Candid Double Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Double Source #

Candid Float Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Float Source #

Candid Int8 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Int8 Source #

Candid Int16 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Int16 Source #

Candid Int32 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Int32 Source #

Candid Int64 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Int64 Source #

Candid Integer Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Integer Source #

Candid Natural Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Natural Source #

Candid Word8 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Word8 Source #

Candid Word16 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Word16 Source #

Candid Word32 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Word32 Source #

Candid Word64 Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Word64 Source #

Candid () Source #

Maybe a bit opinionated, but null seems to be the unit of Candid

Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid () Source #

Methods

toCandid :: () -> AsCandid () Source #

fromCandid :: AsCandid () -> () Source #

Candid Void Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Void Source #

Candid ByteString Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid ByteString Source #

Candid ByteString Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid ByteString Source #

Candid Text Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Text Source #

Candid Principal Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Principal Source #

Candid Reserved Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Reserved Source #

Candid a => Candid [a] Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid [a] Source #

Methods

toCandid :: [a] -> AsCandid [a] Source #

fromCandid :: AsCandid [a] -> [a] Source #

Candid a => Candid (Maybe a) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (Maybe a) Source #

CandidRow r => Candid (Var r) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (Var r) Source #

Methods

toCandid :: Var r -> AsCandid (Var r) Source #

fromCandid :: AsCandid (Var r) -> Var r Source #

CandidRow r => Candid (Rec r) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (Rec r) Source #

Methods

toCandid :: Rec r -> AsCandid (Rec r) Source #

fromCandid :: AsCandid (Rec r) -> Rec r Source #

Candid a => Candid (Vector a) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (Vector a) Source #

CanBeCandidVariant a => Candid (AsVariant a) Source # 
Instance details

Defined in Codec.Candid.Generic

Associated Types

type AsCandid (AsVariant a) Source #

CanBeCandidRecord a => Candid (AsRecord a) Source # 
Instance details

Defined in Codec.Candid.Generic

Associated Types

type AsCandid (AsRecord a) Source #

(Candid a, Candid b) => Candid (Either a b) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (Either a b) Source #

Methods

toCandid :: Either a b -> AsCandid (Either a b) Source #

fromCandid :: AsCandid (Either a b) -> Either a b Source #

(Candid a, Candid b) => Candid (a, b) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b) Source #

Methods

toCandid :: (a, b) -> AsCandid (a, b) Source #

fromCandid :: AsCandid (a, b) -> (a, b) Source #

(Candid a, Candid b, Candid c) => Candid (a, b, c) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c) Source #

Methods

toCandid :: (a, b, c) -> AsCandid (a, b, c) Source #

fromCandid :: AsCandid (a, b, c) -> (a, b, c) Source #

(Candid a, Candid b, Candid c, Candid d) => Candid (a, b, c, d) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d) Source #

Methods

toCandid :: (a, b, c, d) -> AsCandid (a, b, c, d) Source #

fromCandid :: AsCandid (a, b, c, d) -> (a, b, c, d) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e) => Candid (a, b, c, d, e) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e) Source #

Methods

toCandid :: (a, b, c, d, e) -> AsCandid (a, b, c, d, e) Source #

fromCandid :: AsCandid (a, b, c, d, e) -> (a, b, c, d, e) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f) => Candid (a, b, c, d, e, f) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f) Source #

Methods

toCandid :: (a, b, c, d, e, f) -> AsCandid (a, b, c, d, e, f) Source #

fromCandid :: AsCandid (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g) => Candid (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g) Source #

Methods

toCandid :: (a, b, c, d, e, f, g) -> AsCandid (a, b, c, d, e, f, g) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h) => Candid (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h) -> AsCandid (a, b, c, d, e, f, g, h) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h, Candid i) => Candid (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h, i) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h, i) -> AsCandid (a, b, c, d, e, f, g, h, i) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h, Candid i, Candid j) => Candid (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h, i, j) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h, i, j) -> AsCandid (a, b, c, d, e, f, g, h, i, j) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h, Candid i, Candid j, Candid k) => Candid (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h, i, j, k) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h, i, j, k) -> AsCandid (a, b, c, d, e, f, g, h, i, j, k) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h, Candid i, Candid j, Candid k, Candid l) => Candid (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h, i, j, k, l) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h, i, j, k, l) -> AsCandid (a, b, c, d, e, f, g, h, i, j, k, l) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h, Candid i, Candid j, Candid k, Candid l, Candid m) => Candid (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h, Candid i, Candid j, Candid k, Candid l, Candid m, Candid n) => Candid (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(Candid a, Candid b, Candid c, Candid d, Candid e, Candid f, Candid g, Candid h, Candid i, Candid j, Candid k, Candid l, Candid m, Candid n, Candid o) => Candid (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

Methods

toCandid :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

fromCandid :: AsCandid (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

type CandidArg a = (CandidSeq (AsTuple a), Tuplable a) Source #

The class of types that can be used as Candid argument sequences. Essentially all types that are in Candid, but tuples need to be treated specially.

class Typeable a => CandidVal a Source #

The internal class of Haskell types that canonically map to Candid. You would add instances to the Candid type class.

Minimal complete definition

asType, toCandidVal', fromCandidVal'

Instances

Instances details
CandidVal Bool Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Double Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Float Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Int8 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Int16 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Int32 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Int64 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Integer Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Natural Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Word8 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Word16 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Word32 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Word64 Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal () Source # 
Instance details

Defined in Codec.Candid.Class

Methods

asType :: Type (Ref TypeRep Type)

toCandidVal' :: () -> Value

fromCandidVal' :: Value -> Either DeserializeError ()

fromMissingField :: Maybe ()

CandidVal Void Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal ByteString Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Text Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Principal Source # 
Instance details

Defined in Codec.Candid.Class

CandidVal Reserved Source # 
Instance details

Defined in Codec.Candid.Class

Candid a => CandidVal (Maybe a) Source # 
Instance details

Defined in Codec.Candid.Class

Methods

asType :: Type (Ref TypeRep Type)

toCandidVal' :: Maybe a -> Value

fromCandidVal' :: Value -> Either DeserializeError (Maybe a)

fromMissingField :: Maybe (Maybe a)

CandidRow r => CandidVal (Var r) Source # 
Instance details

Defined in Codec.Candid.Class

Methods

asType :: Type (Ref TypeRep Type)

toCandidVal' :: Var r -> Value

fromCandidVal' :: Value -> Either DeserializeError (Var r)

fromMissingField :: Maybe (Var r)

CandidRow r => CandidVal (Rec r) Source # 
Instance details

Defined in Codec.Candid.Class

Methods

asType :: Type (Ref TypeRep Type)

toCandidVal' :: Rec r -> Value

fromCandidVal' :: Value -> Either DeserializeError (Rec r)

fromMissingField :: Maybe (Rec r)

Candid a => CandidVal (Vector a) Source # 
Instance details

Defined in Codec.Candid.Class

Methods

asType :: Type (Ref TypeRep Type)

toCandidVal' :: Vector a -> Value

fromCandidVal' :: Value -> Either DeserializeError (Vector a)

fromMissingField :: Maybe (Vector a)

seqDesc :: forall a. CandidArg a => SeqDesc Source #

data SeqDesc Source #

Instances

Instances details
Pretty SeqDesc Source # 
Instance details

Defined in Codec.Candid.TypTable

Methods

pretty :: SeqDesc -> Doc ann #

prettyList :: [SeqDesc] -> Doc ann #

typeDesc :: forall a. Candid a => Type Void Source #

NB: This will loop with recursive types!

Special types

newtype Unary a Source #

A newtype to stand in for the unary tuple

Constructors

Unary 

Fields

Instances

Instances details
Eq a => Eq (Unary a) Source # 
Instance details

Defined in Codec.Candid.Tuples

Methods

(==) :: Unary a -> Unary a -> Bool #

(/=) :: Unary a -> Unary a -> Bool #

Show a => Show (Unary a) Source # 
Instance details

Defined in Codec.Candid.Tuples

Methods

showsPrec :: Int -> Unary a -> ShowS #

show :: Unary a -> String #

showList :: [Unary a] -> ShowS #

data Reserved Source #

Constructors

Reserved 

Instances

Instances details
Eq Reserved Source # 
Instance details

Defined in Codec.Candid.Data

Ord Reserved Source # 
Instance details

Defined in Codec.Candid.Data

Show Reserved Source # 
Instance details

Defined in Codec.Candid.Data

Candid Reserved Source # 
Instance details

Defined in Codec.Candid.Class

Associated Types

type AsCandid Reserved Source #

CandidVal Reserved Source # 
Instance details

Defined in Codec.Candid.Class

type AsCandid Reserved Source # 
Instance details

Defined in Codec.Candid.Class

Generics

newtype AsRecord a Source #

This newtype encodes a Haskell record type using generic programming. Best used with DerivingVia, as shown in the tutorial.

Constructors

AsRecord 

Fields

Instances

Instances details
CanBeCandidRecord a => Candid (AsRecord a) Source # 
Instance details

Defined in Codec.Candid.Generic

Associated Types

type AsCandid (AsRecord a) Source #

type AsCandid (AsRecord a) Source # 
Instance details

Defined in Codec.Candid.Generic

newtype AsVariant a Source #

This newtype encodes a Haskell data type as a variant using generic programming. Best used with DerivingVia, as shown in the tutorial.

Constructors

AsVariant 

Fields

Instances

Instances details
CanBeCandidVariant a => Candid (AsVariant a) Source # 
Instance details

Defined in Codec.Candid.Generic

Associated Types

type AsCandid (AsVariant a) Source #

type AsCandid (AsVariant a) Source # 
Instance details

Defined in Codec.Candid.Generic

Candid services

type CandidService m r = (Forall r (CandidMethod m), AllUniqueLabels r) Source #

A Candid service. The r describes the type of a Rec.

type RawService m = Text -> ByteString -> m ByteString Source #

A raw service, operating on bytes

toCandidService Source #

Arguments

:: forall m r. CandidService m r 
=> (forall a. String -> m a)

What to do if the raw service returns unparsable data

-> RawService m 
-> Rec r 

Turns a raw service (function operating on bytes) into a typed Candid service (a record of typed methods). The raw service is typically code that talks over the network.

fromCandidService Source #

Arguments

:: forall m r. CandidService m r 
=> (forall a. Text -> m a)

What to do if the method name does not exist

-> (forall a. String -> m a)

What to do when the caller provides unparsable data

-> Rec r 
-> RawService m 

Turns a typed candid service into a raw service. Typically used in a framework warpping Candid services.

Meta-programming

candid :: QuasiQuoter Source #

This quasi-quoter turns a Candid description into a Haskell type. It assumes a type variable m to be in scope.

candidFile :: QuasiQuoter Source #

As candid, but takes a filename

candidType :: QuasiQuoter Source #

This quasi-quoter turns works on individual candid types, e.g.

type InstallMode = [candidType| variant {install : null; reinstall : null; upgrade : null}; |]

Types and values

data Type a Source #

Constructors

NatT 
Nat8T 
Nat16T 
Nat32T 
Nat64T 
IntT 
Int8T 
Int16T 
Int32T 
Int64T 
Float32T 
Float64T 
BoolT 
TextT 
NullT 
ReservedT 
EmptyT 
OptT (Type a) 
VecT (Type a) 
RecT (Fields a) 
VariantT (Fields a) 
PrincipalT 
BlobT

a short-hand for VecT Nat8T for recursive types

RefT a

A reference to a named type

Instances

Instances details
Monad Type Source # 
Instance details

Defined in Codec.Candid.Types

Methods

(>>=) :: Type a -> (a -> Type b) -> Type b #

(>>) :: Type a -> Type b -> Type b #

return :: a -> Type a #

Functor Type Source # 
Instance details

Defined in Codec.Candid.Types

Methods

fmap :: (a -> b) -> Type a -> Type b #

(<$) :: a -> Type b -> Type a #

Applicative Type Source # 
Instance details

Defined in Codec.Candid.Types

Methods

pure :: a -> Type a #

(<*>) :: Type (a -> b) -> Type a -> Type b #

liftA2 :: (a -> b -> c) -> Type a -> Type b -> Type c #

(*>) :: Type a -> Type b -> Type b #

(<*) :: Type a -> Type b -> Type a #

Foldable Type Source # 
Instance details

Defined in Codec.Candid.Types

Methods

fold :: Monoid m => Type m -> m #

foldMap :: Monoid m => (a -> m) -> Type a -> m #

foldMap' :: Monoid m => (a -> m) -> Type a -> m #

foldr :: (a -> b -> b) -> b -> Type a -> b #

foldr' :: (a -> b -> b) -> b -> Type a -> b #

foldl :: (b -> a -> b) -> b -> Type a -> b #

foldl' :: (b -> a -> b) -> b -> Type a -> b #

foldr1 :: (a -> a -> a) -> Type a -> a #

foldl1 :: (a -> a -> a) -> Type a -> a #

toList :: Type a -> [a] #

null :: Type a -> Bool #

length :: Type a -> Int #

elem :: Eq a => a -> Type a -> Bool #

maximum :: Ord a => Type a -> a #

minimum :: Ord a => Type a -> a #

sum :: Num a => Type a -> a #

product :: Num a => Type a -> a #

Traversable Type Source # 
Instance details

Defined in Codec.Candid.Types

Methods

traverse :: Applicative f => (a -> f b) -> Type a -> f (Type b) #

sequenceA :: Applicative f => Type (f a) -> f (Type a) #

mapM :: Monad m => (a -> m b) -> Type a -> m (Type b) #

sequence :: Monad m => Type (m a) -> m (Type a) #

Eq a => Eq (Type a) Source # 
Instance details

Defined in Codec.Candid.Types

Methods

(==) :: Type a -> Type a -> Bool #

(/=) :: Type a -> Type a -> Bool #

Ord a => Ord (Type a) Source # 
Instance details

Defined in Codec.Candid.Types

Methods

compare :: Type a -> Type a -> Ordering #

(<) :: Type a -> Type a -> Bool #

(<=) :: Type a -> Type a -> Bool #

(>) :: Type a -> Type a -> Bool #

(>=) :: Type a -> Type a -> Bool #

max :: Type a -> Type a -> Type a #

min :: Type a -> Type a -> Type a #

Show a => Show (Type a) Source # 
Instance details

Defined in Codec.Candid.Types

Methods

showsPrec :: Int -> Type a -> ShowS #

show :: Type a -> String #

showList :: [Type a] -> ShowS #

Pretty a => Pretty (Type a) Source # 
Instance details

Defined in Codec.Candid.Types

Methods

pretty :: Type a -> Doc ann #

prettyList :: [Type a] -> Doc ann #

type Fields a = [(FieldName, Type a)] Source #

data FieldName Source #

A type for a Candid field name. Essentially a Word32 with maybe a textual label attached

Instances

Instances details
Eq FieldName Source # 
Instance details

Defined in Codec.Candid.FieldName

Ord FieldName Source # 
Instance details

Defined in Codec.Candid.FieldName

Show FieldName Source # 
Instance details

Defined in Codec.Candid.FieldName

IsString FieldName Source # 
Instance details

Defined in Codec.Candid.FieldName

Pretty FieldName Source # 
Instance details

Defined in Codec.Candid.FieldName

Methods

pretty :: FieldName -> Doc ann #

prettyList :: [FieldName] -> Doc ann #

labledField :: Text -> FieldName Source #

Create a FieldName from a label

hashedField :: Word32 -> FieldName Source #

Create a FieldName from the raw hash

fieldHash :: FieldName -> Word32 Source #

Extract the raw field hash value

escapeFieldName :: FieldName -> Text Source #

Represent a FieldName (which may be numeric) in contexts where only text is allowed, using the same encoding/decoding algorithm as Motoko.

This used in the Candid instance for Rec and Vec

candidHash :: Text -> Word32 Source #

The Candid field label hashing algorithm

Dynamic use

decodeVals :: ByteString -> Either String [Value] Source #

Decode to value representation

fromCandidVals :: CandidArg a => [Value] -> Either String a Source #

Decode values to Haskell type

encodeDynValues :: [Value] -> Either String Builder Source #

Encodes a Candid value given in the dynamic Value form, at inferred type.

This may fail if the values have inconsistent types. It does not use the reserved supertype (unless explicitly told to).

encodeTextual :: String -> Either String ByteString Source #

Encodes a Candid value given in textual form.

This may fail if the textual form cannot be parsed or has inconsistent types. It does not use the reserved supertype (unless explicitly told to).

data DidFile Source #

Instances

Instances details
Eq DidFile Source # 
Instance details

Defined in Codec.Candid.Types

Methods

(==) :: DidFile -> DidFile -> Bool #

(/=) :: DidFile -> DidFile -> Bool #

Show DidFile Source # 
Instance details

Defined in Codec.Candid.Types

Pretty DidFile Source # 
Instance details

Defined in Codec.Candid.Types

Methods

pretty :: DidFile -> Doc ann #

prettyList :: [DidFile] -> Doc ann #

parseDid :: String -> Either String DidFile Source #

Parses a Candid description (.did) from a string

parseValue :: String -> Either String Value Source #

Parses a Candid textual value from a string

parseValues :: String -> Either String [Value] Source #

Parses a sequence of Candid textual values from a string