hails-0.11.0.0: Multi-app web platform framework

Safe HaskellTrustworthy

Hails.Web.Frank

Description

Frank is a Sinatra-inspired DSL (see http://www.sinatrarb.com) for creating routes. It is composable with all Routeable types, but is designed to be used with Controllers. Each verb (get, post, put, etc') takes a URL pattern of the form "/dir/:paramname/dir" (see routePattern for details) and a Routeable:

module SimpleFrank (server) where

import           Data.String
import           Data.Maybe
import           Control.Monad

import           LIO
import           Hails.HttpServer.Types
import           Hails.Web
import qualified Hails.Web.Frank as F

server :: Application
server = mkRouter $ do
  F.get "/users" $ do
    req <- request >>= unlabel
    return $ okHtml $ fromString $
      "Welcome Home " ++ (show $ serverName req)
  F.get "/users/:id" $ do
    userId <- fromMaybe "" `liftM` queryParam "id"
    return $ ok "text/json" $ fromString $
      "{\"myid\": " ++ (show userId) ++ "}"
  F.put "/user/:id" $ do
  ...

With hails, you can directly run this:

 hails --app=SimpleFrank

And, with curl, you can now checkout your page:

 $ curl localhost:8080/users
 Welcome Home "localhost"

 $ curl localhost:8080/users/123
 {"myid": "123"}

 $ ...

Synopsis

Documentation

get :: Routeable r => ByteString -> r -> RouteSource

Matches the GET method on the given URL pattern

post :: Routeable r => ByteString -> r -> RouteSource

Matches the POST method on the given URL pattern

put :: Routeable r => ByteString -> r -> RouteSource

Matches the PUT method on the given URL pattern

delete :: Routeable r => ByteString -> r -> RouteSource

Matches the DELETE method on the given URL pattern

options :: Routeable r => ByteString -> r -> RouteSource

Matches the OPTIONS method on the given URL pattern