trasa-0.3: Type Safe Web Routing

Safe HaskellNone
LanguageHaskell2010

Trasa.Core

Contents

Synopsis

Types

data Bodiedness Source #

Constructors

Body a 
Bodyless 

data Content Source #

The HTTP content type and body.

Constructors

Content 

data Router route Source #

Existential

data Prepared :: ([Type] -> [Param] -> Bodiedness -> Type -> Type) -> Type -> Type where Source #

Includes the route, path, query parameters, and request body.

Constructors

Prepared :: !(route captures querys request response) -> !(Rec Identity captures) -> !(Rec Parameter querys) -> !(RequestBody Identity request) -> Prepared route response 

data Concealed :: ([Type] -> [Param] -> Bodiedness -> Type -> Type) -> Type where Source #

Only needed to implement parseWith. Most users do not need this. If you need to create a route hierarchy to provide breadcrumbs, then you will need this.

Constructors

Concealed :: !(route captures querys request response) -> !(Rec Identity captures) -> !(Rec Parameter querys) -> !(RequestBody Identity request) -> Concealed route 

data Constructed :: ([Type] -> [Param] -> Bodiedness -> Type -> Type) -> Type where Source #

A route with all types hidden: the captures, the request body, and the response body. This is needed so that users can enumerate over all the routes.

Constructors

Constructed :: !(route captures querys request response) -> Constructed route 

conceal :: Prepared route response -> Concealed route Source #

Conceal the response type.

concealedToPrepared :: forall route a. Concealed route -> (forall resp. Prepared route resp -> a) -> a Source #

mapConstructed :: (forall caps qrys req resp. sub caps qrys req resp -> route caps qrys req resp) -> Constructed sub -> Constructed route Source #

Request Types

Method

Queries

Url

data Url Source #

Constructors

Url 

Instances

Eq Url Source # 

Methods

(==) :: Url -> Url -> Bool #

(/=) :: Url -> Url -> Bool #

Show Url Source # 

Methods

showsPrec :: Int -> Url -> ShowS #

show :: Url -> String #

showList :: [Url] -> ShowS #

Errors

Using Routes

prepareWith Source #

Arguments

:: (forall caps qrys req resp. route caps qrys req resp -> Meta capCodec qryCodec reqCodec respCodec caps qrys req resp) 
-> route captures query request response

The route to prepare

-> Arguments captures query request (Prepared route response) 

Used my users to define a function called prepare, see tutorial

linkWith Source #

Arguments

:: (forall caps qrys req resp. route caps qrys req resp -> Meta CaptureEncoding CaptureEncoding reqCodec respCodec caps qrys req resp) 
-> Prepared route response

The route to encode

-> Url 

Generate a Url for use in hyperlinks.

dispatchWith Source #

Arguments

:: Applicative m 
=> (forall caps qrys req resp. route caps qrys req resp -> MetaServer caps qrys req resp) 
-> (forall caps qrys req resp. route caps qrys req resp -> Rec Identity caps -> Rec Parameter qrys -> RequestBody Identity req -> m resp) 
-> Router route

Router

-> Method

Method

-> [MediaType]

Accept headers

-> Url

Everything after the authority

-> Maybe Content

Content type and request body

-> m (Either TrasaErr Content)

Encoded response

Only useful to implement packages like 'trasa-server'

parseWith Source #

Arguments

:: (forall caps qrys req resp. route caps qrys req resp -> Meta capCodec CaptureDecoding (Many BodyDecoding) respCodec caps qrys req resp) 
-> Router route

Router

-> Method

Request Method

-> Url

Everything after the authority

-> Maybe Content

Request content type and body

-> Either TrasaErr (Concealed route) 

Parses the path, the querystring, and the request body.

payloadWith Source #

Arguments

:: (forall caps qrys req resp. route caps qrys req resp -> MetaClient caps qrys req resp) 
-> Prepared route response

The route to be payload encoded

-> Payload 

Only useful for library authors

requestWith Source #

Arguments

:: Functor m 
=> (forall caps qrys req resp. route caps qrys req resp -> MetaClient caps qrys req resp) 
-> (Method -> Url -> Maybe Content -> NonEmpty MediaType -> m (Either TrasaErr Content))

