License | BSD3 |
---|---|
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Param serialization and deserialization. ToParam
and EncodeParam
are responsible for serialization part.
EncodeParam
converts the value into a wire format. ToParam
is responsible for creating (nested) key value pairs, which can be then used to deserialize to original type. For example
encodeParam 5 == "5" data Foo = Foo { foo :: Int } deriving (Show, Eq, Generic) data Bar = Bar { bar :: Foo } deriving (Show, Eq, Generic) instance ToParam Foo 'FormParam instance ToParam Bar 'FormParam toParam (Proxy :: Proxy 'FormParam) "" (Bar (Foo 5)) == [("bar.foo","5")]
Deserialization works analogously, FromParam
and DecodeParam
are counterparts to ToParam
and EncodeParam
respectively. Generic instances are provided for all of them. This means that the user only need to derive Generic in their type, and provide instance with an empty body. Note that for headers FromHeader
and ToHeader
is being used in place of FromParam
and ToParam
. Nesting is not supported for headers.
- class ToParam a parK where
- toParam :: Proxy (parK :: ParamK) -> ByteString -> a -> [SerializedData parK]
- class EncodeParam t where
- encodeParam :: t -> ByteString
- class ToHeader a where
- type family SerializedData par
- toQueryParam :: ToParam a QueryParam => a -> Query
- toFormParam :: ToParam a FormParam => a -> [(ByteString, ByteString)]
- toFileParam :: ToParam a FileParam => a -> [(ByteString, FileInfo FilePath)]
- toPathParam :: ToParam a PathParam => a -> [ByteString]
- toCookie :: ToParam a Cookie => a -> [(ByteString, ByteString)]
- toNonNestedParam :: ToParam (NonNested a) parK => Proxy (parK :: ParamK) -> ByteString -> a -> [SerializedData parK]
- class FromParam a parK where
- fromParam :: Proxy (parK :: ParamK) -> ByteString -> Trie (DeSerializedData parK) -> Validation [ParamErr] a
- class DecodeParam t where
- decodeParam :: ByteString -> Maybe t
- class FromHeader a where
- fromHeader :: [Header] -> Validation [ParamErr] a
- newtype Validation e a = Validation {
- getValidation :: Either e a
- data ParamErr
- class ParamErrToApiErr apiErr where
- type family DeSerializedData par
- fromQueryParam :: FromParam a QueryParam => Query -> Validation [ParamErr] a
- fromFormParam :: FromParam a FormParam => [(ByteString, ByteString)] -> Validation [ParamErr] a
- fromFileParam :: FromParam a FileParam => [(ByteString, FileInfo FilePath)] -> Validation [ParamErr] a
- fromCookie :: FromParam a Cookie => [(ByteString, ByteString)] -> Validation [ParamErr] a
- lookupParam :: Proxy (parK :: ParamK) -> ByteString -> Trie (DeSerializedData parK) -> Maybe (DeSerializedData parK)
- fromNonNestedParam :: FromParam (NonNested a) parK => Proxy (parK :: ParamK) -> ByteString -> Trie (DeSerializedData parK) -> Validation [ParamErr] a
- newtype Field s a = Field {
- unField :: a
- newtype JsonOf a = JsonOf {
- getValue :: a
- newtype OptValue a = OptValue {}
- newtype FileInfo = FileInfo {}
- newtype NonNested a = NonNested {
- getNonNestedParam :: a
- data ParamK
- filePath :: FileInfo -> FilePath
- nest :: ByteString -> ByteString -> ByteString
Serialization
class ToParam a parK where Source
Serialize a type to a given type of kind ParamK
.
Nothing
toParam :: Proxy (parK :: ParamK) -> ByteString -> a -> [SerializedData parK] Source
class EncodeParam t where Source
Serialize a type to ByteString
.
Nothing
encodeParam :: t -> ByteString Source
Serialize a type to the header params
Nothing
type family SerializedData par Source
Define result of serialization of a type of kind ParamK
.
toQueryParam :: ToParam a QueryParam => a -> Query Source
Serialize a type into query params.
toFormParam :: ToParam a FormParam => a -> [(ByteString, ByteString)] Source
Serialize a type into form params.
toFileParam :: ToParam a FileParam => a -> [(ByteString, FileInfo FilePath)] Source
Serialize a type into file params.
toPathParam :: ToParam a PathParam => a -> [ByteString] Source
Serialize a type into path params.
toCookie :: ToParam a Cookie => a -> [(ByteString, ByteString)] Source
Serialize a type into cookie.
toNonNestedParam :: ToParam (NonNested a) parK => Proxy (parK :: ParamK) -> ByteString -> a -> [SerializedData parK] Source
Serialize a type without nesting.
Deserialization
class FromParam a parK where Source
(Try to) Deserialize a type from a given type of kind ParamK
.
Nothing
fromParam :: Proxy (parK :: ParamK) -> ByteString -> Trie (DeSerializedData parK) -> Validation [ParamErr] a Source
class DecodeParam t where Source
(Try to) Deserialize a type from ByteString
.
Nothing
decodeParam :: ByteString -> Maybe t Source
class FromHeader a where Source
(Try to) Deserialize a type from the header params
Nothing
fromHeader :: [Header] -> Validation [ParamErr] a Source
FromHeader () Source |
newtype Validation e a Source
Datatype representing the parsed result of params.
Validation | |
|
Functor (Validation e) Source | |
Monoid e => Applicative (Validation e) Source | |
(Eq e, Eq a) => Eq (Validation e a) Source | |
(Show e, Show a) => Show (Validation e a) Source |
Errors that occured during deserialization.
NotFound ByteString | The key was not found. |
ParseErr ByteString Text | A parse error occured while deserializing the type. |
class ParamErrToApiErr apiErr where Source
Convert the ParamErr
that occured during deserialization into ApiErr
type which can then be put in Response
.
type family DeSerializedData par Source
Define result of deserialization of a type of kind ParamK
.
fromQueryParam :: FromParam a QueryParam => Query -> Validation [ParamErr] a Source
(Try to) Deserialize a type from query params.
fromFormParam :: FromParam a FormParam => [(ByteString, ByteString)] -> Validation [ParamErr] a Source
(Try to) Deserialize a type from form params.
fromFileParam :: FromParam a FileParam => [(ByteString, FileInfo FilePath)] -> Validation [ParamErr] a Source
(Try to) Deserialize a type from file params.
fromCookie :: FromParam a Cookie => [(ByteString, ByteString)] -> Validation [ParamErr] a Source
(Try to) Deserialize a type from cookie.
lookupParam :: Proxy (parK :: ParamK) -> ByteString -> Trie (DeSerializedData parK) -> Maybe (DeSerializedData parK) Source
Lookup a value from the Trie
using the given key.
fromNonNestedParam :: FromParam (NonNested a) parK => Proxy (parK :: ParamK) -> ByteString -> Trie (DeSerializedData parK) -> Validation [ParamErr] a Source
(Try to) Deserialize a type without nesting.
Wrappers
Used to alias the field name while serailizing FromParam/ToParam instances
data Foo = Foo { foobar :: Field "foo_bar" Int} -- fieldname would be aliased to foo_bar instead of foobar
Serializing JsonOf
will produce a JSON representation of the value contained within. This is useful if params has to be sent as JSON.
Eq a => Eq (JsonOf a) Source | |
Ord a => Ord (JsonOf a) Source | |
Read a => Read (JsonOf a) Source | |
Show a => Show (JsonOf a) Source | |
ToJSON a => ToJSON (JsonOf a) Source | |
FromJSON a => FromJSON (JsonOf a) Source | |
FromJSON a => DecodeParam (JsonOf a) Source | |
ToJSON a => EncodeParam (JsonOf a) Source | |
ToJSON a => ToParam (JsonOf a) PathParam Source | |
ToJSON a => ToParam (JsonOf a) Cookie Source | |
ToJSON a => ToParam (JsonOf a) FormParam Source | |
ToJSON a => ToParam (JsonOf a) QueryParam Source |
Use this type if a key is required but the value is optional.
Eq a => Eq (OptValue a) Source | |
Ord a => Ord (OptValue a) Source | |
Read a => Read (OptValue a) Source | |
Show a => Show (OptValue a) Source | |
DecodeParam a => FromParam (OptValue a) Cookie Source | |
DecodeParam a => FromParam (OptValue a) FormParam Source | |
DecodeParam a => FromParam (OptValue a) QueryParam Source | |
EncodeParam a => ToParam (OptValue a) Cookie Source | |
EncodeParam a => ToParam (OptValue a) FormParam Source | |
EncodeParam a => ToParam (OptValue a) QueryParam Source |
A type for holding a file.
Use this type if for serialization / deserialization nesting is not required. The type contained within most likely requires EncodeParam
/ DecodeParam
.
Eq a => Eq (NonNested a) Source | |
Read a => Read (NonNested a) Source | |
Show a => Show (NonNested a) Source | |
(DecodeParam a, Typeable * a) => FromParam (NonNested a) Cookie Source | |
(DecodeParam a, Typeable * a) => FromParam (NonNested a) FormParam Source | |
(DecodeParam a, Typeable * a) => FromParam (NonNested a) QueryParam Source | |
EncodeParam a => ToParam (NonNested a) Cookie Source | |
EncodeParam a => ToParam (NonNested a) FormParam Source | |
EncodeParam a => ToParam (NonNested a) QueryParam Source |
Helpers
(Kind) Describes the various types of Param.
nest :: ByteString -> ByteString -> ByteString Source
Nest the key with a prefix.
nest "pfx" "key" == "pfx.key" nest "" "key" == "key"