Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Router = Router' Void
- type MiddlewareM m = ApplicationM m -> ApplicationM m
- type MakeError = Status -> ByteString -> ServerError
- type ValueCombinator i v ts m = Router' i (ts :+ v) m -> Router' i ts m
- type Combinator i ts m = Router' i ts m -> Router' i ts m
- data Router' i (ts :: Type) m where
- Piece :: Text -> Router' i ts m -> Router' i ts m
- QueryParam :: forall a presence parsing m ts i. (Introspection i QueryParam a, IsRequired presence, IsLenient parsing) => ByteString -> (MakeError -> Maybe (Maybe ByteString) -> m (Arg presence parsing a)) -> Router' i (ts :+ WithQueryParam presence parsing m a) m -> Router' i ts m
- Captures :: forall a ts m i. Introspection i Captures a => (MakeError -> [Text] -> m [a]) -> Text -> Router' i (ts :+ WithPieces a) m -> Router' i ts m
- Capture :: forall a ts m i. Introspection i Capture a => (MakeError -> Text -> m a) -> Text -> Router' i (ts :+ WithPiece a) m -> Router' i ts m
- Middleware :: MiddlewareM m -> Router' i ts m -> Router' i ts m
- Header :: forall a presence parsing m ts i. (Introspection i Header a, IsRequired presence, IsLenient parsing) => HeaderName -> (MakeError -> [ByteString] -> m (Arg presence parsing a)) -> Router' i (ts :+ WithHeader presence parsing m a) m -> Router' i ts m
- Request :: forall r m i ts. (Introspection i Request r, IsRequest r) => (ErrorBuilder -> Request -> m r) -> Router' i (ts :+ WithReq m r) m -> Router' i ts m
- Alt :: [Router' i ts m] -> Router' i ts m
- Handle :: forall o m ts i st. (HandleArgs ts st m, ToResponse m o, CanRespond o, Introspection i Response o) => Method -> (HList (DelayedArgs st) -> m o) -> Router' i ts m
- Description :: Introspection i Description desc => desc -> Router' i ts m -> Router' i ts m
- MapArgs :: forall m ts ts' i. (RHList ts -> RHList ts') -> Router' i ts' m -> Router' i ts m
- HideIntrospection :: forall i' i ts m. Router' i ts m -> Router' i' ts m
- route :: forall m ts i. (MonadIO m, MonadCatch m) => ErrorBuilders -> RoutingState -> RHList ts -> Router' i ts m -> ApplicationM m
- routeHandle :: forall m o ts st. (MonadIO m, ToResponse m o, CanRespond o, HandleArgs ts st m) => [Text] -> RHList ts -> Method -> (HList (DelayedArgs st) -> m o) -> ApplicationM m
- goThrough :: (MonadIO m, MonadCatch m) => [m b] -> m b
- throwMIO :: (Exception e, MonadIO m) => e -> m a
- checkHandler :: MonadIO f => Request -> [Text] -> Method -> f ()
- lookupHeader :: Request -> HeaderName -> [ByteString]
- smartPiece :: String -> Combinator i ts m
- newtype RoutingState = RoutingState {}
- type ApplicationM m = Request -> (Response -> IO ResponseReceived) -> m ResponseReceived
- makeHandle :: forall f o m ts i st. (HandleArgs ts st m, ToResponse m (f o), CanRespond (f o), Introspection i Response (f o)) => Method -> (o -> f o) -> (DelayedArgs st ~> m o) -> Router' i ts m
Documentation
type MiddlewareM m = ApplicationM m -> ApplicationM m Source #
type MakeError = Status -> ByteString -> ServerError Source #
type Combinator i ts m = Router' i ts m -> Router' i ts m Source #
data Router' i (ts :: Type) m where Source #
Piece | |
QueryParam | |
| |
Captures | |
| |
Capture | |
Middleware :: MiddlewareM m -> Router' i ts m -> Router' i ts m | |
Header | |
| |
Request | |
| |
Alt | |
Handle | |
| |
Description | |
| |
MapArgs :: forall m ts ts' i. (RHList ts -> RHList ts') -> Router' i ts' m -> Router' i ts m | |
HideIntrospection :: forall i' i ts m. Router' i ts m -> Router' i' ts m |
Instances
route :: forall m ts i. (MonadIO m, MonadCatch m) => ErrorBuilders -> RoutingState -> RHList ts -> Router' i ts m -> ApplicationM m Source #
routeHandle :: forall m o ts st. (MonadIO m, ToResponse m o, CanRespond o, HandleArgs ts st m) => [Text] -> RHList ts -> Method -> (HList (DelayedArgs st) -> m o) -> ApplicationM m Source #
goThrough :: (MonadIO m, MonadCatch m) => [m b] -> m b Source #
lookupHeader :: Request -> HeaderName -> [ByteString] Source #
smartPiece :: String -> Combinator i ts m Source #
newtype RoutingState Source #
type ApplicationM m = Request -> (Response -> IO ResponseReceived) -> m ResponseReceived Source #
Application
lifted to m
makeHandle :: forall f o m ts i st. (HandleArgs ts st m, ToResponse m (f o), CanRespond (f o), Introspection i Response (f o)) => Method -> (o -> f o) -> (DelayedArgs st ~> m o) -> Router' i ts m Source #