scotty-binding-play-1.3: The Play Framework style data binding in Scotty.

Safe HaskellNone

Web.Scotty.Binding.Play

Description

The Play Framework style data binding in Scotty.

Data difinition:

 {-# LANGUAGE TemplateHaskell #-}

 import Web.Scotty.Binding.Play (deriveBindable)

 data Sample = Sample
     { field1 :: Int
     , field2 :: Text
     }

 deriveBindable ''Sample

set as GET parameter:

 > curl http://localhost:3000/?data.field1=1&data.field2=whisky

We can get Sample in Scotty:

 main :: IO ()
 main = scotty 3000 $ get "/" $ do
     a <- parseParam "data"
     liftIO $ print $ field1 a --> 1
     liftIO $ print $ field2 a --> "whisky"

Synopsis

Documentation

class Bindable a whereSource

Class of generic bindable data structure.

Methods

parseParamsSource

Arguments

:: Text

prefix

-> ActionM a 

parseParams'Source

Arguments

:: Text

prefix

-> Maybe Text

suffix

-> ActionM a 

Instances

Bindable Bool 
Bindable Double 
Bindable Float 
Bindable Int 
Bindable Integer 
Bindable String 
Bindable () 
Bindable ByteString 
Bindable Text 
Bindable Text 
Bindable a => Bindable [a] 
Bindable a => Bindable (Maybe a) 

deriveBindable :: Name -> DecsQSource

by TH