jordan-servant-0.1.0.0: Servant Combinators for Jordan
Safe HaskellNone
LanguageHaskell2010

Jordan.Servant

Synopsis

Documentation

data JordanJSON Source #

Servant content type that lets you render or parse via Jordan.

Note: It is generally better to use ViaJordan instead, which gets you nice API documentation. However, you might want to slowly migrate your API to Jordan. In this case, you can use this as a content type.

Instances

Instances details
Accept JordanJSON Source #

Jordan JSON will have a content type of application/json; haskell-encoder=jordan; encoding=utf-8 . This allows you to conditionally request the Jordanified response.

Instance details

Defined in Jordan.Servant

ToJSON a => MimeRender JordanJSON a Source #

Uses toJSONViaBuilder

Instance details

Defined in Jordan.Servant

FromJSON a => MimeUnrender JordanJSON a Source #

Parses directly from a lazy bytestring via Attoparsec

Instance details

Defined in Jordan.Servant

data ReportingRequestBody a Source #

A parameter for use with Servant, which lets you parse the request body or report parse errors to the user. It is different from using the existing ReqBody param from Servant in that it will give a detailed report of why the format of the request body was wrong if need be.

This will use parseJSONReporting for its work. This is generally a little slower than direct attoparsec parsing, but avoids us having to parse twice.

Instances

Instances details
HasLink sub => HasLink (ReportingRequestBody a :> sub :: Type) Source # 
Instance details

Defined in Jordan.Servant

Associated Types

type MkLink (ReportingRequestBody a :> sub) a #

Methods

toLink :: (Link -> a0) -> Proxy (ReportingRequestBody a :> sub) -> Link -> MkLink (ReportingRequestBody a :> sub) a0 #

type MkLink (ReportingRequestBody a :> sub :: Type) r Source # 
Instance details

Defined in Jordan.Servant

type MkLink (ReportingRequestBody a :> sub :: Type) r = MkLink sub r

data JordanQuery' (baseStr :: Symbol) (options :: [*]) (a :: *) Source #

A query argument at some key, that will be parsed via Jordan. If the query needs to contain nested data, it will all be nested under the same key.

We do not support lenient queries as figuring out what to return in the case where the Jordan parser would have parsed nested keys is too difficult.

Note: this type *does not* have a HasLink instance, because unfortunately Servant is way too restrictive of what it exports, making such an instance impossible to write. I will open up a PR against Servant to fix this soon.

type RequiredJordanQuery (baseStr :: Symbol) (a :: *) = JordanQuery' baseStr '[Required] a Source #

A query argument that is required.

Will render an error message, in JSON format, if the query was bad in some way.

type OptionalJordanQuery (baseStr :: Symbol) (a :: *) = JordanQuery' (baseStr :: Symbol) '[] (a :: *) Source #

A query argument that is *optional*.

Will render an error message, in JSON format, if the query was bad in some way.

newtype ViaJordan a Source #

Wrapper to perform JSON serialization via Jordan.

Types used with this wrapper should have isomorphic ToJSON and FromJSON instances. A utility is provided to check this.

Constructors

ViaJordan 

Fields

Instances

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

Defined in Jordan.Servant.Response

Methods

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

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

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

Defined in Jordan.Servant.Response

Read a => Read (ViaJordan a) Source # 
Instance details

Defined in Jordan.Servant.Response

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

Defined in Jordan.Servant.Response

Generic (ViaJordan a) Source # 
Instance details

Defined in Jordan.Servant.Response

Associated Types

type Rep (ViaJordan a) :: Type -> Type #

Methods

from :: ViaJordan a -> Rep (ViaJordan a) x #

to :: Rep (ViaJordan a) x -> ViaJordan a #

ToJSON a => ToJSON (ViaJordan a) Source # 
Instance details

Defined in Jordan.Servant.Response

Methods

toJSON :: JSONSerializer f => f (ViaJordan a) #

FromJSON a => FromJSON (ViaJordan a) Source # 
Instance details

Defined in Jordan.Servant.Response

Methods

fromJSON :: JSONParser f => f (ViaJordan a) #

HasStatus a => HasStatus (ViaJordan a) Source # 
Instance details

Defined in Jordan.Servant.Response

Associated Types

type StatusOf (ViaJordan a) :: Nat #

ToJSON a => MimeRender JSON (ViaJordan a) Source #

Overlapping instance: sidestep Aeson, use Jordan.

Instance details

Defined in Jordan.Servant.Response

FromJSON a => MimeUnrender JSON (ViaJordan a) Source #

Overlapping instance: sidestep Aeson, just Jordan.

Instance details

Defined in Jordan.Servant.Response

type Rep (ViaJordan a) Source # 
Instance details

Defined in Jordan.Servant.Response

type Rep (ViaJordan a) = D1 ('MetaData "ViaJordan" "Jordan.Servant.Response" "jordan-servant-0.1.0.0-4pWi47ZOJ6bHDVnhgja79c" 'True) (C1 ('MetaCons "ViaJordan" 'PrefixI 'True) (S1 ('MetaSel ('Just "getViaJordan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type StatusOf (ViaJordan a) Source # 
Instance details

Defined in Jordan.Servant.Response