| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Symantic.HTTP.Server
Contents
- Type
Server - Type
ServerRes - Type
ServerResStream - Carrying the
framingtype variable toserver. - Carrying the
tstype variable toserver. - Providing a
returnfor the simple response case - Orphan instances
Description
See symantic-http-demo for an example of how to use this module.
Synopsis
- newtype Server responses k = Server {
- unServer :: StateT ServerState (ServerCheckT [ServerErrorBody] (ServerCheckT [ServerErrorHeader] (ServerCheckT [ServerErrorQuery] (ServerCheckT [ServerErrorContentType] (ServerCheckT [ServerErrorAccept] (ServerCheckT [ServerErrorBasicAuth] (ServerCheckT [ServerErrorMethod] (ServerCheckT [ServerErrorPath] IO)))))))) (responses -> k)
- server :: Server responses (Response Server) -> responses -> Application
- runServerChecks :: StateT ServerState (ExceptT e1 (ExceptT e2 (ExceptT e3 (ExceptT e4 (ExceptT e5 (ExceptT e6 (ExceptT e7 (ExceptT e8 IO)))))))) a -> ServerState -> IO (Either e8 (Either e7 (Either e6 (Either e5 (Either e4 (Either e3 (Either e2 (Either e1 (a, ServerState)))))))))
- type ServerCheckT e = ExceptT (Fail e)
- type RouteResult e = Either (Fail e)
- data Fail e
- = Fail ServerState e
- | FailFatal !ServerState !e
- failState :: Fail e -> ServerState
- failError :: Fail e -> e
- newtype ServerState = ServerState {}
- newtype ServerErrorPath = ServerErrorPath Text
- data ServerErrorMethod = ServerErrorMethod
- data ServerErrorAccept = ServerErrorAccept MediaTypes (Maybe (Either ByteString MediaType))
- data ServerErrorContentType = ServerErrorContentType
- newtype ServerErrorQuery = ServerErrorQuery Text
- data ServerErrorHeader = ServerErrorHeader
- data ServerErrorBasicAuth = ServerErrorBasicAuth BasicAuthRealm (BasicAuth ())
- class ServerBasicAuth a where
- serverBasicAuth :: BasicAuthUser -> BasicAuthPass -> IO (BasicAuth a)
- newtype ServerErrorBody = ServerErrorBody String
- newtype ServerBodyArg (ts :: [*]) a = ServerBodyArg a
- newtype ServerBodyStreamArg as (ts :: [*]) framing = ServerBodyStreamArg as
- newtype ServerRes (ts :: [*]) m a = ServerResponse {
- unServerResponse :: m a
- type ServerResponse ts m = ServerRes ts (ReaderT Request (WriterT ResponseHeaders (WriterT Status (ContT Response m))))
- newtype ServerResStream framing (ts :: [*]) m as = ServerResponseStream {
- unServerResponseStream :: m as
- type ServerResponseStream framing ts m = ServerResStream framing ts (ReaderT Request (WriterT ResponseHeaders (WriterT Status (ContT Response m))))
Type Server
newtype Server responses k Source #
is a recipe to produce an Server responses kApplication
from arguments responses (one per number of alternative routes),
separated by (:!:).
Server is analogous to a scanf using a format customized for HTTP routing.
The multiple ServerCheckT monad transformers are there
to prioritize the errors according to the type of check raising them,
instead of the order of the combinators within an actual API specification.
Constructors
| Server | |
Fields
| |
Instances
server :: Server responses (Response Server) -> responses -> Application Source #
returns a server api responsesApplication
ready to be given to Warp.run 80.
runServerChecks :: StateT ServerState (ExceptT e1 (ExceptT e2 (ExceptT e3 (ExceptT e4 (ExceptT e5 (ExceptT e6 (ExceptT e7 (ExceptT e8 IO)))))))) a -> ServerState -> IO (Either e8 (Either e7 (Either e6 (Either e5 (Either e4 (Either e3 (Either e2 (Either e1 (a, ServerState))))))))) Source #
Type ServerCheckT
type ServerCheckT e = ExceptT (Fail e) Source #
Type RouteResult
type RouteResult e = Either (Fail e) Source #
Type Fail
Constructors
| Fail ServerState e | Keep trying other paths. 404, 405 or 406. |
| FailFatal !ServerState !e | Don't try other paths. |
failState :: Fail e -> ServerState Source #
Type ServerState
newtype ServerState Source #
Constructors
| ServerState | |
Fields | |
Instances
| Show ServerState Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerState -> ShowS # show :: ServerState -> String # showList :: [ServerState] -> ShowS # | |
Type ServerErrorPath
newtype ServerErrorPath Source #
Constructors
| ServerErrorPath Text |
Instances
| Eq ServerErrorPath Source # | |
Defined in Symantic.HTTP.Server Methods (==) :: ServerErrorPath -> ServerErrorPath -> Bool # (/=) :: ServerErrorPath -> ServerErrorPath -> Bool # | |
| Show ServerErrorPath Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorPath -> ShowS # show :: ServerErrorPath -> String # showList :: [ServerErrorPath] -> ShowS # | |
Type ServerErrorMethod
data ServerErrorMethod Source #
Constructors
| ServerErrorMethod |
Instances
| Eq ServerErrorMethod Source # | |
Defined in Symantic.HTTP.Server Methods (==) :: ServerErrorMethod -> ServerErrorMethod -> Bool # (/=) :: ServerErrorMethod -> ServerErrorMethod -> Bool # | |
| Show ServerErrorMethod Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorMethod -> ShowS # show :: ServerErrorMethod -> String # showList :: [ServerErrorMethod] -> ShowS # | |
Type ServerErrorAccept
data ServerErrorAccept Source #
Constructors
| ServerErrorAccept MediaTypes (Maybe (Either ByteString MediaType)) |
Instances
| Eq ServerErrorAccept Source # | |
Defined in Symantic.HTTP.Server Methods (==) :: ServerErrorAccept -> ServerErrorAccept -> Bool # (/=) :: ServerErrorAccept -> ServerErrorAccept -> Bool # | |
| Show ServerErrorAccept Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorAccept -> ShowS # show :: ServerErrorAccept -> String # showList :: [ServerErrorAccept] -> ShowS # | |
Type ServerErrorContentType
data ServerErrorContentType Source #
Constructors
| ServerErrorContentType |
Instances
| Eq ServerErrorContentType Source # | |
Defined in Symantic.HTTP.Server Methods (==) :: ServerErrorContentType -> ServerErrorContentType -> Bool # (/=) :: ServerErrorContentType -> ServerErrorContentType -> Bool # | |
| Show ServerErrorContentType Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorContentType -> ShowS # show :: ServerErrorContentType -> String # showList :: [ServerErrorContentType] -> ShowS # | |
Type ServerErrorQuery
newtype ServerErrorQuery Source #
Constructors
| ServerErrorQuery Text |
Instances
| Show ServerErrorQuery Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorQuery -> ShowS # show :: ServerErrorQuery -> String # showList :: [ServerErrorQuery] -> ShowS # | |
Type ServerErrorHeader
data ServerErrorHeader Source #
Constructors
| ServerErrorHeader |
Instances
| Eq ServerErrorHeader Source # | |
Defined in Symantic.HTTP.Server Methods (==) :: ServerErrorHeader -> ServerErrorHeader -> Bool # (/=) :: ServerErrorHeader -> ServerErrorHeader -> Bool # | |
| Show ServerErrorHeader Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorHeader -> ShowS # show :: ServerErrorHeader -> String # showList :: [ServerErrorHeader] -> ShowS # | |
Type ServerErrorBasicAuth
data ServerErrorBasicAuth Source #
Constructors
| ServerErrorBasicAuth BasicAuthRealm (BasicAuth ()) |
Instances
| Show ServerErrorBasicAuth Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorBasicAuth -> ShowS # show :: ServerErrorBasicAuth -> String # showList :: [ServerErrorBasicAuth] -> ShowS # | |
Class ServerBasicAuth
class ServerBasicAuth a where Source #
Methods
serverBasicAuth :: BasicAuthUser -> BasicAuthPass -> IO (BasicAuth a) Source #
Type ServerErrorBody
newtype ServerErrorBody Source #
Constructors
| ServerErrorBody String |
Instances
| Eq ServerErrorBody Source # | |
Defined in Symantic.HTTP.Server Methods (==) :: ServerErrorBody -> ServerErrorBody -> Bool # (/=) :: ServerErrorBody -> ServerErrorBody -> Bool # | |
| Show ServerErrorBody Source # | |
Defined in Symantic.HTTP.Server Methods showsPrec :: Int -> ServerErrorBody -> ShowS # show :: ServerErrorBody -> String # showList :: [ServerErrorBody] -> ShowS # | |
Type ServerBodyArg
newtype ServerBodyArg (ts :: [*]) a Source #
Constructors
| ServerBodyArg a |
Type ServerBodyStreamArg
newtype ServerBodyStreamArg as (ts :: [*]) framing Source #
Constructors
| ServerBodyStreamArg as |
Type ServerRes
newtype ServerRes (ts :: [*]) m a Source #
A continuation for |server|'s users to respond.
This newtype has two uses :
* Carrying the ts type variable to server.
* Providing a return for the simple response case
of status200 and no extra headers.
Constructors
| ServerResponse | |
Fields
| |
Instances
| MonadTrans (ServerRes ts) Source # | |
Defined in Symantic.HTTP.Server | |
| Monad m => Monad (ServerRes ts m) Source # | |
| Functor m => Functor (ServerRes ts m) Source # | |
| Applicative m => Applicative (ServerRes ts m) Source # | |
Defined in Symantic.HTTP.Server Methods pure :: a -> ServerRes ts m a # (<*>) :: ServerRes ts m (a -> b) -> ServerRes ts m a -> ServerRes ts m b # liftA2 :: (a -> b -> c) -> ServerRes ts m a -> ServerRes ts m b -> ServerRes ts m c # (*>) :: ServerRes ts m a -> ServerRes ts m b -> ServerRes ts m b # (<*) :: ServerRes ts m a -> ServerRes ts m b -> ServerRes ts m a # | |
| type CanDo (ServerResponse ts m) (eff :: Type) Source # | All supported effects are handled by nested |
Defined in Symantic.HTTP.Server | |
type ServerResponse ts m = ServerRes ts (ReaderT Request (WriterT ResponseHeaders (WriterT Status (ContT Response m)))) Source #
Type ServerResStream
Carrying the framing type variable to server.
Carrying the ts type variable to server.
Providing a return for the simple response case
newtype ServerResStream framing (ts :: [*]) m as Source #
Constructors
| ServerResponseStream | |
Fields
| |
Instances
| MonadTrans (ServerResStream framing ts) Source # | |
Defined in Symantic.HTTP.Server Methods lift :: Monad m => m a -> ServerResStream framing ts m a # | |
| Monad m => Monad (ServerResStream framing ts m) Source # | |
Defined in Symantic.HTTP.Server Methods (>>=) :: ServerResStream framing ts m a -> (a -> ServerResStream framing ts m b) -> ServerResStream framing ts m b # (>>) :: ServerResStream framing ts m a -> ServerResStream framing ts m b -> ServerResStream framing ts m b # return :: a -> ServerResStream framing ts m a # fail :: String -> ServerResStream framing ts m a # | |
| Functor m => Functor (ServerResStream framing ts m) Source # | |
Defined in Symantic.HTTP.Server Methods fmap :: (a -> b) -> ServerResStream framing ts m a -> ServerResStream framing ts m b # (<$) :: a -> ServerResStream framing ts m b -> ServerResStream framing ts m a # | |
| Applicative m => Applicative (ServerResStream framing ts m) Source # | |
Defined in Symantic.HTTP.Server Methods pure :: a -> ServerResStream framing ts m a # (<*>) :: ServerResStream framing ts m (a -> b) -> ServerResStream framing ts m a -> ServerResStream framing ts m b # liftA2 :: (a -> b -> c) -> ServerResStream framing ts m a -> ServerResStream framing ts m b -> ServerResStream framing ts m c # (*>) :: ServerResStream framing ts m a -> ServerResStream framing ts m b -> ServerResStream framing ts m b # (<*) :: ServerResStream framing ts m a -> ServerResStream framing ts m b -> ServerResStream framing ts m a # | |
| type CanDo (ServerResponseStream framing ts m) (eff :: Type) Source # | All supported effects are handled by nested |
Defined in Symantic.HTTP.Server | |
type ServerResponseStream framing ts m = ServerResStream framing ts (ReaderT Request (WriterT ResponseHeaders (WriterT Status (ContT Response m)))) Source #