Merge branch 'jkarni/qq-docs' into new-impl
This commit is contained in:
commit
52c24c8b35
7 changed files with 74 additions and 8 deletions
|
@ -31,8 +31,8 @@ library
|
||||||
Servant.Common.Req
|
Servant.Common.Req
|
||||||
Servant.Common.Text
|
Servant.Common.Text
|
||||||
Servant.Docs
|
Servant.Docs
|
||||||
|
Servant.QQ
|
||||||
Servant.Server
|
Servant.Server
|
||||||
Servant.Utils.ApiQuasiQuoting
|
|
||||||
Servant.Utils.Links
|
Servant.Utils.Links
|
||||||
Servant.Utils.StaticFiles
|
Servant.Utils.StaticFiles
|
||||||
build-depends:
|
build-depends:
|
||||||
|
|
|
@ -12,7 +12,7 @@ module Servant (
|
||||||
-- | Using your types in request paths and query string parameters
|
-- | Using your types in request paths and query string parameters
|
||||||
module Servant.Common.Text,
|
module Servant.Common.Text,
|
||||||
-- | Utilities on top of the servant core
|
-- | Utilities on top of the servant core
|
||||||
module Servant.Utils.ApiQuasiQuoting,
|
module Servant.QQ,
|
||||||
module Servant.Utils.Links,
|
module Servant.Utils.Links,
|
||||||
module Servant.Utils.StaticFiles,
|
module Servant.Utils.StaticFiles,
|
||||||
-- | Useful re-exports
|
-- | Useful re-exports
|
||||||
|
@ -25,6 +25,6 @@ import Servant.Client
|
||||||
import Servant.Common.Text
|
import Servant.Common.Text
|
||||||
import Servant.Docs
|
import Servant.Docs
|
||||||
import Servant.Server
|
import Servant.Server
|
||||||
import Servant.Utils.ApiQuasiQuoting
|
import Servant.QQ
|
||||||
import Servant.Utils.Links
|
import Servant.Utils.Links
|
||||||
import Servant.Utils.StaticFiles
|
import Servant.Utils.StaticFiles
|
||||||
|
|
|
@ -31,7 +31,7 @@ module Servant.API (
|
||||||
|
|
||||||
-- * Utilities
|
-- * Utilities
|
||||||
-- | QuasiQuotes for endpoints
|
-- | QuasiQuotes for endpoints
|
||||||
module Servant.Utils.ApiQuasiQuoting,
|
module Servant.QQ,
|
||||||
-- | Type-safe internal URLs
|
-- | Type-safe internal URLs
|
||||||
module Servant.Utils.Links,
|
module Servant.Utils.Links,
|
||||||
) where
|
) where
|
||||||
|
@ -46,6 +46,6 @@ import Servant.API.QueryParam
|
||||||
import Servant.API.Raw
|
import Servant.API.Raw
|
||||||
import Servant.API.ReqBody
|
import Servant.API.ReqBody
|
||||||
import Servant.API.Sub
|
import Servant.API.Sub
|
||||||
import Servant.Utils.ApiQuasiQuoting (sitemap)
|
import Servant.QQ (sitemap)
|
||||||
import Servant.Utils.Links (mkLink)
|
import Servant.Utils.Links (mkLink)
|
||||||
import Servant.Utils.StaticFiles
|
import Servant.Utils.StaticFiles
|
||||||
|
|
|
@ -5,7 +5,28 @@
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
||||||
module Servant.Utils.ApiQuasiQuoting where
|
-- | 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.QQ where
|
||||||
|
|
||||||
import Control.Monad (void)
|
import Control.Monad (void)
|
||||||
import Control.Applicative hiding (many, (<|>), optional)
|
import Control.Applicative hiding (many, (<|>), optional)
|
||||||
|
@ -23,6 +44,11 @@ import Servant.API.ReqBody
|
||||||
import Servant.API.Sub
|
import Servant.API.Sub
|
||||||
import Servant.API.Alternative
|
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
|
class ExpSYM repr' repr | repr -> repr', repr' -> repr where
|
||||||
lit :: String -> repr' -> repr
|
lit :: String -> repr' -> repr
|
||||||
capture :: String -> String -> repr -> repr
|
capture :: String -> String -> repr -> repr
|
||||||
|
@ -148,6 +174,19 @@ parseAll = do
|
||||||
where union :: Type -> Type -> Type
|
where union :: Type -> Type -> Type
|
||||||
union a = AppT (AppT (ConT ''(:<|>)) a)
|
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
|
||||||
sitemap = QuasiQuoter { quoteExp = undefined
|
sitemap = QuasiQuoter { quoteExp = undefined
|
||||||
, quotePat = undefined
|
, quotePat = undefined
|
|
@ -6,6 +6,33 @@
|
||||||
{-# LANGUAGE FunctionalDependencies #-}
|
{-# LANGUAGE FunctionalDependencies #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# 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
|
module Servant.Utils.Links where
|
||||||
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
module Servant.Utils.ApiQuasiQuotingSpec where
|
module Servant.QQSpec where
|
||||||
|
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
|
@ -6,7 +6,7 @@ module Servant.Utils.LinksSpec where
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
||||||
import Servant.API
|
import Servant.API
|
||||||
import Servant.Utils.ApiQuasiQuotingSpec ( (~>) )
|
import Servant.QQSpec ( (~>) )
|
||||||
import Servant.Utils.Links (IsElem, IsLink)
|
import Servant.Utils.Links (IsElem, IsLink)
|
||||||
|
|
||||||
type TestApi =
|
type TestApi =
|
||||||
|
|
Loading…
Reference in a new issue