servant-0.2: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.QQ

Description

QuasiQuoting utilities for API types.

sitemap allows you to write your type in a very natural way:

[sitemap|
PUT        hello                 String -> ()
POST       hello/p:Int           String -> ()
GET        hello/?name:String    Int
|]

Will generate:

       "hello" :> ReqBody String :> Put ()
  :<|> "hello" :> Capture "p" Int :> ReqBody String :> Post ()
  :<|> "hello" :> QueryParam "name" String :> Get Int

Note the / before a QueryParam!

Synopsis

Documentation

class ExpSYM repr' repr | repr -> repr', repr' -> repr where Source

Finally-tagless encoding for our DSL. Keeping repr' and repr distinct when writing functions with an ExpSYM context ensures certain invariants (for instance, that there is only one of get, post, put, and delete in a value), but sometimes requires a little more work.

Methods

lit :: String -> repr' -> repr Source

capture :: String -> String -> repr -> repr Source

reqBody :: String -> repr -> repr Source

queryParam :: String -> String -> repr -> repr Source

conj :: repr' -> repr -> repr Source

get :: String -> repr Source

post :: String -> repr Source

put :: String -> repr Source

delete :: String -> repr Source

Instances

(>:) :: Type -> Type -> Type infixr 6 Source

parseMethod :: ExpSYM repr' repr => Parser (String -> repr) Source

parseUrlSegment :: ExpSYM repr repr => Parser (repr -> repr) Source

parseUrl :: ExpSYM repr repr => Parser (repr -> repr) Source

parseEntry :: ExpSYM repr repr => Parser repr Source

sitemap :: QuasiQuoter Source

The sitemap QuasiQuoter.

Comments are allowed, and have the standard Haskell format

  • -- for inline
  • {- ... -} for block