| Safe Haskell | None |
|---|
Snap.Web.Routes
Description
This module provides a ready to use implementation of `web-routes` for Snap.
To get going, you'll need to add a few things to hs.
DeriveGeneric is used to derive the PathInfo instance for your URL data type,
the rest are needed by `web-routes`.
import Data.Text (Text) import Snap.Web.Routes
Snap.Web.Routes exports the data types needed to define your PathInfo and
MonadRoute instances below.
data AppUrl
= Count Int
| Echo Text
| Paths [Text]
deriving (Generic)
Define your application's URL data type. Deriving a Generic instance gives
you a PathInfo instance for free.
data App = App
{ _routeFn :: AppUrl -> [(Text, Maybe Text)] -> Text
}
Extend your App type to include a routing function.
instance PathInfo AppUrl
Get your free PathInfo instance. Alternatives are to use `web-routes-th` or implement PathInfo yourself.
instance MonadRoute (Handler App App) where
type URL (Handler App App) = AppUrl
askRouteFn = gets _routeFn
Define your MonadRoute instance. In particular, `type URL (Handler App App)`
must be set to your URL data type defined above and askRouteFn should point
to the routing function you added to your App type.
Moving on to hs.
import Snap.Web.Routes
Snap.Web.Routes provides a convenience router function you'll need.
routes :: [(ByteString, Handler App App ())]
routes = [ ("", serveDirectory "static")
, ("", routeWith routeAppUrl)
]
Add your routes to the bottom of the routes list using routeWith.
routeAppUrl :: AppUrl -> Handler App App ()
routeAppUrl appUrl =
case appUrl of
(Count n) -> writeText $ ("Count = " `T.append` (T.pack $ show n))
(Echo text) -> echo text
(Paths ps) -> writeText $ T.intercalate " " ps
echo :: T.Text -> Handler App App () echo msg = heistLocal (bindString "message" msg) $ render "echo"
Define the handler for each data constructor in your URL data type.
app :: SnapletInit App App
app = makeSnaplet "app" "An example application with snap-web-routes." Nothing $ do
addRoutes routes
return $ App renderRoute
Lastly, add the routing function to your app. If you prefixed the routes in routeWith:
, ("/prefix", routeWith routeAppUrl)
then use renderRouteWithPrefix instead:
return . App $ renderRouteWithPrefix "/prefix"
|
- renderRoute :: PathInfo url => url -> [(Text, Maybe Text)] -> Text
- renderRouteWithPrefix :: PathInfo url => Text -> url -> [(Text, Maybe Text)] -> Text
- routeWith :: (PathInfo url, MonadSnap m) => (url -> m ()) -> m ()
- heistUrl :: MonadRoute m => URL m -> m [Node]
- gets :: MonadState s m => (s -> a) -> m a
- class Generic a
- class Monad m => MonadRoute m where
- class PathInfo url where
- toPathSegments :: url -> [Text]
- fromPathSegments :: URLParser url
Documentation
heistUrl :: MonadRoute m => URL m -> m [Node]Source
gets :: MonadState s m => (s -> a) -> m a
Gets specific component of the state, using a projection function supplied.
class Generic a
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Instances
| Generic Bool | |
| Generic Char | |
| Generic Double | |
| Generic Float | |
| Generic Int | |
| Generic Ordering | |
| Generic () | |
| Generic Void | |
| Generic [a] | |
| Generic (Maybe a) | |
| Generic (Max a) | |
| Generic (First a) | |
| Generic (Last a) | |
| Generic (WrappedMonoid m) | |
| Generic (Option a) | |
| Generic (Either a b) | |
| Generic (a, b) | |
| Generic (a, b, c) | |
| Generic (a, b, c, d) | |
| Generic (a, b, c, d, e) | |
| Generic (a, b, c, d, e, f) | |
| Generic (a, b, c, d, e, f, g) |
class Monad m => MonadRoute m where
Associated Types
type URL m1 :: *
Instances
| MonadRoute m => MonadRoute (HeistT n m) | |
| Monad m => MonadRoute (RouteT url m) |
class PathInfo url where
Simple parsing and rendering for a type to and from URL path segments.
If you're using GHC 7.2 or later, you can use DeriveGeneric to derive
instances of this class:
{-# LANGUAGE DeriveGeneric #-}
data Sitemap = Home | BlogPost Int deriving Generic
instance PathInfo Sitemap
This results in the following instance:
instance PathInfo Sitemap where
toPathSegments Home = ["home"]
toPathSegments (BlogPost x) = "blog-post" : toPathSegments x
fromPathSegments = Home <$ segment "home"
<|> BlogPost <$ segment "blog-post" <*> fromPathSegments
And here it is in action:
>>>toPathInfo (BlogPost 123)"/blog-post/123">>>fromPathInfo "/blog-post/123" :: Either String SitemapRight (BlogPost 123)
To instead derive instances using TemplateHaskell, see
web-routes-th.