Reformat servant

This commit is contained in:
Oleg Grenrus 2018-03-11 17:58:31 +02:00
parent 74cf82946e
commit 8058891299
27 changed files with 292 additions and 203 deletions

View File

@ -184,6 +184,7 @@ newline: lf
# needs to be aware of these, so it can parse the file correctly. # needs to be aware of these, so it can parse the file correctly.
# #
# No language extensions are enabled by default. # No language extensions are enabled by default.
# language_extensions: language_extensions:
# - TemplateHaskell - FlexibleContexts
# - QuasiQuotes - TemplateHaskell
- QuasiQuotes

View File

@ -66,71 +66,75 @@ module Servant.API (
-- * Utilities -- * Utilities
module Servant.Utils.Links, module Servant.Utils.Links,
-- | Type-safe internal URIs -- | Type-safe internal URIs
-- * Re-exports -- * Re-exports
If, If,
SBool (..), SBoolI (..) SBool (..), SBoolI (..)
) where ) where
import Servant.API.Alternative ((:<|>) (..)) import Data.Singletons.Bool
import Servant.API.BasicAuth (BasicAuth,BasicAuthData(..)) (SBool (..), SBoolI (..))
import Servant.API.Capture (Capture, Capture', CaptureAll) import Data.Type.Bool
import Servant.API.ContentTypes (Accept (..), FormUrlEncoded, (If)
JSON, import Servant.API.Alternative
MimeRender (..), NoContent (NoContent), ((:<|>) (..))
MimeUnrender (..), OctetStream, import Servant.API.BasicAuth
PlainText) (BasicAuth, BasicAuthData (..))
import Servant.API.Description (Description, Summary) import Servant.API.Capture
import Servant.API.Empty (EmptyAPI (..)) (Capture, Capture', CaptureAll)
import Servant.API.Experimental.Auth (AuthProtect) import Servant.API.ContentTypes
import Servant.API.Header (Header, Header') (Accept (..), FormUrlEncoded, JSON, MimeRender (..),
import Servant.API.HttpVersion (HttpVersion (..)) MimeUnrender (..), NoContent (NoContent), OctetStream,
import Servant.API.IsSecure (IsSecure (..)) PlainText)
import Servant.API.Modifiers (Required, Optional, Lenient, Strict) import Servant.API.Description
import Servant.API.QueryParam (QueryFlag, QueryParam, QueryParam', (Description, Summary)
QueryParams) import Servant.API.Empty
import Servant.API.Raw (Raw) (EmptyAPI (..))
import Servant.API.Stream (Stream, StreamGet, StreamPost, import Servant.API.Experimental.Auth
StreamGenerator (..), (AuthProtect)
ToStreamGenerator (..), import Servant.API.Header
ResultStream(..), BuildFromStream (..), (Header, Header')
ByteStringParser (..), import Servant.API.HttpVersion
FramingRender (..), BoundaryStrategy (..), (HttpVersion (..))
FramingUnrender (..), import Servant.API.IsSecure
NewlineFraming, (IsSecure (..))
NetstringFraming) import Servant.API.Modifiers
import Servant.API.RemoteHost (RemoteHost) (Lenient, Optional, Required, Strict)
import Servant.API.ReqBody (ReqBody, ReqBody') import Servant.API.QueryParam
import Servant.API.ResponseHeaders (AddHeader, addHeader, noHeader, (QueryFlag, QueryParam, QueryParam', QueryParams)
BuildHeadersTo (buildHeadersTo), import Servant.API.Raw
GetHeaders (getHeaders), (Raw)
HList (..), Headers (..), import Servant.API.RemoteHost
getHeadersHList, getResponse, ResponseHeader (..)) (RemoteHost)
import Servant.API.Sub ((:>)) import Servant.API.ReqBody
import Servant.API.Vault (Vault) (ReqBody, ReqBody')
import Servant.API.Verbs (PostCreated, Delete, DeleteAccepted, import Servant.API.ResponseHeaders
DeleteNoContent, (AddHeader, BuildHeadersTo (buildHeadersTo),
DeleteNonAuthoritative, Get, GetHeaders (getHeaders), HList (..), Headers (..),
GetAccepted, GetNoContent, ResponseHeader (..), addHeader, getHeadersHList, getResponse,
GetNonAuthoritative, noHeader)
GetPartialContent, import Servant.API.Stream
GetResetContent, (BoundaryStrategy (..), BuildFromStream (..),
Patch, ByteStringParser (..), FramingRender (..),
PatchAccepted, PatchNoContent, FramingUnrender (..), NetstringFraming, NewlineFraming,
PatchNoContent, ResultStream (..), Stream, StreamGenerator (..), StreamGet,
PatchNonAuthoritative, Post, StreamPost, ToStreamGenerator (..))
PostAccepted, PostNoContent, import Servant.API.Sub
PostNonAuthoritative, ((:>))
PostResetContent, Put, import Servant.API.Vault
PutAccepted, PutNoContent, (Vault)
PutNoContent, PutNonAuthoritative, import Servant.API.Verbs
ReflectMethod (reflectMethod), (Delete, DeleteAccepted, DeleteNoContent,
Verb, StdMethod(..)) DeleteNonAuthoritative, Get, GetAccepted, GetNoContent,
import Servant.API.WithNamedContext (WithNamedContext) GetNonAuthoritative, GetPartialContent, GetResetContent,
import Servant.Utils.Links (HasLink (..), Link, IsElem, IsElem', Patch, PatchAccepted, PatchNoContent, PatchNonAuthoritative,
URI (..), safeLink) Post, PostAccepted, PostCreated, PostNoContent,
import Web.HttpApiData (FromHttpApiData (..), PostNonAuthoritative, PostResetContent, Put, PutAccepted,
ToHttpApiData (..)) PutNoContent, PutNonAuthoritative,
ReflectMethod (reflectMethod), StdMethod (..), Verb)
import Data.Type.Bool (If) import Servant.API.WithNamedContext
import Data.Singletons.Bool (SBool (..), SBoolI (..)) (WithNamedContext)
import Servant.Utils.Links
(HasLink (..), IsElem, IsElem', Link, URI (..), safeLink)
import Web.HttpApiData
(FromHttpApiData (..), ToHttpApiData (..))

View File

@ -1,14 +1,16 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Alternative ((:<|>)(..)) where module Servant.API.Alternative ((:<|>)(..)) where
import Data.Semigroup (Semigroup (..)) import Data.Semigroup
import Data.Typeable (Typeable) (Semigroup (..))
import Data.Typeable
(Typeable)
import Prelude () import Prelude ()
import Prelude.Compat import Prelude.Compat

View File

@ -1,13 +1,16 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
module Servant.API.BasicAuth where module Servant.API.BasicAuth where
import Data.ByteString (ByteString) import Data.ByteString
import Data.Typeable (Typeable) (ByteString)
import GHC.TypeLits (Symbol) import Data.Typeable
(Typeable)
import GHC.TypeLits
(Symbol)
-- | Combinator for <https://tools.ietf.org/html/rfc2617#section-2 Basic Access Authentication>. -- | Combinator for <https://tools.ietf.org/html/rfc2617#section-2 Basic Access Authentication>.

View File

@ -4,8 +4,10 @@
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Capture (Capture, Capture', CaptureAll) where module Servant.API.Capture (Capture, Capture', CaptureAll) where
import Data.Typeable (Typeable) import Data.Typeable
import GHC.TypeLits (Symbol) (Typeable)
import GHC.TypeLits
(Symbol)
-- | Capture a value from the request path under a certain type @a@. -- | Capture a value from the request path under a certain type @a@.
-- --
-- Example: -- Example:

View File

@ -71,32 +71,38 @@ module Servant.API.ContentTypes
, canHandleAcceptH , canHandleAcceptH
) where ) where
import Control.Arrow (left) import Control.Arrow
(left)
import Control.Monad.Compat import Control.Monad.Compat
import Data.Aeson (FromJSON(..), ToJSON(..), encode) import Data.Aeson
import Data.Aeson.Parser (value) (FromJSON (..), ToJSON (..), encode)
import Data.Aeson.Types (parseEither) import Data.Aeson.Parser
import Data.Attoparsec.ByteString.Char8 (endOfInput, parseOnly, (value)
skipSpace, (<?>)) import Data.Aeson.Types
(parseEither)
import Data.Attoparsec.ByteString.Char8
(endOfInput, parseOnly, skipSpace, (<?>))
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.ByteString.Lazy (ByteString, fromStrict, import Data.ByteString.Lazy
toStrict) (ByteString, fromStrict, toStrict)
import qualified Data.ByteString.Lazy.Char8 as BC import qualified Data.ByteString.Lazy.Char8 as BC
import qualified Data.List.NonEmpty as NE import qualified Data.List.NonEmpty as NE
import Data.Maybe (isJust) import Data.Maybe
import Data.String.Conversions (cs) (isJust)
import Data.String.Conversions
(cs)
import qualified Data.Text as TextS import qualified Data.Text as TextS
import qualified Data.Text.Encoding as TextS import qualified Data.Text.Encoding as TextS
import qualified Data.Text.Lazy as TextL import qualified Data.Text.Lazy as TextL
import qualified Data.Text.Lazy.Encoding as TextL import qualified Data.Text.Lazy.Encoding as TextL
import Data.Typeable import Data.Typeable
import GHC.Generics (Generic) import GHC.Generics
(Generic)
import qualified Network.HTTP.Media as M import qualified Network.HTTP.Media as M
import Web.FormUrlEncoded (FromForm, ToForm, import Prelude ()
urlEncodeAsForm,
urlDecodeAsForm)
import Prelude ()
import Prelude.Compat import Prelude.Compat
import Web.FormUrlEncoded
(FromForm, ToForm, urlDecodeAsForm, urlEncodeAsForm)
#if MIN_VERSION_base(4,9,0) #if MIN_VERSION_base(4,9,0)
import qualified GHC.TypeLits as TL import qualified GHC.TypeLits as TL

View File

@ -3,8 +3,8 @@
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Description ( module Servant.API.Description (
-- * Combinators -- * Combinators
@ -16,9 +16,12 @@ module Servant.API.Description (
reflectDescription, reflectDescription,
) where ) where
import Data.Typeable (Typeable) import Data.Proxy
import GHC.TypeLits (Symbol, KnownSymbol, symbolVal) (Proxy (..))
import Data.Proxy (Proxy (..)) import Data.Typeable
(Typeable)
import GHC.TypeLits
(KnownSymbol, Symbol, symbolVal)
-- | Add a short summary for (part of) API. -- | Add a short summary for (part of) API.
-- --

View File

@ -2,7 +2,8 @@
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Empty(EmptyAPI(..)) where module Servant.API.Empty(EmptyAPI(..)) where
import Data.Typeable (Typeable) import Data.Typeable
(Typeable)
import Prelude () import Prelude ()
import Prelude.Compat import Prelude.Compat

View File

@ -1,10 +1,11 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
module Servant.API.Experimental.Auth where module Servant.API.Experimental.Auth where
import Data.Typeable (Typeable) import Data.Typeable
(Typeable)
-- | A generalized Authentication combinator. Use this if you have a -- | A generalized Authentication combinator. Use this if you have a
-- non-standard authentication technique. -- non-standard authentication technique.

View File

@ -6,8 +6,10 @@ module Servant.API.Header (
Header, Header', Header, Header',
) where ) where
import Data.Typeable (Typeable) import Data.Typeable
import GHC.TypeLits (Symbol) (Typeable)
import GHC.TypeLits
(Symbol)
import Servant.API.Modifiers import Servant.API.Modifiers
-- | Extract the given header's value as a value of type @a@. -- | Extract the given header's value as a value of type @a@.

View File

@ -3,7 +3,8 @@ module Servant.API.HttpVersion
HttpVersion(..) HttpVersion(..)
) where ) where
import Network.HTTP.Types (HttpVersion (..)) import Network.HTTP.Types
(HttpVersion (..))
-- $httpversion -- $httpversion
-- --

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
-- | This is a module containing an API with all `Servant.API` combinators. It -- | This is a module containing an API with all `Servant.API` combinators. It
@ -7,7 +7,6 @@
module Servant.API.Internal.Test.ComprehensiveAPI where module Servant.API.Internal.Test.ComprehensiveAPI where
import Data.Proxy import Data.Proxy
import Servant.API import Servant.API
type GET = Get '[JSON] NoContent type GET = Get '[JSON] NoContent

View File

@ -1,12 +1,14 @@
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
module Servant.API.IsSecure module Servant.API.IsSecure
( -- $issecure ( -- $issecure
IsSecure(..) IsSecure(..)
) where ) where
import Data.Typeable import Data.Typeable
import GHC.Generics (Generic) (Typeable)
import GHC.Generics
(Generic)
-- | Was this request made over an SSL connection? -- | Was this request made over an SSL connection?
-- --

View File

@ -1,6 +1,6 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
@ -19,10 +19,14 @@ module Servant.API.Modifiers (
unfoldRequestArgument, unfoldRequestArgument,
) where ) where
import Data.Proxy (Proxy (..)) import Data.Proxy
import Data.Singletons.Bool (SBool (..), SBoolI (..)) (Proxy (..))
import Data.Text (Text) import Data.Singletons.Bool
import Data.Type.Bool (If) (SBool (..), SBoolI (..))
import Data.Text
(Text)
import Data.Type.Bool
(If)
-- | Required argument. Not wrapped. -- | Required argument. Not wrapped.
data Required data Required

View File

@ -1,12 +1,14 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParam', QueryParams) where module Servant.API.QueryParam (QueryFlag, QueryParam, QueryParam', QueryParams) where
import Data.Typeable (Typeable) import Data.Typeable
import GHC.TypeLits (Symbol) (Typeable)
import GHC.TypeLits
(Symbol)
import Servant.API.Modifiers import Servant.API.Modifiers
-- | Lookup the value associated to the @sym@ query string parameter -- | Lookup the value associated to the @sym@ query string parameter

View File

@ -2,7 +2,9 @@
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Raw where module Servant.API.Raw where
import Data.Typeable (Typeable) import Data.Typeable
(Typeable)
-- | Endpoint for plugging in your own Wai 'Application's. -- | Endpoint for plugging in your own Wai 'Application's.
-- --
-- The given 'Application' will get the request as received by the server, potentially with -- The given 'Application' will get the request as received by the server, potentially with

View File

@ -5,6 +5,7 @@ module Servant.API.RemoteHost
) where ) where
import Data.Typeable import Data.Typeable
(Typeable)
-- | Provides access to the host or IP address -- | Provides access to the host or IP address
-- from which the HTTP request was sent. -- from which the HTTP request was sent.

