Wheb-0.2.0.0: The frictionless WAI Framework

Safe HaskellNone
LanguageHaskell2010

Web.Wheb.Types

Contents

Synopsis

Documentation

newtype WhebT g s m a Source

WhebT g s m

  • g -> The global confirgured context (Read-only data shared between threads)
  • s -> Handler state for each request.
  • m -> Monad we are transforming

Constructors

WhebT 

Instances

Monad m => MonadError WhebError (WhebT g s m) 
MonadTrans (WhebT g s) 
Monad m => Monad (WhebT g s m) 
Functor m => Functor (WhebT g s m) 
(Monad m, Functor m) => Applicative (WhebT g s m) 
MonadIO m => MonadIO (WhebT g s m) 

newtype InitM g s m a Source

Writer Monad to build options.

Constructors

InitM 

Fields

runInitM :: WriterT (InitOptions g s m) IO a
 

Instances

Monad (InitM g s m) 
Functor (InitM g s m) 
Applicative (InitM g s m) 
MonadIO (InitM g s m) 

class WhebContent a where Source

Converts a type to a WAI Response

data WhebFile Source

A Wheb response that represents a file.

Constructors

WhebFile Text 

data HandlerResponse Source

Constructors

forall a . WhebContent a => HandlerResponse Status a 

data HandlerData g s m Source

Our ReaderT portion of WhebT uses this.

data InternalState s Source

Our StateT portion of WhebT uses this.

data SettingsValue Source

Constructors

forall a . Typeable a => MkVal a 

data InitOptions g s m Source

Monoid to use in InitM's WriterT

Constructors

InitOptions 

Instances

data WhebOptions g s m Source

The main option datatype for Wheb

Constructors

MonadIO m => WhebOptions 

Fields

appRoutes :: [Route g s m]
 
appWhebSockets :: [SocketRoute g s m]
 
appSites :: [PackedSite g s m]
 
runTimeSettings :: CSettings
 
warpSettings :: Settings
 
startingCtx :: g

Global ctx shared between requests

startingState :: InternalState s

Handler state given each request

waiStack :: Middleware
 
whebMiddlewares :: [WhebMiddleware g s m]
 
defaultErrorHandler :: WhebError -> WhebHandlerT g s m
 
shutdownTVar :: TVar Bool
 
activeConnections :: TVar Int
 
cleanupActions :: [IO ()]
 

type WhebSocket g s m = Connection -> WhebT g s m () Source

type MinWheb a = WhebT () () IO a Source

A minimal type for WhebT

type MinOpts = WhebOptions () () IO Source

A minimal type for WhebOptions

Routes

data PackedSite g s m Source

Constructors

forall a . PackedSite Text (Site a (WhebHandlerT g s m)) 

data ParsedChunk Source

Constructors

forall a . (Typeable a, Show a) => MkChunk a 

Instances

data UrlParser Source

A Parser should be able to extract params and regenerate URL from params.

data SocketRoute g s m Source

Constructors

SocketRoute 

data ChunkType Source

Constructors

IntChunk 
TextChunk 

Instances