| Safe Haskell | None |
|---|
Snap.Web.Routes.Types
- 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
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) | MonadRoute instance for |
| 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.