servant-client-core-0.13: Core functionality and class for client function generation for servant APIs

Safe HaskellNone
LanguageHaskell2010

Servant.Client.Core.Reexport

Contents

Description

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.

Synopsis

HasClient

class RunClient m => HasClient m api where Source #

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.

Minimal complete definition

clientWithRoute

Associated Types

type Client (m :: * -> *) (api :: *) :: * Source #

Methods

clientWithRoute :: Proxy m -> Proxy api -> Request -> Client m api Source #

Instances

RunClient m => HasClient m Raw Source #

Pick a Method and specify where the server you want to query is. You get back the full Response.

Associated Types

type Client (m :: * -> *) Raw :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * Raw -> Request -> Client m Raw Source #

RunClient m => HasClient m EmptyAPI Source #

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

Associated Types

type Client (m :: * -> *) EmptyAPI :: * Source #

(HasClient m a, HasClient m b) => HasClient m ((:<|>) a b) Source #

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

Associated Types

type Client (m :: * -> *) (a :<|> b) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * (a :<|> b) -> Request -> Client m (a :<|> b) Source #

HasClient m api => HasClient m ((:>) * (BasicAuth realm usr) api) Source # 

Associated Types

type Client (m :: * -> *) ((* :> BasicAuth realm usr) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> BasicAuth realm usr) api) -> Request -> Client m ((* :> BasicAuth realm usr) api) Source #

HasClient m api => HasClient m ((:>) * (AuthProtect k tag) api) Source # 

Associated Types

type Client (m :: * -> *) ((* :> AuthProtect k tag) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> AuthProtect k tag) api) -> Request -> Client m ((* :> AuthProtect k tag) api) Source #

HasClient m subapi => HasClient m (WithNamedContext name context subapi) Source # 

Associated Types

type Client (m :: * -> *) (WithNamedContext name context subapi) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * (WithNamedContext name context subapi) -> Request -> Client m (WithNamedContext name context subapi) Source #

HasClient m api => HasClient m ((:>) * IsSecure api) Source # 

Associated Types

type Client (m :: * -> *) ((* :> IsSecure) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> IsSecure) api) -> Request -> Client m ((* :> IsSecure) api) Source #

HasClient m api => HasClient m ((:>) * RemoteHost api) Source # 

Associated Types

type Client (m :: * -> *) ((* :> RemoteHost) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> RemoteHost) api) -> Request -> Client m ((* :> RemoteHost) api) Source #

HasClient m api => HasClient m ((:>) * Vault api) Source # 

Associated Types

type Client (m :: * -> *) ((* :> Vault) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> Vault) api) -> Request -> Client m ((* :> Vault) api) Source #

(KnownSymbol path, HasClient m api) => HasClient m ((:>) Symbol path api) Source #

Make the querying function append path to the request path.

Associated Types

type Client (m :: * -> *) ((Symbol :> path) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((Symbol :> path) api) -> Request -> Client m ((Symbol :> path) api) Source #

(MimeRender * ct a, HasClient m api) => HasClient m ((:>) * (ReqBody' mods ((:) * ct cts) a) api) Source #

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

Associated Types

type Client (m :: * -> *) ((* :> ReqBody' mods ((* ': ct) cts) a) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> ReqBody' mods ((* ': ct) cts) a) api) -> Request -> Client m ((* :> ReqBody' mods ((* ': ct) cts) a) api) Source #

(KnownSymbol sym, HasClient m api) => HasClient m ((:>) * (QueryFlag sym) api) Source #

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

Associated Types

type Client (m :: * -> *) ((* :> QueryFlag sym) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> QueryFlag sym) api) -> Request -> Client m ((* :> QueryFlag sym) api) Source #

(KnownSymbol sym, ToHttpApiData a, HasClient m api) => HasClient m ((:>) * (QueryParams sym a) api) Source #

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

Associated Types

type Client (m :: * -> *) ((* :> QueryParams sym a) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> QueryParams sym a) api) -> Request -> Client m ((* :> QueryParams sym a) api) Source #

(KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m ((:>) * (QueryParam' mods sym a) api) Source #

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

Associated Types

type Client (m :: * -> *) ((* :> QueryParam' mods sym a) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> QueryParam' mods sym a) api) -> Request -> Client m ((* :> QueryParam' mods sym a) api) Source #

HasClient m api => HasClient m ((:>) * (Description desc) api) Source #

Ignore Description in client functions.

Associated Types

type Client (m :: * -> *) ((* :> Description desc) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> Description desc) api) -> Request -> Client m ((* :> Description desc) api) Source #

HasClient m api => HasClient m ((:>) * (Summary desc) api) Source #

Ignore Summary in client functions.

Associated Types

type Client (m :: * -> *) ((* :> Summary desc) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> Summary desc) api) -> Request -> Client m ((* :> Summary desc) api) Source #

HasClient m api => HasClient m ((:>) * HttpVersion api) Source #

Using a HttpVersion combinator in your API doesn't affect the client functions.

Associated Types

type Client (m :: * -> *) ((* :> HttpVersion) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> HttpVersion) api) -> Request -> Client m ((* :> HttpVersion) api) Source #

(KnownSymbol sym, ToHttpApiData a, HasClient m api, SBoolI (FoldRequired mods)) => HasClient m ((:>) * (Header' * mods sym a) api) Source #

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

Associated Types

type Client (m :: * -> *) ((* :> Header' * mods sym a) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> Header' * mods sym a) api) -> Request -> Client m ((* :> Header' * mods sym a) api) Source #

(KnownSymbol capture, ToHttpApiData a, HasClient m sublayout) => HasClient m ((:>) * (CaptureAll capture a) sublayout) Source #

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

Associated Types

type Client (m :: * -> *) ((* :> CaptureAll capture a) sublayout) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> CaptureAll capture a) sublayout) -> Request -> Client m ((* :> CaptureAll capture a) sublayout) Source #

(KnownSymbol capture, ToHttpApiData a, HasClient m api) => HasClient m ((:>) * (Capture' mods capture a) api) Source #

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

Associated Types

type Client (m :: * -> *) ((* :> Capture' mods capture a) api) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * ((* :> Capture' mods capture a) api) -> Request -> Client m ((* :> Capture' mods capture a) api) Source #

(RunClient m, MimeUnrender * ct a, ReflectMethod k1 method, FramingUnrender * * framing a, BuildFromStream a (f a)) => HasClient m (Stream k1 method framing ct (f a)) Source # 

Associated Types

type Client (m :: * -> *) (Stream k1 method framing ct (f a)) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * (Stream k1 method framing ct (f a)) -> Request -> Client m (Stream k1 method framing ct (f a)) Source #

(RunClient m, BuildHeadersTo ls, ReflectMethod k1 method) => HasClient m (Verb k1 method status cts (Headers ls NoContent)) Source # 

Associated Types

type Client (m :: * -> *) (Verb k1 method status cts (Headers ls NoContent)) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * (Verb k1 method status cts (Headers ls NoContent)) -> Request -> Client m (Verb k1 method status cts (Headers ls NoContent)) Source #

(RunClient m, MimeUnrender * ct a, BuildHeadersTo ls, ReflectMethod k1 method, (~) [*] cts' ((:) * ct cts)) => HasClient m (Verb k1 method status cts' (Headers ls a)) Source # 

Associated Types

type Client (m :: * -> *) (Verb k1 method status cts' (Headers ls a)) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * (Verb k1 method status cts' (Headers ls a)) -> Request -> Client m (Verb k1 method status cts' (Headers ls a)) Source #

(RunClient m, ReflectMethod k1 method) => HasClient m (Verb k1 method status cts NoContent) Source # 

Associated Types

type Client (m :: * -> *) (Verb k1 method status cts NoContent) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * (Verb k1 method status cts NoContent) -> Request -> Client m (Verb k1 method status cts NoContent) Source #

(RunClient m, MimeUnrender * ct a, ReflectMethod k1 method, (~) [*] cts' ((:) * ct cts)) => HasClient m (Verb k1 method status cts' a) Source # 

Associated Types

type Client (m :: * -> *) (Verb k1 method status cts' a) :: * Source #

Methods

clientWithRoute :: Proxy (* -> *) m -> Proxy * (Verb k1 method status cts' a) -> Request -> Client m (Verb k1 method status cts' a) Source #

Response (for Raw)

data GenResponse a Source #

Instances

Functor GenResponse Source # 

Methods

fmap :: (a -> b) -> GenResponse a -> GenResponse b #

(<$) :: a -> GenResponse b -> GenResponse a #

Foldable GenResponse Source # 

Methods

fold :: Monoid m => GenResponse m -> m #

foldMap :: Monoid m => (a -> m) -> GenResponse a -> m #

foldr :: (a -> b -> b) -> b -> GenResponse a -> b #

foldr' :: (a -> b -> b) -> b -> GenResponse a -> b #

foldl :: (b -> a -> b) -> b -> GenResponse a -> b #

foldl' :: (b -> a -> b) -> b -> GenResponse a -> b #

foldr1 :: (a -> a -> a) -> GenResponse a -> a #

foldl1 :: (a -> a -> a) -> GenResponse a -> a #

toList :: GenResponse a -> [a] #

null :: GenResponse a -> Bool #

length :: GenResponse a -> Int #

elem :: Eq a => a -> GenResponse a -> Bool #

maximum :: Ord a => GenResponse a -> a #

minimum :: Ord a => GenResponse a -> a #

sum :: Num a => GenResponse a -> a #

product :: Num a => GenResponse a -> a #

Traversable GenResponse Source # 

Methods

traverse :: Applicative f => (a -> f b) -> GenResponse a -> f (GenResponse b) #

sequenceA :: Applicative f => GenResponse (f a) -> f (GenResponse a) #

mapM :: Monad m => (a -> m b) -> GenResponse a -> m (GenResponse b) #

sequence :: Monad m => GenResponse (m a) -> m (GenResponse a) #

Eq a => Eq (GenResponse a) Source # 
Show a => Show (GenResponse a) Source # 
Generic (GenResponse a) Source # 

Associated Types

type Rep (GenResponse a) :: * -> * #

Methods

from :: GenResponse a -> Rep (GenResponse a) x #

to :: Rep (GenResponse a) x -> GenResponse a #

type Rep (GenResponse a) Source # 
type Rep (GenResponse a) = D1 * (MetaData "GenResponse" "Servant.Client.Core.Internal.Request" "servant-client-core-0.13-DCvzKzA1mBvGLqBbRwhkUX" False) (C1 * (MetaCons "Response" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "responseStatusCode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Status)) (S1 * (MetaSel (Just Symbol "responseHeaders") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Seq Header)))) ((:*:) * (S1 * (MetaSel (Just Symbol "responseHttpVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * HttpVersion)) (S1 * (MetaSel (Just Symbol "responseBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))))

Generic Client

class ClientLike client custom where Source #

This class allows us to match client structure with client functions produced with client without explicit pattern-matching.

The client structure needs a Generic instance.

Example:

type API
    = "foo" :> Capture "x" Int :> Get '[JSON] Int
 :<|> "bar" :> QueryParam "a" Char :> QueryParam "b" String :> Post '[JSON] [Int]
 :<|> Capture "nested" Int :> NestedAPI

type NestedAPI
    = Get '[JSON] String
 :<|> "baz" :> QueryParam "c" Char :> Post '[JSON] ()

data APIClient = APIClient
  { getFoo         :: Int -> ClientM Int
  , postBar        :: Maybe Char -> Maybe String -> ClientM [Int]
  , mkNestedClient :: Int -> NestedClient
  } deriving GHC.Generic

instance Generics.SOP.Generic APIClient
instance (Client API ~ client) => ClientLike client APIClient

data NestedClient = NestedClient
 { getString :: ClientM String
 , postBaz   :: Maybe Char -> ClientM ()
 } deriving GHC.Generic

instance Generics.SOP.Generic NestedClient
instance (Client NestedAPI ~ client) => ClientLike client NestedClient

mkAPIClient :: APIClient
mkAPIClient = mkClient (client (Proxy :: Proxy API))

By default, left-nested alternatives are expanded:

type API1
    = "foo" :> Capture "x" Int :> Get '[JSON] Int
 :<|> "bar" :> QueryParam "a" Char :> Post '[JSON] String

type API2
    = "baz" :> QueryParam "c" Char :> Post '[JSON] ()

type API = API1 :<|> API2

data APIClient = APIClient
  { getFoo  :: Int -> ClientM Int
  , postBar :: Maybe Char -> ClientM String
  , postBaz :: Maybe Char -> ClientM ()
  } deriving GHC.Generic

instance Generics.SOP.Generic APIClient
instance (Client API ~ client) => ClientLike client APIClient

mkAPIClient :: APIClient
mkAPIClient = mkClient (client (Proxy :: Proxy API))

If you want to define client for API1 as a separate data structure, you can use genericMkClientP:

data APIClient1 = APIClient1
  { getFoo  :: Int -> ClientM Int
  , postBar :: Maybe Char -> ClientM String
  } deriving GHC.Generic

instance Generics.SOP.Generic APIClient1
instance (Client API1 ~ client) => ClientLike client APIClient1

data APIClient = APIClient
  { mkAPIClient1 :: APIClient1
  , postBaz      :: Maybe Char -> ClientM ()
  } deriving GHC.Generic

instance Generics.SOP.Generic APIClient
instance (Client API ~ client) => ClientLike client APIClient where
  mkClient = genericMkClientP

mkAPIClient :: APIClient
mkAPIClient = mkClient (client (Proxy :: Proxy API))

Methods

mkClient :: client -> custom Source #

mkClient :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom Source #

Instances

ClientLike client custom => ClientLike (a -> client) (a -> custom) Source # 

Methods

mkClient :: (a -> client) -> a -> custom Source #

genericMkClientL :: (Generic custom, Code custom ~ '[xs], GClientList client '[], GClientLikeL (ClientList client '[]) xs) => client -> custom Source #

Generate client structure from client type, expanding left-nested API (done by default).

genericMkClientP :: (Generic custom, Code custom ~ '[xs], GClientLikeP client xs) => client -> custom Source #

Generate client structure from client type, regarding left-nested API clients as separate data structures.

data ServantError Source #

A type representing possible errors in a request

Note that this type substantially changed in 0.12.

Constructors

FailureResponse Response

The server returned an error response

DecodeFailure Text Response

The body could not be decoded at the expected type

UnsupportedContentType MediaType Response

The content-type of the response is not supported

InvalidContentTypeHeader Response

The content-type header is invalid

ConnectionError Text

There was a connection error, and no response was received

Instances

Eq ServantError Source # 
Show ServantError Source # 
Generic ServantError Source # 

Associated Types

type Rep ServantError :: * -> * #

Exception ServantError Source # 
type Rep ServantError Source # 

BaseUrl

data BaseUrl Source #

Simple data type to represent the target of HTTP requests for servant's automatically-generated clients.

Constructors

BaseUrl 

Fields

Instances

Eq BaseUrl Source # 

Methods

(==) :: BaseUrl -> BaseUrl -> Bool #

(/=) :: BaseUrl -> BaseUrl -> Bool #

Ord BaseUrl Source # 
Show BaseUrl Source # 
Generic BaseUrl Source # 

Associated Types

type Rep BaseUrl :: * -> * #

Methods

from :: BaseUrl -> Rep BaseUrl x #

to :: Rep BaseUrl x -> BaseUrl #

type Rep BaseUrl Source # 
type Rep BaseUrl = D1 * (MetaData "BaseUrl" "Servant.Client.Core.Internal.BaseUrl" "servant-client-core-0.13-DCvzKzA1mBvGLqBbRwhkUX" False) (C1 * (MetaCons "BaseUrl" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "baseUrlScheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Scheme)) (S1 * (MetaSel (Just Symbol "baseUrlHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "baseUrlPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "baseUrlPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))

data Scheme Source #

URI scheme to use

Constructors

Http

http://

Https

https://

Instances

Eq Scheme Source # 

Methods

(==) :: Scheme -> Scheme -> Bool #

(/=) :: Scheme -> Scheme -> Bool #

Ord Scheme Source # 
Show Scheme Source # 
Generic Scheme Source # 

Associated Types

type Rep Scheme :: * -> * #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

type Rep Scheme Source # 
type Rep Scheme = D1 * (MetaData "Scheme" "Servant.Client.Core.Internal.BaseUrl" "servant-client-core-0.13-DCvzKzA1mBvGLqBbRwhkUX" False) ((:+:) * (C1 * (MetaCons "Http" PrefixI False) (U1 *)) (C1 * (MetaCons "Https" PrefixI False) (U1 *)))