solga-0.1.0.2: Simple typesafe web routing

Safe HaskellNone
LanguageHaskell2010

Solga

Contents

Synopsis

Serving APIs

serve :: Router r => r -> Application Source #

Serve a Router with Solga, returning SolgaErrors as HTTP responses and other errors as HTTP 500.

serveThrow :: Router r => r -> Application Source #

Serve a Router with Solga, throwing SolgaErrors.

Basic routers

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

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

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

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

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

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

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

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

newtype JSON a Source #

Return a given JSON object

Constructors

JSON 

Fields

Instances

Eq a => Eq (JSON a) Source # 

Methods

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

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

Ord a => Ord (JSON a) Source # 

Methods

compare :: JSON a -> JSON a -> Ordering #

(<) :: JSON a -> JSON a -> Bool #

(<=) :: JSON a -> JSON a -> Bool #

(>) :: JSON a -> JSON a -> Bool #

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

max :: JSON a -> JSON a -> JSON a #

min :: JSON a -> JSON a -> JSON a #

Show a => Show (JSON a) Source # 

Methods

showsPrec :: Int -> JSON a -> ShowS #

show :: JSON a -> String #

showList :: [JSON a] -> ShowS #

Abbreviated (JSON a) Source # 

Associated Types

type Brief (JSON a) :: * Source #

Methods

brief :: Brief (JSON a) -> JSON a Source #

ToJSON a => Router (JSON a) Source # 
type Brief (JSON a) Source # 
type Brief (JSON a) = a

newtype Raw Source #

Serve a given WAI Application.

Constructors

Raw 

Fields

Instances

Abbreviated Raw Source # 

Associated Types

type Brief Raw :: * Source #

Methods

brief :: Brief Raw -> Raw Source #

Router Raw Source # 
type Brief Raw Source # 

newtype End next Source #

Only accept the end of a path.

Constructors

End 

Fields

Instances

Abbreviated next => Abbreviated (End next) Source # 

Associated Types

type Brief (End next) :: * Source #

Methods

brief :: Brief (End next) -> End next Source #

Router next => Router (End next) Source # 

Methods

tryRoute :: Request -> Maybe (End next -> Responder) Source #

type Brief (End next) Source # 
type Brief (End next) = Brief next

newtype WithIO next Source #

Produce a response with IO.

Constructors

WithIO 

Fields

Instances

Abbreviated next => Abbreviated (WithIO next) Source # 

Associated Types

type Brief (WithIO next) :: * Source #

Methods

brief :: Brief (WithIO next) -> WithIO next Source #

Router next => Router (WithIO next) Source # 

Methods

tryRoute :: Request -> Maybe (WithIO next -> Responder) Source #

type Brief (WithIO next) Source # 
type Brief (WithIO next) = IO (Brief next)

newtype Seg seg next Source #

Match a constant directory in the path.

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

Constructors

Seg 

Fields

Instances

Eq next => Eq (Seg seg next) Source # 

Methods

(==) :: Seg seg next -> Seg seg next -> Bool #

(/=) :: Seg seg next -> Seg seg next -> Bool #

Ord next => Ord (Seg seg next) Source # 

Methods

compare :: Seg seg next -> Seg seg next -> Ordering #

(<) :: Seg seg next -> Seg seg next -> Bool #

(<=) :: Seg seg next -> Seg seg next -> Bool #

(>) :: Seg seg next -> Seg seg next -> Bool #

(>=) :: Seg seg next -> Seg seg next -> Bool #

max :: Seg seg next -> Seg seg next -> Seg seg next #

min :: Seg seg next -> Seg seg next -> Seg seg next #

Show next => Show (Seg seg next) Source # 

Methods

showsPrec :: Int -> Seg seg next -> ShowS #

show :: Seg seg next -> String #

showList :: [Seg seg next] -> ShowS #

Abbreviated next => Abbreviated (Seg seg next) Source # 

Associated Types

type Brief (Seg seg next) :: * Source #

Methods