View File

@ -6,8 +6,9 @@ module Servant.API.ReqBody (
ReqBody, ReqBody', ReqBody, ReqBody',
) where ) where
import Data.Typeable (Typeable) import Data.Typeable
import Servant.API.Modifiers (Typeable)
import Servant.API.Modifiers
-- | Extract the request body as a value of type @a@. -- | Extract the request body as a value of type @a@.
-- --
@ -17,7 +18,7 @@ import Servant.API.Modifiers
-- >>> type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book -- >>> type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book
type ReqBody = ReqBody' '[Required, Strict] type ReqBody = ReqBody' '[Required, Strict]
-- | -- |
-- --
-- /Note:/ 'ReqBody'' is always 'Required'. -- /Note:/ 'ReqBody'' is always 'Required'.
data ReqBody' (mods :: [*]) (contentTypes :: [*]) (a :: *) data ReqBody' (mods :: [*]) (contentTypes :: [*]) (a :: *)

View File

@ -34,18 +34,22 @@ module Servant.API.ResponseHeaders
, HList(..) , HList(..)
) where ) where
import Data.ByteString.Char8 as BS (ByteString, pack, unlines, init) import Data.ByteString.Char8 as BS
import Data.Typeable (Typeable) (ByteString, init, pack, unlines)
import Web.HttpApiData (ToHttpApiData, toHeader, import qualified Data.CaseInsensitive as CI
FromHttpApiData, parseHeader)
import qualified Data.CaseInsensitive as CI
import Data.Proxy import Data.Proxy
import GHC.TypeLits (KnownSymbol, Symbol, symbolVal) import Data.Typeable
import qualified Network.HTTP.Types.Header as HTTP (Typeable)
import GHC.TypeLits
(KnownSymbol, Symbol, symbolVal)
import qualified Network.HTTP.Types.Header as HTTP
import Web.HttpApiData
(FromHttpApiData, ToHttpApiData, parseHeader, toHeader)
import Servant.API.Header (Header) import Prelude ()
import Prelude ()
import Prelude.Compat import Prelude.Compat
import Servant.API.Header
(Header)
-- | Response Header objects. You should never need to construct one directly. -- | Response Header objects. You should never need to construct one directly.
-- Instead, use 'addOptionalHeader'. -- Instead, use 'addOptionalHeader'.

