QQ and safe links documentation.

This commit is contained in:
Julian K. Arni 2014-11-25 16:10:59 +01:00
parent 5b5f530406
commit 63584d52b7
2 changed files with 69 additions and 0 deletions

View file

@ -5,6 +5,27 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
-- | 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'!
module Servant.Utils.ApiQuasiQuoting where
import Control.Monad (void)
@ -23,6 +44,11 @@ import Servant.API.ReqBody
import Servant.API.Sub
import Servant.API.Alternative
-- | 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.
class ExpSYM repr' repr | repr -> repr', repr' -> repr where
lit :: String -> repr' -> repr
capture :: String -> String -> repr -> repr
@ -148,6 +174,23 @@ parseAll = do
where union :: Type -> Type -> Type
union a = AppT (AppT (ConT ''(:<|>)) a)
-- | The sitemap QuasiQuoter.
--
-- * @.../<var>:<type>/...@ becomes a capture
--
-- * @.../?<var>:<type>@ becomes a query parameter
--
-- * @<method> ... <typ>@ becomes a method returning @<typ>@
--
-- * @<method> ... <typ1> -> <typ2>@ becomes a method with request
-- body of @<typ1>@ and returning @<typ2>@
--
-- Comments are allowed, and have the standard Haskell format
--
-- * @--@ for inline
--
-- * @{- ... -}@ for block
--
sitemap :: QuasiQuoter
sitemap = QuasiQuoter { quoteExp = undefined
, quotePat = undefined

View file

@ -6,6 +6,32 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
-- | Type safe internal links.
--
-- Provides the function 'mkLink':
-- @
-- type API = Proxy ("hello" :> Get Int
-- :<|> "bye" :> QueryParam "name" String :> Post Bool)
--
-- api :: API
-- api = proxy
--
-- link1 :: Proxy ("hello" :> Get Int)
-- link1 = proxy
--
-- link2 :: Proxy ("hello" :> Delete)
-- link2 = proxy
--
-- mkLink link1 API -- typechecks, returns 'Link "/hello"'
--
-- mkLink link2 API -- doesn't typecheck
-- @
--
-- That is, 'mkLink' takes two arguments, a link proxy and a sitemap, and
-- returns a 'Link', but only typechecks if the link proxy is a valid link,
-- and part of the sitemap.
--
-- __N.B.:__ 'mkLink' assumes a capture matches any string (without slashes).
module Servant.Utils.Links where
import Data.Proxy