Safe Haskell | None |
---|---|
Language | Haskell2010 |
Web.Growler.Types
Documentation
data MatchResult Source
Instances
data RoutePatternResult Source
Constructors
RoutePatternResult | |
Fields
|
capture :: Text -> RoutePattern Source
type Param = (ByteString, ByteString) Source
data BodySource Source
Constructors
FileSource !FilePath !(Maybe FilePart) | |
BuilderSource !Builder | |
LBSSource !ByteString | |
StreamSource !StreamingBody | |
RawSource !(IO ByteString -> (ByteString -> IO ()) -> IO ()) !Response |
Instances
data RequestState Source
Constructors
RequestState | |
Fields |
data ResponseState Source
Constructors
ResponseState | |
Fields |
class HasHeaders s a | s -> a where Source
Instances
class HasRequest s a | s -> a where Source
Instances
type EarlyTermination = ResponseState Source
type HandlerAbort m = EitherT EarlyTermination m Source
Constructors
HandlerT | |
Fields
|
Instances
MonadTrans HandlerT | |
MonadTransControl HandlerT | |
MonadBase b m => MonadBase b (HandlerT m) | |
MonadBaseControl b m => MonadBaseControl b (HandlerT m) | |
Monad m => Monad (HandlerT m) | |
Monad m => Functor (HandlerT m) | |
Monad m => Applicative (HandlerT m) | |
MonadIO m => MonadIO (HandlerT m) | |
type StT HandlerT a = StHandlerT a | |
type StM (HandlerT m) a = ComposeSt HandlerT m a |
newtype StHandlerT a Source
Constructors
StHandlerT | |
Fields
|
Constructors
GrowlerT | |
Fields
|
data GrowlerConfig m Source
Constructors
GrowlerConfig | |
Fields
|