View File

@ -1,26 +1,34 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-} {-# LANGUAGE TupleSections #-}
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Stream where module Servant.API.Stream where
import Data.ByteString.Lazy (ByteString, empty) import Control.Arrow
import qualified Data.ByteString.Lazy.Char8 as LB (first)
import Data.Monoid ((<>)) import Data.ByteString.Lazy
import Data.Proxy (Proxy) (ByteString, empty)
import Data.Typeable (Typeable) import qualified Data.ByteString.Lazy.Char8 as LB
import GHC.Generics (Generic) import Data.Monoid
import Text.Read (readMaybe) ((<>))
import Control.Arrow (first) import Data.Proxy
import Network.HTTP.Types.Method (StdMethod (..)) (Proxy)
import Data.Typeable
(Typeable)
import GHC.Generics
(Generic)
import Network.HTTP.Types.Method
(StdMethod (..))
import Text.Read
(readMaybe)
-- | A Stream endpoint for a given method emits a stream of encoded values at a given Content-Type, delimited by a framing strategy. Steam endpoints always return response code 200 on success. Type synonyms are provided for standard methods. -- | A Stream endpoint for a given method emits a stream of encoded values at a given Content-Type, delimited by a framing strategy. Steam endpoints always return response code 200 on success. Type synonyms are provided for standard methods.
data Stream (method :: k1) (framing :: *) (contentType :: *) (a :: *) data Stream (method :: k1) (framing :: *) (contentType :: *) (a :: *)

View File

@ -4,7 +4,8 @@
{-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Sub ((:>)) where module Servant.API.Sub ((:>)) where
import Data.Typeable (Typeable) import Data.Typeable
(Typeable)
-- | The contained API (second argument) can be found under @("/" ++ path)@ -- | The contained API (second argument) can be found under @("/" ++ path)@
-- (path being the first argument). -- (path being the first argument).

View File

@ -47,16 +47,25 @@ module Servant.API.TypeLevel (
) where ) where
import GHC.Exts (Constraint) import GHC.Exts
import Servant.API.Alternative (type (:<|>)) (Constraint)
import Servant.API.Capture (Capture, CaptureAll) import Servant.API.Alternative
import Servant.API.Header (Header) (type (:<|>))
import Servant.API.QueryParam (QueryFlag, QueryParam, QueryParams) import Servant.API.Capture
import Servant.API.ReqBody (ReqBody) (Capture, CaptureAll)
import Servant.API.Sub (type (:>)) import Servant.API.Header
import Servant.API.Verbs (Verb) (Header)
import Servant.API.QueryParam
(QueryFlag, QueryParam, QueryParams)
import Servant.API.ReqBody
(ReqBody)
import Servant.API.Sub
(type (:>))
import Servant.API.Verbs
(Verb)
#if MIN_VERSION_base(4,9,0) #if MIN_VERSION_base(4,9,0)
import GHC.TypeLits (TypeError, ErrorMessage(..)) import GHC.TypeLits
(ErrorMessage (..), TypeError)
#endif #endif

View File

@ -3,7 +3,8 @@ module Servant.API.Vault
Vault Vault
) where ) where
import Data.Vault.Lazy (Vault) import Data.Vault.Lazy
(Vault)
-- $vault -- $vault
-- --

