| Safe Haskell | None |
|---|
Web.Wheb.Types
Contents
- newtype WhebT g s m a = WhebT {
- runWhebT :: ErrorT WhebError (ReaderT (HandlerData g s m) (StateT (InternalState s) m)) a
- newtype InitM g s m a = InitM {
- runInitM :: WriterT (InitOptions g s m) IO a
- class WhebContent a where
- toResponse :: Status -> ResponseHeaders -> a -> Response
- data WhebFile = WhebFile Text
- data HandlerResponse = forall a . WhebContent a => HandlerResponse Status a
- data HandlerData g s m = HandlerData {
- globalCtx :: g
- request :: Request
- postData :: ([Param], [File ByteString])
- routeParams :: RouteParamList
- globalSettings :: WhebOptions g s m
- data InternalState s = InternalState {
- reqState :: s
- respHeaders :: Map HeaderName ByteString
- data SettingsValue = forall a . Typeable a => MkVal a
- data WhebError
- data InitOptions g s m = InitOptions {
- initRoutes :: [Route g s m]
- initSettings :: CSettings
- initWaiMw :: Middleware
- initWhebMw :: [WhebMiddleware g s m]
- initCleanup :: [IO ()]
- data WhebOptions g s m = MonadIO m => WhebOptions {
- appRoutes :: [Route g s m]
- runTimeSettings :: CSettings
- warpSettings :: Settings
- startingCtx :: g
- startingState :: InternalState s
- waiStack :: Middleware
- whebMiddlewares :: [WhebMiddleware g s m]
- defaultErrorHandler :: WhebError -> WhebHandlerT g s m
- shutdownTVar :: TVar Bool
- activeConnections :: TVar Int
- cleanupActions :: [IO ()]
- type EResponse = Either WhebError Response
- type CSettings = Map Text SettingsValue
- type WhebHandler g s = WhebT g s IO HandlerResponse
- type WhebHandlerT g s m = WhebT g s m HandlerResponse
- type WhebMiddleware g s m = WhebT g s m (Maybe HandlerResponse)
- type MinWheb a = WhebT () () IO a
- type MinHandler = MinWheb HandlerResponse
- type MinOpts = WhebOptions () () IO
- type RouteParamList = [(Text, ParsedChunk)]
- type MethodMatch = StdMethod -> Bool
- data ParsedChunk = forall a . (Typeable a, Show a) => MkChunk a
- data UrlBuildError
- data UrlParser = UrlParser {
- parseFunc :: [Text] -> Maybe RouteParamList
- genFunc :: RouteParamList -> Either UrlBuildError Text
- data Route g s m = Route {
- routeName :: Maybe Text
- routeMethod :: MethodMatch
- routeParser :: UrlParser
- routeHandler :: WhebHandlerT g s m
- data ChunkType
- data UrlPat
Documentation
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 | |
Fields
| |
Writer Monad to build options.
Constructors
| InitM | |
Fields
| |
class WhebContent a whereSource
Converts a type to a WAI Response
Methods
toResponse :: Status -> ResponseHeaders -> a -> ResponseSource
Instances
A Wheb response that represents a file.
Instances
data HandlerResponse Source
Constructors
| forall a . WhebContent a => HandlerResponse Status a |
data HandlerData g s m Source
Constructors
| HandlerData | |
Fields
| |
data InternalState s Source
Constructors
| InternalState | |
Fields
| |
data SettingsValue Source
data InitOptions g s m Source
Monoid to use in InitM's WriterT
Constructors
| InitOptions | |
Fields
| |
Instances
| Monoid (InitOptions g s m) |
data WhebOptions g s m Source
The main option datatype for Wheb
Constructors
| MonadIO m => WhebOptions | |
Fields
| |
type CSettings = Map Text SettingsValueSource
type WhebHandler g s = WhebT g s IO HandlerResponseSource
type WhebHandlerT g s m = WhebT g s m HandlerResponseSource
type WhebMiddleware g s m = WhebT g s m (Maybe HandlerResponse)Source
type MinOpts = WhebOptions () () IOSource
A minimal type for WhebOptions
Routes
type RouteParamList = [(Text, ParsedChunk)]Source
type MethodMatch = StdMethod -> BoolSource
data ParsedChunk Source
Instances
A Parser should be able to extract params and regenerate URL from params.
Constructors
| UrlParser | |
Fields
| |
Constructors
| Route | |
Fields
| |