Safe Haskell | None |
---|---|
Language | Haskell2010 |
- serve :: Router r => r -> Application
- serveThrow :: Router r => r -> Application
- type (:>) f g = f g
- type (/>) seg g = Seg seg :> g
- type Get a = Endpoint "GET" (JSON a)
- type Post a = Endpoint "POST" (JSON a)
- newtype JSON a = JSON {
- jsonResponse :: a
- newtype Raw = Raw {}
- newtype RawResponse = RawResponse {}
- newtype End next = End {
- endNext :: next
- newtype WithIO next = WithIO {
- withIONext :: IO next
- newtype Seg seg next = Seg {
- segNext :: next
- data OneOfSegs segs next = OneOfSegs {
- oneOfSegsNext :: next
- class FromSegment a where
- newtype Capture a next = Capture {
- captureNext :: a -> next
- newtype Method method next = Method {
- methodNext :: next
- data ExtraHeaders next = ExtraHeaders {
- extraHeaders :: ResponseHeaders
- extraHeadersNext :: next
- newtype NoCache next = NoCache {
- noCacheNext :: next
- newtype ReqBodyJSON a next = ReqBodyJSON {
- reqBodyJSONNext :: a -> next
- type MultiPartData = ([Param], [File FilePath])
- data ReqBodyMultipart a next = ReqBodyMultipart {
- reqMultiPartParse :: MultiPartData -> Either String a
- reqMultiPartNext :: a -> next
- type Endpoint method a = End :> (NoCache :> (Method method :> (WithIO :> a)))
- data left :<|> right = (:<|>) {}
- class Abbreviated a where
- data SolgaError
- badRequest :: Text -> SolgaError
- notFound :: Text -> SolgaError
- class Router r where
- type Responder = (Response -> IO ResponseReceived) -> IO ResponseReceived
- tryRouteNext :: Router r' => (r -> r') -> Request -> Maybe (r -> Responder)
- tryRouteNextIO :: Router r' => (r -> IO r') -> Request -> Maybe (r -> Responder)
Serving APIs
serve :: Router r => r -> Application Source #
Serve a Router
with Solga, returning SolgaError
s as HTTP responses.
serveThrow :: Router r => r -> Application Source #
Serve a Router
with Solga, throwing SolgaError
s.
Basic routers
type (:>) f g = f g infixr 2 Source #
Compose routers. This is just type application,
ie.: Foo :> Bar :> Baz == Foo (Bar Baz)
Return a given JSON object
JSON | |
|
Serve a given WAI Application
.
newtype RawResponse Source #
Serve a given WAI Response
.
Only accept the end of a path.
Produce a response with IO
.
WithIO | |
|
data OneOfSegs segs next Source #
Match any of a set of path segments.
OneOfSegs | |
|
class FromSegment a where Source #
The class of types that can be parsed from a path segment.
fromSegment :: Text -> Maybe a Source #
newtype Capture a next Source #
Capture a path segment and pass it on.
Capture | |
|
Abbreviated next => Abbreviated (Capture a next) Source # | |
(FromSegment a, Router next) => Router (Capture a next) Source # | |
type Brief (Capture a next) Source # | |
newtype Method method next Source #
Accepts requests with a certain method.
Method | |
|
Eq next => Eq (Method method next) Source # | |
Ord next => Ord (Method method next) Source # | |
Show next => Show (Method method next) Source # | |
Abbreviated next => Abbreviated (Method method next) Source # | |
(KnownSymbol method, Router next) => Router (Method method next) Source # | |
type Brief (Method method next) Source # | |
data ExtraHeaders next Source #
Set extra headers on responses. Existing headers will be overriden if specified here.
ExtraHeaders | |
|
Abbreviated (ExtraHeaders next) Source # | |
Router next => Router (ExtraHeaders next) Source # | |
type Brief (ExtraHeaders next) Source # | |
Prevent caching for sub-routers.
NoCache | |
|
newtype ReqBodyJSON a next Source #
Parse a JSON request body.
ReqBodyJSON | |
|
Abbreviated next => Abbreviated (ReqBodyJSON a next) Source # | |
(FromJSON a, Router next) => Router (ReqBodyJSON a next) Source # | |
type Brief (ReqBodyJSON a next) Source # | |
data ReqBodyMultipart a next Source #
Accept a "multipart/form-data" request. Files will be stored in a temporary directory and will be deleted automatically after the request is processed.
ReqBodyMultipart | |
|
Abbreviated (ReqBodyMultipart a next) Source # | |
Router next => Router (ReqBodyMultipart a next) Source # | |
type Brief (ReqBodyMultipart a next) Source # | |
type Endpoint method a = End :> (NoCache :> (Method method :> (WithIO :> a))) Source #
Useful synonym for dynamic endpoints: accept requests with a given method, compute a JSON response in IO
and don't cache.
data left :<|> right infixr 1 Source #
Try to route with left
, or try to route with right
.
(Eq left, Eq right) => Eq ((:<|>) left right) Source # | |
(Ord left, Ord right) => Ord ((:<|>) left right) Source # | |
(Show left, Show right) => Show ((:<|>) left right) Source # | |
(Abbreviated left, Abbreviated right) => Abbreviated ((:<|>) left right) Source # | |
(Router left, Router right) => Router ((:<|>) left right) Source # | |
type Brief ((:<|>) left right) Source # | |
Abbreviation
class Abbreviated a where Source #
Most Router
s are really just newtypes. By using brief
, you can
construct trees of Router
s by providing only their inner types, much
like Servant.
Abbreviated RawResponse Source # | |
Abbreviated Raw Source # | |
Abbreviated next => Abbreviated (WithIO next) Source # | |
Abbreviated next => Abbreviated (NoCache next) Source # | |
Abbreviated (ExtraHeaders next) Source # | |
Abbreviated (JSON a) Source # | |
Abbreviated next => Abbreviated (End next) Source # | |
Abbreviated (ReqBodyMultipart a next) Source # | |
Abbreviated next => Abbreviated (ReqBodyJSON a next) Source # | |
Abbreviated next => Abbreviated (Method method next) Source # | |
Abbreviated next => Abbreviated (Capture a next) Source # | |
Abbreviated next => Abbreviated (OneOfSegs segs next) Source # | |
(Abbreviated left, Abbreviated right) => Abbreviated ((:<|>) left right) Source # | |
Abbreviated next => Abbreviated (Seg seg next) Source # | |
Error handling
data SolgaError Source #
A Router
-related exception with a corresponding HTTP error code.
badRequest :: Text -> SolgaError Source #
Create a 400 Bad Request
error with a given message.
notFound :: Text -> SolgaError Source #
Create a 404 Not Found
error with a given message.
Router implementation
Routers are the basic typeclass of Solga: their types describe what type of requests they accept, and their values describe how to handle them.
You can use Generic
to get free instance of Router
for any data type with one constructor
and Router
s as fields. The fields will be considered alternatives, as if you wrote :<|>
between them.
tryRoute :: Request -> Maybe (r -> Responder) Source #
Given a request, if the router supports the given request return a function that constructs a response with a concrete router.
tryRoute :: (Generic r, Router (Rep r ())) => Request -> Maybe (r -> Responder) Source #
Given a request, if the router supports the given request return a function that constructs a response with a concrete router.
type Responder = (Response -> IO ResponseReceived) -> IO ResponseReceived Source #
The right hand side of Application
. Request
is already known.
tryRouteNext :: Router r' => (r -> r') -> Request -> Maybe (r -> Responder) Source #
Try to route using a type r
by providing a function to turn it into a Router
r'
.
Useful for passing routing on to the next step.
tryRouteNextIO :: Router r' => (r -> IO r') -> Request -> Maybe (r -> Responder) Source #
Like tryRouteNext
but in IO
.