Explicit imports in /src.
This commit is contained in:
parent
9b10181d9a
commit
40b13a9c86
9 changed files with 65 additions and 49 deletions
|
@ -37,16 +37,16 @@ module Servant.API (
|
|||
module Servant.Utils.Links,
|
||||
) where
|
||||
|
||||
import Servant.API.Alternative
|
||||
import Servant.API.Capture
|
||||
import Servant.API.Delete
|
||||
import Servant.API.Get
|
||||
import Servant.API.Header
|
||||
import Servant.API.Post
|
||||
import Servant.API.Put
|
||||
import Servant.API.QueryParam
|
||||
import Servant.API.Raw
|
||||
import Servant.API.ReqBody
|
||||
import Servant.API.Sub
|
||||
import Servant.API.Alternative ( (:<|>)(..) )
|
||||
import Servant.API.Capture ( Capture )
|
||||
import Servant.API.Delete ( Delete )
|
||||
import Servant.API.Get ( Get )
|
||||
import Servant.API.Header ( Header )
|
||||
import Servant.API.Post ( Post )
|
||||
import Servant.API.Put ( Put )
|
||||
import Servant.API.QueryParam ( QueryFlag, QueryParams, QueryParam )
|
||||
import Servant.API.Raw ( Raw )
|
||||
import Servant.API.ReqBody ( ReqBody )
|
||||
import Servant.API.Sub ( (:>)(..) )
|
||||
import Servant.QQ ( sitemap )
|
||||
import Servant.Utils.Links ( mkLink )
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Servant.API.Delete where
|
||||
|
||||
import Data.Typeable
|
||||
import Data.Typeable ( Typeable )
|
||||
|
||||
-- | Combinator for DELETE requests.
|
||||
--
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Servant.API.Get where
|
||||
|
||||
import Data.Typeable
|
||||
import Data.Typeable ( Typeable )
|
||||
|
||||
-- | Endpoint for simple GET requests. Serves the result as JSON.
|
||||
--
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Servant.API.Post where
|
||||
|
||||
import Data.Typeable
|
||||
import Data.Typeable ( Typeable )
|
||||
|
||||
-- | Endpoint for POST requests. The type variable represents the type of the
|
||||
-- response body (not the request body, use 'Servant.API.ReqBody.ReqBody' for
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Servant.API.Put where
|
||||
|
||||
import Data.Typeable
|
||||
import Data.Typeable ( Typeable )
|
||||
|
||||
-- | Endpoint for PUT requests, usually used to update a ressource.
|
||||
-- The type @a@ is the type of the response body that's returned.
|
||||
|
|
|
@ -2,7 +2,7 @@
|
|||
{-# LANGUAGE TypeOperators #-}
|
||||
module Servant.API.Sub where
|
||||
|
||||
import Data.Proxy
|
||||
import Data.Proxy ( Proxy )
|
||||
|
||||
-- | The contained API (second argument) can be found under @("/" ++ path)@
|
||||
-- (path being the first argument).
|
||||
|
|
|
@ -6,11 +6,11 @@ module Servant.Common.Text
|
|||
, ToText(..)
|
||||
) where
|
||||
|
||||
import Data.String.Conversions
|
||||
import Data.Int
|
||||
import Data.Text
|
||||
import Data.Text.Read
|
||||
import Data.Word
|
||||
import Data.String.Conversions ( cs )
|
||||
import Data.Int ( Int8, Int16, Int32, Int64 )
|
||||
import Data.Text ( Text )
|
||||
import Data.Text.Read ( rational, signed, decimal, Reader )
|
||||
import Data.Word ( Word, Word8, Word16, Word32, Word64 )
|
||||
|
||||
-- | For getting values from url captures and query string parameters
|
||||
class FromText a where
|
||||
|
|
|
@ -29,20 +29,38 @@
|
|||
module Servant.QQ (sitemap) where
|
||||
|
||||
import Control.Monad ( void )
|
||||
import Control.Applicative hiding (many, (<|>), optional)
|
||||
import Language.Haskell.TH.Quote
|
||||
import Control.Applicative ( (<$>) )
|
||||
import Language.Haskell.TH.Quote ( QuasiQuoter(..) )
|
||||
import Language.Haskell.TH
|
||||
( mkName, Type(AppT, ConT, LitT), TyLit(StrTyLit) )
|
||||
import Text.ParserCombinators.Parsec
|
||||
|
||||
import Servant.API.Capture
|
||||
import Servant.API.Get
|
||||
import Servant.API.Post
|
||||
import Servant.API.Put
|
||||
import Servant.API.Delete
|
||||
import Servant.API.QueryParam
|
||||
import Servant.API.ReqBody
|
||||
import Servant.API.Sub
|
||||
import Servant.API.Alternative
|
||||
( try,
|
||||
Parser,
|
||||
manyTill,
|
||||
endBy,
|
||||
sepBy1,
|
||||
optional,
|
||||
optionMaybe,
|
||||
string,
|
||||
anyChar,
|
||||
char,
|
||||
spaces,
|
||||
noneOf,
|
||||
parse,
|
||||
skipMany,
|
||||
many,
|
||||
lookAhead,
|
||||
(<|>),
|
||||
(<?>) )
|
||||
import Servant.API.Capture ( Capture )
|
||||
import Servant.API.Get ( Get )
|
||||
import Servant.API.Post ( Post )
|
||||
import Servant.API.Put ( Put )
|
||||
import Servant.API.Delete ( Delete )
|
||||
import Servant.API.QueryParam ( QueryParam )
|
||||
import Servant.API.ReqBody ( ReqBody )
|
||||
import Servant.API.Sub ( (:>) )
|
||||
import Servant.API.Alternative ( (:<|>) )
|
||||
|
||||
-- | Finally-tagless encoding for our DSL.
|
||||
-- Keeping 'repr'' and 'repr' distinct when writing functions with an
|
||||
|
@ -195,4 +213,3 @@ sitemap = QuasiQuoter { quoteExp = undefined
|
|||
Right st -> return st
|
||||
, quoteDec = undefined
|
||||
}
|
||||
|
||||
|
|
|
@ -48,18 +48,18 @@ module Servant.Utils.Links (
|
|||
, IsLink
|
||||
)where
|
||||
|
||||
import Data.Proxy
|
||||
import GHC.TypeLits
|
||||
import Data.Proxy ( Proxy(..) )
|
||||
import GHC.TypeLits ( KnownSymbol, Symbol, symbolVal )
|
||||
|
||||
import Servant.API.Capture
|
||||
import Servant.API.ReqBody
|
||||
import Servant.API.QueryParam
|
||||
import Servant.API.Get
|
||||
import Servant.API.Post
|
||||
import Servant.API.Put
|
||||
import Servant.API.Delete
|
||||
import Servant.API.Sub
|
||||
import Servant.API.Alternative
|
||||
import Servant.API.Capture ( Capture )
|
||||
import Servant.API.ReqBody ( ReqBody )
|
||||
import Servant.API.QueryParam ( QueryParam )
|
||||
import Servant.API.Get ( Get )
|
||||
import Servant.API.Post ( Post )
|
||||
import Servant.API.Put ( Put )
|
||||
import Servant.API.Delete ( Delete )
|
||||
import Servant.API.Sub ( type (:>) )
|
||||
import Servant.API.Alternative ( type (:<|>) )
|
||||
|
||||
|
||||
type family Or a b where
|
||||
|
@ -123,4 +123,3 @@ instance VLinkHelper (Get x) where
|
|||
|
||||
instance VLinkHelper (Post x) where
|
||||
vlh _ = ""
|
||||
|
||||
|
|
Loading…
Reference in a new issue