| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Snap.Snaplet.Router.Types
Contents
- data RouterState = RouterState {}
- class Monad m => HasRouter m where
- type URL m
- getRouterState :: m RouterState
- class PathInfo url
- class Generic a
Documentation
data RouterState Source
Constructors
| RouterState | |
class Monad m => HasRouter m where Source
Instantiate this type class for Handler App App and Handler b
RouterState so that the snaplet can find its state. An instance requires
a type for URL m - being the URL data type you have defined - and an
instance of getRouterState. Assuming your URL data type is called
AppUrl, the instance for Handler b RouterState would be
instance HasRouter (Handler b RouterState) where
type URL (Handler b RouterState) = AppUrl
getRouterState = get
If the lens for the Router snaplet is router, your Handler App App
instance would be
instance HasRouter (Handler App App) where
type URL (Handler App App) = AppUrl
getRouterState = with router get
Methods
class PathInfo url
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 SitemapThis 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" <*> fromPathSegmentsAnd 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.
Re-exported for convenience
class Generic a
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Instances