View File

@ -8,15 +8,18 @@ module Servant.API.Verbs
, StdMethod(GET, POST, HEAD, PUT, DELETE, TRACE, CONNECT, OPTIONS, PATCH) , StdMethod(GET, POST, HEAD, PUT, DELETE, TRACE, CONNECT, OPTIONS, PATCH)
) where ) where
import Data.Typeable (Typeable) import Data.Proxy
import Data.Proxy (Proxy) (Proxy)
import GHC.Generics (Generic) import Data.Typeable
import GHC.TypeLits (Nat) (Typeable)
import Network.HTTP.Types.Method (Method, StdMethod (..), import GHC.Generics
methodDelete, methodGet, methodHead, (Generic)
methodPatch, methodPost, methodPut, import GHC.TypeLits
methodTrace, methodConnect, (Nat)
methodOptions) import Network.HTTP.Types.Method
(Method, StdMethod (..), methodConnect, methodDelete,
methodGet, methodHead, methodOptions, methodPatch, methodPost,
methodPut, methodTrace)
-- | @Verb@ is a general type for representing HTTP verbs (a.k.a. methods). For -- | @Verb@ is a general type for representing HTTP verbs (a.k.a. methods). For
-- convenience, type synonyms for each verb with a 200 response code are -- convenience, type synonyms for each verb with a 200 response code are

