Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype TwainM e a = TwainM (TwainState e -> (a, TwainState e))
- data TwainState e = TwainState {
- middlewares :: [Middleware]
- environment :: e
- onExceptionResponse :: SomeException -> Response
- modify :: (TwainState e -> TwainState e) -> TwainM e ()
- exec :: TwainM e a -> e -> TwainState e
- data RouteM e a = RouteM (RouteState e -> IO (Either RouteAction (a, RouteState e)))
- data RouteAction
- data RouteState e = RouteState {
- reqBodyParams :: [Param]
- reqBodyFiles :: [File ByteString]
- reqPathParams :: [Param]
- reqQueryParams :: [Param]
- reqCookieParams :: [Param]
- reqBodyJson :: Either String Value
- reqBodyParsed :: Bool
- reqEnv :: e
- reqWai :: Request
- type Param = (Text, Text)
- data PathPattern = MatchPath (Request -> Maybe [Param])
- matchPath :: Text -> Request -> Maybe [Param]
- class ParsableParam a where
- parseParam :: Text -> Either Text a
- parseParamList :: Text -> Either Text [a]
- readEither :: Read a => Text -> Either Text a
Documentation
TwainM provides a monad interface for composing routes and middleware.
TwainM (TwainState e -> (a, TwainState e)) |
data TwainState e Source #
TwainState | |
|
modify :: (TwainState e -> TwainState e) -> TwainM e () Source #
exec :: TwainM e a -> e -> TwainState e Source #
RouteM
is a Reader-like monad that can "short-circuit" and return a WAI
response using a given environment. This provides convenient branching with
do notation for redirects, error responses, etc.
RouteM (RouteState e -> IO (Either RouteAction (a, RouteState e))) |
data RouteState e Source #
RouteState | |
|
data PathPattern Source #
Instances
IsString PathPattern Source # | |
Defined in Web.Twain.Types fromString :: String -> PathPattern # |
class ParsableParam a where Source #
Parse values from request parameters.
parseParam :: Text -> Either Text a Source #
parseParamList :: Text -> Either Text [a] Source #
Default implementation parses comma-delimited lists.
Instances
readEither :: Read a => Text -> Either Text a Source #
Useful for creating ParsableParam
instances for things that already implement Read
.