rest-core-0.32.0.2: Rest API library.

Safe HaskellNone
LanguageHaskell98

Rest.Dictionary.Types

Contents

Synopsis

Possible I/O formats.

data Format Source

The Format datatype enumerates all input and output formats we might recognize.

The dictionary type.

data Dict h p i o e Source

The Dict datatype containing sub-dictionaries for translation of identifiers (i), headers (h), parameters (p), inputs (i), outputs (o), and errors (e). Inputs, outputs and errors can have multiple associated dictionaries.

Instances

Show (Dict h p i o e) 

headers :: forall cat h p i o e a. ArrowApply cat => Lens cat (Dict h p i o e -> Dict a p i o e) (Header h -> Header a) Source

params :: forall cat h p i o e a. ArrowApply cat => Lens cat (Dict h p i o e -> Dict h a i o e) (Param p -> Param a) Source

inputs :: forall cat h p i o e a. ArrowApply cat => Lens cat (Dict h p i o e -> Dict h p a o e) (Inputs i -> Inputs a) Source

outputs :: forall cat h p i o e a. ArrowApply cat => Lens cat (Dict h p i o e -> Dict h p i a e) (Outputs o -> Outputs a) Source

errors :: forall cat h p i o e a. ArrowApply cat => Lens cat (Dict h p i o e -> Dict h p i o a) (Errors e -> Errors a) Source

empty :: Dict () () () () () Source

The empty dictionary, recognizing no types.

type Modifier h p i o e = Dict () () () () () -> Dict h p i o e Source

Type synonym for dictionary modification.

Dictionary aspects.

data Ident id where Source

The explicit dictionary Ident describes how to translate a resource identifier (originating from a request URI) to a Haskell value. We allow plain String identifiers or all Haskell types that have a Read instance.

Constructors

ReadId :: (Info id, Read id, Show id) => Ident id 
StringId :: Ident String 

Instances

Show (Ident id) 

data Header h where Source

The explicit dictionary Header describes how to translate HTTP request headers to some Haskell value. The first field in the Header constructor is a white list of headers we can recognize, used in generic validation and for generating documentation. The second field is a custom parser that can fail with a DataError or can produce a some value. When explicitly not interested in the headers we can use NoHeader.

Constructors

NoHeader :: Header () 
Header :: [String] -> ([Maybe String] -> Either DataError h) -> Header h 
TwoHeaders :: Header h -> Header k -> Header (h, k) 

Instances

Show (Header h) 

data Param p where Source

The explicit dictionary Parameter describes how to translate the request parameters to some Haskell value. The first field in the Header constructor is a white list of paramters we can recognize, used in generic validation and for generating documentation. The second field is a custom parser that can fail with a DataError or can produce a some value. When explicitly not interested in the parameters we can use NoParam.

Constructors

NoParam :: Param () 
Param :: [String] -> ([Maybe String] -> Either DataError p) -> Param p 
TwoParams :: Param p -> Param q -> Param (p, q) 

Instances

Show (Param p) 

data Input i where Source

The explicitly dictionary Input describes how to translate the request body into some Haskell value. We currently use a constructor for every combination of input type to output type. For example, we can use XML input in multiple ways, parsed, as plain/text or as raw bytes, depending on the needs of the backend resource.

Constructors

JsonI :: (Typeable i, FromJSON i, JSONSchema i) => Input i 
ReadI :: (Info i, Read i, Show i) => Input i 
StringI :: Input String 
FileI :: Input ByteString 
XmlI :: (Typeable i, XmlPickler i) => Input i 
XmlTextI :: Input Text 
RawXmlI :: Input ByteString 

Instances

Eq (Input i) 
Ord (Input i) 
Show (Input i) 

data Output o where Source

The explicitly dictionary Output describes how to translate some Haskell value to a response body. We currently use a constructor for every combination of input type to output type.

Instances

Eq (Output o) 
Ord (Output o) 
Show (Output o) 

data Error e where Source

The explicitly dictionary Error describes how to translate some Haskell error value to a response body.

Constructors

JsonE :: (Typeable e, ToJSON e, JSONSchema e) => Error e 
XmlE :: (Typeable e, XmlPickler e) => Error e 

Instances

Eq (Error e) 
Ord (Error e) 
Show (Error e) 

Plural dictionaries.

data Dicts f a where Source

Constructors

None :: Dicts f () 
Dicts :: [f a] -> Dicts f a 

Instances

Show (f a) => Show (Dicts f a) 

dicts :: Dicts f a :-> [f a] Source

data SomeError where Source

Custom existential packing an error together with a Reason.

Constructors

SomeError :: Errors e -> Reason e -> SomeError