View File

@ -1,9 +1,9 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE KindSignatures #-}
module Servant.API.WithNamedContext where module Servant.API.WithNamedContext where
import GHC.TypeLits import GHC.TypeLits
-- | 'WithNamedContext' names a specific tagged context to use for the -- | 'WithNamedContext' names a specific tagged context to use for the
-- combinators in the API. (See also in @servant-server@, -- combinators in the API. (See also in @servant-server@,

View File

@ -13,7 +13,6 @@ module Servant.Utils.Enter {-# DEPRECATED "Use hoistServer or hoistServerWithCon
(:~>)(..), (:~>)(..),
) where ) where
import Control.Natural
import Control.Monad.Identity import Control.Monad.Identity
import Control.Monad.Morph import Control.Monad.Morph
import Control.Monad.Reader import Control.Monad.Reader
@ -21,8 +20,10 @@ import qualified Control.Monad.State.Lazy as LState
import qualified Control.Monad.State.Strict as SState import qualified Control.Monad.State.Strict as SState
import qualified Control.Monad.Writer.Lazy as LWriter import qualified Control.Monad.Writer.Lazy as LWriter
import qualified Control.Monad.Writer.Strict as SWriter import qualified Control.Monad.Writer.Strict as SWriter
import Data.Tagged (Tagged, retag) import Control.Natural
import Prelude () import Data.Tagged
(Tagged, retag)
import Prelude ()
import Prelude.Compat import Prelude.Compat
import Servant.API import Servant.API

View File

@ -101,38 +101,63 @@ module Servant.Utils.Links (
) where ) where
import Data.List import Data.List
import Data.Monoid.Compat ( (<>) ) import Data.Monoid.Compat
import Data.Proxy ( Proxy(..) ) ((<>))
import Data.Singletons.Bool ( SBool (..), SBoolI (..) ) import Data.Proxy
import qualified Data.Text as Text (Proxy (..))
import qualified Data.Text.Encoding as TE import Data.Singletons.Bool
import Data.Type.Bool (If) (SBool (..), SBoolI (..))
import GHC.TypeLits ( KnownSymbol, symbolVal ) import qualified Data.Text as Text
import Network.URI ( URI(..), escapeURIString, isUnreserved ) import qualified Data.Text.Encoding as TE
import Prelude () import Data.Type.Bool
(If)
import GHC.TypeLits
(KnownSymbol, symbolVal)
import Network.URI
(URI (..), escapeURIString, isUnreserved)
import Prelude ()
import Prelude.Compat import Prelude.Compat
import Web.HttpApiData import Servant.API.Alternative
import Servant.API.Alternative ( (:<|>)((:<|>)) ) ((:<|>) ((:<|>)))
import Servant.API.BasicAuth ( BasicAuth ) import Servant.API.BasicAuth
import Servant.API.Capture ( Capture', CaptureAll ) (BasicAuth)
import Servant.API.ReqBody ( ReqBody' ) import Servant.API.Capture
import Servant.API.QueryParam ( QueryParam', QueryParams, QueryFlag ) (Capture', CaptureAll)
import Servant.API.Header ( Header' ) import Servant.API.Description
import Servant.API.HttpVersion (HttpVersion) (Description, Summary)
import Servant.API.RemoteHost ( RemoteHost ) import Servant.API.Empty
import Servant.API.IsSecure (IsSecure) (EmptyAPI (..))
import Servant.API.Empty (EmptyAPI (..)) import Servant.API.Experimental.Auth
import Servant.API.Verbs ( Verb ) (AuthProtect)
import Servant.API.Sub ( type (:>) ) import Servant.API.Header
import Servant.API.Raw ( Raw ) (Header')
import Servant.API.Stream ( Stream ) import Servant.API.HttpVersion
import Servant.API.TypeLevel (HttpVersion)
import Servant.API.Modifiers (FoldRequired) import Servant.API.IsSecure
import Servant.API.Description (Description, Summary) (IsSecure)
import Servant.API.Vault (Vault) import Servant.API.Modifiers
import Servant.API.WithNamedContext (WithNamedContext) (FoldRequired)
import Servant.API.Experimental.Auth ( AuthProtect ) import Servant.API.QueryParam
(QueryFlag, QueryParam', QueryParams)
import Servant.API.Raw
(Raw)
import Servant.API.RemoteHost
(RemoteHost)
import Servant.API.ReqBody
(ReqBody')
import Servant.API.Stream
(Stream)
import Servant.API.Sub
(type (:>))
import Servant.API.TypeLevel
import Servant.API.Vault
(Vault)
import Servant.API.Verbs
(Verb)
import Servant.API.WithNamedContext
(WithNamedContext)
import Web.HttpApiData
-- | A safe link datatype. -- | A safe link datatype.
-- The only way of constructing a 'Link' is using 'safeLink', which means any -- The only way of constructing a 'Link' is using 'safeLink', which means any