Safe Haskell | None |
---|---|
Language | Haskell98 |
- runSpock :: Port -> IO Middleware -> IO ()
- runSpockNoBanner :: Port -> IO Middleware -> IO ()
- spockAsApp :: IO Middleware -> IO Application
- spockT :: MonadIO m => (forall a. m a -> IO a) -> SpockT m () -> IO Middleware
- spockLimT :: forall m. MonadIO m => Maybe Word64 -> (forall a. m a -> IO a) -> SpockT m () -> IO Middleware
- spockConfigT :: forall m. MonadIO m => SpockConfig -> (forall a. m a -> IO a) -> SpockT m () -> IO Middleware
- type SpockT = SpockCtxT ()
- data SpockCtxT ctx m a
- data Path as pathState :: [*] -> PathState -> *
- root :: Path ([] *) Open
- type Var a = Path ((:) * a ([] *)) Open
- var :: (Typeable * a, FromHttpApiData a) => Path ((:) * a ([] *)) Open
- static :: String -> Path ([] *) Open
- (<//>) :: Path as Open -> Path bs ps -> Path (Append as bs) ps
- wildcard :: Path ((:) * Text ([] *)) Closed
- renderRoute :: AllHave ToHttpApiData as => Path as Open -> HVectElim as Text
- subcomponent :: (RouteM t, Monad m) => Path '[] Open -> t ctx m () -> t ctx m ()
- prehook :: (RouteM t, MonadIO m) => ActionCtxT ctx m ctx' -> t ctx' m () -> t ctx m ()
- get :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- post :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- getpost :: (HasRep xs, RouteM t, Monad m, Monad (t ctx m)) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- head :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- put :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- delete :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- patch :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- hookRoute :: (HasRep xs, RouteM t, Monad m) => StdMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- hookRouteCustom :: (HasRep xs, RouteM t, Monad m) => Text -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- hookAny :: (RouteM t, Monad m) => StdMethod -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m ()
- hookAnyCustom :: (RouteM t, Monad m) => Text -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m ()
- data StdMethod :: *
- middleware :: (RouteM t, Monad m) => Middleware -> t ctx m ()
- module Web.Spock.Action
- data SpockConfig = SpockConfig {
- sc_maxRequestSize :: Maybe Word64
- sc_errorHandler :: Status -> ActionCtxT () IO ()
- defaultSpockConfig :: SpockConfig
- hookRoute' :: (HasRep xs, RouteM t, Monad m) => SpockMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m ()
- hookAny' :: (RouteM t, Monad m) => SpockMethod -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m ()
- data SpockMethod
- newtype HttpMethod = HttpMethod {}
Lauching Spock
runSpock :: Port -> IO Middleware -> IO () Source #
Run a Spock application. Basically just a wrapper around run
.
runSpockNoBanner :: Port -> IO Middleware -> IO () Source #
Like runSpock
, but does not display the banner "Spock is running on port XXX" on stdout.
spockAsApp :: IO Middleware -> IO Application Source #
Convert a middleware to an application. All failing requests will result in a 404 page
Spock's route definition monad
spockT :: MonadIO m => (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source #
Create a raw spock application with custom underlying monad
Use runSpock
to run the app or spockAsApp
to create a Wai.Application
The first argument is request size limit in bytes. Set to Nothing
to disable.
spockLimT :: forall m. MonadIO m => Maybe Word64 -> (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source #
spockConfigT :: forall m. MonadIO m => SpockConfig -> (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source #
Like spockT
, but with additional configuration for request size and error
handlers passed as first parameter.
Defining routes
wildcard :: Path ((:) * Text ([] *)) Closed #
Matches the rest of the route. Should be the last part of the path.
Rendering routes
renderRoute :: AllHave ToHttpApiData as => Path as Open -> HVectElim as Text Source #
Render a route applying path pieces
Hooking routes
subcomponent :: (RouteM t, Monad m) => Path '[] Open -> t ctx m () -> t ctx m () Source #
Deprecated: Subcomponents will be removed in the next major release. They break route rendering and should not be used. Consider creating helper functions for reusable route components
Define a subcomponent. Usage example:
subcomponent "site" $ do get "home" homeHandler get ("misc" <//> var) $ -- ... subcomponent "admin" $ do get "home" adminHomeHandler
The request /site/home will be routed to homeHandler and the request /admin/home will be routed to adminHomeHandler
prehook :: (RouteM t, MonadIO m) => ActionCtxT ctx m ctx' -> t ctx' m () -> t ctx m () Source #
Specify an action that will be run before all subroutes. It can modify the requests current context
get :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when the HTTP verb GET
and the given route match
post :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when the HTTP verb POST
and the given route match
getpost :: (HasRep xs, RouteM t, Monad m, Monad (t ctx m)) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when the HTTP verb 'GET'/'POST' and the given route match
head :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when the HTTP verb HEAD
and the given route match
put :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when the HTTP verb PUT
and the given route match
delete :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when the HTTP verb DELETE
and the given route match
patch :: (HasRep xs, RouteM t, Monad m) => Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when the HTTP verb PATCH
and the given route match
hookRoute :: (HasRep xs, RouteM t, Monad m) => StdMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when a standard HTTP verb and the given route match
hookRouteCustom :: (HasRep xs, RouteM t, Monad m) => Text -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when a custom HTTP verb and the given route match
hookAny :: (RouteM t, Monad m) => StdMethod -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when a standard HTTP verb matches but no defined route matches. The full path is passed as an argument
hookAnyCustom :: (RouteM t, Monad m) => Text -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when a custom HTTP verb matches but no defined route matches. The full path is passed as an argument
HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).
Adding Wai.Middleware
middleware :: (RouteM t, Monad m) => Middleware -> t ctx m () Source #
Hook wai middleware into Spock
Actions
module Web.Spock.Action
Config
data SpockConfig Source #
SpockConfig | |
|
defaultSpockConfig :: SpockConfig Source #
Default Spock configuration. No restriction on maximum request size; error handler simply prints status message as plain text.
Internals
hookRoute' :: (HasRep xs, RouteM t, Monad m) => SpockMethod -> Path xs ps -> HVectElim xs (ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when a HTTP verb and the given route match
hookAny' :: (RouteM t, Monad m) => SpockMethod -> ([Text] -> ActionCtxT ctx m ()) -> t ctx m () Source #
Specify an action that will be run when a HTTP verb matches but no defined route matches. The full path is passed as an argument
data SpockMethod Source #
The SpockMethod
allows safe use of http verbs via the MethodStandard
constructor and StdMethod
,
and custom verbs via the MethodCustom
constructor.
MethodStandard !HttpMethod | Standard HTTP Verbs from |
MethodCustom !Text | Custom HTTP Verbs using |
newtype HttpMethod Source #