Rename ApiQuasiQuoting.

And fix haddocks for it.
This commit is contained in:
Julian K. Arni 2014-11-25 16:35:56 +01:00
parent 63584d52b7
commit dee47654f9
6 changed files with 11 additions and 14 deletions

View file

@ -31,8 +31,8 @@ library
Servant.Common.Req
Servant.Common.Text
Servant.Docs
Servant.QQ
Servant.Server
Servant.Utils.ApiQuasiQuoting
Servant.Utils.Links
Servant.Utils.StaticFiles
build-depends:

View file

@ -12,7 +12,7 @@ module Servant (
-- | Using your types in request paths and query string parameters
module Servant.Common.Text,
-- | Utilities on top of the servant core
module Servant.Utils.ApiQuasiQuoting,
module Servant.QQ,
module Servant.Utils.Links,
module Servant.Utils.StaticFiles,
-- | Useful re-exports
@ -25,6 +25,6 @@ import Servant.Client
import Servant.Common.Text
import Servant.Docs
import Servant.Server
import Servant.Utils.ApiQuasiQuoting
import Servant.QQ
import Servant.Utils.Links
import Servant.Utils.StaticFiles

View file

@ -31,7 +31,7 @@ module Servant.API (
-- * Utilities
-- | QuasiQuotes for endpoints
module Servant.Utils.ApiQuasiQuoting,
module Servant.QQ,
-- | Type-safe internal URLs
module Servant.Utils.Links,
) where
@ -46,6 +46,6 @@ import Servant.API.QueryParam
import Servant.API.Raw
import Servant.API.ReqBody
import Servant.API.Sub
import Servant.Utils.ApiQuasiQuoting (sitemap)
import Servant.QQ (sitemap)
import Servant.Utils.Links (mkLink)
import Servant.Utils.StaticFiles

View file

@ -21,12 +21,12 @@
--
-- @
-- "hello" :> ReqBody String :> Put ()
-- :<|> "hello" :> Capture "p" Int :> ReqBody String :> Post ()
-- :<|> "hello" :> QueryParam "name" String :> Get Int
-- :\<|> "hello" :> Capture "p" Int :> ReqBody String :> Post ()
-- :\<|> "hello" :> QueryParam "name" String :> Get Int
-- @
--
-- Note the '/' before a 'QueryParam'!
module Servant.Utils.ApiQuasiQuoting where
-- Note the @/@ before a @QueryParam@!
module Servant.QQ where
import Control.Monad (void)
import Control.Applicative hiding (many, (<|>), optional)
@ -177,18 +177,14 @@ parseAll = do
-- | 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

View file

@ -9,6 +9,7 @@
-- | Type safe internal links.
--
-- Provides the function 'mkLink':
--
-- @
-- type API = Proxy ("hello" :> Get Int
-- :<|> "bye" :> QueryParam "name" String :> Post Bool)

View file

@ -7,7 +7,7 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Servant.Utils.ApiQuasiQuotingSpec where
module Servant.Utils.QQSpec where
import Test.Hspec