solga-0.1.0.0: Simple typesafe web routing

Safe HaskellNone
LanguageHaskell2010

Solga

Contents

Synopsis

Serving APIs

serve :: Router r => r -> Application

Serve a Router with Solga, returning SolgaErrors as HTTP responses.

serveThrow :: Router r => r -> Application

Serve a Router with Solga, throwing SolgaErrors.

Basic routers

type (:>) f g = f g infixr 2

Compose routers. This is just type application, ie.: Foo :> Bar :> Baz == Foo (Bar Baz)

type (/>) seg g = Seg seg :> g infixr 2

Match a path, segment, e.g "foo" /> JSON Bar

type Get a = Endpoint "GET" (JSON a)

Handle a GET request and produce a JSON response, with IO.

type Post a = Endpoint "POST" (JSON a)

Handle a POST request and produce a JSON response, with IO.

newtype JSON a

Return a given JSON object

Constructors

JSON 

Fields

jsonResponse :: a
 

Instances

Eq a => Eq (JSON a) 
Ord a => Ord (JSON a) 
Show a => Show (JSON a) 
Abbreviated (JSON a) 
ToJSON a => Router (JSON a) 
type Brief (JSON a) = a 

newtype Raw

Serve a given WAI Application.

Constructors

Raw 

Fields

rawApp :: Application
 

newtype RawResponse

Serve a given WAI Response.

Constructors

RawResponse 

newtype End next

Only accept the end of a path.

Constructors

End 

Fields

endNext :: next
 

Instances

Abbreviated next => Abbreviated (End next) 
Router next => Router (End next) 
type Brief (End next) = Brief next 

newtype WithIO next

Produce a response with IO.

Constructors

WithIO 

Fields

withIONext :: IO next
 

Instances

Abbreviated next => Abbreviated (WithIO next) 
Router next => Router (WithIO next) 
type Brief (WithIO next) = IO (Brief next) 

newtype Seg seg next

Match a constant directory in the path.

When specifying APIs, use the /> combinator to specify sub-paths: "foo" /> JSON Bar

Constructors

Seg 

Fields

segNext :: next
 

Instances

Eq next => Eq (Seg seg next) 
Ord next => Ord (Seg seg next) 
Show next => Show (Seg seg next) 
Abbreviated next => Abbreviated (Seg seg next) 
(KnownSymbol seg, Router next) => Router (Seg seg next) 
type Brief (Seg seg next) = Brief next 

data OneOfSegs segs next

Match any of a set of path segments.

Constructors

OneOfSegs 

Fields

oneOfSegsNext :: next
 

Instances

Abbreviated next => Abbreviated (OneOfSegs segs next) 
(KnownSymbol seg, Router next, Router (OneOfSegs segs next)) => Router (OneOfSegs ((:) Symbol seg segs) next) 
Router next => Router (OneOfSegs ([] Symbol) next) 
type Brief (OneOfSegs segs next) = Brief next 

class FromSegment a where

The class of types that can be parsed from a path segment.

Methods

fromSegment :: Text -> Maybe a

Instances

newtype Capture a next

Capture a path segment and pass it on.

Constructors

Capture 

Fields

captureNext :: a -> next
 

Instances

Abbreviated next => Abbreviated (Capture a next) 
(FromSegment a, Router next) => Router (Capture a next) 
type Brief (Capture a next) = a -> Brief next 

newtype Method method next

Accepts requests with a certain method.

Constructors

Method 

Fields

methodNext :: next
 

Instances

Eq next => Eq (Method method next) 
Ord next => Ord (Method method next) 
Show next => Show (Method method next) 
Abbreviated next => Abbreviated (Method method next) 
(KnownSymbol method, Router next) => Router (Method method next) 
type Brief (Method method next) = Brief next 

data ExtraHeaders next

Set extra headers on responses. Existing headers will be overriden if specified here.

Instances

Abbreviated (ExtraHeaders next) 
Router next => Router (ExtraHeaders next) 
type Brief (ExtraHeaders next) = ExtraHeaders next 

newtype NoCache next

Prevent caching for sub-routers.

Constructors

NoCache 

Fields

noCacheNext :: next
 

Instances

Abbreviated next => Abbreviated (NoCache next) 
Router next => Router (NoCache next) 
type Brief (NoCache next) = Brief next 

newtype ReqBodyJSON a next

Parse a JSON request body.

Constructors

ReqBodyJSON 

Fields

reqBodyJSONNext :: a -> next
 

Instances

Abbreviated next => Abbreviated (ReqBodyJSON a next) 
(FromJSON a, Router next) => Router (ReqBodyJSON a next) 
type Brief (ReqBodyJSON a next) = a -> Brief next 

type MultiPartData = ([Param], [File FilePath])

A parsed "multipart/form-data" request.

data ReqBodyMultipart a next

Accept a "multipart/form-data" request. Files will be stored in a temporary directory and will be deleted automatically after the request is processed.

Instances

type Endpoint method a = End :> (NoCache :> (Method method :> (WithIO :> a)))

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

Try to route with left, or try to route with right.

Constructors

(:<|>) infixr 1 

Fields

altLeft :: left
 
altRight :: right
 

Instances

(Eq left, Eq right) => Eq ((:<|>) left right) 
(Ord left, Ord right) => Ord ((:<|>) left right) 
(Show left, Show right) => Show ((:<|>) left right) 
(Abbreviated left, Abbreviated right) => Abbreviated ((:<|>) left right) 
(Router left, Router right) => Router ((:<|>) left right) 
type Brief ((:<|>) left right) = (:<|>) (Brief left) (Brief right) 

Abbreviation

class Abbreviated a where

Most Routers are really just newtypes. By using brief, you can construct trees of Routers by providing only their inner types, much like Servant.

Minimal complete definition

Nothing

Associated Types

type Brief a :: *

Methods

brief :: Brief a -> a

Instances

Error handling

data SolgaError

A Router-related exception with a corresponding HTTP error code.

badRequest :: Text -> SolgaError

Create a 400 Bad Request error with a given message.

notFound :: Text -> SolgaError

Create a 404 Not Found error with a given message.

Router implementation

class Router r where

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 Routers as fields. The fields will be considered alternatives, as if you wrote :<|> between them.

Minimal complete definition

Nothing

Methods

tryRoute :: Request -> Maybe (r -> Responder)

Given a request, if the router supports the given request return a function that constructs a response with a concrete router.

Instances

Router RawResponse 
Router Raw 
Router next => Router (WithIO next) 
Router next => Router (NoCache next) 
Router next => Router (ExtraHeaders next) 
ToJSON a => Router (JSON a) 
Router next => Router (End next) 
Router next => Router (ReqBodyMultipart a next) 
(FromJSON a, Router next) => Router (ReqBodyJSON a next) 
(KnownSymbol method, Router next) => Router (Method method next) 
(FromSegment a, Router next) => Router (Capture a next) 
(KnownSymbol seg, Router next, Router (OneOfSegs segs next)) => Router (OneOfSegs ((:) Symbol seg segs) next) 
Router next => Router (OneOfSegs ([] Symbol) next) 
(Router left, Router right) => Router ((:<|>) left right) 
(KnownSymbol seg, Router next) => Router (Seg seg next) 
Router r => Router (K1 i r p) 
(Router (left p), Router (right p)) => Router ((:*:) left right p) 
Router (f p) => Router (M1 i c f p) 

type Responder = (Response -> IO ResponseReceived) -> IO ResponseReceived

The right hand side of Application. Request is already known.

tryRouteNext :: Router r' => (r -> r') -> Request -> Maybe (r -> Responder)

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)

Like tryRouteNext but in IO.