module renaming: S.API.QQ -> S.Utils.ApiQuasiQuoting
This commit is contained in:
parent
2f9fb2b713
commit
af00035b99
5 changed files with 6 additions and 6 deletions
|
@ -22,7 +22,6 @@ library
|
||||||
Servant.API.Get
|
Servant.API.Get
|
||||||
Servant.API.Post
|
Servant.API.Post
|
||||||
Servant.API.Put
|
Servant.API.Put
|
||||||
Servant.API.QQ
|
|
||||||
Servant.API.QueryParam
|
Servant.API.QueryParam
|
||||||
Servant.API.Raw
|
Servant.API.Raw
|
||||||
Servant.API.ReqBody
|
Servant.API.ReqBody
|
||||||
|
@ -30,6 +29,7 @@ library
|
||||||
Servant.Client
|
Servant.Client
|
||||||
Servant.Docs
|
Servant.Docs
|
||||||
Servant.Server
|
Servant.Server
|
||||||
|
Servant.Utils.ApiQuasiQuoting
|
||||||
Servant.Utils.BaseUrl
|
Servant.Utils.BaseUrl
|
||||||
Servant.Utils.Req
|
Servant.Utils.Req
|
||||||
Servant.Utils.Text
|
Servant.Utils.Text
|
||||||
|
|
|
@ -26,7 +26,7 @@ module Servant.API (
|
||||||
|
|
||||||
-- * Utilities
|
-- * Utilities
|
||||||
-- | QuasiQuotes for endpoints
|
-- | QuasiQuotes for endpoints
|
||||||
module Servant.API.QQ,
|
module Servant.Utils.ApiQuasiQuoting,
|
||||||
-- | Type-safe internal URLs
|
-- | Type-safe internal URLs
|
||||||
module Servant.API.Elem,
|
module Servant.API.Elem,
|
||||||
) where
|
) where
|
||||||
|
@ -38,7 +38,7 @@ import Servant.API.Get
|
||||||
import Servant.API.Post
|
import Servant.API.Post
|
||||||
import Servant.API.Put
|
import Servant.API.Put
|
||||||
import Servant.API.QueryParam
|
import Servant.API.QueryParam
|
||||||
import Servant.API.QQ (sitemap)
|
import Servant.Utils.ApiQuasiQuoting (sitemap)
|
||||||
import Servant.API.ReqBody
|
import Servant.API.ReqBody
|
||||||
import Servant.API.Sub
|
import Servant.API.Sub
|
||||||
import Servant.API.Alternative
|
import Servant.API.Alternative
|
||||||
|
|
|
@ -4,7 +4,7 @@
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
module Servant.API.QQ where
|
module Servant.Utils.ApiQuasiQuoting where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.List.Split (splitOn)
|
import Data.List.Split (splitOn)
|
|
@ -7,7 +7,7 @@ import Test.Hspec
|
||||||
|
|
||||||
import Servant.API
|
import Servant.API
|
||||||
import Servant.API.Elem (IsElem, IsLink)
|
import Servant.API.Elem (IsElem, IsLink)
|
||||||
import Servant.API.QQSpec ( (~>) )
|
import Servant.Utils.ApiQuasiQuotingSpec ( (~>) )
|
||||||
|
|
||||||
type TestApi =
|
type TestApi =
|
||||||
"hello" :> Capture "name" String :> QueryParam "capital" Bool :> Get Bool
|
"hello" :> Capture "name" String :> QueryParam "capital" Bool :> Get Bool
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
module Servant.API.QQSpec where
|
module Servant.Utils.ApiQuasiQuotingSpec where
|
||||||
|
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
Loading…
Reference in a new issue