servant-client-core-0.20.2/0000755000000000000000000000000007346545000013650 5ustar0000000000000000servant-client-core-0.20.2/CHANGELOG.md0000644000000000000000000002760507346545000015473 0ustar0000000000000000[The latest version of this document is on GitHub.](https://github.com/haskell-servant/servant/blob/master/servant-client-core/CHANGELOG.md) [Changelog for `servant` package contains significant entries for all core packages.](https://github.com/haskell-servant/servant/blob/master/servant/CHANGELOG.md) Package versions follow the [Package Versioning Policy](https://pvp.haskell.org/): in A.B.C, bumps to either A or B represent major versions. 0.20.2 ---- - Full query string helpers [#1604](https://github.com/haskell-servant/servant/pull/1604) This involves exporting `setQueryString` from Servant.Client.Core.Request. 0.20 ---- - Escape special chars in QueryParams. [#1584](https://github.com/haskell-servant/servant/issues/1584) [#1597](https://github.com/haskell-servant/servant/pull/1597) Escape special chars in QueryParam (`:@&=+$`) in servant-client. Note that this mean binary data will not work as is, and so reverts the functionality in [#1432](https://github.com/haskell-servant/servant/pull/1432). - Handle Cookies correctly for RunStreamingClient [#1605](https://github.com/haskell-servant/servant/issues/1605) [#1606](https://github.com/haskell-servant/servant/pull/1606) Makes `performWithStreamingRequest` take into consideration the CookieJar, which it previously didn't. - Fix the handling of multiple headers with the same name. [#1666](https://github.com/haskell-servant/servant/pull/1666) servant-client no longer concatenates the values of response headers with the same name. This fixes an issue with parsing multiple `Set-Cookie` headers. 0.19 ---- ### Significant changes - Drop support for GHC < 8.6. - Support GHC 9.0 (GHC 9.2 should work as well, but isn't fully tested yet). - Support Aeson 2 ([#1475](https://github.com/haskell-servant/servant/pull/1475)), which fixes a [DOS vulnerability](https://github.com/haskell/aeson/issues/864) related to hash collisions. - Add `NamedRoutes` combinator, making support for records first-class in Servant ([#1388](https://github.com/haskell-servant/servant/pull/1388)). - Add custom type errors for partially applied combinators ([#1289](https://github.com/haskell-servant/servant/pull/1289), [#1486](https://github.com/haskell-servant/servant/pull/1486)). - *servant-client* / *servant-client-core* / *servant-http-streams*: Fix erroneous behavior, where only 2XX status codes would be considered successful, irrelevant of the status parameter specified by the verb combinator. ([#1469](https://github.com/haskell-servant/servant/pull/1469)) - *servant-client* / *servant-client-core*: Fix `Show` instance for `Servant.Client.Core.Request`. - *servant-client* / *servant-client-core*: Allow passing arbitrary binary data in Query parameters. ([#1432](https://github.com/haskell-servant/servant/pull/1432)). ### Other changes - Various version bumps. 0.18.3 ------ ### Significant changes - Add response header support to UVerb (#1420) ### Other changes - Support GHC-9.0.1. - Bump `bytestring`, `hspec`, `base64-bytestring` and `QuickCheck` dependencies. 0.18.2 ------ ### Significant changes - Support `Fragment` combinator. 0.18.1 ------ ### Significant changes - Union verbs ### Other changes - Bump "tested-with" ghc versions - Loosen bound on base16-bytestring 0.18 ---- ### Significant changes - Support for ghc8.8 (#1318, #1326, #1327) 0.17 ---- ### Significant changes - Add NoContentVerb [#1028](https://github.com/haskell-servant/servant/issues/1028) [#1219](https://github.com/haskell-servant/servant/pull/1219) [#1228](https://github.com/haskell-servant/servant/pull/1228) The `NoContent` API endpoints should now use `NoContentVerb` combinator. The API type changes are usually of the kind ```diff - :<|> PostNoContent '[JSON] NoContent + :<|> PostNoContent ``` i.e. one doesn't need to specify the content-type anymore. There is no content. - `Capture` can be `Lenient` [#1155](https://github.com/haskell-servant/servant/issues/1155) [#1156](https://github.com/haskell-servant/servant/pull/1156) You can specify a lenient capture as ```haskell :<|> "capture-lenient" :> Capture' '[Lenient] "foo" Int :> GET ``` which will make the capture always succeed. Handlers will be of the type `Either String CapturedType`, where `Left err` represents the possible parse failure. ### Other changes - *servant-client* *servant-client-core* *servant-http-streams* Fix Verb with headers checking content type differently [#1200](https://github.com/haskell-servant/servant/issues/1200) [#1204](https://github.com/haskell-servant/servant/pull/1204) For `Verb`s with response `Headers`, the implementation didn't check for the content-type of the response. Now it does. - *servant-client* *servant-http-streams* `HasClient` instance for `Stream` with `Headers` [#1170](https://github.com/haskell-servant/servant/issues/1170) [#1197](https://github.com/haskell-servant/servant/pull/1197) - *servant-client* Redact the authorization header in Show and exceptions [#1238](https://github.com/haskell-servant/servant/pull/1238) 0.16 ---- - Rename `ServantError` to `ClientError`, `ServantErr` to `ServerError` [#1131](https://github.com/haskell-servant/servant/pull/1131) - *servant-client-core* Rearrange modules. No more `Internal` modules, whole API is versioned. [#1130](https://github.com/haskell-servant/servant/pull/1130) - *servant-client-core* `RequestBody` is now ```haskell = RequestBodyLBS LBS.ByteString | RequestBodyBS BS.ByteString | RequestBodySource (SourceIO LBS.ByteString) ``` i.e. no more replicates `http-client`s API. [#1117](https://github.com/haskell-servant/servant/pull/1117) - *servant-client-core* Keep structured exceptions in `ConnectionError` constructor of `ClientError` [#1115](https://github.com/haskell-servant/servant/pull/1115) ```diff -| ConnectionError Text +| ConnectionError SomeException ``` - *servant-client-core* Preserve failing request in `FailureResponse` constructor of `ClientError` [#1114](https://github.com/haskell-servant/servant/pull/1114) ```diff -FailureResponse Response +-- | The server returned an error response including the +-- failing request. 'requestPath' includes the 'BaseUrl' and the +-- path of the request. +FailureResponse (RequestF () (BaseUrl, BS.ByteString)) Response ``` - *servant-client* Fix (implement) `StreamBody` instance [#1110](https://github.com/haskell-servant/servant/pull/1110) - *servant-client* Update CookieJar with intermediate request/responses (redirects) [#1104](https://github.com/haskell-servant/servant/pull/1104) 0.15 ---- - Streaming refactoring. [#991](https://github.com/haskell-servant/servant/pull/991) [#1076](https://github.com/haskell-servant/servant/pull/1076) [#1077](https://github.com/haskell-servant/servant/pull/1077) The streaming functionality (`Servant.API.Stream`) is refactored to use `servant`'s own `SourceIO` type (see `Servant.Types.SourceT` documentation), which replaces both `StreamGenerator` and `ResultStream` types. New conversion type-classes are `ToSourceIO` and `FromSourceIO` (replacing `ToStreamGenerator` and `BuildFromStream`). There are instances for *conduit*, *pipes* and *machines* in new packages: [servant-conduit](https://hackage.haskell.org/package/servant-conduit) [servant-pipes](https://hackage.haskell.org/package/servant-pipes) and [servant-machines](https://hackage.haskell.org/package/servant-machines) respectively. Writing new framing strategies is simpler. Check existing strategies for examples. This change shouldn't affect you, if you don't use streaming endpoints. - *servant-client* Separate streaming client. [#1066](https://github.com/haskell-servant/servant/pull/1066) We now have two `http-client` based clients, in `Servant.Client` and `Servant.Client.Streaming`. Their API is the same, except for - `Servant.Client` **cannot** request `Stream` endpoints. - `Servant.Client` is *run* by direct `runClientM :: ClientM a -> ClientEnv -> IO (Either ServantError a)` - `Servant.Client.Streaming` **can** request `Stream` endpoints. - `Servant.Client.Streaming` is *used* by CPSised `withClientM :: ClientM a -> ClientEnv -> (Either ServantError a -> IO b) -> IO b` To access `Stream` endpoints use `Servant.Client.Streaming` with `withClientM`; otherwise you can continue using `Servant.Client` with `runClientM`. You can use both too, `ClientEnv` and `BaseUrl` types are same for both. **Note:** `Servant.Client.Streaming` doesn't *stream* non-`Stream` endpoints. Requesting ordinary `Verb` endpoints (e.g. `Get`) will block until the whole response is received. There is `Servant.Client.Streaming.runClientM` function, but it has restricted type. `NFData a` constraint prevents using it with `SourceT`, `Conduit` etc. response types. ```haskell runClientM :: NFData a => ClientM a -> ClientEnv -> IO (Either ServantError a) ``` This change shouldn't affect you, if you don't use streaming endpoints. - *servant-client-core* Related to the previous: `streamingResponse` is removed from `RunClient`. We have a new type-class: ```haskell class RunClient m => RunStreamingClient m where withStreamingRequest :: Request -> (StreamingResponse -> IO a) -> m a ``` - Drop support for GHC older than 8.0 [#1008](https://github.com/haskell-servant/servant/pull/1008) [#1009](https://github.com/haskell-servant/servant/pull/1009) - *servant-client-core* Add `NFData (GenResponse a)` and `NFData ServantError` instances. [#1076](https://github.com/haskell-servant/servant/pull/1076) - *servant-client-core* Add `aeson` and `Lift BaseUrl` instances [#1037](https://github.com/haskell-servant/servant/pull/1037) 0.14.1 ------ - Merge in `servant-generic` (by [Patrick Chilton](https://github.com/chpatrick)) into `servant` (`Servant.API.Generic`), `servant-client-code` (`Servant.Client.Generic`) and `servant-server` (`Servant.Server.Generic`). 0.14 ---- - `Stream` takes a status code argument ```diff -Stream method framing ctype a +Stream method status framing ctype a ``` ([#966](https://github.com/haskell-servant/servant/pull/966) [#972](https://github.com/haskell-servant/servant/pull/972)) - `ToStreamGenerator` definition changed, so it's possible to write an instance for conduits. ```diff -class ToStreamGenerator f a where - toStreamGenerator :: f a -> StreamGenerator a +class ToStreamGenerator a b | a -> b where + toStreamGenerator :: a -> StreamGenerator b ``` ([#959](https://github.com/haskell-servant/servant/pull/959)) - Added `NoFraming` streaming strategy ([#959](https://github.com/haskell-servant/servant/pull/959)) - *servant-client-core* Free `Client` implementation. Useful for testing `HasClient` instances. ([#920](https://github.com/haskell-servant/servant/pull/920)) - *servant-client-core* Add `hoistClient` to `HasClient`. Just like `hoistServer` allows us to change the monad in which request handlers of a web application live, we also have `hoistClient` for changing the monad in which *client functions* live. Read [tutorial section for more information](https://docs.servant.dev/en/release-0.14/tutorial/Client.html#changing-the-monad-the-client-functions-live-in). ([#936](https://github.com/haskell-servant/servant/pull/936)) iF you have own combinators, you'll need to define a new method of `HasClient` class, for example: ```haskell type Client m (MyCombinator :> api) = MyValue :> Client m api hoistClientMonad pm _ nt cl = hoistClientMonad pm (Proxy :: Proxy api) nt . cl ``` 0.13.0.1 -------- - Support `base-compat-0.10` 0.13 ---- - Streaming endpoint support. ([#836](https://github.com/haskell-servant/servant/pull/836)) - *servant* Add `Servant.API.Modifiers` ([#873](https://github.com/haskell-servant/servant/pull/873)) 0.12 ---- - First version. Factored out of `servant-client` all the functionality that was independent of the `http-client` backend. servant-client-core-0.20.2/LICENSE0000644000000000000000000000300707346545000014655 0ustar0000000000000000Copyright (c) 2017-2018, Servant Contributors All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of Servant Contributors nor the names of other contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. servant-client-core-0.20.2/README.md0000644000000000000000000000174107346545000015132 0ustar0000000000000000# servant-client-core ![servant](https://raw.githubusercontent.com/haskell-servant/servant/master/servant.png) HTTP-client-agnostic client functions for servant APIs. This library should mainly be of interest to backend- and combinator-writers. ## For backend-writers If you are creating a new backend, you'll need to: 1. Define a `RunClient` instance for your datatype (call it `MyMonad`) 2. Define a `ClientLike` instance. This will look like: ``` haskell instance ClientLike (MyMonad a) (MyMonad a) where mkClient = id ``` 3. Re-export the module Servant.Client.Core.Reexport so that your end-users can be blissfully unaware of 'servant-client-core', and so each backend-package comes closer to the warm hearth of the drop-in-replacement equivalence class. ## For combinator-writers You'll need to define a new `HasClient` instance for your combinator. There are plenty of examples to guide you in the [HasClient](src/Servant/Client/Core/Internal/HasClient.hs) module. servant-client-core-0.20.2/Setup.hs0000644000000000000000000000007007346545000015301 0ustar0000000000000000import Distribution.Simple main = defaultMain servant-client-core-0.20.2/servant-client-core.cabal0000644000000000000000000001047307346545000020525 0ustar0000000000000000cabal-version: 3.0 name: servant-client-core version: 0.20.2 synopsis: Core functionality and class for client function generation for servant APIs category: Servant, Web description: This library provides backend-agnostic generation of client functions. For more information, see the README. homepage: http://docs.servant.dev/ bug-reports: http://github.com/haskell-servant/servant/issues license: BSD-3-Clause license-file: LICENSE author: Servant Contributors maintainer: haskell-servant-maintainers@googlegroups.com copyright: 2014-2016 Zalora South East Asia Pte Ltd, 2016-2019 Servant Contributors build-type: Simple tested-with: GHC ==8.10.7 || ==9.0.2 || ==9.2.8 || ==9.4.8 || ==9.6.4 || ==9.8.2 || ==9.10.1 extra-source-files: CHANGELOG.md README.md source-repository head type: git location: http://github.com/haskell-servant/servant.git common extensions default-extensions: AllowAmbiguousTypes ConstraintKinds DataKinds DeriveAnyClass DeriveDataTypeable DeriveFunctor DeriveGeneric DerivingStrategies DerivingVia DuplicateRecordFields ExplicitNamespaces FlexibleContexts FlexibleInstances FunctionalDependencies GADTs InstanceSigs KindSignatures LambdaCase MultiParamTypeClasses NoStarIsType OverloadedLabels OverloadedStrings PackageImports PolyKinds RankNTypes RecordWildCards QuantifiedConstraints ScopedTypeVariables StrictData TupleSections TypeApplications TypeFamilies TypeOperators UndecidableInstances ViewPatterns default-language: Haskell2010 common ghc-options ghc-options: -Wall -Wcompat -Widentities -Wincomplete-record-updates -Wincomplete-uni-patterns -Wpartial-fields -Wredundant-constraints -fhide-source-paths -Wno-unused-do-bind -fdicts-strict -Wno-unticked-promoted-constructors -Werror=unused-imports -Wunused-packages library import: extensions import: ghc-options exposed-modules: Servant.Client.Core Servant.Client.Core.Auth Servant.Client.Core.BaseUrl Servant.Client.Core.BasicAuth Servant.Client.Core.ClientError Servant.Client.Core.HasClient Servant.Client.Core.Reexport Servant.Client.Core.Request Servant.Client.Core.Response Servant.Client.Core.RunClient Servant.Client.Free Servant.Client.Generic other-modules: Servant.Client.Core.Internal -- Bundled with GHC: Lower bound to not force re-installs -- text and mtl are bundled starting with GHC-8.4 -- -- note: mtl lower bound is so low because of GHC-7.8 build-depends: , base >=4.14 && <4.21 , bytestring >=0.10.8.1 && <0.13 , constraints >=0.2 && <0.15 , containers >=0.5.7.1 && <0.8 , deepseq >=1.4.2.0 && <1.6 , template-haskell >=2.11.1.0 && <2.23 , text >=1.2.3.0 && <2.2 -- Servant dependencies build-depends: servant >=0.20.2 -- Other dependencies: Lower bound around what is in the latest Stackage LTS. -- Here can be exceptions if we really need features from the newer versions. build-depends: , aeson >=1.4.1.0 && <3 , base-compat >=0.10.5 && <0.15 , base64-bytestring >=1.0.0.1 && <1.3 , exceptions >=0.10.0 && <0.11 , free >=5.1 && <5.3 , http-media >=0.7.1.3 && <0.9 , http-types >=0.12.2 && <0.13 , network-uri >=2.6.1.0 && <2.7 , safe >=0.3.17 && <0.4 , sop-core >=0.4.0.0 && <0.6 hs-source-dirs: src test-suite spec import: extensions import: ghc-options type: exitcode-stdio-1.0 hs-source-dirs: test main-is: Spec.hs other-modules: Servant.Client.Core.Internal.BaseUrlSpec Servant.Client.Core.RequestSpec -- Dependencies inherited from the library. No need to specify bounds. build-depends: , base , base-compat , servant-client-core -- Additional dependencies build-depends: , deepseq >=1.4.2.0 && <1.6 , hspec >=2.6.0 && <2.12 , QuickCheck >=2.12.6.1 && <2.16 build-tool-depends: hspec-discover:hspec-discover >=2.6.0 && <2.12 servant-client-core-0.20.2/src/Servant/Client/0000755000000000000000000000000007346545000017277 5ustar0000000000000000servant-client-core-0.20.2/src/Servant/Client/Core.hs0000644000000000000000000000350007346545000020521 0ustar0000000000000000-- | This module provides backend-agnostic functionality for generating clients -- from @servant@ APIs. By "backend," we mean something that concretely -- executes the request, such as: -- -- * The @http-client@ library -- * The @haxl@ library -- * GHCJS via FFI -- -- etc. -- -- Each backend is encapsulated in a monad that is an instance of the -- 'RunClient' class. -- -- This library is primarily of interest to backend-writers and -- combinator-writers. For more information, see the README.md module Servant.Client.Core ( -- * Client generation clientIn , HasClient(..) , foldMapUnion , matchUnion -- * Request , Request , RequestF(..) , defaultRequest , RequestBody(..) -- * Authentication , mkAuthenticatedRequest , basicAuthReq , AuthenticatedRequest(..) , AuthClientData -- * Generic Client , ClientError(..) , EmptyClient(..) -- * Response , Response , ResponseF (..) , RunClient(..) -- * BaseUrl , BaseUrl (..) , Scheme (..) , showBaseUrl , parseBaseUrl , InvalidBaseUrlException (..) -- ** Streaming , RunStreamingClient(..) , StreamingResponse -- * Writing HasClient instances -- | These functions need not be re-exported by backend libraries. , addHeader , appendToQueryString , appendToPath , setRequestBodyLBS , setRequestBody , encodeQueryParamValue ) where import Servant.Client.Core.Auth import Servant.Client.Core.BaseUrl (BaseUrl (..), InvalidBaseUrlException (..), Scheme (..), parseBaseUrl, showBaseUrl) import Servant.Client.Core.BasicAuth import Servant.Client.Core.ClientError import Servant.Client.Core.HasClient import Servant.Client.Core.Request import Servant.Client.Core.Response import Servant.Client.Core.RunClient servant-client-core-0.20.2/src/Servant/Client/Core/0000755000000000000000000000000007346545000020167 5ustar0000000000000000servant-client-core-0.20.2/src/Servant/Client/Core/Auth.hs0000644000000000000000000000244407346545000021430 0ustar0000000000000000{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeSynonymInstances #-} -- | Authentication for clients module Servant.Client.Core.Auth ( AuthClientData, AuthenticatedRequest (..), mkAuthenticatedRequest, ) where import Data.Kind (Type) import Servant.Client.Core.Request (Request) -- | For a resource protected by authentication (e.g. AuthProtect), we need -- to provide the client with some data used to add authentication data -- to a request -- -- NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE type family AuthClientData a :: Type -- | For better type inference and to avoid usage of a data family, we newtype -- wrap the combination of some 'AuthClientData' and a function to add authentication -- data to a request -- -- NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE newtype AuthenticatedRequest a = AuthenticatedRequest { unAuthReq :: (AuthClientData a, AuthClientData a -> Request -> Request) } -- | Handy helper to avoid wrapping datatypes in tuples everywhere. -- -- NOTE: THIS API IS EXPERIMENTAL AND SUBJECT TO CHANGE mkAuthenticatedRequest :: AuthClientData a -> (AuthClientData a -> Request -> Request) -> AuthenticatedRequest a mkAuthenticatedRequest val func = AuthenticatedRequest (val, func) servant-client-core-0.20.2/src/Servant/Client/Core/BaseUrl.hs0000644000000000000000000001234207346545000022062 0ustar0000000000000000{-# LANGUAGE DeriveLift #-} module Servant.Client.Core.BaseUrl ( BaseUrl (..), Scheme (..), showBaseUrl, parseBaseUrl, InvalidBaseUrlException (..), ) where import Control.DeepSeq (NFData (..)) import Control.Monad.Catch (Exception, MonadThrow, throwM) import Data.Aeson (FromJSON (..), FromJSONKey (..), ToJSON (..), ToJSONKey (..)) import Data.Aeson.Types (FromJSONKeyFunction (..), contramapToJSONKeyFunction, withText) import Data.Data (Data) import qualified Data.List as List import qualified Data.Text as T import GHC.Generics import Language.Haskell.TH.Syntax (Lift) import Network.URI hiding (path) import Safe import Text.Read -- | URI scheme to use data Scheme = Http -- ^ http:// | Https -- ^ https:// deriving (Show, Eq, Ord, Generic, Lift, Data) -- | Simple data type to represent the target of HTTP requests -- for servant's automatically-generated clients. data BaseUrl = BaseUrl { baseUrlScheme :: Scheme -- ^ URI scheme to use , baseUrlHost :: String -- ^ host (eg "haskell.org") , baseUrlPort :: Int -- ^ port (eg 80) , baseUrlPath :: String -- ^ path (eg "/a/b/c") } deriving (Show, Ord, Generic, Lift, Data) -- TODO: Ord is more precise than Eq -- TODO: Add Hashable instance? -- instance NFData BaseUrl where rnf (BaseUrl a b c d) = a `seq` rnf b `seq` rnf c `seq` rnf d instance Eq BaseUrl where BaseUrl a b c path == BaseUrl a' b' c' path' = a == a' && b == b' && c == c' && s path == s path' where s ('/':x) = x s x = x -- | >>> traverse_ (LBS8.putStrLn . encode) (parseBaseUrl "api.example.com" :: [BaseUrl]) -- "http://api.example.com" instance ToJSON BaseUrl where toJSON = toJSON . showBaseUrl toEncoding = toEncoding . showBaseUrl -- | >>> parseBaseUrl "api.example.com" >>= decode . encode :: Maybe BaseUrl -- Just (BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""}) instance FromJSON BaseUrl where parseJSON = withText "BaseUrl" $ \t -> case parseBaseUrl (T.unpack t) of Just u -> return u Nothing -> fail $ "Invalid base url: " ++ T.unpack t -- | >>> :{ -- traverse_ (LBS8.putStrLn . encode) $ do -- u1 <- parseBaseUrl "api.example.com" :: [BaseUrl] -- u2 <- parseBaseUrl "example.com" :: [BaseUrl] -- return $ Map.fromList [(u1, 'x'), (u2, 'y')] -- :} -- {"http://api.example.com":"x","http://example.com":"y"} instance ToJSONKey BaseUrl where toJSONKey = contramapToJSONKeyFunction showBaseUrl toJSONKey instance FromJSONKey BaseUrl where fromJSONKey = FromJSONKeyTextParser $ \t -> case parseBaseUrl (T.unpack t) of Just u -> return u Nothing -> fail $ "Invalid base url: " ++ T.unpack t -- | >>> showBaseUrl <$> parseBaseUrl "api.example.com" -- "http://api.example.com" showBaseUrl :: BaseUrl -> String showBaseUrl (BaseUrl urlscheme host port path) = schemeString ++ "//" ++ host ++ (portString path) where a b = if "/" `List.isPrefixOf` b || null b then a ++ b else a ++ '/':b schemeString = case urlscheme of Http -> "http:" Https -> "https:" portString = case (urlscheme, port) of (Http, 80) -> "" (Https, 443) -> "" _ -> ":" ++ show port newtype InvalidBaseUrlException = InvalidBaseUrlException String deriving (Show) instance Exception InvalidBaseUrlException -- | -- -- >>> parseBaseUrl "api.example.com" -- BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""} -- -- /Note:/ trailing slash is removed -- -- >>> parseBaseUrl "api.example.com/" -- BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""} -- -- >>> parseBaseUrl "api.example.com/dir/" -- BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = "/dir"} -- parseBaseUrl :: MonadThrow m => String -> m BaseUrl parseBaseUrl s = case parseURI (removeTrailingSlash s) of -- This is a rather hacky implementation and should be replaced with something -- implemented in attoparsec (which is already a dependency anyhow (via aeson)). Just (URI "http:" (Just (URIAuth "" host (':' : (readMaybe -> Just port)))) path "" "") -> return (BaseUrl Http host port path) Just (URI "http:" (Just (URIAuth "" host "")) path "" "") -> return (BaseUrl Http host 80 path) Just (URI "https:" (Just (URIAuth "" host (':' : (readMaybe -> Just port)))) path "" "") -> return (BaseUrl Https host port path) Just (URI "https:" (Just (URIAuth "" host "")) path "" "") -> return (BaseUrl Https host 443 path) _ -> if "://" `List.isInfixOf` s then throwM (InvalidBaseUrlException $ "Invalid base URL: " ++ s) else parseBaseUrl ("http://" ++ s) where removeTrailingSlash str = case lastMay str of Just '/' -> init str _ -> str -- $setup -- -- >>> import Data.Aeson -- >>> import Data.Foldable (traverse_) -- >>> import qualified Data.ByteString.Lazy.Char8 as LBS8 -- >>> import qualified Data.Map.Strict as Map servant-client-core-0.20.2/src/Servant/Client/Core/BasicAuth.hs0000644000000000000000000000143607346545000022372 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeSynonymInstances #-} -- | Basic Authentication for clients module Servant.Client.Core.BasicAuth ( basicAuthReq, ) where import Data.ByteString.Base64 (encode) import Data.Text.Encoding (decodeUtf8) import Servant.API.BasicAuth (BasicAuthData (BasicAuthData)) import Servant.Client.Core.Request (Request, addHeader) -- | Authenticate a request using Basic Authentication basicAuthReq :: BasicAuthData -> Request -> Request basicAuthReq (BasicAuthData user pass) req = let authText = decodeUtf8 ("Basic " <> encode (user <> ":" <> pass)) in addHeader "Authorization" authText req servant-client-core-0.20.2/src/Servant/Client/Core/ClientError.hs0000644000000000000000000000650007346545000022754 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Servant.Client.Core.ClientError ( ClientError (..), ) where import Prelude () import Prelude.Compat import Control.DeepSeq (NFData (..)) import Control.Exception (SomeException (..)) import Control.Monad.Catch (Exception) import qualified Data.ByteString as BS import Data.Text (Text) import Data.Typeable (Typeable, typeOf) import GHC.Generics (Generic) import Network.HTTP.Media (MediaType) import Network.HTTP.Types () import Servant.Client.Core.BaseUrl import Servant.Client.Core.Internal (mediaTypeRnf) import Servant.Client.Core.Request import Servant.Client.Core.Response -- | A type representing possible errors in a request -- -- Note that this type substantially changed in 0.12. data ClientError = -- | The server returned an error response including the -- failing request. 'requestPath' includes the 'BaseUrl' and the -- path of the request. FailureResponse (RequestF () (BaseUrl, BS.ByteString)) Response -- | The body could not be decoded at the expected type | DecodeFailure Text Response -- | The content-type of the response is not supported | UnsupportedContentType MediaType Response -- | The content-type header is invalid | InvalidContentTypeHeader Response -- | There was a connection error, and no response was received | ConnectionError SomeException deriving (Show, Generic, Typeable) instance Eq ClientError where FailureResponse req res == FailureResponse req' res' = req == req' && res == res' DecodeFailure t r == DecodeFailure t' r' = t == t' && r == r' UnsupportedContentType mt r == UnsupportedContentType mt' r' = mt == mt' && r == r' InvalidContentTypeHeader r == InvalidContentTypeHeader r' = r == r' ConnectionError exc == ConnectionError exc' = eqSomeException exc exc' where -- returns true, if type of exception is the same eqSomeException (SomeException a) (SomeException b) = typeOf a == typeOf b -- prevent wild card blindness FailureResponse {} == _ = False DecodeFailure {} == _ = False UnsupportedContentType {} == _ = False InvalidContentTypeHeader {} == _ = False ConnectionError {} == _ = False instance Exception ClientError -- | Note: an exception in 'ConnectionError' might not be evaluated fully, -- We only 'rnf' its 'show'ed value. instance NFData ClientError where rnf (FailureResponse req res) = rnf req `seq` rnf res rnf (DecodeFailure err res) = rnf err `seq` rnf res rnf (UnsupportedContentType mt' res) = mediaTypeRnf mt' `seq` rnf res rnf (InvalidContentTypeHeader res) = rnf res rnf (ConnectionError err) = err `seq` rnf (show err) servant-client-core-0.20.2/src/Servant/Client/Core/HasClient.hs0000644000000000000000000011176707346545000022412 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -Wno-missing-methods #-} module Servant.Client.Core.HasClient ( clientIn, HasClient (..), EmptyClient (..), AsClientT, (//), (/:), foldMapUnion, matchUnion ) where import Prelude () import Prelude.Compat import Control.Arrow (left, (+++)) import Control.Monad (unless) import qualified Data.ByteString.Lazy as BL import Data.Either (partitionEithers) import Data.Constraint (Dict(..)) import Data.Foldable (toList) import Data.Kind (Type) import qualified Data.List as List import Data.Sequence (fromList) import qualified Data.Text as T import Data.Text.Encoding (encodeUtf8) import Network.HTTP.Media (MediaType, matches, parseAccept) import qualified Network.HTTP.Media as Media import qualified Data.Sequence as Seq import Data.SOP.BasicFunctors (I (I), (:.:) (Comp)) import Data.SOP.Constraint (All) import Data.SOP.NP (NP (..), cpure_NP) import Data.SOP.NS (NS (S)) import Data.String (fromString) import Data.Text (Text, pack) import Data.Proxy (Proxy (Proxy)) import GHC.TypeLits (KnownNat, KnownSymbol, TypeError, symbolVal) import Network.HTTP.Types (Status) import qualified Network.HTTP.Types as H import Servant.API ((:<|>) ((:<|>)), (:>), BuildHeadersTo (..), EmptyAPI, FromSourceIO (..), IsSecure, MimeUnrender (mimeUnrender), NoContentVerb, ReflectMethod (..), StreamBody', Verb, getResponse, AuthProtect, BasicAuth, BasicAuthData, Capture', CaptureAll, DeepQuery, Description, Fragment, FramingRender (..), FramingUnrender (..), Header', Headers (..), HttpVersion, MimeRender (mimeRender), NoContent (NoContent), QueryFlag, QueryParam', QueryParams, QueryString, Raw, RawM, RemoteHost, ReqBody', SBoolI, Stream, Summary, ToHttpApiData, ToSourceIO (..), Vault, WithNamedContext, WithResource, WithStatus (..), contentType, getHeadersHList, toEncodedUrlPiece, NamedRoutes) import Servant.API.Generic (GenericMode(..), ToServant, ToServantApi , GenericServant, toServant, fromServant) import Servant.API.ContentTypes (contentTypes, AllMime (allMime), AllMimeUnrender (allMimeUnrender)) import Servant.API.QueryString (ToDeepQuery(..), generateDeepParam) import Servant.API.Status (statusFromNat) import Servant.API.TypeLevel (FragmentUnique, AtMostOneFragment) import Servant.API.Modifiers (FoldRequired, RequiredArgument, foldRequiredArgument) import Servant.API.TypeErrors import Servant.API.UVerb (HasStatus, HasStatuses (Statuses, statuses), UVerb, Union, Unique, inject, statusOf, foldMapUnion, matchUnion) import Servant.Client.Core.Auth import Servant.Client.Core.BasicAuth import Servant.Client.Core.ClientError import Servant.Client.Core.Request import Servant.Client.Core.Response import Servant.Client.Core.RunClient -- * Accessing APIs as a Client -- | 'clientIn' allows you to produce operations to query an API from a client -- within a 'RunClient' monad. -- -- > type MyApi = "books" :> Get '[JSON] [Book] -- GET /books -- > :<|> "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book -- POST /books -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > clientM :: Proxy ClientM -- > clientM = Proxy -- > -- > getAllBooks :: ClientM [Book] -- > postNewBook :: Book -> ClientM Book -- > (getAllBooks :<|> postNewBook) = myApi `clientIn` clientM clientIn :: HasClient m api => Proxy api -> Proxy m -> Client m api clientIn p pm = clientWithRoute pm p defaultRequest -- | This class lets us define how each API combinator influences the creation -- of an HTTP request. -- -- Unless you are writing a new backend for @servant-client-core@ or new -- combinators that you want to support client-generation, you can ignore this -- class. class RunClient m => HasClient m api where type Client (m :: Type -> Type) (api :: Type) :: Type clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api hoistClientMonad :: Proxy m -> Proxy api -> (forall x. mon x -> mon' x) -> Client mon api -> Client mon' api -- | A client querying function for @a ':<|>' b@ will actually hand you -- one function for querying @a@ and another one for querying @b@, -- stitching them together with ':<|>', which really is just like a pair. -- -- > type MyApi = "books" :> Get '[JSON] [Book] -- GET /books -- > :<|> "books" :> ReqBody '[JSON] Book :> Post Book -- POST /books -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > getAllBooks :: ClientM [Book] -- > postNewBook :: Book -> ClientM Book -- > (getAllBooks :<|> postNewBook) = client myApi instance (HasClient m a, HasClient m b) => HasClient m (a :<|> b) where type Client m (a :<|> b) = Client m a :<|> Client m b clientWithRoute pm Proxy req = clientWithRoute pm (Proxy :: Proxy a) req :<|> clientWithRoute pm (Proxy :: Proxy b) req hoistClientMonad pm _ f (ca :<|> cb) = hoistClientMonad pm (Proxy :: Proxy a) f ca :<|> hoistClientMonad pm (Proxy :: Proxy b) f cb -- | Singleton type representing a client for an empty API. data EmptyClient = EmptyClient deriving (Eq, Show, Bounded, Enum) -- | The client for 'EmptyAPI' is simply 'EmptyClient'. -- -- > type MyAPI = "books" :> Get '[JSON] [Book] -- GET /books -- > :<|> "nothing" :> EmptyAPI -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > getAllBooks :: ClientM [Book] -- > (getAllBooks :<|> EmptyClient) = client myApi instance RunClient m => HasClient m EmptyAPI where type Client m EmptyAPI = EmptyClient clientWithRoute _pm Proxy _ = EmptyClient hoistClientMonad _ _ _ EmptyClient = EmptyClient -- | If you use a 'Capture' in one of your endpoints in your API, -- the corresponding querying function will automatically take -- an additional argument of the type specified by your 'Capture'. -- That function will take care of inserting a textual representation -- of this value at the right place in the request path. -- -- You can control how values for this type are turned into -- text by specifying a 'ToHttpApiData' instance for your type. -- -- Example: -- -- > type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > getBook :: Text -> ClientM Book -- > getBook = client myApi -- > -- then you can just use "getBook" to query that endpoint instance (ToHttpApiData a, HasClient m api) => HasClient m (Capture' mods capture a :> api) where type Client m (Capture' mods capture a :> api) = a -> Client m api clientWithRoute pm Proxy req val = clientWithRoute pm (Proxy :: Proxy api) (appendToPath p req) where p = toEncodedUrlPiece val hoistClientMonad pm _ f cl = \a -> hoistClientMonad pm (Proxy :: Proxy api) f (cl a) -- | If you use a 'CaptureAll' in one of your endpoints in your API, -- the corresponding querying function will automatically take an -- additional argument of a list of the type specified by your -- 'CaptureAll'. That function will take care of inserting a textual -- representation of this value at the right place in the request -- path. -- -- You can control how these values are turned into text by specifying -- a 'ToHttpApiData' instance of your type. -- -- Example: -- -- > type MyAPI = "src" :> CaptureAll Text -> Get '[JSON] SourceFile -- > -- > myApi :: Proxy -- > myApi = Proxy -- -- > getSourceFile :: [Text] -> ClientM SourceFile -- > getSourceFile = client myApi -- > -- then you can use "getSourceFile" to query that endpoint instance (ToHttpApiData a, HasClient m sublayout) => HasClient m (CaptureAll capture a :> sublayout) where type Client m (CaptureAll capture a :> sublayout) = [a] -> Client m sublayout clientWithRoute pm Proxy req vals = clientWithRoute pm (Proxy :: Proxy sublayout) (List.foldl' (flip appendToPath) req ps) where ps = map toEncodedUrlPiece vals hoistClientMonad pm _ f cl = \as -> hoistClientMonad pm (Proxy :: Proxy sublayout) f (cl as) instance {-# OVERLAPPABLE #-} -- Note [Non-Empty Content Types] ( RunClient m, MimeUnrender ct a, ReflectMethod method, cts' ~ (ct ': cts) , KnownNat status ) => HasClient m (Verb method status cts' a) where type Client m (Verb method status cts' a) = m a clientWithRoute _pm Proxy req = do response <- runRequestAcceptStatus (Just [status]) req { requestAccept = fromList $ toList accept , requestMethod = method } response `decodedAs` (Proxy :: Proxy ct) where accept = contentTypes (Proxy :: Proxy ct) method = reflectMethod (Proxy :: Proxy method) status = statusFromNat (Proxy :: Proxy status) hoistClientMonad _ _ f ma = f ma instance {-# OVERLAPPING #-} ( RunClient m, ReflectMethod method, KnownNat status ) => HasClient m (Verb method status cts NoContent) where type Client m (Verb method status cts NoContent) = m NoContent clientWithRoute _pm Proxy req = do _response <- runRequestAcceptStatus (Just [status]) req { requestMethod = method } return NoContent where method = reflectMethod (Proxy :: Proxy method) status = statusFromNat (Proxy :: Proxy status) hoistClientMonad _ _ f ma = f ma instance (RunClient m, ReflectMethod method) => HasClient m (NoContentVerb method) where type Client m (NoContentVerb method) = m NoContent clientWithRoute _pm Proxy req = do _response <- runRequest req { requestMethod = method } return NoContent where method = reflectMethod (Proxy :: Proxy method) hoistClientMonad _ _ f ma = f ma instance {-# OVERLAPPING #-} -- Note [Non-Empty Content Types] ( RunClient m, MimeUnrender ct a, BuildHeadersTo ls, KnownNat status , ReflectMethod method, cts' ~ (ct ': cts) ) => HasClient m (Verb method status cts' (Headers ls a)) where type Client m (Verb method status cts' (Headers ls a)) = m (Headers ls a) clientWithRoute _pm Proxy req = do response <- runRequestAcceptStatus (Just [status]) req { requestMethod = method , requestAccept = fromList $ toList accept } val <- response `decodedAs` (Proxy :: Proxy ct) return $ Headers { getResponse = val , getHeadersHList = buildHeadersTo . toList $ responseHeaders response } where method = reflectMethod (Proxy :: Proxy method) accept = contentTypes (Proxy :: Proxy ct) status = statusFromNat (Proxy :: Proxy status) hoistClientMonad _ _ f ma = f ma instance {-# OVERLAPPING #-} ( RunClient m, BuildHeadersTo ls, ReflectMethod method, KnownNat status ) => HasClient m (Verb method status cts (Headers ls NoContent)) where type Client m (Verb method status cts (Headers ls NoContent)) = m (Headers ls NoContent) clientWithRoute _pm Proxy req = do response <- runRequestAcceptStatus (Just [status]) req { requestMethod = method } return $ Headers { getResponse = NoContent , getHeadersHList = buildHeadersTo . toList $ responseHeaders response } where method = reflectMethod (Proxy :: Proxy method) status = statusFromNat (Proxy :: Proxy status) hoistClientMonad _ _ f ma = f ma data ClientParseError = ClientParseError MediaType String | ClientStatusMismatch | ClientNoMatchingStatus deriving (Eq, Show) class UnrenderResponse (cts :: [Type]) (a :: Type) where unrenderResponse :: Seq.Seq H.Header -> BL.ByteString -> Proxy cts -> [Either (MediaType, String) a] instance {-# OVERLAPPABLE #-} AllMimeUnrender cts a => UnrenderResponse cts a where unrenderResponse _ body = map parse . allMimeUnrender where parse (mediaType, parser) = left ((,) mediaType) (parser body) instance {-# OVERLAPPING #-} forall cts a h . (UnrenderResponse cts a, BuildHeadersTo h) => UnrenderResponse cts (Headers h a) where unrenderResponse hs body = (map . fmap) setHeaders . unrenderResponse hs body where setHeaders :: a -> Headers h a setHeaders x = Headers x (buildHeadersTo (toList hs)) instance {-# OVERLAPPING #-} UnrenderResponse cts a => UnrenderResponse cts (WithStatus n a) where unrenderResponse hs body = (map . fmap) WithStatus . unrenderResponse hs body instance {-# OVERLAPPING #-} ( RunClient m, contentTypes ~ (contentType ': otherContentTypes), -- ('otherContentTypes' should be '_', but even -XPartialTypeSignatures does not seem -- allow this in instance types as of 8.8.3.) as ~ (a ': as'), AllMime contentTypes, ReflectMethod method, All (UnrenderResponse contentTypes) as, All HasStatus as, HasStatuses as', Unique (Statuses as) ) => HasClient m (UVerb method contentTypes as) where type Client m (UVerb method contentTypes as) = m (Union as) clientWithRoute _ _ request = do let accept = Seq.fromList . allMime $ Proxy @contentTypes -- offering to accept all mime types listed in the api gives best compatibility. eg., -- we might not own the server implementation, and the server may choose to support -- only part of the api. method = reflectMethod $ Proxy @method acceptStatus = statuses (Proxy @as) response <- runRequestAcceptStatus (Just acceptStatus) request {requestMethod = method, requestAccept = accept} responseContentType <- checkContentTypeHeader response unless (any (matches responseContentType) accept) $ do throwClientError $ UnsupportedContentType responseContentType response let status = responseStatusCode response body = responseBody response headers = responseHeaders response res = tryParsers status $ mimeUnrenders (Proxy @contentTypes) headers body case res of Left errors -> throwClientError $ DecodeFailure (T.pack (show errors)) response Right x -> return x where -- | Given a list of parsers of 'mkres', returns the first one that succeeds and all the -- failures it encountered along the way -- TODO; better name, rewrite haddocs. tryParsers :: forall xs. All HasStatus xs => Status -> NP ([] :.: Either (MediaType, String)) xs -> Either [ClientParseError] (Union xs) tryParsers _ Nil = Left [ClientNoMatchingStatus] tryParsers status (Comp x :* xs) | status == statusOf (Comp x) = case partitionEithers x of (err', []) -> (map (uncurry ClientParseError) err' ++) +++ S $ tryParsers status xs (_, (res : _)) -> Right . inject . I $ res | otherwise = -- no reason to parse in the first place. This ain't the one we're looking for (ClientStatusMismatch :) +++ S $ tryParsers status xs -- | Given a list of types, parses the given response body as each type mimeUnrenders :: forall cts xs. All (UnrenderResponse cts) xs => Proxy cts -> Seq.Seq H.Header -> BL.ByteString -> NP ([] :.: Either (MediaType, String)) xs mimeUnrenders ctp headers body = cpure_NP (Proxy @(UnrenderResponse cts)) (Comp . unrenderResponse headers body $ ctp) hoistClientMonad _ _ nt s = nt s instance {-# OVERLAPPABLE #-} ( RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method, FramingUnrender framing, FromSourceIO chunk a ) => HasClient m (Stream method status framing ct a) where type Client m (Stream method status framing ct a) = m a hoistClientMonad _ _ f ma = f ma clientWithRoute _pm Proxy req = withStreamingRequest req' $ \gres -> do let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk framingUnrender' = framingUnrender (Proxy :: Proxy framing) mimeUnrender' fromSourceIO $ framingUnrender' $ responseBody gres where req' = req { requestAccept = fromList [contentType (Proxy :: Proxy ct)] , requestMethod = reflectMethod (Proxy :: Proxy method) } instance {-# OVERLAPPING #-} ( RunStreamingClient m, MimeUnrender ct chunk, ReflectMethod method, FramingUnrender framing, FromSourceIO chunk a, BuildHeadersTo hs ) => HasClient m (Stream method status framing ct (Headers hs a)) where type Client m (Stream method status framing ct (Headers hs a)) = m (Headers hs a) hoistClientMonad _ _ f ma = f ma clientWithRoute _pm Proxy req = withStreamingRequest req' $ \gres -> do let mimeUnrender' = mimeUnrender (Proxy :: Proxy ct) :: BL.ByteString -> Either String chunk framingUnrender' = framingUnrender (Proxy :: Proxy framing) mimeUnrender' val <- fromSourceIO $ framingUnrender' $ responseBody gres return $ Headers { getResponse = val , getHeadersHList = buildHeadersTo . toList $ responseHeaders gres } where req' = req { requestAccept = fromList [contentType (Proxy :: Proxy ct)] , requestMethod = reflectMethod (Proxy :: Proxy method) } -- | If you use a 'Header' in one of your endpoints in your API, -- the corresponding querying function will automatically take -- an additional argument of the type specified by your 'Header', -- wrapped in Maybe. -- -- That function will take care of encoding this argument as Text -- in the request headers. -- -- All you need is for your type to have a 'ToHttpApiData' instance. -- -- Example: -- -- > newtype Referer = Referer { referrer :: Text } -- > deriving (Eq, Show, Generic, ToHttpApiData) -- > -- > -- GET /view-my-referer -- > type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > viewReferer :: Maybe Referer -> ClientM Book -- > viewReferer = client myApi -- > -- then you can just use "viewRefer" to query that endpoint -- > -- specifying Nothing or e.g Just "http://haskell.org/" as arguments instance (KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m (Header' mods sym a :> api) where type Client m (Header' mods sym a :> api) = RequiredArgument mods a -> Client m api clientWithRoute pm Proxy req mval = clientWithRoute pm (Proxy :: Proxy api) $ foldRequiredArgument (Proxy :: Proxy mods) add (maybe req add) mval where hname = fromString $ symbolVal (Proxy :: Proxy sym) add :: a -> Request add value = addHeader hname value req hoistClientMonad pm _ f cl = \arg -> hoistClientMonad pm (Proxy :: Proxy api) f (cl arg) -- | Using a 'HttpVersion' combinator in your API doesn't affect the client -- functions. instance HasClient m api => HasClient m (HttpVersion :> api) where type Client m (HttpVersion :> api) = Client m api clientWithRoute pm Proxy = clientWithRoute pm (Proxy :: Proxy api) hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl -- | Ignore @'Summary'@ in client functions. instance HasClient m api => HasClient m (Summary desc :> api) where type Client m (Summary desc :> api) = Client m api clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api) hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl -- | Ignore @'Description'@ in client functions. instance HasClient m api => HasClient m (Description desc :> api) where type Client m (Description desc :> api) = Client m api clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api) hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl -- | If you use a 'QueryParam' in one of your endpoints in your API, -- the corresponding querying function will automatically take -- an additional argument of the type specified by your 'QueryParam', -- enclosed in Maybe. -- -- If you give Nothing, nothing will be added to the query string. -- -- If you give a non-'Nothing' value, this function will take care -- of inserting a textual representation of this value in the query string. -- -- You can control how values for your type are turned into -- text by specifying a 'ToHttpApiData' instance for your type. -- -- Example: -- -- > type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book] -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > getBooksBy :: Maybe Text -> ClientM [Book] -- > getBooksBy = client myApi -- > -- then you can just use "getBooksBy" to query that endpoint. -- > -- 'getBooksBy Nothing' for all books -- > -- 'getBooksBy (Just "Isaac Asimov")' to get all books by Isaac Asimov instance (KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m (QueryParam' mods sym a :> api) where type Client m (QueryParam' mods sym a :> api) = RequiredArgument mods a -> Client m api -- if mparam = Nothing, we don't add it to the query string clientWithRoute pm Proxy req mparam = clientWithRoute pm (Proxy :: Proxy api) $ foldRequiredArgument (Proxy :: Proxy mods) add (maybe req add) mparam where add :: a -> Request add param = appendToQueryString pname (Just $ encodeQueryParamValue param) req pname :: Text pname = pack $ symbolVal (Proxy :: Proxy sym) hoistClientMonad pm _ f cl = \arg -> hoistClientMonad pm (Proxy :: Proxy api) f (cl arg) -- | If you use a 'QueryParams' in one of your endpoints in your API, -- the corresponding querying function will automatically take -- an additional argument, a list of values of the type specified -- by your 'QueryParams'. -- -- If you give an empty list, nothing will be added to the query string. -- -- Otherwise, this function will take care -- of inserting a textual representation of your values in the query string, -- under the same query string parameter name. -- -- You can control how values for your type are turned into -- text by specifying a 'ToHttpApiData' instance for your type. -- -- Example: -- -- > type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book] -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > getBooksBy :: [Text] -> ClientM [Book] -- > getBooksBy = client myApi -- > -- then you can just use "getBooksBy" to query that endpoint. -- > -- 'getBooksBy []' for all books -- > -- 'getBooksBy ["Isaac Asimov", "Robert A. Heinlein"]' -- > -- to get all books by Asimov and Heinlein instance (KnownSymbol sym, ToHttpApiData a, HasClient m api) => HasClient m (QueryParams sym a :> api) where type Client m (QueryParams sym a :> api) = [a] -> Client m api clientWithRoute pm Proxy req paramlist = clientWithRoute pm (Proxy :: Proxy api) (List.foldl' (\ req' -> maybe req' (flip (appendToQueryString pname) req' . Just)) req paramlist' ) where pname = pack $ symbolVal (Proxy :: Proxy sym) paramlist' = map (Just . encodeQueryParamValue) paramlist hoistClientMonad pm _ f cl = \as -> hoistClientMonad pm (Proxy :: Proxy api) f (cl as) -- | If you use a 'QueryFlag' in one of your endpoints in your API, -- the corresponding querying function will automatically take -- an additional 'Bool' argument. -- -- If you give 'False', nothing will be added to the query string. -- -- Otherwise, this function will insert a value-less query string -- parameter under the name associated to your 'QueryFlag'. -- -- Example: -- -- > type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book] -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > getBooks :: Bool -> ClientM [Book] -- > getBooks = client myApi -- > -- then you can just use "getBooks" to query that endpoint. -- > -- 'getBooksBy False' for all books -- > -- 'getBooksBy True' to only get _already published_ books instance (KnownSymbol sym, HasClient m api) => HasClient m (QueryFlag sym :> api) where type Client m (QueryFlag sym :> api) = Bool -> Client m api clientWithRoute pm Proxy req flag = clientWithRoute pm (Proxy :: Proxy api) (if flag then appendToQueryString paramname Nothing req else req ) where paramname = pack $ symbolVal (Proxy :: Proxy sym) hoistClientMonad pm _ f cl = \b -> hoistClientMonad pm (Proxy :: Proxy api) f (cl b) instance (HasClient m api) => HasClient m (QueryString :> api) where type Client m (QueryString :> api) = H.Query -> Client m api clientWithRoute pm Proxy req query = clientWithRoute pm (Proxy :: Proxy api) (setQueryString query req) hoistClientMonad pm _ f cl = \b -> hoistClientMonad pm (Proxy :: Proxy api) f (cl b) instance (KnownSymbol sym, ToDeepQuery a, HasClient m api) => HasClient m (DeepQuery sym a :> api) where type Client m (DeepQuery sym a :> api) = a -> Client m api clientWithRoute pm Proxy req deepObject = let params = toDeepQuery deepObject withParams = List.foldl' addDeepParam req params addDeepParam r' kv = let (k, textV) = generateDeepParam paramname kv in appendToQueryString k (encodeUtf8 <$> textV) r' paramname = pack $ symbolVal (Proxy :: Proxy sym) in clientWithRoute pm (Proxy :: Proxy api) withParams hoistClientMonad pm _ f cl = \b -> hoistClientMonad pm (Proxy :: Proxy api) f (cl b) -- | Pick a 'Method' and specify where the server you want to query is. You get -- back the full `Response`. instance RunClient m => HasClient m Raw where type Client m Raw = H.Method -> m Response clientWithRoute :: Proxy m -> Proxy Raw -> Request -> Client m Raw clientWithRoute _pm Proxy req httpMethod = do runRequest req { requestMethod = httpMethod } hoistClientMonad _ _ f cl = \meth -> f (cl meth) instance RunClient m => HasClient m RawM where type Client m RawM = H.Method -> m Response clientWithRoute :: Proxy m -> Proxy RawM -> Request -> Client m RawM clientWithRoute _pm Proxy req httpMethod = do runRequest req { requestMethod = httpMethod } hoistClientMonad _ _ f cl = \meth -> f (cl meth) -- | If you use a 'ReqBody' in one of your endpoints in your API, -- the corresponding querying function will automatically take -- an additional argument of the type specified by your 'ReqBody'. -- That function will take care of encoding this argument as JSON and -- of using it as the request body. -- -- All you need is for your type to have a 'ToJSON' instance. -- -- Example: -- -- > type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > addBook :: Book -> ClientM Book -- > addBook = client myApi -- > -- then you can just use "addBook" to query that endpoint instance (MimeRender ct a, HasClient m api) => HasClient m (ReqBody' mods (ct ': cts) a :> api) where type Client m (ReqBody' mods (ct ': cts) a :> api) = a -> Client m api clientWithRoute pm Proxy req body = clientWithRoute pm (Proxy :: Proxy api) (let ctProxy = Proxy :: Proxy ct in setRequestBodyLBS (mimeRender ctProxy body) -- We use first contentType from the Accept list (contentType ctProxy) req ) hoistClientMonad pm _ f cl = \a -> hoistClientMonad pm (Proxy :: Proxy api) f (cl a) instance ( HasClient m api, MimeRender ctype chunk, FramingRender framing, ToSourceIO chunk a ) => HasClient m (StreamBody' mods framing ctype a :> api) where type Client m (StreamBody' mods framing ctype a :> api) = a -> Client m api hoistClientMonad pm _ f cl = \a -> hoistClientMonad pm (Proxy :: Proxy api) f (cl a) clientWithRoute pm Proxy req body = clientWithRoute pm (Proxy :: Proxy api) $ setRequestBody (RequestBodySource sourceIO) (contentType ctypeP) req where ctypeP = Proxy :: Proxy ctype framingP = Proxy :: Proxy framing sourceIO = framingRender framingP (mimeRender ctypeP :: chunk -> BL.ByteString) (toSourceIO body) -- | Make the querying function append @path@ to the request path. instance (KnownSymbol path, HasClient m api) => HasClient m (path :> api) where type Client m (path :> api) = Client m api clientWithRoute pm Proxy req = clientWithRoute pm (Proxy :: Proxy api) (appendToPath p req) where p = toEncodedUrlPiece $ pack $ symbolVal (Proxy :: Proxy path) hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl instance HasClient m api => HasClient m (Vault :> api) where type Client m (Vault :> api) = Client m api clientWithRoute pm Proxy req = clientWithRoute pm (Proxy :: Proxy api) req hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl instance HasClient m api => HasClient m (RemoteHost :> api) where type Client m (RemoteHost :> api) = Client m api clientWithRoute pm Proxy req = clientWithRoute pm (Proxy :: Proxy api) req hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl instance HasClient m api => HasClient m (IsSecure :> api) where type Client m (IsSecure :> api) = Client m api clientWithRoute pm Proxy req = clientWithRoute pm (Proxy :: Proxy api) req hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl instance HasClient m subapi => HasClient m (WithNamedContext name context subapi) where type Client m (WithNamedContext name context subapi) = Client m subapi clientWithRoute pm Proxy = clientWithRoute pm (Proxy :: Proxy subapi) hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy subapi) f cl instance HasClient m subapi => HasClient m (WithResource res :> subapi) where type Client m (WithResource res :> subapi) = Client m subapi clientWithRoute pm Proxy = clientWithRoute pm (Proxy :: Proxy subapi) hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy subapi) f cl instance ( HasClient m api ) => HasClient m (AuthProtect tag :> api) where type Client m (AuthProtect tag :> api) = AuthenticatedRequest (AuthProtect tag) -> Client m api clientWithRoute pm Proxy req (AuthenticatedRequest (val,func)) = clientWithRoute pm (Proxy :: Proxy api) (func val req) hoistClientMonad pm _ f cl = \authreq -> hoistClientMonad pm (Proxy :: Proxy api) f (cl authreq) -- | Ignore @'Fragment'@ in client functions. -- See for more details. -- -- Example: -- -- > type MyApi = "books" :> Fragment Text :> Get '[JSON] [Book] -- > -- > myApi :: Proxy MyApi -- > myApi = Proxy -- > -- > getBooks :: ClientM [Book] -- > getBooks = client myApi -- > -- then you can just use "getBooksBy" to query that endpoint. -- > -- 'getBooks' for all books. instance (AtMostOneFragment api, FragmentUnique (Fragment a :> api), HasClient m api ) => HasClient m (Fragment a :> api) where type Client m (Fragment a :> api) = Client m api clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api) hoistClientMonad pm _ = hoistClientMonad pm (Proxy :: Proxy api) -- * Basic Authentication instance HasClient m api => HasClient m (BasicAuth realm usr :> api) where type Client m (BasicAuth realm usr :> api) = BasicAuthData -> Client m api clientWithRoute pm Proxy req val = clientWithRoute pm (Proxy :: Proxy api) (basicAuthReq val req) hoistClientMonad pm _ f cl = \bauth -> hoistClientMonad pm (Proxy :: Proxy api) f (cl bauth) -- | A type that specifies that an API record contains a client implementation. data AsClientT (m :: Type -> Type) instance GenericMode (AsClientT m) where type AsClientT m :- api = Client m api type GClientConstraints api m = ( GenericServant api (AsClientT m) , Client m (ToServantApi api) ~ ToServant api (AsClientT m) ) class GClient (api :: Type -> Type) m where gClientProof :: Dict (GClientConstraints api m) instance GClientConstraints api m => GClient api m where gClientProof = Dict instance ( forall n. GClient api n , HasClient m (ToServantApi api) , RunClient m , ErrorIfNoGeneric api ) => HasClient m (NamedRoutes api) where type Client m (NamedRoutes api) = api (AsClientT m) clientWithRoute :: Proxy m -> Proxy (NamedRoutes api) -> Request -> Client m (NamedRoutes api) clientWithRoute pm _ request = case gClientProof @api @m of Dict -> fromServant $ clientWithRoute pm (Proxy @(ToServantApi api)) request hoistClientMonad :: forall ma mb. Proxy m -> Proxy (NamedRoutes api) -> (forall x. ma x -> mb x) -> Client ma (NamedRoutes api) -> Client mb (NamedRoutes api) hoistClientMonad _ _ nat clientA = case (gClientProof @api @ma, gClientProof @api @mb) of (Dict, Dict) -> fromServant @api @(AsClientT mb) $ hoistClientMonad @m @(ToServantApi api) @ma @mb Proxy Proxy nat $ toServant @api @(AsClientT ma) clientA infixl 1 // infixl 2 /: -- | Helper to make code using records of clients more readable. -- -- Can be mixed with (/:) for supplying arguments. -- -- Example: -- -- @ -- type Api = NamedRoutes RootApi -- -- data RootApi mode = RootApi -- { subApi :: mode :- NamedRoutes SubApi -- , … -- } deriving Generic -- -- data SubApi mode = SubApi -- { endpoint :: mode :- Get '[JSON] Person -- , … -- } deriving Generic -- -- api :: Proxy API -- api = Proxy -- -- rootClient :: RootApi (AsClientT ClientM) -- rootClient = client api -- -- endpointClient :: ClientM Person -- endpointClient = client \/\/ subApi \/\/ endpoint -- @ (//) :: a -> (a -> b) -> b x // f = f x -- | Convenience function for supplying arguments to client functions when -- working with records of clients. -- -- Intended to be used in conjunction with '(//)'. -- -- Example: -- -- @ -- type Api = NamedRoutes RootApi -- -- data RootApi mode = RootApi -- { subApi :: mode :- Capture "token" String :> NamedRoutes SubApi -- , hello :: mode :- Capture "name" String :> Get '[JSON] String -- , … -- } deriving Generic -- -- data SubApi mode = SubApi -- { endpoint :: mode :- Get '[JSON] Person -- , … -- } deriving Generic -- -- api :: Proxy API -- api = Proxy -- -- rootClient :: RootApi (AsClientT ClientM) -- rootClient = client api -- -- hello :: String -> ClientM String -- hello name = rootClient \/\/ hello \/: name -- -- endpointClient :: ClientM Person -- endpointClient = client \/\/ subApi \/: "foobar123" \/\/ endpoint -- @ (/:) :: (a -> b -> c) -> b -> a -> c (/:) = flip {- Note [Non-Empty Content Types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Rather than have instance (..., cts' ~ (ct ': cts)) => ... cts' ... It may seem to make more sense to have: instance (...) => ... (ct ': cts) ... But this means that if another instance exists that does *not* require non-empty lists, but is otherwise more specific, no instance will be overall more specific. This in turn generally means adding yet another instance (one for empty and one for non-empty lists). -} ------------------------------------------------------------------------------- -- helpers ------------------------------------------------------------------------------- checkContentTypeHeader :: RunClient m => Response -> m MediaType checkContentTypeHeader response = case lookup "Content-Type" $ toList $ responseHeaders response of Nothing -> return $ "application" Media.// "octet-stream" Just t -> case parseAccept t of Nothing -> throwClientError $ InvalidContentTypeHeader response Just t' -> return t' decodedAs :: forall ct a m. (MimeUnrender ct a, RunClient m) => Response -> Proxy ct -> m a decodedAs response ct = do responseContentType <- checkContentTypeHeader response unless (any (matches responseContentType) accept) $ throwClientError $ UnsupportedContentType responseContentType response case mimeUnrender ct $ responseBody response of Left err -> throwClientError $ DecodeFailure (T.pack err) response Right val -> return val where accept = toList $ contentTypes ct ------------------------------------------------------------------------------- -- Custom type errors ------------------------------------------------------------------------------- -- Erroring instance for HasClient' when a combinator is not fully applied instance (RunClient m, TypeError (PartialApplication HasClient arr)) => HasClient m ((arr :: a -> b) :> sub) where type Client m (arr :> sub) = TypeError (PartialApplication HasClient arr) clientWithRoute _ _ _ = error "unreachable" hoistClientMonad _ _ _ _ = error "unreachable" -- Erroring instances for 'HasClient' for unknown API combinators instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceForSub (HasClient m) ty)) => HasClient m (ty :> sub) instance {-# OVERLAPPABLE #-} (RunClient m, TypeError (NoInstanceFor (HasClient m api))) => HasClient m api servant-client-core-0.20.2/src/Servant/Client/Core/Internal.hs0000644000000000000000000000050507346545000022277 0ustar0000000000000000module Servant.Client.Core.Internal where import Control.DeepSeq (rnf) import Network.HTTP.Media (MediaType, mainType, parameters, subType) mediaTypeRnf :: MediaType -> () mediaTypeRnf mt = rnf (mainType mt) `seq` rnf (subType mt) `seq` rnf (parameters mt) servant-client-core-0.20.2/src/Servant/Client/Core/Reexport.hs0000644000000000000000000000137007346545000022334 0ustar0000000000000000-- | This module is a utility for @servant-client-core@ backend writers. It -- contains all the functionality from @servant-client-core@ that should be -- re-exported. module Servant.Client.Core.Reexport ( -- * HasClient HasClient(..) , foldMapUnion , matchUnion , AsClientT , (//) , (/:) -- * Response (for @Raw@) , Response , StreamingResponse , ResponseF(..) -- * Data types , ClientError(..) , EmptyClient(..) -- * BaseUrl , BaseUrl(..) , Scheme(..) , showBaseUrl , parseBaseUrl , InvalidBaseUrlException ) where import Servant.Client.Core.BaseUrl import Servant.Client.Core.HasClient import Servant.Client.Core.Response import Servant.Client.Core.ClientError servant-client-core-0.20.2/src/Servant/Client/Core/Request.hs0000644000000000000000000001542007346545000022155 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Servant.Client.Core.Request ( Request, RequestF (..), RequestBody (..), defaultRequest, -- ** Modifiers addHeader, appendToPath, appendToQueryString, encodeQueryParamValue, setQueryString, setRequestBody, setRequestBodyLBS, ) where import Prelude () import Prelude.Compat import Control.DeepSeq (NFData (..)) import Data.Bifoldable (Bifoldable (..)) import Data.Bifunctor (Bifunctor (..)) import Data.Bitraversable (Bitraversable (..), bifoldMapDefault, bimapDefault) import qualified Data.ByteString as BS import Data.ByteString.Builder (Builder) import qualified Data.ByteString.Builder as Builder import qualified Data.ByteString.Lazy as LBS import qualified Data.Sequence as Seq import Data.Text (Text) import Data.Text.Encoding (encodeUtf8) import Data.Typeable (Typeable) import GHC.Generics (Generic) import Network.HTTP.Media (MediaType) import Network.HTTP.Types (Header, HeaderName, HttpVersion (..), Method, Query, QueryItem, http11, methodGet, urlEncodeBuilder) import Servant.API (ToHttpApiData, toQueryParam, toHeader, SourceIO) import Servant.Client.Core.Internal (mediaTypeRnf) data RequestF body path = Request { requestPath :: path , requestQueryString :: Seq.Seq QueryItem , requestBody :: Maybe (body, MediaType) , requestAccept :: Seq.Seq MediaType , requestHeaders :: Seq.Seq Header , requestHttpVersion :: HttpVersion , requestMethod :: Method } deriving (Generic, Typeable, Eq, Functor, Foldable, Traversable) instance (Show a, Show b) => Show (Servant.Client.Core.Request.RequestF a b) where showsPrec p req = showParen (p >= 11) ( showString "Request {requestPath = " . showsPrec 0 (requestPath req) . showString ", requestQueryString = " . showsPrec 0 (requestQueryString req) . showString ", requestBody = " . showsPrec 0 (requestBody req) . showString ", requestAccept = " . showsPrec 0 (requestAccept req) . showString ", requestHeaders = " . showsPrec 0 (redactSensitiveHeader <$> requestHeaders req) . showString ", requestHttpVersion = " . showsPrec 0 (requestHttpVersion req) . showString ", requestMethod = " . showsPrec 0 (requestMethod req) . showString "}" ) where redactSensitiveHeader :: Header -> Header redactSensitiveHeader ("Authorization", _) = ("Authorization", "") redactSensitiveHeader h = h instance Bifunctor RequestF where bimap = bimapDefault instance Bifoldable RequestF where bifoldMap = bifoldMapDefault instance Bitraversable RequestF where bitraverse f g r = mk <$> traverse (bitraverse f pure) (requestBody r) <*> g (requestPath r) where mk b p = r { requestBody = b, requestPath = p } instance (NFData path, NFData body) => NFData (RequestF body path) where rnf r = rnf (requestPath r) `seq` rnf (requestQueryString r) `seq` rnfB (requestBody r) `seq` rnf (fmap mediaTypeRnf (requestAccept r)) `seq` rnf (requestHeaders r) `seq` requestHttpVersion r `seq` rnf (requestMethod r) where rnfB Nothing = () rnfB (Just (b, mt)) = rnf b `seq` mediaTypeRnf mt type Request = RequestF RequestBody Builder -- | The request body. R replica of the @http-client@ @RequestBody@. data RequestBody = RequestBodyLBS LBS.ByteString | RequestBodyBS BS.ByteString | RequestBodySource (SourceIO LBS.ByteString) deriving (Generic, Typeable) instance Show RequestBody where showsPrec d (RequestBodyLBS lbs) = showParen (d > 10) $ showString "RequestBodyLBS " . showsPrec 11 lbs showsPrec d (RequestBodyBS bs) = showParen (d > 10) $ showString "RequestBodyBS " . showsPrec 11 bs showsPrec d (RequestBodySource _) = showParen (d > 10) $ showString "RequestBodySource " -- A GET request to the top-level path defaultRequest :: Request defaultRequest = Request { requestPath = "" , requestQueryString = Seq.empty , requestBody = Nothing , requestAccept = Seq.empty , requestHeaders = Seq.empty , requestHttpVersion = http11 , requestMethod = methodGet } -- | Append extra path to the request being constructed. -- -- Warning: This function assumes that the path fragment is already URL-encoded. appendToPath :: Builder -> Request -> Request appendToPath p req = req { requestPath = requestPath req <> "/" <> p } -- | Append a query parameter to the request being constructed. -- appendToQueryString :: Text -- ^ query param name -> Maybe BS.ByteString -- ^ query param value -> Request -> Request appendToQueryString pname pvalue req = req { requestQueryString = requestQueryString req Seq.|> (encodeUtf8 pname, pvalue)} setQueryString :: Query -> Request -> Request setQueryString query req = req { requestQueryString = Seq.fromList query } -- | Encode a query parameter value. -- encodeQueryParamValue :: ToHttpApiData a => a -> BS.ByteString encodeQueryParamValue = LBS.toStrict . Builder.toLazyByteString . urlEncodeBuilder True . encodeUtf8 . toQueryParam -- | Add header to the request being constructed. -- addHeader :: ToHttpApiData a => HeaderName -> a -> Request -> Request addHeader name val req = req { requestHeaders = requestHeaders req Seq.|> (name, toHeader val)} -- | Set body and media type of the request being constructed. -- -- The body is set to the given bytestring using the 'RequestBodyLBS' -- constructor. -- -- @since 0.12 -- setRequestBodyLBS :: LBS.ByteString -> MediaType -> Request -> Request setRequestBodyLBS b t req = req { requestBody = Just (RequestBodyLBS b, t) } -- | Set body and media type of the request being constructed. -- -- @since 0.12 -- setRequestBody :: RequestBody -> MediaType -> Request -> Request setRequestBody b t req = req { requestBody = Just (b, t) } servant-client-core-0.20.2/src/Servant/Client/Core/Response.hs0000644000000000000000000000321407346545000022321 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Servant.Client.Core.Response ( Response, StreamingResponse, ResponseF (..), ) where import Prelude () import Prelude.Compat import Control.DeepSeq (NFData (..)) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LBS import qualified Data.Sequence as Seq import Data.Typeable (Typeable) import GHC.Generics (Generic) import Network.HTTP.Types (Header, HttpVersion (..), Status (..)) import Servant.API.Stream (SourceIO) data ResponseF a = Response { responseStatusCode :: Status , responseHeaders :: Seq.Seq Header , responseHttpVersion :: HttpVersion , responseBody :: a } deriving (Eq, Show, Generic, Typeable, Functor, Foldable, Traversable) instance NFData a => NFData (ResponseF a) where rnf (Response sc hs hv body) = rnfStatus sc `seq` rnf hs `seq` rnfHttpVersion hv `seq` rnf body where rnfStatus (Status code msg) = rnf code `seq` rnf msg rnfHttpVersion (HttpVersion _ _) = () -- HttpVersion fields are strict type Response = ResponseF LBS.ByteString type StreamingResponse = ResponseF (SourceIO BS.ByteString) servant-client-core-0.20.2/src/Servant/Client/Core/RunClient.hs0000644000000000000000000000350707346545000022433 0ustar0000000000000000{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -- | Types for possible backends to run client-side `Request` queries module Servant.Client.Core.RunClient ( RunClient (..), runRequest, RunStreamingClient (..), ClientF (..), ) where import Prelude () import Prelude.Compat import Network.HTTP.Types.Status (Status) import Control.Monad.Free (Free (..), liftF) import Servant.Client.Core.ClientError import Servant.Client.Core.Request import Servant.Client.Core.Response class Monad m => RunClient m where -- | How to make a request, with an optional list of status codes to not throw exceptions -- for (default: [200..299]). runRequestAcceptStatus :: Maybe [Status] -> Request -> m Response throwClientError :: ClientError -> m a -- | How to make a request. runRequest :: RunClient m => Request -> m Response runRequest = runRequestAcceptStatus Nothing class RunClient m => RunStreamingClient m where withStreamingRequest :: Request -> (StreamingResponse -> IO a) -> m a ------------------------------------------------------------------------------- -- Free ------------------------------------------------------------------------------- -- | 'ClientF' cannot stream. -- -- Compare to 'RunClient'. data ClientF a = RunRequest Request (Response -> a) | Throw ClientError deriving (Functor) -- TODO: honour the accept-status argument. instance ClientF ~ f => RunClient (Free f) where runRequestAcceptStatus _ req = liftF (RunRequest req id) throwClientError = liftF . Throw servant-client-core-0.20.2/src/Servant/Client/Free.hs0000644000000000000000000000111607346545000020513 0ustar0000000000000000{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} module Servant.Client.Free ( client, ClientF (..), module Servant.Client.Core.Reexport, ) where import Control.Monad.Free import Data.Proxy (Proxy (..)) import Servant.Client.Core import Servant.Client.Core.Reexport import Servant.Client.Core.RunClient client :: HasClient (Free ClientF) api => Proxy api -> Client (Free ClientF) api client api = api `clientIn` (Proxy :: Proxy (Free ClientF)) servant-client-core-0.20.2/src/Servant/Client/Generic.hs0000644000000000000000000000272507346545000021215 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Servant.Client.Generic ( AsClientT, genericClient, genericClientHoist, ) where import Data.Proxy (Proxy (..)) import Servant.API.Generic import Servant.Client.Core import Servant.Client.Core.HasClient (AsClientT) -- | Generate a record of client functions. genericClient :: forall routes m. ( HasClient m (ToServantApi routes) , GenericServant routes (AsClientT m) , Client m (ToServantApi routes) ~ ToServant routes (AsClientT m) ) => routes (AsClientT m) genericClient = fromServant $ clientIn (Proxy :: Proxy (ToServantApi routes)) (Proxy :: Proxy m) -- | 'genericClient' but with 'hoistClientMonad' in between. genericClientHoist :: forall routes m n. ( HasClient m (ToServantApi routes) , GenericServant routes (AsClientT n) , Client n (ToServantApi routes) ~ ToServant routes (AsClientT n) ) => (forall x. m x -> n x) -- ^ natural transformation -> routes (AsClientT n) genericClientHoist nt = fromServant $ hoistClientMonad m api nt $ clientIn api m where m = Proxy :: Proxy m api = Proxy :: Proxy (ToServantApi routes) servant-client-core-0.20.2/test/Servant/Client/Core/Internal/0000755000000000000000000000000007346545000022133 5ustar0000000000000000servant-client-core-0.20.2/test/Servant/Client/Core/Internal/BaseUrlSpec.hs0000644000000000000000000000544007346545000024642 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} module Servant.Client.Core.Internal.BaseUrlSpec (spec) where import Control.DeepSeq import Prelude () import Prelude.Compat import Test.Hspec import Test.QuickCheck import Servant.Client.Core.BaseUrl spec :: Spec spec = do let parse = parseBaseUrl :: String -> Maybe BaseUrl describe "showBaseUrl" $ do it "shows a BaseUrl" $ do showBaseUrl (BaseUrl Http "foo.com" 80 "") `shouldBe` "http://foo.com" it "shows a https BaseUrl" $ do showBaseUrl (BaseUrl Https "foo.com" 443 "") `shouldBe` "https://foo.com" it "shows the path of a BaseUrl" $ do showBaseUrl (BaseUrl Http "foo.com" 80 "api") `shouldBe` "http://foo.com/api" it "shows the path of an https BaseUrl" $ do showBaseUrl (BaseUrl Https "foo.com" 443 "api") `shouldBe` "https://foo.com/api" it "handles leading slashes in path" $ do showBaseUrl (BaseUrl Https "foo.com" 443 "/api") `shouldBe` "https://foo.com/api" describe "httpBaseUrl" $ do it "allows to construct default http BaseUrls" $ do BaseUrl Http "bar" 80 "" `shouldBe` BaseUrl Http "bar" 80 "" describe "parseBaseUrl" $ do it "is total" $ do property $ \ string -> deepseq (fmap show (parse string )) True it "is the inverse of showBaseUrl" $ do property $ \ baseUrl -> counterexample (showBaseUrl baseUrl) $ parse (showBaseUrl baseUrl) === Just baseUrl context "trailing slashes" $ do it "allows trailing slashes" $ do parse "foo.com/" `shouldBe` Just (BaseUrl Http "foo.com" 80 "") it "allows trailing slashes in paths" $ do parse "foo.com/api/" `shouldBe` Just (BaseUrl Http "foo.com" 80 "api") context "urls without scheme" $ do it "assumes http" $ do parse "foo.com" `shouldBe` Just (BaseUrl Http "foo.com" 80 "") it "allows port numbers" $ do parse "foo.com:8080" `shouldBe` Just (BaseUrl Http "foo.com" 8080 "") it "can parse paths" $ do parse "http://foo.com/api" `shouldBe` Just (BaseUrl Http "foo.com" 80 "api") it "rejects ftp urls" $ do parse "ftp://foo.com" `shouldBe` Nothing instance Arbitrary BaseUrl where arbitrary = BaseUrl <$> elements [Http, Https] <*> hostNameGen <*> portGen <*> pathGen where letters = ['a' .. 'z'] ++ ['A' .. 'Z'] -- this does not perfectly mirror the url standard, but I hope it's good -- enough. hostNameGen = do first <- elements letters middle <- listOf1 $ elements (letters ++ ['0' .. '9'] ++ ['.', '-']) last' <- elements letters return (first : middle ++ [last']) portGen = frequency $ (1, return 80) : (1, return 443) : (1, choose (1, 20000)) : [] pathGen = listOf1 . elements $ letters servant-client-core-0.20.2/test/Servant/Client/Core/0000755000000000000000000000000007346545000020357 5ustar0000000000000000servant-client-core-0.20.2/test/Servant/Client/Core/RequestSpec.hs0000644000000000000000000000252607346545000023163 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE OverloadedStrings #-} module Servant.Client.Core.RequestSpec (spec) where import Prelude () import Prelude.Compat import Control.Monad import Data.List (isInfixOf) import Servant.Client.Core.Request import Test.Hspec newtype DataWithRequest = DataWithRequest (RequestF RequestBody ()) deriving Show spec :: Spec spec = do describe "Request" $ do describe "show" $ do it "has parenthesis correctly positioned" $ do let d = DataWithRequest (void defaultRequest) show d `shouldBe` "DataWithRequest (Request {requestPath = ()\ \, requestQueryString = fromList []\ \, requestBody = Nothing\ \, requestAccept = fromList []\ \, requestHeaders = fromList []\ \, requestHttpVersion = HTTP/1.1\ \, requestMethod = \"GET\"})" it "redacts the authorization header" $ do let request = void $ defaultRequest { requestHeaders = pure ("authorization", "secret") } isInfixOf "secret" (show request) `shouldBe` False servant-client-core-0.20.2/test/0000755000000000000000000000000007346545000014627 5ustar0000000000000000servant-client-core-0.20.2/test/Spec.hs0000644000000000000000000000005407346545000016054 0ustar0000000000000000{-# OPTIONS_GHC -F -pgmF hspec-discover #-}