method, url, content, accepts -> response

-> Prepared route response 
-> m (Either TrasaErr response) 

routerWith :: forall route qryCodec reqCodec respCodec. (forall caps qrys req resp. route caps qrys req resp -> Meta CaptureDecoding qryCodec reqCodec respCodec caps qrys req resp) -> [Constructed route] -> Router route Source #

Build a router from all the possible routes, and methods to turn routes into needed metadata

Defining Routes

Path

data Path :: (Type -> Type) -> [Type] -> Type where Source #

Constructors

PathNil :: Path cap '[] 
PathConsCapture :: !(cap a) -> !(Path cap as) -> Path cap (a ': as) 
PathConsMatch :: !Text -> !(Path cap as) -> Path cap as 

match :: Text -> Path cpf caps -> Path cpf caps Source #

capture :: cpf cap -> Path cpf caps -> Path cpf (cap ': caps) Source #

end :: Path cpf '[] Source #

(./) :: (a -> b) -> a -> b infixr 7 Source #

mapPath :: (forall x. cf x -> cf' x) -> Path cf ps -> Path cf' ps Source #

appendPath :: Path f as -> Path f bs -> Path f (as ++ bs) Source #

Query

data Param Source #

Constructors

Flag 
Optional a 
List a 

data Query :: (Type -> Type) -> Param -> Type where Source #

Constructors

QueryFlag :: !Text -> Query cap Flag 
QueryOptional :: !Text -> !(cap a) -> Query cap (Optional a) 
QueryList :: !Text -> !(cap a) -> Query cap (List a) 

data Parameter :: Param -> Type where Source #

data Rec u (a :: u -> *) (b :: [u]) :: forall u. (u -> *) -> [u] -> * where #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: Rec u a ([] u) 
(:&) :: Rec u a ((:) u r rs) infixr 7 

Instances

TestCoercion u f => TestCoercion [u] (Rec u f) 

Methods

testCoercion :: f a -> f b -> Maybe (Coercion (Rec u f) a b) #

TestEquality u f => TestEquality [u] (Rec u f) 

Methods

testEquality :: f a -> f b -> Maybe ((Rec u f :~: a) b) #

Eq (Rec u f ([] u)) 

Methods

(==) :: Rec u f [u] -> Rec u f [u] -> Bool #

(/=) :: Rec u f [u] -> Rec u f [u] -> Bool #

(Eq (f r), Eq (Rec a f rs)) => Eq (Rec a f ((:) a r rs)) 

Methods

(==) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(/=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

Ord (Rec u f ([] u)) 

Methods

compare :: Rec u f [u] -> Rec u f [u] -> Ordering #

(<) :: Rec u f [u] -> Rec u f [u] -> Bool #

(<=) :: Rec u f [u] -> Rec u f [u] -> Bool #

(>) :: Rec u f [u] -> Rec u f [u] -> Bool #

(>=) :: Rec u f [u] -> Rec u f [u] -> Bool #

max :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

min :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

(Ord (f r), Ord (Rec a f rs)) => Ord (Rec a f ((:) a r rs)) 

Methods

compare :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Ordering #

(<) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(<=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(>) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(>=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

max :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

min :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

RecAll u f rs Show => Show (Rec u f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Methods

showsPrec :: Int -> Rec u f rs -> ShowS #

show :: Rec u f rs -> String #

showList :: [Rec u f rs] -> ShowS #

Semigroup (Rec u f ([] u)) 

Methods

(<>) :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

sconcat :: NonEmpty (Rec u f [u]) -> Rec u f [u] #

stimes :: Integral b => b -> Rec u f [u] -> Rec u f [u] #

(Monoid (f r), Monoid (Rec a f rs)) => Semigroup (Rec a f ((:) a r rs)) 

Methods

(<>) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

sconcat :: NonEmpty (Rec a f ((a ': r) rs)) -> Rec a f ((a ': r) rs) #

stimes :: Integral b => b -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

Monoid (Rec u f ([] u)) 

Methods

mempty :: Rec u f [u] #

mappend :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

mconcat :: [Rec u f [u]] -> Rec u f [u] #

(Monoid (f r), Monoid (Rec a f rs)) => Monoid (Rec a f ((:) a r rs)) 

Methods

mempty :: Rec a f ((a ': r) rs) #

mappend :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

mconcat :: [Rec a f ((a ': r) rs)] -> Rec a f ((a ': r) rs) #

Storable (Rec u f ([] u)) 

Methods

sizeOf :: Rec u f [u] -> Int #

alignment :: Rec u f [u] -> Int #

peekElemOff :: Ptr (Rec u f [u]) -> Int -> IO (Rec u f [u]) #

pokeElemOff :: Ptr (Rec u f [u]) -> Int -> Rec u f [u] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec u f [u]) #

pokeByteOff :: Ptr b -> Int -> Rec u f [u] -> IO () #

peek :: Ptr (Rec u f [u]) -> IO (Rec u f [u]) #

poke :: Ptr (Rec u f [u]) -> Rec u f [u] -> IO () #

(Storable (f r), Storable (Rec a f rs)) => Storable (Rec a f ((:) a r rs)) 

Methods

sizeOf :: Rec a f ((a ': r) rs) -> Int #

alignment :: Rec a f ((a ': r) rs) -> Int #

peekElemOff :: Ptr (Rec a f ((a ': r) rs)) -> Int -> IO (Rec a f ((a ': r) rs)) #

pokeElemOff :: Ptr (Rec a f ((a ': r) rs)) -> Int -> Rec a f ((a ': r) rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec a f ((a ': r) rs)) #

pokeByteOff :: Ptr b -> Int -> Rec a f ((a ': r) rs) -> IO () #

peek :: Ptr (Rec a f ((a ': r) rs)) -> IO (Rec a f ((a ': r) rs)) #

poke :: Ptr (Rec a f ((a ': r) rs)) -> Rec a f ((a ': r) rs) -> IO () #

optional :: Text -> cpf query -> Query cpf (Optional query) Source #

list :: Text -> cpf query -> Query cpf (List query) Source #

qend :: Rec (Query qpf) '[] Source #

(.&) :: Query qpf q -> Rec (Query qpf) qs -> Rec (Query qpf) (q ': qs) infixr 7 Source #

mapQuery :: (forall x. f x -> g x) -> Rec (Query f) qs -> Rec (Query g) qs Source #

Request Body

data RequestBody :: (Type -> Type) -> Bodiedness -> Type where Source #

body :: rqf req -> RequestBody rqf (Body req) Source #

mapRequestBody :: (forall x. rqf x -> rqf' x) -> RequestBody rqf request -> RequestBody rqf' request Source #

Response Body

newtype ResponseBody rpf response Source #

Constructors

ResponseBody 

Fields

resp :: rpf resp -> ResponseBody rpf resp Source #

encodeResponseBody :: forall response. [MediaType] -> ResponseBody (Many BodyEncoding) response -> response -> Either TrasaErr Content Source #

mapResponseBody :: (forall x. rpf x -> rpf' x) -> ResponseBody rpf request -> ResponseBody rpf' request Source #

Many

newtype Many f a Source #

Constructors

Many 

Fields

Instances

Functor f => Functor (Many * f) Source # 

Methods

fmap :: (a -> b) -> Many * f a -> Many * f b #

(<$) :: a -> Many * f b -> Many * f a #

Applicative f => Applicative (Many * f) Source # 

Methods

pure :: a -> Many * f a #

(<*>) :: Many * f (a -> b) -> Many * f a -> Many * f b #

liftA2 :: (a -> b -> c) -> Many * f a -> Many * f b -> Many * f c #

(*>) :: Many * f a -> Many * f b -> Many * f b #

(<*) :: Many * f a -> Many * f b -> Many * f a #

one :: f a -> Many f a Source #

mapMany :: (forall x. f x -> g x) -> Many f a -> Many g a Source #

Meta

data Meta capCodec qryCodec reqCodec respCodec caps qrys req resp Source #

Constructors

Meta 

Fields

metaBuilderToMetaCodec :: Meta capCodec qryCodec reqCodec respCodec caps qrys req resp -> Meta capCodec qryCodec (Many reqCodec) (Many respCodec) caps qrys req resp Source #

This function is a more general way to transform MetaBuilder into MetaCodec.

It wraps the req and resp codecs in Many.

metaCodecToMetaClient :: MetaCodec caps qrys req resp -> MetaClient caps qrys req resp Source #

metaCodecToMetaServer :: MetaCodec caps qrys req resp -> MetaServer caps qrys req resp Source #

mapMetaPath :: (forall x. cf x -> cg x) -> Meta cf qryCodec reqCodec respCodec caps qrys req resp -> Meta cg qryCodec reqCodec respCodec caps qrys req resp Source #

mapMetaQuery :: (forall x. qf x -> qg x) -> Meta capCodec qf reqCodec respCodec caps qrys req resp -> Meta capCodec qg reqCodec respCodec caps qrys req resp Source #

mapMetaRequestBody :: (forall x. rf x -> rg x) -> Meta capCodec qryCodec rf respCodec caps qrys req resp -> Meta capCodec qryCodec rg respCodec caps qrys req resp Source #

mapMetaResponseBody :: (forall x. rf x -> rg x) -> Meta capCodec qryCodec reqCodec rf caps qrys req resp -> Meta capCodec qryCodec reqCodec rg caps qrys req resp Source #

mapMeta :: (forall x. capCodec1 x -> capCodec2 x) -> (forall x. qryCodec1 x -> qryCodec2 x) -> (forall x. reqCodec1 x -> reqCodec2 x) -> (forall x. respCodec1 x -> respCodec2 x) -> Meta capCodec1 qryCodec1 reqCodec1 respCodec1 caps qrys req resp -> Meta capCodec2 qryCodec2 reqCodec2 respCodec2 caps qrys req resp Source #

Codecs

class HasCaptureCodec capStrategy where Source #

Minimal complete definition

captureCodec

Methods

captureCodec :: capStrategy a -> CaptureCodec a Source #

class HasBodyEncoding bodyStrategy where Source #

Minimal complete definition

bodyEncoding

Methods

bodyEncoding :: bodyStrategy a -> BodyEncoding a Source #

class HasBodyDecoding bodyStrategy where Source #

Minimal complete definition

bodyDecoding

Methods

bodyDecoding :: bodyStrategy a -> BodyDecoding a Source #

class HasBodyCodec bodyStrategy where Source #

Minimal complete definition

bodyCodec

Methods

bodyCodec :: bodyStrategy a -> BodyCodec a Source #

Converting Codecs

Type Class based Codecs

Argument Currying

type family ParamBase (param :: Param) :: Type where ... Source #

Equations

ParamBase Flag = Bool 
ParamBase (Optional a) = Maybe a 
ParamBase (List a) = [a] 

type family Arguments (pieces :: [Type]) (querys :: [Param]) (body :: Bodiedness) (result :: Type) :: Type where ... Source #

A closed, total type family provided as a convenience to end users. Other function is this library take advantage of Arguments to allow end users use normal function application. Without this, users would need to write out Record and RequestBody values by hand, which is tedious.

>>> :kind! Arguments '[Int,Bool] '[Flag,Optional Double,List Int] 'Bodyless Double
Arguments '[Int,Bool] '[Flag,Optional Double,List Int] 'Bodyless Double :: *
= Int -> Bool -> Bool -> Maybe Double -> [Int] -> Double

Equations

Arguments '[] '[] (Body b) r = b -> r 
Arguments '[] '[] Bodyless r = r 
Arguments '[] (q ': qs) r b = ParamBase q -> Arguments '[] qs r b 
Arguments (c ': cs) qs b r = c -> Arguments cs qs b r 

handler :: forall captures querys request x. Rec Identity captures -> Rec Parameter querys -> RequestBody Identity request -> Arguments captures querys request x -> x Source #

Uncurry the arguments type family

Helpers

prettyRouter :: Router route -> String Source #

Pretty prints a router, using indentation to show nesting of routes under a common prefix. This also shows the request methods that each route accepts. If there are any trivially overlapped routes, the appends are asterisk to the method name for which the routes are overlapped.