brief :: Brief (Seg seg next) -> Seg seg next Source #

(KnownSymbol seg, Router next) => Router (Seg seg next) Source # 

Methods

tryRoute :: Request -> Maybe (Seg seg next -> Responder) Source #

type Brief (Seg seg next) Source # 
type Brief (Seg seg next) = Brief next

data OneOfSegs segs next Source #

Match any of a set of path segments.

Constructors

OneOfSegs 

Fields

Instances

Abbreviated next => Abbreviated (OneOfSegs segs next) Source # 

Associated Types

type Brief (OneOfSegs segs next) :: * Source #

Methods

brief :: Brief (OneOfSegs segs next) -> OneOfSegs segs next Source #

(KnownSymbol seg, Router next, Router (OneOfSegs segs next)) => Router (OneOfSegs ((:) Symbol seg segs) next) Source # 

Methods

tryRoute :: Request -> Maybe (OneOfSegs ((Symbol ': seg) segs) next -> Responder) Source #

Router next => Router (OneOfSegs ([] Symbol) next) Source # 
type Brief (OneOfSegs segs next) Source # 
type Brief (OneOfSegs segs next) = Brief next

class FromSegment a where Source #

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

Minimal complete definition

fromSegment

Methods

fromSegment :: Text -> Maybe a Source #

newtype Capture a next Source #

Capture a path segment and pass it on.

Constructors

Capture 

Fields

Instances

Abbreviated next => Abbreviated (Capture a next) Source # 

Associated Types

type Brief (Capture a next) :: * Source #

Methods

brief :: Brief (Capture a next) -> Capture a next Source #

(FromSegment a, Router next) => Router (Capture a next) Source # 

Methods

tryRoute :: Request -> Maybe (Capture a next -> Responder) Source #

type Brief (Capture a next) Source # 
type Brief (Capture a next) = a -> Brief next

newtype Method method next Source #

Accepts requests with a certain method.

Constructors

Method 

Fields

Instances

Eq next => Eq (Method method next) Source # 

Methods

(==) :: Method method next -> Method method next -> Bool #

(/=) :: Method method next -> Method method next -> Bool #

Ord next => Ord (Method method next) Source # 

Methods

compare :: Method method next -> Method method next -> Ordering #

(<) :: Method method next -> Method method next -> Bool #

(<=) :: Method method next -> Method method next -> Bool #

(>) :: Method method next -> Method method next -> Bool #

(>=) :: Method method next -> Method method next -> Bool #

max :: Method method next -> Method method next -> Method method next #

min :: Method method next -> Method method next -> Method method next #

Show next => Show (Method method next) Source # 

Methods

showsPrec :: Int -> Method method next -> ShowS #

show :: Method method next -> String #

showList :: [Method method next] -> ShowS #

Abbreviated next => Abbreviated (Method method next) Source # 

Associated Types

type Brief (Method method next) :: * Source #

Methods

brief :: Brief (Method method next) -> Method method next Source #

(KnownSymbol method, Router next) => Router (Method method next) Source # 

Methods

tryRoute :: Request -> Maybe (Method method next -> Responder) Source #

type Brief (Method method next) Source # 
type Brief (Method method next) = Brief next

data ExtraHeaders next Source #

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

Instances

Abbreviated (ExtraHeaders next) Source # 

Associated Types

type Brief (ExtraHeaders next) :: * Source #

Methods

brief :: Brief (ExtraHeaders next) -> ExtraHeaders next Source #

Router next => Router (ExtraHeaders next) Source # 
type Brief (ExtraHeaders next) Source # 
type Brief (ExtraHeaders next) = ExtraHeaders next

newtype NoCache next Source #

Prevent caching for sub-routers.

Constructors

NoCache 

Fields

Instances

Abbreviated next => Abbreviated (NoCache next) Source # 

Associated Types

type Brief (NoCache next) :: * Source #

Methods

brief :: Brief (NoCache next) -> NoCache next Source #

Router next => Router (NoCache next) Source # 

Methods

tryRoute :: Request -> Maybe (NoCache next -> Responder) Source #

type Brief (NoCache next) Source # 
type Brief (NoCache next) = Brief next

newtype ReqBodyJSON a next Source #

Parse a JSON request body.

Constructors

ReqBodyJSON 

Fields

Instances

Abbreviated next => Abbreviated (ReqBodyJSON a next) Source # 

Associated Types

type Brief (ReqBodyJSON a next) :: * Source #

Methods

brief :: Brief (ReqBodyJSON a next) -> ReqBodyJSON a next Source #

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

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

A parsed "multipart/form-data" request.

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.

Instances

Abbreviated (ReqBodyMultipart a next) Source # 

Associated Types

type Brief (ReqBodyMultipart a next) :: * Source #

Methods

brief :: Brief (ReqBodyMultipart a next) -> ReqBodyMultipart a next Source #

Router next => Router (ReqBodyMultipart a next) Source # 
type Brief (ReqBodyMultipart a next) Source # 
type Brief (ReqBodyMultipart a next) = ReqBodyMultipart a next

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.

Constructors

(:<|>) infixr 1 

Fields

Instances

(Eq right, Eq left) => Eq ((:<|>) left right) Source # 

Methods

(==) :: (left :<|> right) -> (left :<|> right) -> Bool #

(/=) :: (left :<|> right) -> (left :<|> right) -> Bool #

(Ord right, Ord left) => Ord ((:<|>) left right) Source # 

Methods

compare :: (left :<|> right) -> (left :<|> right) -> Ordering #

(<) :: (left :<|> right) -> (left :<|> right) -> Bool #

(<=) :: (left :<|> right) -> (left :<|> right) -> Bool #

(>) :: (left :<|> right) -> (left :<|> right) -> Bool #

(>=) :: (left :<|> right) -> (left :<|> right) -> Bool #

max :: (left :<|> right) -> (left :<|> right) -> left :<|> right #

min :: (left :<|> right) -> (left :<|> right) -> left :<|> right #

(Show right, Show left) => Show ((:<|>) left right) Source # 

Methods

showsPrec :: Int -> (left :<|> right) -> ShowS #

show :: (left :<|> right) -> String #

showList :: [left :<|> right] -> ShowS #

(Abbreviated left, Abbreviated right) => Abbreviated ((:<|>) left right) Source # 

Associated Types

type Brief ((:<|>) left right) :: * Source #

Methods

brief :: Brief (left :<|> right) -> left :<|> right Source #

(Router left, Router right) => Router ((:<|>) left right) Source # 

Methods

tryRoute :: Request -> Maybe ((left :<|> right) -> Responder) Source #

type Brief ((:<|>) left right) Source # 
type Brief ((:<|>) left right) = (:<|>) (Brief left) (Brief right)

Abbreviation

class Abbreviated a where Source #

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

Associated Types

type Brief a :: * Source #

Methods

brief :: Brief a -> a Source #

brief :: a -> a Source #

Instances

Abbreviated RawResponse Source # 

Associated Types

type Brief RawResponse :: * Source #

Abbreviated Raw Source # 

Associated Types

type Brief Raw :: * Source #

Methods

brief :: Brief Raw -> Raw Source #

Abbreviated next => Abbreviated (WithIO next) Source # 

Associated Types

type Brief (WithIO next) :: * Source #

Methods

brief :: Brief (WithIO next) -> WithIO next Source #

Abbreviated next => Abbreviated (NoCache next) Source # 

Associated Types

type Brief (NoCache next) :: * Source #

Methods

brief :: Brief (NoCache next) -> NoCache next Source #

Abbreviated (ExtraHeaders next) Source # 

Associated Types

type Brief (ExtraHeaders next) :: * Source #

Methods

brief :: Brief (ExtraHeaders next) -> ExtraHeaders next Source #

Abbreviated (JSON a) Source # 

Associated Types

type Brief (JSON a) :: * Source #

Methods

brief :: Brief (JSON a) -> JSON a Source #

Abbreviated next => Abbreviated (End next) Source # 

Associated Types

type Brief (End next) :: * Source #

Methods

brief :: Brief (End next) -> End next Source #

Abbreviated (ReqBodyMultipart a next) Source # 

Associated Types

type Brief (ReqBodyMultipart a next) :: * Source #

Methods

brief :: Brief (ReqBodyMultipart a next) -> ReqBodyMultipart a next Source #

Abbreviated next => Abbreviated (ReqBodyJSON a next) Source # 

Associated Types

type Brief (ReqBodyJSON a next) :: * Source #

Methods

brief :: Brief (ReqBodyJSON a next) -> ReqBodyJSON a next Source #

Abbreviated next => Abbreviated (Method method next) Source # 

Associated Types

type Brief (Method method next) :: * Source #

Methods

brief :: Brief (Method method next) -> Method method next Source #

Abbreviated next => Abbreviated (Capture a next) Source # 

Associated Types

type Brief (Capture a next) :: * Source #

Methods

brief :: Brief (Capture a next) -> Capture a next Source #

Abbreviated next => Abbreviated (OneOfSegs segs next) Source # 

Associated Types

type Brief (OneOfSegs segs next) :: * Source #

Methods

brief :: Brief (OneOfSegs segs next) -> OneOfSegs segs next Source #

(Abbreviated left, Abbreviated right) => Abbreviated ((:<|>) left right) Source # 

Associated Types

type Brief ((:<|>) left right) :: * Source #

Methods

brief :: Brief (left :<|> right) -> left :<|> right Source #

Abbreviated next => Abbreviated (Seg seg next) Source # 

Associated Types

type Brief (Seg seg next) :: * Source #

Methods

brief :: Brief (Seg seg next) -> Seg seg next Source #

Error handling

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

class Router r where Source #

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.

Methods

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.

Instances

Router RawResponse Source # 
Router Raw Source # 
Router next => Router (WithIO next) Source # 

Methods

tryRoute :: Request -> Maybe (WithIO next -> Responder) Source #

Router next => Router (NoCache next) Source # 

Methods

tryRoute :: Request -> Maybe (NoCache next -> Responder) Source #

Router next => Router (ExtraHeaders next) Source # 
ToJSON a => Router (JSON a) Source # 
Router next => Router (End next) Source # 

Methods

tryRoute :: Request -> Maybe (End next -> Responder) Source #

Router next => Router (ReqBodyMultipart a next) Source # 
(FromJSON a, Router next) => Router (ReqBodyJSON a next) Source # 
(KnownSymbol method, Router next) => Router (Method method next) Source # 

Methods

tryRoute :: Request -> Maybe (Method method next -> Responder) Source #

(FromSegment a, Router next) => Router (Capture a next) Source # 

Methods

tryRoute :: Request -> Maybe (Capture a next -> Responder) Source #

(KnownSymbol seg, Router next, Router (OneOfSegs segs next)) => Router (OneOfSegs ((:) Symbol seg segs) next) Source # 

Methods

tryRoute :: Request -> Maybe (OneOfSegs ((Symbol ': seg) segs) next -> Responder) Source #

Router next => Router (OneOfSegs ([] Symbol) next) Source # 
(Router left, Router right) => Router ((:<|>) left right) Source # 

Methods

tryRoute :: Request -> Maybe ((left :<|> right) -> Responder) Source #

(KnownSymbol seg, Router next) => Router (Seg seg next) Source # 

Methods

tryRoute :: Request -> Maybe (Seg seg next -> Responder) Source #

Router r => Router (K1 i r p) Source # 

Methods

tryRoute :: Request -> Maybe (K1 i r p -> Responder) Source #

(Router (left p), Router (right p)) => Router ((:*:) left right p) Source # 

Methods

tryRoute :: Request -> Maybe ((left :*: right) p -> Responder) Source #

Router (f p) => Router (M1 i c f p) Source # 

Methods

tryRoute :: Request -> Maybe (M1 i c f p -> Responder) Source #

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.