okapi-0.2.0.0: A micro web framework based on monadic parsing
Safe HaskellNone
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • ScopedTypeVariables
  • AllowAmbiguousTypes
  • OverloadedStrings
  • DisambiguateRecordFields
  • RecordWildCards
  • ViewPatterns
  • ConstraintKinds
  • InstanceSigs
  • DerivingStrategies
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • ExistentialQuantification
  • GeneralizedNewtypeDeriving
  • RankNTypes
  • ExplicitForAll
  • LambdaCase
  • PatternSynonyms
  • StrictData

Okapi

Description

Okapi is a micro web framework.

Synopsis

Parsing

These are the parsers that you'll use to build you own app.

type MonadOkapi m = (Functor m, Applicative m, Alternative m, Monad m, MonadPlus m, MonadError Failure m, MonadState State m) Source #

A type constraint representing monads that have the ability to parse an HTTP request.

newtype OkapiT m a Source #

A concrete implementation of the MonadOkapi type constraint.

Constructors

OkapiT 

Instances

Instances details
MonadTrans OkapiT Source # 
Instance details

Defined in Okapi

Methods

lift :: Monad m => m a -> OkapiT m a #

Monad m => MonadState State (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

get :: OkapiT m State #

put :: State -> OkapiT m () #

state :: (State -> (a, State)) -> OkapiT m a #

MonadReader r m => MonadReader r (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

ask :: OkapiT m r #

local :: (r -> r) -> OkapiT m a -> OkapiT m a #

reader :: (r -> a) -> OkapiT m a #

Monad m => MonadError Failure (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

throwError :: Failure -> OkapiT m a #

catchError :: OkapiT m a -> (Failure -> OkapiT m a) -> OkapiT m a #

Monad m => Monad (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

(>>=) :: OkapiT m a -> (a -> OkapiT m b) -> OkapiT m b #

(>>) :: OkapiT m a -> OkapiT m b -> OkapiT m b #

return :: a -> OkapiT m a #

Functor m => Functor (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

fmap :: (a -> b) -> OkapiT m a -> OkapiT m b #

(<$) :: a -> OkapiT m b -> OkapiT m a #

Monad m => Applicative (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

pure :: a -> OkapiT m a #

(<*>) :: OkapiT m (a -> b) -> OkapiT m a -> OkapiT m b #

liftA2 :: (a -> b -> c) -> OkapiT m a -> OkapiT m b -> OkapiT m c #

(*>) :: OkapiT m a -> OkapiT m b -> OkapiT m b #

(<*) :: OkapiT m a -> OkapiT m b -> OkapiT m a #

MonadIO m => MonadIO (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

liftIO :: IO a -> OkapiT m a #

Monad m => Alternative (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

empty :: OkapiT m a #

(<|>) :: OkapiT m a -> OkapiT m a -> OkapiT m a #

some :: OkapiT m a -> OkapiT m [a] #

many :: OkapiT m a -> OkapiT m [a] #

Monad m => MonadPlus (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

mzero :: OkapiT m a #

mplus :: OkapiT m a -> OkapiT m a -> OkapiT m a #

MFunctor OkapiT Source # 
Instance details

Defined in Okapi

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> OkapiT m b -> OkapiT n b

data Failure Source #

Represents the two variants of failure that can occur when parsing a HTTP request.

Constructors

Skip 
Error Response 

Instances

Instances details
Show Failure Source # 
Instance details

Defined in Okapi

Monad m => MonadError Failure (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

throwError :: Failure -> OkapiT m a #

catchError :: OkapiT m a -> (Failure -> OkapiT m a) -> OkapiT m a #

data State Source #

Represents the state of a parser. Set on every request to the Okapi server.

Constructors

State 

Fields

Instances

Instances details
Monad m => MonadState State (OkapiT m) Source # 
Instance details

Defined in Okapi

Methods

get :: OkapiT m State #

put :: State -> OkapiT m () #

state :: (State -> (a, State)) -> OkapiT m a #

data Request Source #

Represents the HTTP request being parsed.

Instances

Instances details
Eq Request Source # 
Instance details

Defined in Okapi

Methods

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

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

Show Request Source # 
Instance details

Defined in Okapi

type Path = [Text] Source #

data QueryValue Source #

Constructors

QueryParam Text 
QueryFlag 

Instances

Instances details
Eq QueryValue Source # 
Instance details

Defined in Okapi

Show QueryValue Source # 
Instance details

Defined in Okapi

type HeaderName = HeaderName Source #

type Cookie = [Crumb] Source #

Request Parsers

request :: MonadOkapi m => m Request Source #

Parses the entire request.

Method Parsers

Path Parsers

These are the path parsers.

path :: MonadOkapi m => m [Text] Source #

Parses and discards mutiple path segments matching the values and order of the given [Text] value

pathParam :: (FromHttpApiData a, MonadOkapi m) => m a Source #

Parses and discards a single path segment matching the given Text value

Query Parsers

These are the query parsers.

queryFlag :: MonadOkapi m => Text -> m () Source #

Test for the existance of a query flag

queryParam :: (FromHttpApiData a, MonadOkapi m) => Text -> m a Source #

Parses the value of a query parameter with the given type and name

queryList :: (FromHttpApiData a, MonadOkapi m) => Text -> m (NonEmpty a) Source #

Body Parsers

 

bodyJSON :: (FromJSON a, MonadOkapi m) => m a Source #

bodyForm :: (FromForm a, MonadOkapi m) => m a Source #

bodyEnd :: MonadOkapi m => m () Source #

Header Parsers

These are header parsers.

header :: MonadOkapi m => HeaderName -> m ByteString Source #

Vault Parsers

 

vaultLookup :: MonadOkapi m => Key a -> m a Source #

vaultInsert :: MonadOkapi m => Key a -> a -> m () Source #

vaultDelete :: MonadOkapi m => Key a -> m () Source #

vaultAdjust :: MonadOkapi m => (a -> a) -> Key a -> m () Source #

Combinators

 

is :: (Eq a, MonadOkapi m) => m a -> a -> m () Source #

satisfies :: (Eq a, MonadOkapi m) => m a -> (a -> Bool) -> m () Source #

look :: MonadOkapi m => m a -> m a Source #

Parses without modifying the state, even if it succeeds.

Failure

next :: MonadOkapi m => m a Source #

(<!>) :: MonadOkapi m => m a -> m a -> m a Source #

Responding

type Handler m = m Response Source #

Represents monadic actions that return a Response, for some m.

data Response Source #

Represents HTTP responses that can be returned by a parser.

data ResponseBody Source #

Represents the body of an HTTP response.

Values

Setters

setJSON :: ToJSON a => a -> Response -> Response Source #

Special

Middleware

Middlewares allow you to modify the behavior of Okapi handlers. Middlewares are functions that take a handler and return another handler. Middlewares can be composed with the fish operator >=>.

 clearHeadersMiddleware >=> pathPrefix ["jello"] :: forall m. Middleware m

type Middleware m = Handler m -> Handler m Source #

A middleware takes an action that returns a Response and can modify the action in various ways

Routing

Okapi implements routes and type-safe relative URLs using bidirectional pattern synonyms and view patterns. Routing can be extended to dispatch on any property of the request, including method, path, query, headers, and even body. By default, Okapi provides a route function for dispatching on the path of the request.

type Router m a Source #

Arguments

 = m a

Parser for dispatcher

-> (a -> Handler m)

Dispatches parser result to the correct handler

-> Handler m 

pattern PathParam :: (ToHttpApiData a, FromHttpApiData a) => a -> Text Source #

pattern GET :: Method Source #

pattern POST :: Method Source #

pattern DELETE :: Method Source #

pattern PUT :: Method Source #

pattern PATCH :: Method Source #

pattern IsQueryParam :: (ToHttpApiData a, FromHttpApiData a) => a -> QueryValue Source #

viewQueryParam :: FromHttpApiData a => Text -> Query -> (Maybe a, Query) Source #

Relative URLs

Relative URLs are useful when we want to refer to other locations within our app. Thanks to bidirectional patterns, we can use the same pattern to deconstruct an incoming request AND construct the relative URL that leads to itself.

data RelURL Source #

Constructors

RelURL Path Query 

Testing

There are two ways to test in Okapi.

WAI

These functions are for interfacing with WAI (Web Application Interface).

run :: Monad m => (forall a. m a -> IO a) -> OkapiT m Response -> IO () Source #

serve Source #

Arguments

:: Monad m 
=> Int

Port

-> Response

Default Response

-> (forall a. m a -> IO a)

Monad unlift function

-> OkapiT m Response

Parser

-> IO () 

serveTLS :: Monad m => TLSSettings -> Settings -> Response -> (forall a. m a -> IO a) -> OkapiT m Response -> IO () Source #

serveWebsockets :: Monad m => ConnectionOptions -> ServerApp -> Int -> Response -> (forall a. m a -> IO a) -> OkapiT m Response -> IO () Source #

serveWebsocketsTLS :: Monad m => TLSSettings -> Settings -> ConnectionOptions -> ServerApp -> Response -> (forall a. m a -> IO a) -> OkapiT m Response -> IO () Source #

app Source #

Arguments

:: Monad m 
=> Response

The default response to pure if parser fails

-> (forall a. m a -> IO a)

Function for "unlifting" monad inside OkapiT to IO monad

-> OkapiT m Response

The parser used to equals the request

-> Application 

Turns a parser into a WAI application

websocketsApp Source #

Arguments

:: Monad m 
=> ConnectionOptions

Connection options configuration for the WebSocket server

-> ServerApp

The server to use for handling WebSocket connections

-> Response 
-> (forall a. m a -> IO a) 
-> OkapiT m Response 
-> Application 

Turns a parsers into a WAI application with WebSocket functionality See __ for information on how to create a WebSocket server

testRunSession :: Monad m => Session a -> (forall a. m a -> IO a) -> OkapiT m Response -> IO a Source #

testWithSession :: Monad m => (forall a. m a -> IO a) -> OkapiT m Response -> Session a -> IO a Source #

testRequest :: Request -> Session SResponse Source #

Utilities

Server Sent Events

 

data Event Source #

Instances

Instances details
Eq Event Source # 
Instance details

Defined in Okapi

Methods

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

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

Show Event Source # 
Instance details

Defined in Okapi

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

class ToSSE a where Source #

Methods

toSSE :: a -> Event Source #

sendValue :: ToSSE a => EventSource -> a -> IO () Source #

Sessions