rest-core-0.38: 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) Source 

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 () () Nothing Nothing Nothing Source

The empty dictionary, recognizing no types.

type Modifier h p i o e = Dict () () Nothing Nothing Nothing -> 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) => Ident id 
StringId :: Ident String 

Instances

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

data Param p where Source

The explicit dictionary Param describes how to translate the request parameters to some Haskell value. The first field in the Param 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

data Input i where Source

The explicit 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.

Instances

data Output o where Source

The explicit 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

data Error e where Source

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

Constructors

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

Instances

newtype Xml Source

Newtype around ByteStrings used in RawJsonAndXmlI to add some protection from parsing the input incorrectly.

Constructors

Xml 

Fields

unXml :: ByteString
 

Instances

newtype Json Source

Newtype around ByteStrings used in RawJsonAndXmlI to add some protection from parsing the input incorrectly.

Constructors

Json 

Fields

unJson :: ByteString
 

Plural dictionaries.

data Dicts f a where Source

Constructors

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

Instances

Show (f (FromMaybe Void a)) => Show (Dicts f a) Source 

dicts :: forall a o f. (o ~ FromMaybe o a) => Dicts f a :-> [f o] Source

Deprecated: The modifier for this lens doesn't do anything when Dicts is None. Use getDicts and modDicts instead.

getDicts :: (o ~ FromMaybe o a) => Dicts f a -> [f o] Source

Get the list of dictionaries. If there are none, you get a [o]. If this is too polymorphic, try getDicts_.

getDicts_ :: (o ~ FromMaybe () a) => Dicts f a -> [f o] Source

Get the list of dictionaries. If there are none, you get a [()]. Sometimes useful to constraint the types if the element type of the list isn't clear from the context.

modDicts :: (FromMaybe o i ~ o) => ([f o] -> [f o]) -> Dicts f i -> Dicts f (Just o) Source

data SomeError where Source

Custom existential packing an error together with a Reason.

Constructors

SomeError :: Errors e -> Reason (FromMaybe Void e) -> SomeError 

type family FromMaybe d m :: * Source

Instances

type FromMaybe b (Nothing *) = b Source 
type FromMaybe b (Just * a) = a Source