hails-0.11.2.1: Multi-app web platform framework

Safe HaskellTrustworthy
LanguageHaskell98

Hails.Web.REST

Description

REST is a DSL for creating routes using RESTful HTTP verbs. See http://en.wikipedia.org/wiki/Representational_state_transfer

For example, an app handling users may define a REST controller as:

module SimpleREST (server) where
 
import           Data.String
import           Data.Maybe
import           Control.Monad

import           LIO
import           Hails.HttpServer.Types
import           Hails.Web
import qualified Hails.Web.REST as REST

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

With hails, you can directly run this:

hails --app=SimpleREST

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

type RESTController = RESTControllerM () Source

Monad used to encode a REST controller incrementally. The return type is not used, hence always '()'.

show :: Routeable r => r -> RESTController Source

GET /:id

update :: Routeable r => r -> RESTController Source

PUT /:id

delete :: Routeable r => r -> RESTController Source

DELETE /:id

edit :: Routeable r => r -> RESTController Source

GET /:id/edit

new :: Routeable r => r -> RESTController Source

GET /new