registry-messagepack-0.4.0.0: MessagePack encoders / decoders
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Registry.MessagePack.Decoder

Synopsis

DECODER DATA TYPE

newtype Decoder a Source #

Constructors

Decoder 

Fields

  • decode :: Object -> Result a
     

Instances

Instances details
Applicative Decoder Source # 
Instance details

Defined in Data.Registry.MessagePack.Decoder

Methods

pure :: a -> Decoder a #

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

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

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

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

Functor Decoder Source # 
Instance details

Defined in Data.Registry.MessagePack.Decoder

Methods

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

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

decoderAp :: Decoder a -> Decoder b -> Decoder (a, b) Source #

DECODING

decodeByteString :: forall a. Typeable a => Decoder a -> ByteString -> Either Text a Source #

Use a Decoder to decode a ByteString into the desired type

decodeObject :: Decoder a -> Object -> Either Text a Source #

Use a Decoder to decode an Object into the desired type

CREATING DECODERS

messagePackDecoder :: forall a. (MessagePack a, Typeable a) => Typed (Decoder a) Source #

Add a Decoder a to a registry of decoders when a MessagePack a instance exists usage: decoders = messagePackDecoder @a <: otherDecoders

messagePackDecoderOf :: MessagePack a => Decoder a Source #

readDecoder :: forall a. (Typeable a, Read a) => Typed (Decoder String -> Decoder a) Source #

Create a Decoder from a Read instance

COMBINATORS

decodeMaybeOf :: forall a. Typeable a => Typed (Decoder a -> Decoder (Maybe a)) Source #

Add a Maybe (Decoder a) to a registry of decoders usage: decoders = decodeMaybeOf @a <: otherDecoders the list of otherDecoders must contain a Decoder a otherwise there will be a compilation error

maybeOfDecoder :: forall a. Decoder a -> Decoder (Maybe a) Source #

decodePairOf :: forall a b. (Typeable a, Typeable b) => Typed (Decoder a -> Decoder b -> Decoder (a, b)) Source #

Add a Maybe (a, b) to a registry of decoders usage: decoders = decodePairOf a b <: otherDecoders the list of otherDecoders must contain a Decoder a and a Decoder b otherwise there will be a compilation error

pairOfDecoder :: forall a b. (Typeable a, Typeable b) => Decoder a -> Decoder b -> Decoder (a, b) Source #

decodeTripleOf :: forall a b c. (Typeable a, Typeable b, Typeable c) => Typed (Decoder a -> Decoder b -> Decoder c -> Decoder (a, b, c)) Source #

Add a Maybe (a, b, c) to a registry of decoders usage: decoders = decodeTripleOf a b @c <: otherDecoders the list of otherDecoders must contain a Decoder a, a Decoder b and a Decoder c otherwise there will be a compilation error

tripleOfDecoder :: forall a b c. (Typeable a, Typeable b, Typeable c) => Decoder a -> Decoder b -> Decoder c -> Decoder (a, b, c) Source #

decodeListOf :: forall a. Typeable a => Typed (Decoder a -> Decoder [a]) Source #

Add a Decoder [a] to a registry of decoders usage: decoders = decodeListOf @a <: otherDecoders the list of otherDecoders must contain a Decoder a otherwise there will be a compilation error

listOfDecoder :: forall a. Typeable a => Decoder a -> Decoder [a] Source #

decodeNonEmptyOf :: forall a. Typeable a => Typed (Decoder a -> Decoder (NonEmpty a)) Source #

Add a Decoder (NonEmpty a) to a registry of decoders usage: decoders = decodeNonEmptyOf @a <: otherDecoders the list of otherDecoders must contain a Decoder a otherwise there will be a compilation error

showType :: forall a. Typeable a => String Source #

TEMPLATE HASKELL

makeDecoder :: Name -> ExpQ Source #

Make a Decoder for a given data type Usage: $(makeDecoder ''MyDataType <: otherDecoders)

makeDecoderQualified :: Name -> ExpQ Source #

Make a Decoder for a given data type, where all constructors and decoded types are qualified Usage: $(makeDecoderQualified ''MyDataType <: otherDecoders)

makeDecoderQualifiedLast :: Name -> ExpQ Source #

Make a Decoder for a given data type, where all constructors and decoded types are qualified Usage: $(makeDecoderQualifiedLast ''MyDataType <: otherDecoders)

makeDecoderWith :: Options -> Name -> ExpQ Source #

Make a Decoder with a given set of options Usage: $(makeDecoderWith (Options qualify) ''MyDataType <: otherDecoders)

makeConstructorDecoder :: Options -> Name -> Con -> ExpQ Source #

Make a Decoder for a single Constructor, where each field of the constructor is encoded as an element of an ObjectArray

makeConstructorsDecoder :: Options -> Name -> [Con] -> ExpQ Source #

Make a Decoder for a each Constructor of a data type: - each constructor is specified by an ObjectArray [ObjectInt n, o1, o2, ...] - n specifies the number of the constructor - each object in the array represents a constructor field

makeErrorClause :: Options -> Name -> MatchQ Source #

Return an error if an object is not an ObjectArray as expected other -> Error (mconcat ["not a valid ", show typeName, ": ", show other])

makeMatchClause :: Options -> [Type] -> Con -> Integer -> MatchQ Source #

Decode the nth constructor of a data type