Merge pull request #680 from phadej/stylish-haskell

Update .stylish-haskell
This commit is contained in:
Oleg Grenrus 2018-03-11 18:28:25 +02:00 committed by GitHub
commit 6d1ae0dccd
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
27 changed files with 406 additions and 205 deletions

View File

@ -15,6 +15,14 @@ steps:
# # true.
# add_language_pragma: true
# Align the right hand side of some elements. This is quite conservative
# and only applies to statements where each element occupies a single
# line.
- simple_align:
cases: false
top_level_patterns: false
records: false
# Import cleanup
- imports:
# There are different ways we can align names and lists.
@ -33,6 +41,91 @@ steps:
# Default: global.
align: global
# Folowing options affect only import list alignment.
#
# List align has following options:
#
# - after_alias: Import list is aligned with end of import including
# 'as' and 'hiding' keywords.
#
# > import qualified Data.List as List (concat, foldl, foldr, head,
# > init, last, length)
#
# - with_alias: Import list is aligned with start of alias or hiding.
#
# > import qualified Data.List as List (concat, foldl, foldr, head,
# > init, last, length)
#
# - new_line: Import list starts always on new line.
#
# > import qualified Data.List as List
# > (concat, foldl, foldr, head, init, last, length)
#
# Default: after_alias
list_align: new_line
# Long list align style takes effect when import is too long. This is
# determined by 'columns' setting.
#
# - inline: This option will put as much specs on same line as possible.
#
# - new_line: Import list will start on new line.
#
# - new_line_multiline: Import list will start on new line when it's
# short enough to fit to single line. Otherwise it'll be multiline.
#
# - multiline: One line per import list entry.
# Type with contructor list acts like single import.
#
# > import qualified Data.Map as M
# > ( empty
# > , singleton
# > , ...
# > , delete
# > )
#
# Default: inline
long_list_align: new_line
# Align empty list (importing instances)
#
# Empty list align has following options
#
# - inherit: inherit list_align setting
#
# - right_after: () is right after the module name:
#
# > import Vector.Instances ()
#
# Default: inherit
empty_list_align: right_after
# List padding determines indentation of import list on lines after import.
# This option affects 'long_list_align'.
#
# - <integer>: constant value
#
# - module_name: align under start of module name.
# Useful for 'file' and 'group' align settings.
list_padding: module_name
# Separate lists option affects formating of import list for type
# or class. The only difference is single space between type and list
# of constructors, selectors and class functions.
#
# - true: There is single space between Foldable type and list of it's
# functions.
#
# > import Data.Foldable (Foldable (fold, foldl, foldMap))
#
# - false: There is no space between Foldable type and list of it's
# functions.
#
# > import Data.Foldable (Foldable(fold, foldl, foldMap))
#
# Default: true
separate_lists: true
# Language pragmas
- language_pragmas:
# We can generate different styles of language pragma lists.
@ -47,13 +140,20 @@ steps:
# Default: vertical.
style: vertical
# Align affects alignment of closing pragma brackets.
#
# - true: Brackets are aligned in same collumn.
#
# - false: Brackets are not aligned together. There is only one space
# between actual import and closing bracket.
#
# Default: true
align: true
# stylish-haskell can detect redundancy of some language pragmas. If this
# is set to true, it will remove those redundant pragmas. Default: true.
remove_redundant: true
# Align the types in record declarations
- records: {}
# Replace tabs by spaces. This is disabled by default.
# - tabs:
# # Number of spaces to use for each tab. Default: 8, as specified by the
@ -67,11 +167,24 @@ steps:
# to. Different steps take this into account. Default: 80.
columns: 80
# By default, line endings are converted according to the OS. You can override
# preferred format here.
#
# - native: Native newline format. CRLF on Windows, LF on other OSes.
#
# - lf: Convert to LF ("\n").
#
# - crlf: Convert to CRLF ("\r\n").
#
# Default: native.
newline: lf
# Sometimes, language extensions are specified in a cabal file or from the
# command line instead of using language pragmas in the file. stylish-haskell
# needs to be aware of these, so it can parse the file correctly.
#
# No language extensions are enabled by default.
language_extensions:
- TemplateHaskell
- QuasiQuotes
- FlexibleContexts
- TemplateHaskell
- QuasiQuotes

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

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

View File

@ -2,7 +2,9 @@
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Raw where
import Data.Typeable (Typeable)
import Data.Typeable
(Typeable)
-- | Endpoint for plugging in your own Wai 'Application's.
--
-- 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
import Data.Typeable
(Typeable)
-- | Provides access to the host or IP address
-- from which the HTTP request was sent.

View File

@ -6,8 +6,9 @@ module Servant.API.ReqBody (
ReqBody, ReqBody',
) where
import Data.Typeable (Typeable)
import Servant.API.Modifiers
import Data.Typeable
(Typeable)
import Servant.API.Modifiers
-- | 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 ReqBody = ReqBody' '[Required, Strict]
-- |
-- |
--
-- /Note:/ 'ReqBody'' is always 'Required'.
data ReqBody' (mods :: [*]) (contentTypes :: [*]) (a :: *)

View File

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

View File

@ -1,26 +1,34 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Stream where
import Data.ByteString.Lazy (ByteString, empty)
import qualified Data.ByteString.Lazy.Char8 as LB
import Data.Monoid ((<>))
import Data.Proxy (Proxy)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Read (readMaybe)
import Control.Arrow (first)
import Network.HTTP.Types.Method (StdMethod (..))
import Control.Arrow
(first)
import Data.ByteString.Lazy
(ByteString, empty)
import qualified Data.ByteString.Lazy.Char8 as LB
import Data.Monoid
((<>))
import Data.Proxy
(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.
data Stream (method :: k1) (framing :: *) (contentType :: *) (a :: *)

View File

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

View File

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

View File

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

View File

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

View File

@ -1,9 +1,9 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
module Servant.API.WithNamedContext where
import GHC.TypeLits
import GHC.TypeLits
-- | 'WithNamedContext' names a specific tagged context to use for the
-- 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
import Control.Natural
import Control.Monad.Identity
import Control.Monad.Morph
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.Writer.Lazy as LWriter
import qualified Control.Monad.Writer.Strict as SWriter
import Data.Tagged (Tagged, retag)
import Prelude ()
import Control.Natural
import Data.Tagged
(Tagged, retag)
import Prelude ()
import Prelude.Compat
import Servant.API

View File

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