snap-web-routes: Type safe URLs for Snap

[ bsd3, library, snap, web ] [ Propose Tags ]

Type safe URL generation and routing for Snap using web-routes, and builds on work done by Jeremy Shaw.

Get started with the comprehensive tutorial.

Brief overview

It allows you to define a data type that represents the routes in your application:

data AppUrl
    = Login                   -- routes to /login
    | Logout                  -- routes to /logout
    | User (Resource UserId)  -- provides RESTful routes at /user

Resource is documented in Snap.Snaplet.Router.REST, and makes defining RESTful routes easier. Also provided are functions to use the URL data type in your app:

someHandler :: Handler App App ()
someHandler :: doSomething >> redirectURL $ User Index

and to generate URLs in views:

linksHandler :: Handler App App ()
linksHandler = heistLocal (I.bindSplices linksSplices) $ render "links"
  where
    linksSplices = do
        "loginUrl" ## urlSplice Login

[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.2.0.0, 0.3.0.0, 0.3.0.1, 0.4.0.0, 0.5.0.0, 0.5.1.0
Change log changelog
Dependencies base (>=4.4 && <5), bytestring (>=0.9.1 && <0.11), heist (>=0.13 && <1.20), mtl (>=2 && <3), snap (>=0.13 && <1.1), snap-core (>=0.9 && <1.1), text (>=0.11 && <1.3), web-routes (>=0.27 && <0.28), xmlhtml (>=0.1) [details]
License BSD-3-Clause
Author Luke Randall
Maintainer luke.randall@gmail.com
Category Web, Snap
Home page https://github.com/lukerandall/snap-web-routes
Bug tracker https://github.com/lukerandall/snap-web-routes/issues
Source repo head: git clone https://github.com/lukerandall/snap-web-routes.git
Uploaded by lukerandall at 2015-08-12T08:43:22Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 4682 total (11 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-08-12 [all 1 reports]

Readme for snap-web-routes-0.5.1.0

[back to package description]

snap-web-routes

Type safe URLs for Snap

Snap web routes provides type safe URLs for Snap using web routes.

How to use

The tutorial assumes you have a standard Snap app layout with an Application.hs and Site.hs. If your setup differs you'll need to adapt things accordingly.

Application.hs

To get going, you'll need to add a few things to Application.hs. This includes creating the URL data type and adding the routing function to our App data type.

-- Enable a few extensions
{-# LANGUAGE FlexibleInstances #-} -- Needed by
{-# LANGUAGE TypeFamilies      #-} -- web-routes
{-# LANGUAGE DeriveGeneric     #-} -- Needed to derive Generic
                                   -- for our URL data type

-- Used in HasRouter instances
import Control.Monad.State (get)

-- Paths and params use Text.
import Data.Text (Text)

-- Snap.Snaplet.Router.Types exports everything you need to
-- define your PathInfo and HasRouter instances.
import Snap.Snaplet.Router.Types

-- Your URL data type.  Deriving a `Generic` allows you to
-- get a free `PathInfo` instance.
data AppUrl
    = Login
    | Logout
    | Count Int
    | Echo Text
    | Paths [Text]
      deriving (Eq, Show, Read, Generic)

-- Extend your App type to include the router snaplet.
data App = App
    { _heist :: Snaplet (Heist App)
    , _router :: Snaplet RouterState
    }

-- Thanks to Generic, an empty instance definition is all
-- you need. Alternately, you can implement 'toPathSegments'
-- and 'fromPathSegments' yourself or use web-routes-th.
instance PathInfo AppUrl

-- You need to define a HasRouter instance for your app.
-- You must set type URL (Handler App App) to the URL
-- data type you defined above. The router in
-- `with router` is the lens for the @RouterState@ snaplet
-- you added to App.
instance HasRouter (Handler App App) where
    type URL (Handler App App) = AppUrl
    getRouterState = with router get

-- You also need to define a HasRouter instance for the
-- router snaplet. Once again, set type URL (Handler b
-- RouterState) to the data type you defined above.
instance HasRouter (Handler b RouterState) where
    type URL (Handler b RouterState) = AppUrl
    getRouterState = get

Site.hs

Moving on to Site.hs, we'll setup handlers for each URL, as well as initialise our app with the router snaplet..

-- Snap.Snaplet.Router provides routing functions
import Snap.Snaplet.Router

-- Add your new routes using routeWith
routes :: [(ByteString, Handler App App ())]
routes = [ ("", routeWith routeAppUrl)
         , ("", serveDirectory "static")
         ]

-- Define handlers for each value constructor in your URL data type.
routeAppUrl :: AppUrl -> Handler App App ()
routeAppUrl appUrl =
    case appUrl of
      (Login)     -> with auth handleLoginSubmit
      (Logout)    -> with auth handleLogout
      (Count n)   -> writeText $ ("Count = " `T.append` (T.pack $ show n))
      (Echo text) -> echo text
      (Paths ps)  -> writeText $ T.intercalate " " ps

-- You'll note that these are normal Snap handlers, except they can take
-- values from the value constructor as arguments. This is a lot nicer than
-- having to use getParam.
echo :: T.Text -> Handler App App ()
echo msg = heistLocal (bindString "message" msg) $ render "echo"

-- Add the router snaplet to your app.
app :: SnapletInit App App
app = makeSnaplet "app" "An example snap-web-routes app." Nothing $ do
    h <- nestSnaplet "" heist $ heistInit "templates"
    r <- nestSnaplet "router" router $ initRouter ""
    addRoutes routes
    return $ App h r

The prefix you pass to the router snaplet must match the prefix you specified in routes, e.g. if it was ("/prefix", routeWith routeAppUrl)) then:

r <- nestSnaplet "router" router $ initRouter "/prefix"

If you are having trouble figuring out why a particular request isn't routing as expected, try replacing routeWith with routeWithDebug. It'll display the available routes, as well as any failed route parses. Just remember that it's not suitable for production use, and only displays debugging information for local requests.

Using URLs

Let's look at how you can use your newly defined URL data type in your app. Firstly, you'll probably want to add links in Heist views. This is easily accomplished with the urlSplice and urlParamsSplice functions.

linksHandler :: Handler App App ()
linksHandler = heistLocal (I.bindSplices linksSplices) $ render "links"
  where
    linksSplices = do
        "loginUrl" ## urlSplice Login
        "echoUrl"  ## urlSplice (Echo "ping")
        "countUrl" ## urlParamsSplice (Count 10) [("explanation", Just "true")]

As you can see, splicing URLs into Heist views is easily accomplished. You will likely also want to redirect to the handler for a certain URL. To do this we've got redirectURL and redirectURLParams. Let's look at an example.

doSomethingHandler :: Handler App App ()
doSomethingHandler = doSomething >> redirectURL Logout

However, you will sometimes wish to redirect within a handler that runs in a snaplet other than the main app. With the router snaplet though, this is easily done:

handleLogout :: Handler App (AuthManager App) ()
handleLogout = logout >> (withTop router $ redirectURL (Echo "logged out"))

Lastly, you can render a URL as Text with urlPath and urlPathParams.

messageHandler :: Handler App App ()
messageHandler = do
    pathText <- urlPath (Echo "hello")
    heistLocal (I.bindSplices $ messageSplices path) $ render "message"
  where
    messageSplices path = do
        "message"  ## I.textSplice $ "The path is " `append` pathText

Remember, for each of urlSplice, redirectURL and urlPath there is a params version that takes a params list as an extra argument, and renders the URL with the given params as a query string.