Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Bodiedness
- data Path :: (Type -> Type) -> [Type] -> Type where
- PathNil :: Path cap '[]
- PathConsCapture :: cap a -> Path cap as -> Path cap (a ': as)
- PathConsMatch :: Text -> Path cap as -> Path cap as
- newtype ResponseBody rpf response = ResponseBody {
- getResponseBody :: rpf response
- data RequestBody :: (Type -> Type) -> Bodiedness -> Type where
- RequestBodyPresent :: f a -> RequestBody f (Body a)
- RequestBodyAbsent :: RequestBody f Bodyless
- data Param
- data Query :: (Type -> Type) -> Param -> Type where
- data Parameter :: Param -> Type where
- ParameterFlag :: Bool -> Parameter Flag
- ParameterOptional :: Maybe a -> Parameter (Optional a)
- ParameterList :: [a] -> Parameter (List a)
- data Rec u a b :: forall u. (u -> *) -> [u] -> * where
- data BodyCodec a = BodyCodec {
- bodyCodecNames :: NonEmpty Text
- bodyCodecEncode :: a -> ByteString
- bodyCodecDecode :: ByteString -> Either Text a
- data BodyDecoding a = BodyDecoding {}
- data BodyEncoding a = BodyEncoding {}
- newtype Many f a = Many {}
- data CaptureCodec a = CaptureCodec {
- captureCodecEncode :: a -> Text
- captureCodecDecode :: Text -> Maybe a
- newtype CaptureEncoding a = CaptureEncoding {
- appCaptureEncoding :: a -> Text
- newtype CaptureDecoding a = CaptureDecoding {
- appCaptureDecoding :: Text -> Maybe a
- data Content = Content {}
- newtype QueryString = QueryString {
- unQueryString :: HashMap Text QueryParam
- data Url = Url {
- urlPath :: ![Text]
- urlQueryString :: !QueryString
- data Payload = Payload {
- payloadUrl :: !Url
- payloadContent :: !(Maybe Content)
- payloadAccepts :: !(NonEmpty Text)
- data TrasaErr = TrasaErr {}
- data Router route
- data Prepared :: ([Type] -> [Param] -> Bodiedness -> Type -> Type) -> Type -> Type where
- data Concealed :: ([Type] -> [Param] -> Bodiedness -> Type -> Type) -> Type where
- data Constructed :: ([Type] -> [Param] -> Bodiedness -> Type -> Type) -> Type where
- Constructed :: route captures querys request response -> Constructed route
- encodeQuery :: QueryString -> Query
- decodeQuery :: Query -> QueryString
- encodeUrl :: Url -> Text
- decodeUrl :: Text -> Url
- prepareWith :: (forall caps qry req resp. route caps qry req resp -> Path pf caps) -> (forall caps qry req resp. route caps qry req resp -> Rec (Query qf) qry) -> (forall caps qry req resp. route caps qry req resp -> RequestBody rqf req) -> route captures query request response -> Arguments captures query request (Prepared route response)
- dispatchWith :: forall route m. Applicative m => (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureDecoding) qrys) -> (forall caps qrys req resp. route caps qrys req resp -> RequestBody (Many BodyDecoding) req) -> (forall caps qrys req resp. route caps qrys req resp -> ResponseBody (Many BodyEncoding) resp) -> (forall caps qrys req resp. route caps qrys req resp -> Rec Identity caps -> Rec Parameter qrys -> RequestBody Identity req -> m resp) -> Router route -> Text -> [Text] -> Url -> Maybe Content -> m (Either TrasaErr Content)
- parseWith :: forall route. (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureDecoding) qrys) -> (forall caps qrys req resp. route caps qrys req resp -> RequestBody (Many BodyDecoding) req) -> Router route -> Text -> Url -> Maybe Content -> Either TrasaErr (Concealed route)
- linkWith :: forall route response. (forall caps qrys req resp. route caps qrys req resp -> Path CaptureEncoding caps) -> (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureEncoding) qrys) -> Prepared route response -> Url
- payloadWith :: forall route response. (forall caps qrys req resp. route caps qrys req resp -> Path CaptureEncoding caps) -> (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureEncoding) qrys) -> (forall caps qrys req resp. route caps qrys req resp -> RequestBody (Many BodyEncoding) req) -> (forall caps qrys req resp. route caps qrys req resp -> ResponseBody (Many BodyDecoding) resp) -> Prepared route response -> Payload
- requestWith :: Functor m => (forall caps querys req resp. route caps querys req resp -> Text) -> (forall caps querys req resp. route caps querys req resp -> Path CaptureEncoding caps) -> (forall caps querys req resp. route caps querys req resp -> Rec (Query CaptureEncoding) querys) -> (forall caps querys req resp. route caps querys req resp -> RequestBody (Many BodyEncoding) req) -> (forall caps querys req resp. route caps querys req resp -> ResponseBody (Many BodyDecoding) resp) -> (Text -> Url -> Maybe Content -> [Text] -> m (Either TrasaErr Content)) -> Prepared route response -> m (Either TrasaErr response)
- routerWith :: (forall caps querys req resp. route caps querys req resp -> Text) -> (forall caps querys req resp. route caps querys req resp -> Path CaptureDecoding caps) -> [Constructed route] -> Router route
- handler :: forall captures querys request x. Rec Identity captures -> Rec Parameter querys -> RequestBody Identity request -> Arguments captures querys request x -> x
- match :: Text -> Path cpf caps -> Path cpf caps
- capture :: cpf cap -> Path cpf caps -> Path cpf (cap ': caps)
- end :: Path cpf '[]
- (./) :: (a -> b) -> a -> b
- appendPath :: Path f as -> Path f bs -> Path f (as ++ bs)
- body :: rqf req -> RequestBody rqf (Body req)
- bodyless :: RequestBody rqf Bodyless
- resp :: rpf resp -> ResponseBody rpf resp
- demoteParameter :: Parameter param -> ParamBase param
- flag :: Text -> Query cpf Flag
- optional :: Text -> cpf query -> Query cpf (Optional query)
- list :: Text -> cpf query -> Query cpf (List query)
- qend :: Rec (Query qpf) '[]
- (.&) :: Query qpf q -> Rec (Query qpf) qs -> Rec (Query qpf) (q ': qs)
- mapQuery :: (forall x. f x -> g x) -> Rec (Query f) qs -> Rec (Query g) qs
- one :: f a -> Many f a
- mapMany :: (forall x. f x -> g x) -> Many f a -> Many g a
- mapPath :: (forall x. cf x -> cf' x) -> Path cf ps -> Path cf' ps
- mapRequestBody :: (forall x. rqf x -> rqf' x) -> RequestBody rqf request -> RequestBody rqf' request
- mapResponseBody :: (forall x. rpf x -> rpf' x) -> ResponseBody rpf request -> ResponseBody rpf' request
- mapConstructed :: (forall caps qrys req resp. sub caps qrys req resp -> route cap qrys req resp) -> Constructed sub -> Constructed route
- bodyCodecToBodyEncoding :: BodyCodec a -> BodyEncoding a
- bodyCodecToBodyDecoding :: BodyCodec a -> BodyDecoding a
- captureCodecToCaptureEncoding :: CaptureCodec a -> CaptureEncoding a
- captureCodecToCaptureDecoding :: CaptureCodec a -> CaptureDecoding a
- status :: Status -> TrasaErr
- type family ParamBase (param :: Param) :: Type where ...
- type family Arguments (pieces :: [Type]) (querys :: [Param]) (body :: Bodiedness) (result :: Type) :: Type where ...
- conceal :: Prepared route response -> Concealed route
- encodeRequestBody :: RequestBody (Many BodyEncoding) request -> RequestBody Identity request -> Maybe Content
- decodeResponseBody :: ResponseBody (Many BodyDecoding) response -> Content -> Maybe response
- prettyRouter :: Router route -> String
- showReadBodyCodec :: (Show a, Read a) => BodyCodec a
- showReadCaptureCodec :: (Show a, Read a) => CaptureCodec a
Types
data Bodiedness Source #
data Path :: (Type -> Type) -> [Type] -> Type where Source #
PathNil :: Path cap '[] | |
PathConsCapture :: cap a -> Path cap as -> Path cap (a ': as) | |
PathConsMatch :: Text -> Path cap as -> Path cap as |
newtype ResponseBody rpf response Source #
ResponseBody | |
|
data RequestBody :: (Type -> Type) -> Bodiedness -> Type where Source #
RequestBodyPresent :: f a -> RequestBody f (Body a) | |
RequestBodyAbsent :: RequestBody f Bodyless |
data Parameter :: Param -> Type where Source #
ParameterFlag :: Bool -> Parameter Flag | |
ParameterOptional :: Maybe a -> Parameter (Optional a) | |
ParameterList :: [a] -> Parameter (List a) |
data Rec u a b :: 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 :: *
.
TestCoercion u f => TestCoercion [u] (Rec u f) | |
TestEquality u f => TestEquality [u] (Rec u f) | |
Eq (Rec u f ([] u)) | |
(Eq (f r), Eq (Rec a f rs)) => Eq (Rec a f ((:) a r rs)) | |
Ord (Rec u f ([] u)) | |
(Ord (f r), Ord (Rec a f rs)) => Ord (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.
|
Monoid (Rec u f ([] u)) | |
(Monoid (f r), Monoid (Rec a f rs)) => Monoid (Rec a f ((:) a r rs)) | |
Storable (Rec u f ([] u)) | |
(Storable (f r), Storable (Rec a f rs)) => Storable (Rec a f ((:) a r rs)) | |
BodyCodec | |
|
data BodyDecoding a Source #
data BodyEncoding a Source #
data CaptureCodec a Source #
CaptureCodec | |
|
newtype CaptureEncoding a Source #
CaptureEncoding | |
|
newtype CaptureDecoding a Source #
CaptureDecoding | |
|
The HTTP content type and body.
newtype QueryString Source #
QueryString | |
|
Url | |
|
Payload | |
|
Existential
data Prepared :: ([Type] -> [Param] -> Bodiedness -> Type -> Type) -> Type -> Type where Source #
Includes the path and the request body (and the querystring params after they get added to this library).
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.
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.
Constructed :: route captures querys request response -> Constructed route |
Queries
encodeQuery :: QueryString -> Query Source #
decodeQuery :: Query -> QueryString Source #
Url
Using Routes
:: (forall caps qry req resp. route caps qry req resp -> Path pf caps) | Extract the path codec from a route |
-> (forall caps qry req resp. route caps qry req resp -> Rec (Query qf) qry) | Extract the query parameter codec from a route |
-> (forall caps qry req resp. route caps qry req resp -> RequestBody rqf req) | Extract the request body codec from a route |
-> 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
:: Applicative m | |
=> (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureDecoding) qrys) | |
-> (forall caps qrys req resp. route caps qrys req resp -> RequestBody (Many BodyDecoding) req) | |
-> (forall caps qrys req resp. route caps qrys req resp -> ResponseBody (Many BodyEncoding) 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 |
-> Text | Method |
-> [Text] | 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'
:: (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureDecoding) qrys) | |
-> (forall caps qrys req resp. route caps qrys req resp -> RequestBody (Many BodyDecoding) req) | |
-> Router route | Router |
-> Text | 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.
:: (forall caps qrys req resp. route caps qrys req resp -> Path CaptureEncoding caps) | How to encode the path pieces of a route |
-> (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureEncoding) qrys) | How to encode the query parameters of a route |
-> Prepared route response | The route to encode |
-> Url |
Generate a Url
for use in hyperlinks.
:: (forall caps qrys req resp. route caps qrys req resp -> Path CaptureEncoding caps) | How to encode the path pieces of a route |
-> (forall caps qrys req resp. route caps qrys req resp -> Rec (Query CaptureEncoding) qrys) | How to encode the query parameters of a route |
-> (forall caps qrys req resp. route caps qrys req resp -> RequestBody (Many BodyEncoding) req) | How to encode the request body of a route |
-> (forall caps qrys req resp. route caps qrys req resp -> ResponseBody (Many BodyDecoding) resp) | How to decode the response body from a route |
-> Prepared route response | The route to be payload encoded |
-> Payload |
Only useful for library authors
:: Functor m | |
=> (forall caps querys req resp. route caps querys req resp -> Text) | |
-> (forall caps querys req resp. route caps querys req resp -> Path CaptureEncoding caps) | |
-> (forall caps querys req resp. route caps querys req resp -> Rec (Query CaptureEncoding) querys) | |
-> (forall caps querys req resp. route caps querys req resp -> RequestBody (Many BodyEncoding) req) | |
-> (forall caps querys req resp. route caps querys req resp -> ResponseBody (Many BodyDecoding) resp) | |
-> (Text -> Url -> Maybe Content -> [Text] -> m (Either TrasaErr Content)) | method, url, content, accepts -> response |
-> Prepared route response | |
-> m (Either TrasaErr response) |
:: (forall caps querys req resp. route caps querys req resp -> Text) | Get the method from a route |
-> (forall caps querys req resp. route caps querys req resp -> Path CaptureDecoding caps) | How to decode path pieces of a route |
-> [Constructed route] | |
-> Router route |
Build a router from all the possible routes, and methods to turn routes into needed metadata
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
Defining Routes
Path
Request Body
body :: rqf req -> RequestBody rqf (Body req) Source #
bodyless :: RequestBody rqf Bodyless Source #
Response Body
resp :: rpf resp -> ResponseBody rpf resp Source #
Query
demoteParameter :: Parameter param -> ParamBase param Source #
Converting Route Metadata
mapRequestBody :: (forall x. rqf x -> rqf' x) -> RequestBody rqf request -> RequestBody rqf' request Source #
mapResponseBody :: (forall x. rpf x -> rpf' x) -> ResponseBody rpf request -> ResponseBody rpf' request Source #
mapConstructed :: (forall caps qrys req resp. sub caps qrys req resp -> route cap qrys req resp) -> Constructed sub -> Constructed route Source #
Converting Codecs
bodyCodecToBodyEncoding :: BodyCodec a -> BodyEncoding a Source #
bodyCodecToBodyDecoding :: BodyCodec a -> BodyDecoding a Source #
Errors
Argument Currying
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
Random Stuff
encodeRequestBody :: RequestBody (Many BodyEncoding) request -> RequestBody Identity request -> Maybe Content Source #
decodeResponseBody :: ResponseBody (Many BodyDecoding) response -> Content -> Maybe response Source #
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.
Show/Read Codecs
showReadCaptureCodec :: (Show a, Read a) => CaptureCodec a Source #