stylish-haskell servant-client-core
This commit is contained in:
parent
07716b8f4e
commit
319dcc2fe1
12 changed files with 118 additions and 104 deletions
|
@ -1,2 +1,2 @@
|
||||||
import Distribution.Simple
|
import Distribution.Simple
|
||||||
main = defaultMain
|
main = defaultMain
|
||||||
|
|
|
@ -55,13 +55,11 @@ module Servant.Client.Core
|
||||||
, setRequestBody
|
, setRequestBody
|
||||||
) where
|
) where
|
||||||
import Servant.Client.Core.Internal.Auth
|
import Servant.Client.Core.Internal.Auth
|
||||||
import Servant.Client.Core.Internal.BaseUrl (BaseUrl (..),
|
import Servant.Client.Core.Internal.BaseUrl
|
||||||
InvalidBaseUrlException,
|
(BaseUrl (..), InvalidBaseUrlException, Scheme (..),
|
||||||
Scheme (..),
|
parseBaseUrl, showBaseUrl)
|
||||||
parseBaseUrl,
|
|
||||||
showBaseUrl)
|
|
||||||
import Servant.Client.Core.Internal.BasicAuth
|
import Servant.Client.Core.Internal.BasicAuth
|
||||||
import Servant.Client.Core.Internal.HasClient
|
|
||||||
import Servant.Client.Core.Internal.Generic
|
import Servant.Client.Core.Internal.Generic
|
||||||
|
import Servant.Client.Core.Internal.HasClient
|
||||||
import Servant.Client.Core.Internal.Request
|
import Servant.Client.Core.Internal.Request
|
||||||
import Servant.Client.Core.Internal.RunClient
|
import Servant.Client.Core.Internal.RunClient
|
||||||
|
|
|
@ -6,7 +6,8 @@
|
||||||
|
|
||||||
module Servant.Client.Core.Internal.Auth where
|
module Servant.Client.Core.Internal.Auth where
|
||||||
|
|
||||||
import Servant.Client.Core.Internal.Request (Request)
|
import Servant.Client.Core.Internal.Request
|
||||||
|
(Request)
|
||||||
|
|
||||||
-- | For a resource protected by authentication (e.g. AuthProtect), we need
|
-- | For a resource protected by authentication (e.g. AuthProtect), we need
|
||||||
-- to provide the client with some data used to add authentication data
|
-- to provide the client with some data used to add authentication data
|
||||||
|
|
|
@ -3,11 +3,13 @@
|
||||||
{-# LANGUAGE ViewPatterns #-}
|
{-# LANGUAGE ViewPatterns #-}
|
||||||
module Servant.Client.Core.Internal.BaseUrl where
|
module Servant.Client.Core.Internal.BaseUrl where
|
||||||
|
|
||||||
import Control.Monad.Catch (Exception, MonadThrow, throwM)
|
import Control.Monad.Catch
|
||||||
|
(Exception, MonadThrow, throwM)
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Typeable
|
import Data.Typeable
|
||||||
import GHC.Generics
|
import GHC.Generics
|
||||||
import Network.URI hiding (path)
|
import Network.URI hiding
|
||||||
|
(path)
|
||||||
import Safe
|
import Safe
|
||||||
import Text.Read
|
import Text.Read
|
||||||
|
|
||||||
|
|
|
@ -6,11 +6,16 @@
|
||||||
|
|
||||||
module Servant.Client.Core.Internal.BasicAuth where
|
module Servant.Client.Core.Internal.BasicAuth where
|
||||||
|
|
||||||
import Data.ByteString.Base64 (encode)
|
import Data.ByteString.Base64
|
||||||
import Data.Monoid ((<>))
|
(encode)
|
||||||
import Data.Text.Encoding (decodeUtf8)
|
import Data.Monoid
|
||||||
import Servant.API.BasicAuth (BasicAuthData (BasicAuthData))
|
((<>))
|
||||||
import Servant.Client.Core.Internal.Request (Request, addHeader)
|
import Data.Text.Encoding
|
||||||
|
(decodeUtf8)
|
||||||
|
import Servant.API.BasicAuth
|
||||||
|
(BasicAuthData (BasicAuthData))
|
||||||
|
import Servant.Client.Core.Internal.Request
|
||||||
|
(Request, addHeader)
|
||||||
|
|
||||||
-- | Authenticate a request using Basic Authentication
|
-- | Authenticate a request using Basic Authentication
|
||||||
basicAuthReq :: BasicAuthData -> Request -> Request
|
basicAuthReq :: BasicAuthData -> Request -> Request
|
||||||
|
|
|
@ -1,7 +1,7 @@
|
||||||
{-# LANGUAGE DeriveFunctor #-}
|
{-# LANGUAGE DeriveFunctor #-}
|
||||||
module Servant.Client.Core.Internal.ClientF where
|
module Servant.Client.Core.Internal.ClientF where
|
||||||
|
|
||||||
import Servant.Client.Core.Internal.Request
|
import Servant.Client.Core.Internal.Request
|
||||||
|
|
||||||
data ClientF a
|
data ClientF a
|
||||||
= RunRequest Request (Response -> a)
|
= RunRequest Request (Response -> a)
|
||||||
|
|
|
@ -1,19 +1,21 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE DefaultSignatures #-}
|
{-# LANGUAGE DefaultSignatures #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
|
||||||
#include "overlapping-compat.h"
|
#include "overlapping-compat.h"
|
||||||
|
|
||||||
module Servant.Client.Core.Internal.Generic where
|
module Servant.Client.Core.Internal.Generic where
|
||||||
|
|
||||||
import Generics.SOP (Code, Generic, I(..), NP(..), NS(Z), SOP(..), to)
|
import Generics.SOP
|
||||||
import Servant.API ((:<|>)(..))
|
(Code, Generic, I (..), NP (..), NS (Z), SOP (..), to)
|
||||||
|
import Servant.API
|
||||||
|
((:<|>) (..))
|
||||||
|
|
||||||
-- | This class allows us to match client structure with client functions
|
-- | This class allows us to match client structure with client functions
|
||||||
-- produced with 'client' without explicit pattern-matching.
|
-- produced with 'client' without explicit pattern-matching.
|
||||||
|
|
|
@ -15,54 +15,46 @@
|
||||||
#include "overlapping-compat.h"
|
#include "overlapping-compat.h"
|
||||||
module Servant.Client.Core.Internal.HasClient where
|
module Servant.Client.Core.Internal.HasClient where
|
||||||
|
|
||||||
import Prelude ()
|
import Prelude ()
|
||||||
import Prelude.Compat
|
import Prelude.Compat
|
||||||
|
|
||||||
import Control.Concurrent (newMVar, modifyMVar)
|
import Control.Concurrent
|
||||||
import Data.Foldable (toList)
|
(modifyMVar, newMVar)
|
||||||
|
import Control.Monad.IO.Class
|
||||||
|
(MonadIO (..))
|
||||||
import qualified Data.ByteString.Lazy as BL
|
import qualified Data.ByteString.Lazy as BL
|
||||||
import Control.Monad.IO.Class (MonadIO (..))
|
import Data.Foldable
|
||||||
import Data.List (foldl')
|
(toList)
|
||||||
import Data.Proxy (Proxy (Proxy))
|
import Data.List
|
||||||
import Data.Semigroup ((<>))
|
(foldl')
|
||||||
import Data.Sequence (fromList)
|
import Data.Proxy
|
||||||
import Data.String (fromString)
|
(Proxy (Proxy))
|
||||||
import Data.Text (Text, pack)
|
import Data.Semigroup
|
||||||
import GHC.TypeLits (KnownSymbol, symbolVal)
|
((<>))
|
||||||
|
import Data.Sequence
|
||||||
|
(fromList)
|
||||||
|
import Data.String
|
||||||
|
(fromString)
|
||||||
|
import Data.Text
|
||||||
|
(Text, pack)
|
||||||
|
import GHC.TypeLits
|
||||||
|
(KnownSymbol, symbolVal)
|
||||||
import qualified Network.HTTP.Types as H
|
import qualified Network.HTTP.Types as H
|
||||||
import Servant.API ((:<|>) ((:<|>)), (:>),
|
import Servant.API
|
||||||
AuthProtect, BasicAuth,
|
((:<|>) ((:<|>)), (:>), AuthProtect, BasicAuth, BasicAuthData,
|
||||||
BasicAuthData,
|
BuildHeadersTo (..), ByteStringParser (..), Capture',
|
||||||
BuildHeadersTo (..),
|
CaptureAll, Description, EmptyAPI, FramingUnrender (..),
|
||||||
FromResultStream (..),
|
FromResultStream (..), Header', Headers (..), HttpVersion,
|
||||||
ByteStringParser (..),
|
IsSecure, MimeRender (mimeRender),
|
||||||
Capture', CaptureAll,
|
MimeUnrender (mimeUnrender), NoContent (NoContent), QueryFlag,
|
||||||
Description, EmptyAPI,
|
QueryParam', QueryParams, Raw, ReflectMethod (..), RemoteHost,
|
||||||
FramingUnrender (..),
|
ReqBody', ResultStream (..), SBoolI, Stream, Summary,
|
||||||
Header', Headers (..),
|
ToHttpApiData, Vault, Verb, WithNamedContext, contentType,
|
||||||
HttpVersion, IsSecure,
|
getHeadersHList, getResponse, toQueryParam, toUrlPiece)
|
||||||
MimeRender (mimeRender),
|
import Servant.API.ContentTypes
|
||||||
MimeUnrender (mimeUnrender),
|
(contentTypes)
|
||||||
NoContent (NoContent),
|
import Servant.API.Modifiers
|
||||||
QueryFlag, QueryParam',
|
(FoldRequired, RequiredArgument, foldRequiredArgument)
|
||||||
QueryParams, Raw,
|
|
||||||
ReflectMethod (..),
|
|
||||||
RemoteHost, ReqBody',
|
|
||||||
ResultStream(..),
|
|
||||||
SBoolI,
|
|
||||||
Stream,
|
|
||||||
Summary, ToHttpApiData,
|
|
||||||
Vault, Verb,
|
|
||||||
WithNamedContext,
|
|
||||||
contentType,
|
|
||||||
getHeadersHList,
|
|
||||||
getResponse,
|
|
||||||
toQueryParam,
|
|
||||||
toUrlPiece)
|
|
||||||
import Servant.API.ContentTypes (contentTypes)
|
|
||||||
import Servant.API.Modifiers (FoldRequired,
|
|
||||||
RequiredArgument,
|
|
||||||
foldRequiredArgument)
|
|
||||||
|
|
||||||
import Servant.Client.Core.Internal.Auth
|
import Servant.Client.Core.Internal.Auth
|
||||||
import Servant.Client.Core.Internal.BasicAuth
|
import Servant.Client.Core.Internal.BasicAuth
|
||||||
|
|
|
@ -12,26 +12,34 @@
|
||||||
|
|
||||||
module Servant.Client.Core.Internal.Request where
|
module Servant.Client.Core.Internal.Request where
|
||||||
|
|
||||||
import Prelude ()
|
import Prelude ()
|
||||||
import Prelude.Compat
|
import Prelude.Compat
|
||||||
|
|
||||||
import Control.Monad.Catch (Exception)
|
import Control.Monad.Catch
|
||||||
|
(Exception)
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import qualified Data.ByteString.Builder as Builder
|
import qualified Data.ByteString.Builder as Builder
|
||||||
import qualified Data.ByteString.Lazy as LBS
|
import qualified Data.ByteString.Lazy as LBS
|
||||||
import Data.Int (Int64)
|
import Data.Int
|
||||||
import Data.Semigroup ((<>))
|
(Int64)
|
||||||
|
import Data.Semigroup
|
||||||
|
((<>))
|
||||||
import qualified Data.Sequence as Seq
|
import qualified Data.Sequence as Seq
|
||||||
import Data.Text (Text)
|
import Data.Text
|
||||||
import Data.Text.Encoding (encodeUtf8)
|
(Text)
|
||||||
import Data.Typeable (Typeable)
|
import Data.Text.Encoding
|
||||||
import GHC.Generics (Generic)
|
(encodeUtf8)
|
||||||
import Network.HTTP.Media (MediaType)
|
import Data.Typeable
|
||||||
import Network.HTTP.Types (Header, HeaderName, HttpVersion,
|
(Typeable)
|
||||||
Method, QueryItem, Status, http11,
|
import GHC.Generics
|
||||||
methodGet)
|
(Generic)
|
||||||
import Web.HttpApiData (ToHttpApiData, toEncodedUrlPiece,
|
import Network.HTTP.Media
|
||||||
toHeader)
|
(MediaType)
|
||||||
|
import Network.HTTP.Types
|
||||||
|
(Header, HeaderName, HttpVersion, Method, QueryItem, Status,
|
||||||
|
http11, methodGet)
|
||||||
|
import Web.HttpApiData
|
||||||
|
(ToHttpApiData, toEncodedUrlPiece, toHeader)
|
||||||
|
|
||||||
-- | A type representing possible errors in a request
|
-- | A type representing possible errors in a request
|
||||||
--
|
--
|
||||||
|
|
|
@ -6,24 +6,27 @@
|
||||||
-- | Types for possible backends to run client-side `Request` queries
|
-- | Types for possible backends to run client-side `Request` queries
|
||||||
module Servant.Client.Core.Internal.RunClient where
|
module Servant.Client.Core.Internal.RunClient where
|
||||||
|
|
||||||
import Prelude ()
|
import Prelude ()
|
||||||
import Prelude.Compat
|
import Prelude.Compat
|
||||||
|
|
||||||
import Control.Monad (unless)
|
import Control.Monad
|
||||||
import Control.Monad.Free (Free (..), liftF)
|
(unless)
|
||||||
import Data.Foldable (toList)
|
import Control.Monad.Free
|
||||||
import Data.Proxy (Proxy)
|
(Free (..), liftF)
|
||||||
|
import Data.Foldable
|
||||||
|
(toList)
|
||||||
|
import Data.Proxy
|
||||||
|
(Proxy)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Network.HTTP.Media (MediaType, matches,
|
import Network.HTTP.Media
|
||||||
parseAccept, (//))
|
(MediaType, matches, parseAccept, (//))
|
||||||
import Servant.API (MimeUnrender,
|
import Servant.API
|
||||||
contentTypes,
|
(MimeUnrender, contentTypes, mimeUnrender)
|
||||||
mimeUnrender)
|
|
||||||
|
|
||||||
import Servant.Client.Core.Internal.Request (Request, Response, GenResponse (..),
|
|
||||||
StreamingResponse (..),
|
|
||||||
ServantError (..))
|
|
||||||
import Servant.Client.Core.Internal.ClientF
|
import Servant.Client.Core.Internal.ClientF
|
||||||
|
import Servant.Client.Core.Internal.Request
|
||||||
|
(GenResponse (..), Request, Response, ServantError (..),
|
||||||
|
StreamingResponse (..))
|
||||||
|
|
||||||
class Monad m => RunClient m where
|
class Monad m => RunClient m where
|
||||||
-- | How to make a request.
|
-- | How to make a request.
|
||||||
|
|
|
@ -28,6 +28,6 @@ module Servant.Client.Core.Reexport
|
||||||
|
|
||||||
|
|
||||||
import Servant.Client.Core.Internal.BaseUrl
|
import Servant.Client.Core.Internal.BaseUrl
|
||||||
import Servant.Client.Core.Internal.HasClient
|
|
||||||
import Servant.Client.Core.Internal.Generic
|
import Servant.Client.Core.Internal.Generic
|
||||||
|
import Servant.Client.Core.Internal.HasClient
|
||||||
import Servant.Client.Core.Internal.Request
|
import Servant.Client.Core.Internal.Request
|
||||||
|
|
|
@ -1,15 +1,18 @@
|
||||||
{-# LANGUAGE ScopedTypeVariables, FlexibleContexts, GADTs #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE GADTs #-}
|
||||||
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
module Servant.Client.Free (
|
module Servant.Client.Free (
|
||||||
client,
|
client,
|
||||||
ClientF (..),
|
ClientF (..),
|
||||||
module Servant.Client.Core.Reexport,
|
module Servant.Client.Core.Reexport,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Proxy (Proxy (..))
|
import Control.Monad.Free
|
||||||
import Control.Monad.Free
|
import Data.Proxy
|
||||||
import Servant.Client.Core
|
(Proxy (..))
|
||||||
import Servant.Client.Core.Reexport
|
import Servant.Client.Core
|
||||||
import Servant.Client.Core.Internal.ClientF
|
import Servant.Client.Core.Internal.ClientF
|
||||||
|
import Servant.Client.Core.Reexport
|
||||||
|
|
||||||
client :: HasClient (Free ClientF) api => Proxy api -> Client (Free ClientF) api
|
client :: HasClient (Free ClientF) api => Proxy api -> Client (Free ClientF) api
|
||||||
client api = api `clientIn` (Proxy :: Proxy (Free ClientF))
|
client api = api `clientIn` (Proxy :: Proxy (Free ClientF))
|
||||||
|
|
Loading…
Reference in a new issue