{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Gogol.Types where
import Control.Exception.Lens (exception)
import Control.Lens
import Control.Monad.Catch
import Control.Monad.Trans.Resource
import Data.Aeson
import Data.ByteString (ByteString)
import Data.ByteString.Char8 qualified as BS8
import Data.ByteString.Lazy qualified as LBS
import Data.CaseInsensitive qualified as CI
import Data.Coerce
import Data.Conduit
import Data.Conduit.Combinators qualified as Conduit
import Data.DList (DList)
import Data.DList qualified as DList
import Data.Data
import Data.Foldable qualified as Foldable
import Data.Kind (Type)
import Data.String
import Data.Text (Text)
import Data.Text.Encoding qualified as Text
import Data.Text.Lazy.Builder (Builder)
import Data.Text.Lazy.Builder qualified as Build
import GHC.Generics
import GHC.TypeLits
import Network.HTTP.Client (HttpException, RequestBody (..))
import Network.HTTP.Media hiding (Accept)
import Network.HTTP.Types hiding (Header)
import Network.HTTP.Types qualified as HTTP
import Servant.API hiding (Stream)
data AltJSON = AltJSON
deriving (AltJSON -> AltJSON -> Bool
(AltJSON -> AltJSON -> Bool)
-> (AltJSON -> AltJSON -> Bool) -> Eq AltJSON
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AltJSON -> AltJSON -> Bool
== :: AltJSON -> AltJSON -> Bool
$c/= :: AltJSON -> AltJSON -> Bool
/= :: AltJSON -> AltJSON -> Bool
Eq, Eq AltJSON
Eq AltJSON =>
(AltJSON -> AltJSON -> Ordering)
-> (AltJSON -> AltJSON -> Bool)
-> (AltJSON -> AltJSON -> Bool)
-> (AltJSON -> AltJSON -> Bool)
-> (AltJSON -> AltJSON -> Bool)
-> (AltJSON -> AltJSON -> AltJSON)
-> (AltJSON -> AltJSON -> AltJSON)
-> Ord AltJSON
AltJSON -> AltJSON -> Bool
AltJSON -> AltJSON -> Ordering
AltJSON -> AltJSON -> AltJSON
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AltJSON -> AltJSON -> Ordering
compare :: AltJSON -> AltJSON -> Ordering
$c< :: AltJSON -> AltJSON -> Bool
< :: AltJSON -> AltJSON -> Bool
$c<= :: AltJSON -> AltJSON -> Bool
<= :: AltJSON -> AltJSON -> Bool
$c> :: AltJSON -> AltJSON -> Bool
> :: AltJSON -> AltJSON -> Bool
$c>= :: AltJSON -> AltJSON -> Bool
>= :: AltJSON -> AltJSON -> Bool
$cmax :: AltJSON -> AltJSON -> AltJSON
max :: AltJSON -> AltJSON -> AltJSON
$cmin :: AltJSON -> AltJSON -> AltJSON
min :: AltJSON -> AltJSON -> AltJSON
Ord, Int -> AltJSON -> ShowS
[AltJSON] -> ShowS
AltJSON -> String
(Int -> AltJSON -> ShowS)
-> (AltJSON -> String) -> ([AltJSON] -> ShowS) -> Show AltJSON
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AltJSON -> ShowS
showsPrec :: Int -> AltJSON -> ShowS
$cshow :: AltJSON -> String
show :: AltJSON -> String
$cshowList :: [AltJSON] -> ShowS
showList :: [AltJSON] -> ShowS
Show, ReadPrec [AltJSON]
ReadPrec AltJSON
Int -> ReadS AltJSON
ReadS [AltJSON]
(Int -> ReadS AltJSON)
-> ReadS [AltJSON]
-> ReadPrec AltJSON
-> ReadPrec [AltJSON]
-> Read AltJSON
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AltJSON
readsPrec :: Int -> ReadS AltJSON
$creadList :: ReadS [AltJSON]
readList :: ReadS [AltJSON]
$creadPrec :: ReadPrec AltJSON
readPrec :: ReadPrec AltJSON
$creadListPrec :: ReadPrec [AltJSON]
readListPrec :: ReadPrec [AltJSON]
Read, (forall x. AltJSON -> Rep AltJSON x)
-> (forall x. Rep AltJSON x -> AltJSON) -> Generic AltJSON
forall x. Rep AltJSON x -> AltJSON
forall x. AltJSON -> Rep AltJSON x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AltJSON -> Rep AltJSON x
from :: forall x. AltJSON -> Rep AltJSON x
$cto :: forall x. Rep AltJSON x -> AltJSON
to :: forall x. Rep AltJSON x -> AltJSON
Generic)
instance ToHttpApiData AltJSON where
toQueryParam :: AltJSON -> Text
toQueryParam = Text -> AltJSON -> Text
forall a b. a -> b -> a
const Text
"json"
data AltMedia = AltMedia
deriving (AltMedia -> AltMedia -> Bool
(AltMedia -> AltMedia -> Bool)
-> (AltMedia -> AltMedia -> Bool) -> Eq AltMedia
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AltMedia -> AltMedia -> Bool
== :: AltMedia -> AltMedia -> Bool
$c/= :: AltMedia -> AltMedia -> Bool
/= :: AltMedia -> AltMedia -> Bool
Eq, Eq AltMedia
Eq AltMedia =>
(AltMedia -> AltMedia -> Ordering)
-> (AltMedia -> AltMedia -> Bool)
-> (AltMedia -> AltMedia -> Bool)
-> (AltMedia -> AltMedia -> Bool)
-> (AltMedia -> AltMedia -> Bool)
-> (AltMedia -> AltMedia -> AltMedia)
-> (AltMedia -> AltMedia -> AltMedia)
-> Ord AltMedia
AltMedia -> AltMedia -> Bool
AltMedia -> AltMedia -> Ordering
AltMedia -> AltMedia -> AltMedia
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AltMedia -> AltMedia -> Ordering
compare :: AltMedia -> AltMedia -> Ordering
$c< :: AltMedia -> AltMedia -> Bool
< :: AltMedia -> AltMedia -> Bool
$c<= :: AltMedia -> AltMedia -> Bool
<= :: AltMedia -> AltMedia -> Bool
$c> :: AltMedia -> AltMedia -> Bool
> :: AltMedia -> AltMedia -> Bool
$c>= :: AltMedia -> AltMedia -> Bool
>= :: AltMedia -> AltMedia -> Bool
$cmax :: AltMedia -> AltMedia -> AltMedia
max :: AltMedia -> AltMedia -> AltMedia
$cmin :: AltMedia -> AltMedia -> AltMedia
min :: AltMedia -> AltMedia -> AltMedia
Ord, Int -> AltMedia -> ShowS
[AltMedia] -> ShowS
AltMedia -> String
(Int -> AltMedia -> ShowS)
-> (AltMedia -> String) -> ([AltMedia] -> ShowS) -> Show AltMedia
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AltMedia -> ShowS
showsPrec :: Int -> AltMedia -> ShowS
$cshow :: AltMedia -> String
show :: AltMedia -> String
$cshowList :: [AltMedia] -> ShowS
showList :: [AltMedia] -> ShowS
Show, ReadPrec [AltMedia]
ReadPrec AltMedia
Int -> ReadS AltMedia
ReadS [AltMedia]
(Int -> ReadS AltMedia)
-> ReadS [AltMedia]
-> ReadPrec AltMedia
-> ReadPrec [AltMedia]
-> Read AltMedia
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AltMedia
readsPrec :: Int -> ReadS AltMedia
$creadList :: ReadS [AltMedia]
readList :: ReadS [AltMedia]
$creadPrec :: ReadPrec AltMedia
readPrec :: ReadPrec AltMedia
$creadListPrec :: ReadPrec [AltMedia]
readListPrec :: ReadPrec [AltMedia]
Read, (forall x. AltMedia -> Rep AltMedia x)
-> (forall x. Rep AltMedia x -> AltMedia) -> Generic AltMedia
forall x. Rep AltMedia x -> AltMedia
forall x. AltMedia -> Rep AltMedia x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AltMedia -> Rep AltMedia x
from :: forall x. AltMedia -> Rep AltMedia x
$cto :: forall x. Rep AltMedia x -> AltMedia
to :: forall x. Rep AltMedia x -> AltMedia
Generic)
instance ToHttpApiData AltMedia where
toQueryParam :: AltMedia -> Text
toQueryParam = Text -> AltMedia -> Text
forall a b. a -> b -> a
const Text
"media"
data Multipart = Multipart
deriving (Multipart -> Multipart -> Bool
(Multipart -> Multipart -> Bool)
-> (Multipart -> Multipart -> Bool) -> Eq Multipart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Multipart -> Multipart -> Bool
== :: Multipart -> Multipart -> Bool
$c/= :: Multipart -> Multipart -> Bool
/= :: Multipart -> Multipart -> Bool
Eq, Eq Multipart
Eq Multipart =>
(Multipart -> Multipart -> Ordering)
-> (Multipart -> Multipart -> Bool)
-> (Multipart -> Multipart -> Bool)
-> (Multipart -> Multipart -> Bool)
-> (Multipart -> Multipart -> Bool)
-> (Multipart -> Multipart -> Multipart)
-> (Multipart -> Multipart -> Multipart)
-> Ord Multipart
Multipart -> Multipart -> Bool
Multipart -> Multipart -> Ordering
Multipart -> Multipart -> Multipart
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Multipart -> Multipart -> Ordering
compare :: Multipart -> Multipart -> Ordering
$c< :: Multipart -> Multipart -> Bool
< :: Multipart -> Multipart -> Bool
$c<= :: Multipart -> Multipart -> Bool
<= :: Multipart -> Multipart -> Bool
$c> :: Multipart -> Multipart -> Bool
> :: Multipart -> Multipart -> Bool
$c>= :: Multipart -> Multipart -> Bool
>= :: Multipart -> Multipart -> Bool
$cmax :: Multipart -> Multipart -> Multipart
max :: Multipart -> Multipart -> Multipart
$cmin :: Multipart -> Multipart -> Multipart
min :: Multipart -> Multipart -> Multipart
Ord, Int -> Multipart -> ShowS
[Multipart] -> ShowS
Multipart -> String
(Int -> Multipart -> ShowS)
-> (Multipart -> String)
-> ([Multipart] -> ShowS)
-> Show Multipart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Multipart -> ShowS
showsPrec :: Int -> Multipart -> ShowS
$cshow :: Multipart -> String
show :: Multipart -> String
$cshowList :: [Multipart] -> ShowS
showList :: [Multipart] -> ShowS
Show, ReadPrec [Multipart]
ReadPrec Multipart
Int -> ReadS Multipart
ReadS [Multipart]
(Int -> ReadS Multipart)
-> ReadS [Multipart]
-> ReadPrec Multipart
-> ReadPrec [Multipart]
-> Read Multipart
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Multipart
readsPrec :: Int -> ReadS Multipart
$creadList :: ReadS [Multipart]
readList :: ReadS [Multipart]
$creadPrec :: ReadPrec Multipart
readPrec :: ReadPrec Multipart
$creadListPrec :: ReadPrec [Multipart]
readListPrec :: ReadPrec [Multipart]
Read, (forall x. Multipart -> Rep Multipart x)
-> (forall x. Rep Multipart x -> Multipart) -> Generic Multipart
forall x. Rep Multipart x -> Multipart
forall x. Multipart -> Rep Multipart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Multipart -> Rep Multipart x
from :: forall x. Multipart -> Rep Multipart x
$cto :: forall x. Rep Multipart x -> Multipart
to :: forall x. Rep Multipart x -> Multipart
Generic)
instance ToHttpApiData Multipart where
toQueryParam :: Multipart -> Text
toQueryParam = Text -> Multipart -> Text
forall a b. a -> b -> a
const Text
"multipart"
newtype OAuthScope = OAuthScope Text
deriving
( OAuthScope -> OAuthScope -> Bool
(OAuthScope -> OAuthScope -> Bool)
-> (OAuthScope -> OAuthScope -> Bool) -> Eq OAuthScope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OAuthScope -> OAuthScope -> Bool
== :: OAuthScope -> OAuthScope -> Bool
$c/= :: OAuthScope -> OAuthScope -> Bool
/= :: OAuthScope -> OAuthScope -> Bool
Eq,
Eq OAuthScope
Eq OAuthScope =>
(OAuthScope -> OAuthScope -> Ordering)
-> (OAuthScope -> OAuthScope -> Bool)
-> (OAuthScope -> OAuthScope -> Bool)
-> (OAuthScope -> OAuthScope -> Bool)
-> (OAuthScope -> OAuthScope -> Bool)
-> (OAuthScope -> OAuthScope -> OAuthScope)
-> (OAuthScope -> OAuthScope -> OAuthScope)
-> Ord OAuthScope
OAuthScope -> OAuthScope -> Bool
OAuthScope -> OAuthScope -> Ordering
OAuthScope -> OAuthScope -> OAuthScope
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OAuthScope -> OAuthScope -> Ordering
compare :: OAuthScope -> OAuthScope -> Ordering
$c< :: OAuthScope -> OAuthScope -> Bool
< :: OAuthScope -> OAuthScope -> Bool
$c<= :: OAuthScope -> OAuthScope -> Bool
<= :: OAuthScope -> OAuthScope -> Bool
$c> :: OAuthScope -> OAuthScope -> Bool
> :: OAuthScope -> OAuthScope -> Bool
$c>= :: OAuthScope -> OAuthScope -> Bool
>= :: OAuthScope -> OAuthScope -> Bool
$cmax :: OAuthScope -> OAuthScope -> OAuthScope
max :: OAuthScope -> OAuthScope -> OAuthScope
$cmin :: OAuthScope -> OAuthScope -> OAuthScope
min :: OAuthScope -> OAuthScope -> OAuthScope
Ord,
Int -> OAuthScope -> ShowS
[OAuthScope] -> ShowS
OAuthScope -> String
(Int -> OAuthScope -> ShowS)
-> (OAuthScope -> String)
-> ([OAuthScope] -> ShowS)
-> Show OAuthScope
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OAuthScope -> ShowS
showsPrec :: Int -> OAuthScope -> ShowS
$cshow :: OAuthScope -> String
show :: OAuthScope -> String
$cshowList :: [OAuthScope] -> ShowS
showList :: [OAuthScope] -> ShowS
Show,
ReadPrec [OAuthScope]
ReadPrec OAuthScope
Int -> ReadS OAuthScope
ReadS [OAuthScope]
(Int -> ReadS OAuthScope)
-> ReadS [OAuthScope]
-> ReadPrec OAuthScope
-> ReadPrec [OAuthScope]
-> Read OAuthScope
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OAuthScope
readsPrec :: Int -> ReadS OAuthScope
$creadList :: ReadS [OAuthScope]
readList :: ReadS [OAuthScope]
$creadPrec :: ReadPrec OAuthScope
readPrec :: ReadPrec OAuthScope
$creadListPrec :: ReadPrec [OAuthScope]
readListPrec :: ReadPrec [OAuthScope]
Read,
String -> OAuthScope
(String -> OAuthScope) -> IsString OAuthScope
forall a. (String -> a) -> IsString a
$cfromString :: String -> OAuthScope
fromString :: String -> OAuthScope
IsString,
(forall x. OAuthScope -> Rep OAuthScope x)
-> (forall x. Rep OAuthScope x -> OAuthScope) -> Generic OAuthScope
forall x. Rep OAuthScope x -> OAuthScope
forall x. OAuthScope -> Rep OAuthScope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OAuthScope -> Rep OAuthScope x
from :: forall x. OAuthScope -> Rep OAuthScope x
$cto :: forall x. Rep OAuthScope x -> OAuthScope
to :: forall x. Rep OAuthScope x -> OAuthScope
Generic,
Text -> Either Text OAuthScope
ByteString -> Either Text OAuthScope
(Text -> Either Text OAuthScope)
-> (ByteString -> Either Text OAuthScope)
-> (Text -> Either Text OAuthScope)
-> FromHttpApiData OAuthScope
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text OAuthScope
parseUrlPiece :: Text -> Either Text OAuthScope
$cparseHeader :: ByteString -> Either Text OAuthScope
parseHeader :: ByteString -> Either Text OAuthScope
$cparseQueryParam :: Text -> Either Text OAuthScope
parseQueryParam :: Text -> Either Text OAuthScope
FromHttpApiData,
OAuthScope -> Text
OAuthScope -> ByteString
OAuthScope -> Builder
(OAuthScope -> Text)
-> (OAuthScope -> Builder)
-> (OAuthScope -> ByteString)
-> (OAuthScope -> Text)
-> (OAuthScope -> Builder)
-> ToHttpApiData OAuthScope
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: OAuthScope -> Text
toUrlPiece :: OAuthScope -> Text
$ctoEncodedUrlPiece :: OAuthScope -> Builder
toEncodedUrlPiece :: OAuthScope -> Builder
$ctoHeader :: OAuthScope -> ByteString
toHeader :: OAuthScope -> ByteString
$ctoQueryParam :: OAuthScope -> Text
toQueryParam :: OAuthScope -> Text
$ctoEncodedQueryParam :: OAuthScope -> Builder
toEncodedQueryParam :: OAuthScope -> Builder
ToHttpApiData,
Maybe OAuthScope
Value -> Parser [OAuthScope]
Value -> Parser OAuthScope
(Value -> Parser OAuthScope)
-> (Value -> Parser [OAuthScope])
-> Maybe OAuthScope
-> FromJSON OAuthScope
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser OAuthScope
parseJSON :: Value -> Parser OAuthScope
$cparseJSONList :: Value -> Parser [OAuthScope]
parseJSONList :: Value -> Parser [OAuthScope]
$comittedField :: Maybe OAuthScope
omittedField :: Maybe OAuthScope
FromJSON,
[OAuthScope] -> Value
[OAuthScope] -> Encoding
OAuthScope -> Bool
OAuthScope -> Value
OAuthScope -> Encoding
(OAuthScope -> Value)
-> (OAuthScope -> Encoding)
-> ([OAuthScope] -> Value)
-> ([OAuthScope] -> Encoding)
-> (OAuthScope -> Bool)
-> ToJSON OAuthScope
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: OAuthScope -> Value
toJSON :: OAuthScope -> Value
$ctoEncoding :: OAuthScope -> Encoding
toEncoding :: OAuthScope -> Encoding
$ctoJSONList :: [OAuthScope] -> Value
toJSONList :: [OAuthScope] -> Value
$ctoEncodingList :: [OAuthScope] -> Encoding
toEncodingList :: [OAuthScope] -> Encoding
$comitField :: OAuthScope -> Bool
omitField :: OAuthScope -> Bool
ToJSON
)
newtype AccessToken = AccessToken Text
deriving
( AccessToken -> AccessToken -> Bool
(AccessToken -> AccessToken -> Bool)
-> (AccessToken -> AccessToken -> Bool) -> Eq AccessToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccessToken -> AccessToken -> Bool
== :: AccessToken -> AccessToken -> Bool
$c/= :: AccessToken -> AccessToken -> Bool
/= :: AccessToken -> AccessToken -> Bool
Eq,
Eq AccessToken
Eq AccessToken =>
(AccessToken -> AccessToken -> Ordering)
-> (AccessToken -> AccessToken -> Bool)
-> (AccessToken -> AccessToken -> Bool)
-> (AccessToken -> AccessToken -> Bool)
-> (AccessToken -> AccessToken -> Bool)
-> (AccessToken -> AccessToken -> AccessToken)
-> (AccessToken -> AccessToken -> AccessToken)
-> Ord AccessToken
AccessToken -> AccessToken -> Bool
AccessToken -> AccessToken -> Ordering
AccessToken -> AccessToken -> AccessToken
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AccessToken -> AccessToken -> Ordering
compare :: AccessToken -> AccessToken -> Ordering
$c< :: AccessToken -> AccessToken -> Bool
< :: AccessToken -> AccessToken -> Bool
$c<= :: AccessToken -> AccessToken -> Bool
<= :: AccessToken -> AccessToken -> Bool
$c> :: AccessToken -> AccessToken -> Bool
> :: AccessToken -> AccessToken -> Bool
$c>= :: AccessToken -> AccessToken -> Bool
>= :: AccessToken -> AccessToken -> Bool
$cmax :: AccessToken -> AccessToken -> AccessToken
max :: AccessToken -> AccessToken -> AccessToken
$cmin :: AccessToken -> AccessToken -> AccessToken
min :: AccessToken -> AccessToken -> AccessToken
Ord,
Int -> AccessToken -> ShowS
[AccessToken] -> ShowS
AccessToken -> String
(Int -> AccessToken -> ShowS)
-> (AccessToken -> String)
-> ([AccessToken] -> ShowS)
-> Show AccessToken
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccessToken -> ShowS
showsPrec :: Int -> AccessToken -> ShowS
$cshow :: AccessToken -> String
show :: AccessToken -> String
$cshowList :: [AccessToken] -> ShowS
showList :: [AccessToken] -> ShowS
Show,
ReadPrec [AccessToken]
ReadPrec AccessToken
Int -> ReadS AccessToken
ReadS [AccessToken]
(Int -> ReadS AccessToken)
-> ReadS [AccessToken]
-> ReadPrec AccessToken
-> ReadPrec [AccessToken]
-> Read AccessToken
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AccessToken
readsPrec :: Int -> ReadS AccessToken
$creadList :: ReadS [AccessToken]
readList :: ReadS [AccessToken]
$creadPrec :: ReadPrec AccessToken
readPrec :: ReadPrec AccessToken
$creadListPrec :: ReadPrec [AccessToken]
readListPrec :: ReadPrec [AccessToken]
Read,
String -> AccessToken
(String -> AccessToken) -> IsString AccessToken
forall a. (String -> a) -> IsString a
$cfromString :: String -> AccessToken
fromString :: String -> AccessToken
IsString,
(forall x. AccessToken -> Rep AccessToken x)
-> (forall x. Rep AccessToken x -> AccessToken)
-> Generic AccessToken
forall x. Rep AccessToken x -> AccessToken
forall x. AccessToken -> Rep AccessToken x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AccessToken -> Rep AccessToken x
from :: forall x. AccessToken -> Rep AccessToken x
$cto :: forall x. Rep AccessToken x -> AccessToken
to :: forall x. Rep AccessToken x -> AccessToken
Generic,
Text -> Either Text AccessToken
ByteString -> Either Text AccessToken
(Text -> Either Text AccessToken)
-> (ByteString -> Either Text AccessToken)
-> (Text -> Either Text AccessToken)
-> FromHttpApiData AccessToken
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text AccessToken
parseUrlPiece :: Text -> Either Text AccessToken
$cparseHeader :: ByteString -> Either Text AccessToken
parseHeader :: ByteString -> Either Text AccessToken
$cparseQueryParam :: Text -> Either Text AccessToken
parseQueryParam :: Text -> Either Text AccessToken
FromHttpApiData,
AccessToken -> Text
AccessToken -> ByteString
AccessToken -> Builder
(AccessToken -> Text)
-> (AccessToken -> Builder)
-> (AccessToken -> ByteString)
-> (AccessToken -> Text)
-> (AccessToken -> Builder)
-> ToHttpApiData AccessToken
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: AccessToken -> Text
toUrlPiece :: AccessToken -> Text
$ctoEncodedUrlPiece :: AccessToken -> Builder
toEncodedUrlPiece :: AccessToken -> Builder
$ctoHeader :: AccessToken -> ByteString
toHeader :: AccessToken -> ByteString
$ctoQueryParam :: AccessToken -> Text
toQueryParam :: AccessToken -> Text
$ctoEncodedQueryParam :: AccessToken -> Builder
toEncodedQueryParam :: AccessToken -> Builder
ToHttpApiData,
Maybe AccessToken
Value -> Parser [AccessToken]
Value -> Parser AccessToken
(Value -> Parser AccessToken)
-> (Value -> Parser [AccessToken])
-> Maybe AccessToken
-> FromJSON AccessToken
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser AccessToken
parseJSON :: Value -> Parser AccessToken
$cparseJSONList :: Value -> Parser [AccessToken]
parseJSONList :: Value -> Parser [AccessToken]
$comittedField :: Maybe AccessToken
omittedField :: Maybe AccessToken
FromJSON,
[AccessToken] -> Value
[AccessToken] -> Encoding
AccessToken -> Bool
AccessToken -> Value
AccessToken -> Encoding
(AccessToken -> Value)
-> (AccessToken -> Encoding)
-> ([AccessToken] -> Value)
-> ([AccessToken] -> Encoding)
-> (AccessToken -> Bool)
-> ToJSON AccessToken
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: AccessToken -> Value
toJSON :: AccessToken -> Value
$ctoEncoding :: AccessToken -> Encoding
toEncoding :: AccessToken -> Encoding
$ctoJSONList :: [AccessToken] -> Value
toJSONList :: [AccessToken] -> Value
$ctoEncodingList :: [AccessToken] -> Encoding
toEncodingList :: [AccessToken] -> Encoding
$comitField :: AccessToken -> Bool
omitField :: AccessToken -> Bool
ToJSON
)
newtype RefreshToken = RefreshToken Text
deriving
( RefreshToken -> RefreshToken -> Bool
(RefreshToken -> RefreshToken -> Bool)
-> (RefreshToken -> RefreshToken -> Bool) -> Eq RefreshToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RefreshToken -> RefreshToken -> Bool
== :: RefreshToken -> RefreshToken -> Bool
$c/= :: RefreshToken -> RefreshToken -> Bool
/= :: RefreshToken -> RefreshToken -> Bool
Eq,
Eq RefreshToken
Eq RefreshToken =>
(RefreshToken -> RefreshToken -> Ordering)
-> (RefreshToken -> RefreshToken -> Bool)
-> (RefreshToken -> RefreshToken -> Bool)
-> (RefreshToken -> RefreshToken -> Bool)
-> (RefreshToken -> RefreshToken -> Bool)
-> (RefreshToken -> RefreshToken -> RefreshToken)
-> (RefreshToken -> RefreshToken -> RefreshToken)
-> Ord RefreshToken
RefreshToken -> RefreshToken -> Bool
RefreshToken -> RefreshToken -> Ordering
RefreshToken -> RefreshToken -> RefreshToken
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RefreshToken -> RefreshToken -> Ordering
compare :: RefreshToken -> RefreshToken -> Ordering
$c< :: RefreshToken -> RefreshToken -> Bool
< :: RefreshToken -> RefreshToken -> Bool
$c<= :: RefreshToken -> RefreshToken -> Bool
<= :: RefreshToken -> RefreshToken -> Bool
$c> :: RefreshToken -> RefreshToken -> Bool
> :: RefreshToken -> RefreshToken -> Bool
$c>= :: RefreshToken -> RefreshToken -> Bool
>= :: RefreshToken -> RefreshToken -> Bool
$cmax :: RefreshToken -> RefreshToken -> RefreshToken
max :: RefreshToken -> RefreshToken -> RefreshToken
$cmin :: RefreshToken -> RefreshToken -> RefreshToken
min :: RefreshToken -> RefreshToken -> RefreshToken
Ord,
Int -> RefreshToken -> ShowS
[RefreshToken] -> ShowS
RefreshToken -> String
(Int -> RefreshToken -> ShowS)
-> (RefreshToken -> String)
-> ([RefreshToken] -> ShowS)
-> Show RefreshToken
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RefreshToken -> ShowS
showsPrec :: Int -> RefreshToken -> ShowS
$cshow :: RefreshToken -> String
show :: RefreshToken -> String
$cshowList :: [RefreshToken] -> ShowS
showList :: [RefreshToken] -> ShowS
Show,
ReadPrec [RefreshToken]
ReadPrec RefreshToken
Int -> ReadS RefreshToken
ReadS [RefreshToken]
(Int -> ReadS RefreshToken)
-> ReadS [RefreshToken]
-> ReadPrec RefreshToken
-> ReadPrec [RefreshToken]
-> Read RefreshToken
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RefreshToken
readsPrec :: Int -> ReadS RefreshToken
$creadList :: ReadS [RefreshToken]
readList :: ReadS [RefreshToken]
$creadPrec :: ReadPrec RefreshToken
readPrec :: ReadPrec RefreshToken
$creadListPrec :: ReadPrec [RefreshToken]
readListPrec :: ReadPrec [RefreshToken]
Read,
String -> RefreshToken
(String -> RefreshToken) -> IsString RefreshToken
forall a. (String -> a) -> IsString a
$cfromString :: String -> RefreshToken
fromString :: String -> RefreshToken
IsString,
(forall x. RefreshToken -> Rep RefreshToken x)
-> (forall x. Rep RefreshToken x -> RefreshToken)
-> Generic RefreshToken
forall x. Rep RefreshToken x -> RefreshToken
forall x. RefreshToken -> Rep RefreshToken x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RefreshToken -> Rep RefreshToken x
from :: forall x. RefreshToken -> Rep RefreshToken x
$cto :: forall x. Rep RefreshToken x -> RefreshToken
to :: forall x. Rep RefreshToken x -> RefreshToken
Generic,
Text -> Either Text RefreshToken
ByteString -> Either Text RefreshToken
(Text -> Either Text RefreshToken)
-> (ByteString -> Either Text RefreshToken)
-> (Text -> Either Text RefreshToken)
-> FromHttpApiData RefreshToken
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text RefreshToken
parseUrlPiece :: Text -> Either Text RefreshToken
$cparseHeader :: ByteString -> Either Text RefreshToken
parseHeader :: ByteString -> Either Text RefreshToken
$cparseQueryParam :: Text -> Either Text RefreshToken
parseQueryParam :: Text -> Either Text RefreshToken
FromHttpApiData,
RefreshToken -> Text
RefreshToken -> ByteString
RefreshToken -> Builder
(RefreshToken -> Text)
-> (RefreshToken -> Builder)
-> (RefreshToken -> ByteString)
-> (RefreshToken -> Text)
-> (RefreshToken -> Builder)
-> ToHttpApiData RefreshToken
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: RefreshToken -> Text
toUrlPiece :: RefreshToken -> Text
$ctoEncodedUrlPiece :: RefreshToken -> Builder
toEncodedUrlPiece :: RefreshToken -> Builder
$ctoHeader :: RefreshToken -> ByteString
toHeader :: RefreshToken -> ByteString
$ctoQueryParam :: RefreshToken -> Text
toQueryParam :: RefreshToken -> Text
$ctoEncodedQueryParam :: RefreshToken -> Builder
toEncodedQueryParam :: RefreshToken -> Builder
ToHttpApiData,
Maybe RefreshToken
Value -> Parser [RefreshToken]
Value -> Parser RefreshToken
(Value -> Parser RefreshToken)
-> (Value -> Parser [RefreshToken])
-> Maybe RefreshToken
-> FromJSON RefreshToken
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser RefreshToken
parseJSON :: Value -> Parser RefreshToken
$cparseJSONList :: Value -> Parser [RefreshToken]
parseJSONList :: Value -> Parser [RefreshToken]
$comittedField :: Maybe RefreshToken
omittedField :: Maybe RefreshToken
FromJSON,
[RefreshToken] -> Value
[RefreshToken] -> Encoding
RefreshToken -> Bool
RefreshToken -> Value
RefreshToken -> Encoding
(RefreshToken -> Value)
-> (RefreshToken -> Encoding)
-> ([RefreshToken] -> Value)
-> ([RefreshToken] -> Encoding)
-> (RefreshToken -> Bool)
-> ToJSON RefreshToken
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: RefreshToken -> Value
toJSON :: RefreshToken -> Value
$ctoEncoding :: RefreshToken -> Encoding
toEncoding :: RefreshToken -> Encoding
$ctoJSONList :: [RefreshToken] -> Value
toJSONList :: [RefreshToken] -> Value
$ctoEncodingList :: [RefreshToken] -> Encoding
toEncodingList :: [RefreshToken] -> Encoding
$comitField :: RefreshToken -> Bool
omitField :: RefreshToken -> Bool
ToJSON
)
newtype ClientId = ClientId Text
deriving
( ClientId -> ClientId -> Bool
(ClientId -> ClientId -> Bool)
-> (ClientId -> ClientId -> Bool) -> Eq ClientId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClientId -> ClientId -> Bool
== :: ClientId -> ClientId -> Bool
$c/= :: ClientId -> ClientId -> Bool
/= :: ClientId -> ClientId -> Bool
Eq,
Eq ClientId
Eq ClientId =>
(ClientId -> ClientId -> Ordering)
-> (ClientId -> ClientId -> Bool)
-> (ClientId -> ClientId -> Bool)
-> (ClientId -> ClientId -> Bool)
-> (ClientId -> ClientId -> Bool)
-> (ClientId -> ClientId -> ClientId)
-> (ClientId -> ClientId -> ClientId)
-> Ord ClientId
ClientId -> ClientId -> Bool
ClientId -> ClientId -> Ordering
ClientId -> ClientId -> ClientId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ClientId -> ClientId -> Ordering
compare :: ClientId -> ClientId -> Ordering
$c< :: ClientId -> ClientId -> Bool
< :: ClientId -> ClientId -> Bool
$c<= :: ClientId -> ClientId -> Bool
<= :: ClientId -> ClientId -> Bool
$c> :: ClientId -> ClientId -> Bool
> :: ClientId -> ClientId -> Bool
$c>= :: ClientId -> ClientId -> Bool
>= :: ClientId -> ClientId -> Bool
$cmax :: ClientId -> ClientId -> ClientId
max :: ClientId -> ClientId -> ClientId
$cmin :: ClientId -> ClientId -> ClientId
min :: ClientId -> ClientId -> ClientId
Ord,
Int -> ClientId -> ShowS
[ClientId] -> ShowS
ClientId -> String
(Int -> ClientId -> ShowS)
-> (ClientId -> String) -> ([ClientId] -> ShowS) -> Show ClientId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClientId -> ShowS
showsPrec :: Int -> ClientId -> ShowS
$cshow :: ClientId -> String
show :: ClientId -> String
$cshowList :: [ClientId] -> ShowS
showList :: [ClientId] -> ShowS
Show,
ReadPrec [ClientId]
ReadPrec ClientId
Int -> ReadS ClientId
ReadS [ClientId]
(Int -> ReadS ClientId)
-> ReadS [ClientId]
-> ReadPrec ClientId
-> ReadPrec [ClientId]
-> Read ClientId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ClientId
readsPrec :: Int -> ReadS ClientId
$creadList :: ReadS [ClientId]
readList :: ReadS [ClientId]
$creadPrec :: ReadPrec ClientId
readPrec :: ReadPrec ClientId
$creadListPrec :: ReadPrec [ClientId]
readListPrec :: ReadPrec [ClientId]
Read,
String -> ClientId
(String -> ClientId) -> IsString ClientId
forall a. (String -> a) -> IsString a
$cfromString :: String -> ClientId
fromString :: String -> ClientId
IsString,
(forall x. ClientId -> Rep ClientId x)
-> (forall x. Rep ClientId x -> ClientId) -> Generic ClientId
forall x. Rep ClientId x -> ClientId
forall x. ClientId -> Rep ClientId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ClientId -> Rep ClientId x
from :: forall x. ClientId -> Rep ClientId x
$cto :: forall x. Rep ClientId x -> ClientId
to :: forall x. Rep ClientId x -> ClientId
Generic,
Text -> Either Text ClientId
ByteString -> Either Text ClientId
(Text -> Either Text ClientId)
-> (ByteString -> Either Text ClientId)
-> (Text -> Either Text ClientId)
-> FromHttpApiData ClientId
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text ClientId
parseUrlPiece :: Text -> Either Text ClientId
$cparseHeader :: ByteString -> Either Text ClientId
parseHeader :: ByteString -> Either Text ClientId
$cparseQueryParam :: Text -> Either Text ClientId
parseQueryParam :: Text -> Either Text ClientId
FromHttpApiData,
ClientId -> Text
ClientId -> ByteString
ClientId -> Builder
(ClientId -> Text)
-> (ClientId -> Builder)
-> (ClientId -> ByteString)
-> (ClientId -> Text)
-> (ClientId -> Builder)
-> ToHttpApiData ClientId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: ClientId -> Text
toUrlPiece :: ClientId -> Text
$ctoEncodedUrlPiece :: ClientId -> Builder
toEncodedUrlPiece :: ClientId -> Builder
$ctoHeader :: ClientId -> ByteString
toHeader :: ClientId -> ByteString
$ctoQueryParam :: ClientId -> Text
toQueryParam :: ClientId -> Text
$ctoEncodedQueryParam :: ClientId -> Builder
toEncodedQueryParam :: ClientId -> Builder
ToHttpApiData,
Maybe ClientId
Value -> Parser [ClientId]
Value -> Parser ClientId
(Value -> Parser ClientId)
-> (Value -> Parser [ClientId])
-> Maybe ClientId
-> FromJSON ClientId
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ClientId
parseJSON :: Value -> Parser ClientId
$cparseJSONList :: Value -> Parser [ClientId]
parseJSONList :: Value -> Parser [ClientId]
$comittedField :: Maybe ClientId
omittedField :: Maybe ClientId
FromJSON,
[ClientId] -> Value
[ClientId] -> Encoding
ClientId -> Bool
ClientId -> Value
ClientId -> Encoding
(ClientId -> Value)
-> (ClientId -> Encoding)
-> ([ClientId] -> Value)
-> ([ClientId] -> Encoding)
-> (ClientId -> Bool)
-> ToJSON ClientId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ClientId -> Value
toJSON :: ClientId -> Value
$ctoEncoding :: ClientId -> Encoding
toEncoding :: ClientId -> Encoding
$ctoJSONList :: [ClientId] -> Value
toJSONList :: [ClientId] -> Value
$ctoEncodingList :: [ClientId] -> Encoding
toEncodingList :: [ClientId] -> Encoding
$comitField :: ClientId -> Bool
omitField :: ClientId -> Bool
ToJSON
)
newtype ServiceId = ServiceId Text
deriving
( ServiceId -> ServiceId -> Bool
(ServiceId -> ServiceId -> Bool)
-> (ServiceId -> ServiceId -> Bool) -> Eq ServiceId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServiceId -> ServiceId -> Bool
== :: ServiceId -> ServiceId -> Bool
$c/= :: ServiceId -> ServiceId -> Bool
/= :: ServiceId -> ServiceId -> Bool
Eq,
Eq ServiceId
Eq ServiceId =>
(ServiceId -> ServiceId -> Ordering)
-> (ServiceId -> ServiceId -> Bool)
-> (ServiceId -> ServiceId -> Bool)
-> (ServiceId -> ServiceId -> Bool)
-> (ServiceId -> ServiceId -> Bool)
-> (ServiceId -> ServiceId -> ServiceId)
-> (ServiceId -> ServiceId -> ServiceId)
-> Ord ServiceId
ServiceId -> ServiceId -> Bool
ServiceId -> ServiceId -> Ordering
ServiceId -> ServiceId -> ServiceId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ServiceId -> ServiceId -> Ordering
compare :: ServiceId -> ServiceId -> Ordering
$c< :: ServiceId -> ServiceId -> Bool
< :: ServiceId -> ServiceId -> Bool
$c<= :: ServiceId -> ServiceId -> Bool
<= :: ServiceId -> ServiceId -> Bool
$c> :: ServiceId -> ServiceId -> Bool
> :: ServiceId -> ServiceId -> Bool
$c>= :: ServiceId -> ServiceId -> Bool
>= :: ServiceId -> ServiceId -> Bool
$cmax :: ServiceId -> ServiceId -> ServiceId
max :: ServiceId -> ServiceId -> ServiceId
$cmin :: ServiceId -> ServiceId -> ServiceId
min :: ServiceId -> ServiceId -> ServiceId
Ord,
Int -> ServiceId -> ShowS
[ServiceId] -> ShowS
ServiceId -> String
(Int -> ServiceId -> ShowS)
-> (ServiceId -> String)
-> ([ServiceId] -> ShowS)
-> Show ServiceId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServiceId -> ShowS
showsPrec :: Int -> ServiceId -> ShowS
$cshow :: ServiceId -> String
show :: ServiceId -> String
$cshowList :: [ServiceId] -> ShowS
showList :: [ServiceId] -> ShowS
Show,
ReadPrec [ServiceId]
ReadPrec ServiceId
Int -> ReadS ServiceId
ReadS [ServiceId]
(Int -> ReadS ServiceId)
-> ReadS [ServiceId]
-> ReadPrec ServiceId
-> ReadPrec [ServiceId]
-> Read ServiceId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ServiceId
readsPrec :: Int -> ReadS ServiceId
$creadList :: ReadS [ServiceId]
readList :: ReadS [ServiceId]
$creadPrec :: ReadPrec ServiceId
readPrec :: ReadPrec ServiceId
$creadListPrec :: ReadPrec [ServiceId]
readListPrec :: ReadPrec [ServiceId]
Read,
String -> ServiceId
(String -> ServiceId) -> IsString ServiceId
forall a. (String -> a) -> IsString a
$cfromString :: String -> ServiceId
fromString :: String -> ServiceId
IsString,
(forall x. ServiceId -> Rep ServiceId x)
-> (forall x. Rep ServiceId x -> ServiceId) -> Generic ServiceId
forall x. Rep ServiceId x -> ServiceId
forall x. ServiceId -> Rep ServiceId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ServiceId -> Rep ServiceId x
from :: forall x. ServiceId -> Rep ServiceId x
$cto :: forall x. Rep ServiceId x -> ServiceId
to :: forall x. Rep ServiceId x -> ServiceId
Generic,
Text -> Either Text ServiceId
ByteString -> Either Text ServiceId
(Text -> Either Text ServiceId)
-> (ByteString -> Either Text ServiceId)
-> (Text -> Either Text ServiceId)
-> FromHttpApiData ServiceId
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text ServiceId
parseUrlPiece :: Text -> Either Text ServiceId
$cparseHeader :: ByteString -> Either Text ServiceId
parseHeader :: ByteString -> Either Text ServiceId
$cparseQueryParam :: Text -> Either Text ServiceId
parseQueryParam :: Text -> Either Text ServiceId
FromHttpApiData,
ServiceId -> Text
ServiceId -> ByteString
ServiceId -> Builder
(ServiceId -> Text)
-> (ServiceId -> Builder)
-> (ServiceId -> ByteString)
-> (ServiceId -> Text)
-> (ServiceId -> Builder)
-> ToHttpApiData ServiceId
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: ServiceId -> Text
toUrlPiece :: ServiceId -> Text
$ctoEncodedUrlPiece :: ServiceId -> Builder
toEncodedUrlPiece :: ServiceId -> Builder
$ctoHeader :: ServiceId -> ByteString
toHeader :: ServiceId -> ByteString
$ctoQueryParam :: ServiceId -> Text
toQueryParam :: ServiceId -> Text
$ctoEncodedQueryParam :: ServiceId -> Builder
toEncodedQueryParam :: ServiceId -> Builder
ToHttpApiData,
Maybe ServiceId
Value -> Parser [ServiceId]
Value -> Parser ServiceId
(Value -> Parser ServiceId)
-> (Value -> Parser [ServiceId])
-> Maybe ServiceId
-> FromJSON ServiceId
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser ServiceId
parseJSON :: Value -> Parser ServiceId
$cparseJSONList :: Value -> Parser [ServiceId]
parseJSONList :: Value -> Parser [ServiceId]
$comittedField :: Maybe ServiceId
omittedField :: Maybe ServiceId
FromJSON,
[ServiceId] -> Value
[ServiceId] -> Encoding
ServiceId -> Bool
ServiceId -> Value
ServiceId -> Encoding
(ServiceId -> Value)
-> (ServiceId -> Encoding)
-> ([ServiceId] -> Value)
-> ([ServiceId] -> Encoding)
-> (ServiceId -> Bool)
-> ToJSON ServiceId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ServiceId -> Value
toJSON :: ServiceId -> Value
$ctoEncoding :: ServiceId -> Encoding
toEncoding :: ServiceId -> Encoding
$ctoJSONList :: [ServiceId] -> Value
toJSONList :: [ServiceId] -> Value
$ctoEncodingList :: [ServiceId] -> Encoding
toEncodingList :: [ServiceId] -> Encoding
$comitField :: ServiceId -> Bool
omitField :: ServiceId -> Bool
ToJSON
)
newtype GSecret = GSecret Text
deriving
( GSecret -> GSecret -> Bool
(GSecret -> GSecret -> Bool)
-> (GSecret -> GSecret -> Bool) -> Eq GSecret
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GSecret -> GSecret -> Bool
== :: GSecret -> GSecret -> Bool
$c/= :: GSecret -> GSecret -> Bool
/= :: GSecret -> GSecret -> Bool
Eq,
Eq GSecret
Eq GSecret =>
(GSecret -> GSecret -> Ordering)
-> (GSecret -> GSecret -> Bool)
-> (GSecret -> GSecret -> Bool)
-> (GSecret -> GSecret -> Bool)
-> (GSecret -> GSecret -> Bool)
-> (GSecret -> GSecret -> GSecret)
-> (GSecret -> GSecret -> GSecret)
-> Ord GSecret
GSecret -> GSecret -> Bool
GSecret -> GSecret -> Ordering
GSecret -> GSecret -> GSecret
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GSecret -> GSecret -> Ordering
compare :: GSecret -> GSecret -> Ordering
$c< :: GSecret -> GSecret -> Bool
< :: GSecret -> GSecret -> Bool
$c<= :: GSecret -> GSecret -> Bool
<= :: GSecret -> GSecret -> Bool
$c> :: GSecret -> GSecret -> Bool
> :: GSecret -> GSecret -> Bool
$c>= :: GSecret -> GSecret -> Bool
>= :: GSecret -> GSecret -> Bool
$cmax :: GSecret -> GSecret -> GSecret
max :: GSecret -> GSecret -> GSecret
$cmin :: GSecret -> GSecret -> GSecret
min :: GSecret -> GSecret -> GSecret
Ord,
ReadPrec [GSecret]
ReadPrec GSecret
Int -> ReadS GSecret
ReadS [GSecret]
(Int -> ReadS GSecret)
-> ReadS [GSecret]
-> ReadPrec GSecret
-> ReadPrec [GSecret]
-> Read GSecret
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GSecret
readsPrec :: Int -> ReadS GSecret
$creadList :: ReadS [GSecret]
readList :: ReadS [GSecret]
$creadPrec :: ReadPrec GSecret
readPrec :: ReadPrec GSecret
$creadListPrec :: ReadPrec [GSecret]
readListPrec :: ReadPrec [GSecret]
Read,
String -> GSecret
(String -> GSecret) -> IsString GSecret
forall a. (String -> a) -> IsString a
$cfromString :: String -> GSecret
fromString :: String -> GSecret
IsString,
(forall x. GSecret -> Rep GSecret x)
-> (forall x. Rep GSecret x -> GSecret) -> Generic GSecret
forall x. Rep GSecret x -> GSecret
forall x. GSecret -> Rep GSecret x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GSecret -> Rep GSecret x
from :: forall x. GSecret -> Rep GSecret x
$cto :: forall x. Rep GSecret x -> GSecret
to :: forall x. Rep GSecret x -> GSecret
Generic,
Text -> Either Text GSecret
ByteString -> Either Text GSecret
(Text -> Either Text GSecret)
-> (ByteString -> Either Text GSecret)
-> (Text -> Either Text GSecret)
-> FromHttpApiData GSecret
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text GSecret
parseUrlPiece :: Text -> Either Text GSecret
$cparseHeader :: ByteString -> Either Text GSecret
parseHeader :: ByteString -> Either Text GSecret
$cparseQueryParam :: Text -> Either Text GSecret
parseQueryParam :: Text -> Either Text GSecret
FromHttpApiData,
GSecret -> Text
GSecret -> ByteString
GSecret -> Builder
(GSecret -> Text)
-> (GSecret -> Builder)
-> (GSecret -> ByteString)
-> (GSecret -> Text)
-> (GSecret -> Builder)
-> ToHttpApiData GSecret
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: GSecret -> Text
toUrlPiece :: GSecret -> Text
$ctoEncodedUrlPiece :: GSecret -> Builder
toEncodedUrlPiece :: GSecret -> Builder
$ctoHeader :: GSecret -> ByteString
toHeader :: GSecret -> ByteString
$ctoQueryParam :: GSecret -> Text
toQueryParam :: GSecret -> Text
$ctoEncodedQueryParam :: GSecret -> Builder
toEncodedQueryParam :: GSecret -> Builder
ToHttpApiData,
Maybe GSecret
Value -> Parser [GSecret]
Value -> Parser GSecret
(Value -> Parser GSecret)
-> (Value -> Parser [GSecret]) -> Maybe GSecret -> FromJSON GSecret
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser GSecret
parseJSON :: Value -> Parser GSecret
$cparseJSONList :: Value -> Parser [GSecret]
parseJSONList :: Value -> Parser [GSecret]
$comittedField :: Maybe GSecret
omittedField :: Maybe GSecret
FromJSON,
[GSecret] -> Value
[GSecret] -> Encoding
GSecret -> Bool
GSecret -> Value
GSecret -> Encoding
(GSecret -> Value)
-> (GSecret -> Encoding)
-> ([GSecret] -> Value)
-> ([GSecret] -> Encoding)
-> (GSecret -> Bool)
-> ToJSON GSecret
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: GSecret -> Value
toJSON :: GSecret -> Value
$ctoEncoding :: GSecret -> Encoding
toEncoding :: GSecret -> Encoding
$ctoJSONList :: [GSecret] -> Value
toJSONList :: [GSecret] -> Value
$ctoEncodingList :: [GSecret] -> Encoding
toEncodingList :: [GSecret] -> Encoding
$comitField :: GSecret -> Bool
omitField :: GSecret -> Bool
ToJSON
)
instance Show GSecret where
show :: GSecret -> String
show = String -> GSecret -> String
forall a b. a -> b -> a
const String
"*****"
newtype MediaDownload a = MediaDownload a
data MediaUpload a = MediaUpload a GBody
_Coerce :: (Coercible a b, Coercible b a) => Iso' a b
_Coerce :: forall a b. (Coercible a b, Coercible b a) => Iso' a b
_Coerce = (a -> b) -> (b -> a) -> Iso a a b b
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso a -> b
forall a b. Coercible a b => a -> b
coerce b -> a
forall a b. Coercible a b => a -> b
coerce
_Default :: (Monoid a) => Iso' (Maybe a) a
_Default :: forall a. Monoid a => Iso' (Maybe a) a
_Default = (Maybe a -> a) -> (a -> Maybe a) -> Iso (Maybe a) (Maybe a) a a
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Maybe a -> a
forall {a}. Monoid a => Maybe a -> a
f a -> Maybe a
forall a. a -> Maybe a
Just
where
f :: Maybe a -> a
f (Just a
x) = a
x
f Maybe a
Nothing = a
forall a. Monoid a => a
mempty
type Stream = ConduitM () ByteString (ResourceT IO) ()
data Error
= TransportError HttpException
| SerializeError SerializeError
| ServiceError ServiceError
deriving (Int -> Error -> ShowS
[Error] -> ShowS
Error -> String
(Int -> Error -> ShowS)
-> (Error -> String) -> ([Error] -> ShowS) -> Show Error
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Error -> ShowS
showsPrec :: Int -> Error -> ShowS
$cshow :: Error -> String
show :: Error -> String
$cshowList :: [Error] -> ShowS
showList :: [Error] -> ShowS
Show)
instance Exception Error
data SerializeError = SerializeError'
{ SerializeError -> ServiceId
_serializeId :: !ServiceId,
:: [HTTP.Header],
SerializeError -> Status
_serializeStatus :: !Status,
SerializeError -> String
_serializeMessage :: !String,
SerializeError -> Maybe ByteString
_serializeBody :: !(Maybe LBS.ByteString)
}
deriving (SerializeError -> SerializeError -> Bool
(SerializeError -> SerializeError -> Bool)
-> (SerializeError -> SerializeError -> Bool) -> Eq SerializeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SerializeError -> SerializeError -> Bool
== :: SerializeError -> SerializeError -> Bool
$c/= :: SerializeError -> SerializeError -> Bool
/= :: SerializeError -> SerializeError -> Bool
Eq, Int -> SerializeError -> ShowS
[SerializeError] -> ShowS
SerializeError -> String
(Int -> SerializeError -> ShowS)
-> (SerializeError -> String)
-> ([SerializeError] -> ShowS)
-> Show SerializeError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SerializeError -> ShowS
showsPrec :: Int -> SerializeError -> ShowS
$cshow :: SerializeError -> String
show :: SerializeError -> String
$cshowList :: [SerializeError] -> ShowS
showList :: [SerializeError] -> ShowS
Show)
data ServiceError = ServiceError'
{ ServiceError -> ServiceId
_serviceId :: !ServiceId,
ServiceError -> Status
_serviceStatus :: !Status,
:: ![HTTP.Header],
ServiceError -> Maybe ByteString
_serviceBody :: !(Maybe LBS.ByteString)
}
deriving (ServiceError -> ServiceError -> Bool
(ServiceError -> ServiceError -> Bool)
-> (ServiceError -> ServiceError -> Bool) -> Eq ServiceError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServiceError -> ServiceError -> Bool
== :: ServiceError -> ServiceError -> Bool
$c/= :: ServiceError -> ServiceError -> Bool
/= :: ServiceError -> ServiceError -> Bool
Eq, Int -> ServiceError -> ShowS
[ServiceError] -> ShowS
ServiceError -> String
(Int -> ServiceError -> ShowS)
-> (ServiceError -> String)
-> ([ServiceError] -> ShowS)
-> Show ServiceError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServiceError -> ShowS
showsPrec :: Int -> ServiceError -> ShowS
$cshow :: ServiceError -> String
show :: ServiceError -> String
$cshowList :: [ServiceError] -> ShowS
showList :: [ServiceError] -> ShowS
Show)
class AsError a where
_Error :: Prism' a Error
{-# MINIMAL _Error #-}
_TransportError :: Prism' a HttpException
_SerializeError :: Prism' a SerializeError
_ServiceError :: Prism' a ServiceError
_TransportError = p Error (f Error) -> p a (f a)
forall a. AsError a => Prism' a Error
Prism' a Error
_Error (p Error (f Error) -> p a (f a))
-> (p HttpException (f HttpException) -> p Error (f Error))
-> p HttpException (f HttpException)
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p HttpException (f HttpException) -> p Error (f Error)
forall a. AsError a => Prism' a HttpException
Prism' Error HttpException
_TransportError
_SerializeError = p Error (f Error) -> p a (f a)
forall a. AsError a => Prism' a Error
Prism' a Error
_Error (p Error (f Error) -> p a (f a))
-> (p SerializeError (f SerializeError) -> p Error (f Error))
-> p SerializeError (f SerializeError)
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p SerializeError (f SerializeError) -> p Error (f Error)
forall a. AsError a => Prism' a SerializeError
Prism' Error SerializeError
_SerializeError
_ServiceError = p Error (f Error) -> p a (f a)
forall a. AsError a => Prism' a Error
Prism' a Error
_Error (p Error (f Error) -> p a (f a))
-> (p ServiceError (f ServiceError) -> p Error (f Error))
-> p ServiceError (f ServiceError)
-> p a (f a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p ServiceError (f ServiceError) -> p Error (f Error)
forall a. AsError a => Prism' a ServiceError
Prism' Error ServiceError
_ServiceError
instance AsError SomeException where
_Error :: Prism' SomeException Error
_Error = p Error (f Error) -> p SomeException (f SomeException)
forall a. Exception a => Prism' SomeException a
Prism' SomeException Error
exception
instance AsError Error where
_Error :: Prism' Error Error
_Error = p Error (f Error) -> p Error (f Error)
forall a. a -> a
id
_TransportError :: Prism' Error HttpException
_TransportError = (HttpException -> Error)
-> (Error -> Either Error HttpException)
-> Prism' Error HttpException
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism HttpException -> Error
TransportError ((Error -> Either Error HttpException)
-> Prism' Error HttpException)
-> (Error -> Either Error HttpException)
-> Prism' Error HttpException
forall a b. (a -> b) -> a -> b
$ \case
TransportError HttpException
e -> HttpException -> Either Error HttpException
forall a b. b -> Either a b
Right HttpException
e
Error
x -> Error -> Either Error HttpException
forall a b. a -> Either a b
Left Error
x
_SerializeError :: Prism' Error SerializeError
_SerializeError = (SerializeError -> Error)
-> (Error -> Either Error SerializeError)
-> Prism' Error SerializeError
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism SerializeError -> Error
SerializeError ((Error -> Either Error SerializeError)
-> Prism' Error SerializeError)
-> (Error -> Either Error SerializeError)
-> Prism' Error SerializeError
forall a b. (a -> b) -> a -> b
$ \case
SerializeError SerializeError
e -> SerializeError -> Either Error SerializeError
forall a b. b -> Either a b
Right SerializeError
e
Error
x -> Error -> Either Error SerializeError
forall a b. a -> Either a b
Left Error
x
_ServiceError :: Prism' Error ServiceError
_ServiceError = (ServiceError -> Error)
-> (Error -> Either Error ServiceError)
-> Prism' Error ServiceError
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism ServiceError -> Error
ServiceError ((Error -> Either Error ServiceError) -> Prism' Error ServiceError)
-> (Error -> Either Error ServiceError)
-> Prism' Error ServiceError
forall a b. (a -> b) -> a -> b
$ \case
ServiceError ServiceError
e -> ServiceError -> Either Error ServiceError
forall a b. b -> Either a b
Right ServiceError
e
Error
x -> Error -> Either Error ServiceError
forall a b. a -> Either a b
Left Error
x
data ServiceConfig = ServiceConfig
{ ServiceConfig -> ServiceId
_svcId :: !ServiceId,
ServiceConfig -> ByteString
_svcHost :: !ByteString,
ServiceConfig -> Builder
_svcPath :: !Builder,
ServiceConfig -> Int
_svcPort :: !Int,
ServiceConfig -> Bool
_svcSecure :: !Bool,
ServiceConfig -> Maybe Seconds
_svcTimeout :: !(Maybe Seconds)
}
defaultService :: ServiceId -> ByteString -> ServiceConfig
defaultService :: ServiceId -> ByteString -> ServiceConfig
defaultService ServiceId
i ByteString
h =
ServiceConfig
{ _svcId :: ServiceId
_svcId = ServiceId
i,
_svcHost :: ByteString
_svcHost = ByteString
h,
_svcPath :: Builder
_svcPath = Builder
forall a. Monoid a => a
mempty,
_svcPort :: Int
_svcPort = Int
443,
_svcSecure :: Bool
_svcSecure = Bool
True,
_svcTimeout :: Maybe Seconds
_svcTimeout = Seconds -> Maybe Seconds
forall a. a -> Maybe a
Just Seconds
70
}
serviceHost :: Lens' ServiceConfig ByteString
serviceHost :: Lens' ServiceConfig ByteString
serviceHost = (ServiceConfig -> ByteString)
-> (ServiceConfig -> ByteString -> ServiceConfig)
-> Lens' ServiceConfig ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ServiceConfig -> ByteString
_svcHost (\ServiceConfig
s ByteString
a -> ServiceConfig
s {_svcHost = a})
servicePort :: Lens' ServiceConfig Int
servicePort :: Lens' ServiceConfig Int
servicePort = (ServiceConfig -> Int)
-> (ServiceConfig -> Int -> ServiceConfig)
-> Lens' ServiceConfig Int
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ServiceConfig -> Int
_svcPort (\ServiceConfig
s Int
a -> ServiceConfig
s {_svcPort = a})
servicePath :: Lens' ServiceConfig Builder
servicePath :: Lens' ServiceConfig Builder
servicePath = (ServiceConfig -> Builder)
-> (ServiceConfig -> Builder -> ServiceConfig)
-> Lens' ServiceConfig Builder
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ServiceConfig -> Builder
_svcPath (\ServiceConfig
s Builder
a -> ServiceConfig
s {_svcPath = a})
serviceSecure :: Lens' ServiceConfig Bool
serviceSecure :: Lens' ServiceConfig Bool
serviceSecure = (ServiceConfig -> Bool)
-> (ServiceConfig -> Bool -> ServiceConfig)
-> Lens' ServiceConfig Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ServiceConfig -> Bool
_svcSecure (\ServiceConfig
s Bool
a -> ServiceConfig
s {_svcSecure = a})
serviceTimeout :: Lens' ServiceConfig (Maybe Seconds)
serviceTimeout :: Lens' ServiceConfig (Maybe Seconds)
serviceTimeout = (ServiceConfig -> Maybe Seconds)
-> (ServiceConfig -> Maybe Seconds -> ServiceConfig)
-> Lens' ServiceConfig (Maybe Seconds)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ServiceConfig -> Maybe Seconds
_svcTimeout (\ServiceConfig
s Maybe Seconds
a -> ServiceConfig
s {_svcTimeout = a})
data GBody = GBody !MediaType !RequestBody
instance IsString GBody where
fromString :: String -> GBody
fromString = MediaType -> RequestBody -> GBody
GBody (ByteString
"text" ByteString -> ByteString -> MediaType
// ByteString
"plain") (RequestBody -> GBody)
-> (String -> RequestBody) -> String -> GBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> RequestBody
forall a. IsString a => String -> a
fromString
bodyContentType :: Lens' GBody MediaType
bodyContentType :: Lens' GBody MediaType
bodyContentType = (GBody -> MediaType)
-> (GBody -> MediaType -> GBody) -> Lens' GBody MediaType
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\(GBody MediaType
m RequestBody
_) -> MediaType
m) (\(GBody MediaType
_ RequestBody
b) MediaType
m -> MediaType -> RequestBody -> GBody
GBody MediaType
m RequestBody
b)
data Request = Request
{ Request -> Builder
_rqPath :: !Builder,
Request -> DList (ByteString, Maybe ByteString)
_rqQuery :: !(DList (ByteString, Maybe ByteString)),
:: !(DList (HeaderName, ByteString)),
Request -> [GBody]
_rqBody :: ![GBody]
}
instance Monoid Request where
mempty :: Request
mempty = Builder
-> DList (ByteString, Maybe ByteString)
-> DList Header
-> [GBody]
-> Request
Request Builder
forall a. Monoid a => a
mempty DList (ByteString, Maybe ByteString)
forall a. Monoid a => a
mempty DList Header
forall a. Monoid a => a
mempty [GBody]
forall a. Monoid a => a
mempty
mappend :: Request -> Request -> Request
mappend = Request -> Request -> Request
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Request where
Request
a <> :: Request -> Request -> Request
<> Request
b =
Builder
-> DList (ByteString, Maybe ByteString)
-> DList Header
-> [GBody]
-> Request
Request
(Request -> Builder
_rqPath Request
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
"/" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Request -> Builder
_rqPath Request
b)
(Request -> DList (ByteString, Maybe ByteString)
_rqQuery Request
a DList (ByteString, Maybe ByteString)
-> DList (ByteString, Maybe ByteString)
-> DList (ByteString, Maybe ByteString)
forall a. Semigroup a => a -> a -> a
<> Request -> DList (ByteString, Maybe ByteString)
_rqQuery Request
b)
(Request -> DList Header
_rqHeaders Request
a DList Header -> DList Header -> DList Header
forall a. Semigroup a => a -> a -> a
<> Request -> DList Header
_rqHeaders Request
b)
(Request -> [GBody]
_rqBody Request
b [GBody] -> [GBody] -> [GBody]
forall a. Semigroup a => a -> a -> a
<> Request -> [GBody]
_rqBody Request
a)
appendPath :: Request -> Builder -> Request
appendPath :: Request -> Builder -> Request
appendPath Request
rq Builder
x = Request
rq {_rqPath = _rqPath rq <> "/" <> x}
appendPaths :: (ToHttpApiData a) => Request -> [a] -> Request
appendPaths :: forall a. ToHttpApiData a => Request -> [a] -> Request
appendPaths Request
rq = Request -> Builder -> Request
appendPath Request
rq (Builder -> Request) -> ([a] -> Builder) -> [a] -> Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Builder) -> [a] -> Builder
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
mappend Builder
"/" (Builder -> Builder) -> (a -> Builder) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
forall a. ToHttpApiData a => a -> Builder
buildText)
appendQuery :: Request -> ByteString -> Maybe Text -> Request
appendQuery :: Request -> ByteString -> Maybe Text -> Request
appendQuery Request
rq ByteString
k Maybe Text
v =
Request
rq
{ _rqQuery = DList.snoc (_rqQuery rq) (k, Text.encodeUtf8 <$> v)
}
appendHeader :: Request -> HeaderName -> Maybe Text -> Request
Request
rq CI ByteString
_ Maybe Text
Nothing = Request
rq
appendHeader Request
rq CI ByteString
k (Just Text
v) =
Request
rq
{ _rqHeaders = DList.snoc (_rqHeaders rq) (k, Text.encodeUtf8 v)
}
setBody :: Request -> [GBody] -> Request
setBody :: Request -> [GBody] -> Request
setBody Request
rq [GBody]
bs = Request
rq {_rqBody = bs}
data GClient a = GClient
{ forall a. GClient a -> Maybe MediaType
_cliAccept :: !(Maybe MediaType),
forall a. GClient a -> ByteString
_cliMethod :: !Method,
forall a. GClient a -> Status -> Bool
_cliCheck :: !(Status -> Bool),
forall a. GClient a -> ServiceConfig
_cliService :: !ServiceConfig,
forall a. GClient a -> Request
_cliRequest :: !Request,
forall a.
GClient a -> Stream -> ResourceT IO (Either (String, ByteString) a)
_cliResponse :: !(Stream -> ResourceT IO (Either (String, LBS.ByteString) a))
}
clientService :: Lens' (GClient a) ServiceConfig
clientService :: forall a (f :: * -> *).
Functor f =>
(ServiceConfig -> f ServiceConfig) -> GClient a -> f (GClient a)
clientService = (GClient a -> ServiceConfig)
-> (GClient a -> ServiceConfig -> GClient a)
-> Lens (GClient a) (GClient a) ServiceConfig ServiceConfig
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GClient a -> ServiceConfig
forall a. GClient a -> ServiceConfig
_cliService (\GClient a
s ServiceConfig
a -> GClient a
s {_cliService = a})
mime ::
(FromStream c a) =>
Proxy c ->
Method ->
[Int] ->
Request ->
ServiceConfig ->
GClient a
mime :: forall {k} (c :: k) a.
FromStream c a =>
Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
mime Proxy c
p = (Stream -> ResourceT IO (Either (String, ByteString) a))
-> Maybe MediaType
-> ByteString
-> [Int]
-> Request
-> ServiceConfig
-> GClient a
forall a.
(Stream -> ResourceT IO (Either (String, ByteString) a))
-> Maybe MediaType
-> ByteString
-> [Int]
-> Request
-> ServiceConfig
-> GClient a
gClient (Proxy c -> Stream -> ResourceT IO (Either (String, ByteString) a)
forall {k} (c :: k) a.
FromStream c a =>
Proxy c -> Stream -> ResourceT IO (Either (String, ByteString) a)
fromStream Proxy c
p) (MediaType -> Maybe MediaType
forall a. a -> Maybe a
Just (Proxy c -> MediaType
forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy c
p))
discard ::
Method ->
[Int] ->
Request ->
ServiceConfig ->
GClient ()
discard :: ByteString -> [Int] -> Request -> ServiceConfig -> GClient ()
discard = (Stream -> ResourceT IO (Either (String, ByteString) ()))
-> Maybe MediaType
-> ByteString
-> [Int]
-> Request
-> ServiceConfig
-> GClient ()
forall a.
(Stream -> ResourceT IO (Either (String, ByteString) a))
-> Maybe MediaType
-> ByteString
-> [Int]
-> Request
-> ServiceConfig
-> GClient a
gClient (\Stream
b -> ConduitT () Void (ResourceT IO) () -> ResourceT IO ()
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (Stream
b Stream
-> ConduitT ByteString Void (ResourceT IO) ()
-> ConduitT () Void (ResourceT IO) ()
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ConduitT ByteString Void (ResourceT IO) ()
forall (m :: * -> *) a o. Monad m => ConduitT a o m ()
Conduit.sinkNull) ResourceT IO ()
-> ResourceT IO (Either (String, ByteString) ())
-> ResourceT IO (Either (String, ByteString) ())
forall a b. ResourceT IO a -> ResourceT IO b -> ResourceT IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Either (String, ByteString) ()
-> ResourceT IO (Either (String, ByteString) ())
forall a. a -> ResourceT IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> Either (String, ByteString) ()
forall a b. b -> Either a b
Right ())) Maybe MediaType
forall a. Maybe a
Nothing
gClient ::
(Stream -> ResourceT IO (Either (String, LBS.ByteString) a)) ->
Maybe MediaType ->
Method ->
[Int] ->
Request ->
ServiceConfig ->
GClient a
gClient :: forall a.
(Stream -> ResourceT IO (Either (String, ByteString) a))
-> Maybe MediaType
-> ByteString
-> [Int]
-> Request
-> ServiceConfig
-> GClient a
gClient Stream -> ResourceT IO (Either (String, ByteString) a)
f Maybe MediaType
cs ByteString
m [Int]
statuses Request
rq ServiceConfig
s =
GClient
{ _cliAccept :: Maybe MediaType
_cliAccept = Maybe MediaType
cs,
_cliMethod :: ByteString
_cliMethod = ByteString
m,
_cliCheck :: Status -> Bool
_cliCheck = \Status
status -> Status -> Int
forall a. Enum a => a -> Int
fromEnum Status
status Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Int]
statuses,
_cliService :: ServiceConfig
_cliService = ServiceConfig
s,
_cliRequest :: Request
_cliRequest = Request
rq,
_cliResponse :: Stream -> ResourceT IO (Either (String, ByteString) a)
_cliResponse = Stream -> ResourceT IO (Either (String, ByteString) a)
f
}
class (Accept c) => ToBody c a where
toBody :: Proxy c -> a -> GBody
instance ToBody OctetStream ByteString where
toBody :: Proxy OctetStream -> ByteString -> GBody
toBody Proxy OctetStream
p = MediaType -> RequestBody -> GBody
GBody (Proxy OctetStream -> MediaType
forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy OctetStream
p) (RequestBody -> GBody)
-> (ByteString -> RequestBody) -> ByteString -> GBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
RequestBodyBS
instance ToBody OctetStream LBS.ByteString where
toBody :: Proxy OctetStream -> ByteString -> GBody
toBody Proxy OctetStream
p = MediaType -> RequestBody -> GBody
GBody (Proxy OctetStream -> MediaType
forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy OctetStream
p) (RequestBody -> GBody)
-> (ByteString -> RequestBody) -> ByteString -> GBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
RequestBodyLBS
instance ToBody PlainText ByteString where
toBody :: Proxy PlainText -> ByteString -> GBody
toBody Proxy PlainText
p = MediaType -> RequestBody -> GBody
GBody (Proxy PlainText -> MediaType
forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy PlainText
p) (RequestBody -> GBody)
-> (ByteString -> RequestBody) -> ByteString -> GBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
RequestBodyBS
instance ToBody PlainText LBS.ByteString where
toBody :: Proxy PlainText -> ByteString -> GBody
toBody Proxy PlainText
p = MediaType -> RequestBody -> GBody
GBody (Proxy PlainText -> MediaType
forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy PlainText
p) (RequestBody -> GBody)
-> (ByteString -> RequestBody) -> ByteString -> GBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
RequestBodyLBS
instance (ToJSON a) => ToBody JSON a where
toBody :: Proxy JSON -> a -> GBody
toBody Proxy JSON
p = MediaType -> RequestBody -> GBody
GBody (Proxy JSON -> MediaType
forall {k} (ctype :: k). Accept ctype => Proxy ctype -> MediaType
contentType Proxy JSON
p) (RequestBody -> GBody) -> (a -> RequestBody) -> a -> GBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> RequestBody
RequestBodyLBS (ByteString -> RequestBody)
-> (a -> ByteString) -> a -> RequestBody
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. ToJSON a => a -> ByteString
encode
class (Accept c) => FromStream c a where
fromStream ::
Proxy c ->
Stream ->
ResourceT IO (Either (String, LBS.ByteString) a)
instance FromStream OctetStream Stream where
fromStream :: Proxy OctetStream
-> Stream -> ResourceT IO (Either (String, ByteString) Stream)
fromStream Proxy OctetStream
Proxy = Either (String, ByteString) Stream
-> ResourceT IO (Either (String, ByteString) Stream)
forall a. a -> ResourceT IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (String, ByteString) Stream
-> ResourceT IO (Either (String, ByteString) Stream))
-> (Stream -> Either (String, ByteString) Stream)
-> Stream
-> ResourceT IO (Either (String, ByteString) Stream)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream -> Either (String, ByteString) Stream
forall a b. b -> Either a b
Right
instance (FromJSON a) => FromStream JSON a where
fromStream :: Proxy JSON
-> Stream -> ResourceT IO (Either (String, ByteString) a)
fromStream Proxy JSON
Proxy Stream
s = do
ByteString
bs <- Stream -> ResourceT IO ByteString
sinkLBS Stream
s
case ByteString -> Either String a
forall a. FromJSON a => ByteString -> Either String a
eitherDecode ByteString
bs of
Left String
e -> Either (String, ByteString) a
-> ResourceT IO (Either (String, ByteString) a)
forall a. a -> ResourceT IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (String, ByteString) a
-> ResourceT IO (Either (String, ByteString) a))
-> Either (String, ByteString) a
-> ResourceT IO (Either (String, ByteString) a)
forall a b. (a -> b) -> a -> b
$! (String, ByteString) -> Either (String, ByteString) a
forall a b. a -> Either a b
Left (String
e, ByteString
bs)
Right a
x -> Either (String, ByteString) a
-> ResourceT IO (Either (String, ByteString) a)
forall a. a -> ResourceT IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (String, ByteString) a
-> ResourceT IO (Either (String, ByteString) a))
-> Either (String, ByteString) a
-> ResourceT IO (Either (String, ByteString) a)
forall a b. (a -> b) -> a -> b
$! a -> Either (String, ByteString) a
forall a b. b -> Either a b
Right a
x
class GoogleRequest a where
type Rs a :: Type
type Scopes a :: [Symbol]
requestClient :: a -> GClient (Rs a)
class GoogleClient fn where
type Fn fn :: Type
buildClient :: Proxy fn -> Request -> Fn fn
data Captures (s :: Symbol) a
data CaptureMode (s :: Symbol) (m :: Symbol) a
data MultipartRelated (cs :: [Type]) m
instance
( ToBody c m,
GoogleClient fn
) =>
GoogleClient (MultipartRelated (c ': cs) m :> fn)
where
type Fn (MultipartRelated (c ': cs) m :> fn) = m -> GBody -> Fn fn
buildClient :: Proxy (MultipartRelated (c : cs) m :> fn)
-> Request -> Fn (MultipartRelated (c : cs) m :> fn)
buildClient Proxy (MultipartRelated (c : cs) m :> fn)
Proxy Request
rq m
m GBody
b =
Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn) (Request -> Fn fn) -> Request -> Fn fn
forall a b. (a -> b) -> a -> b
$
Request -> [GBody] -> Request
setBody Request
rq [Proxy c -> m -> GBody
forall {k} (c :: k) a. ToBody c a => Proxy c -> a -> GBody
toBody (Proxy c
forall {k} (t :: k). Proxy t
Proxy :: Proxy c) m
m, GBody
b]
instance (GoogleClient fn) => GoogleClient (AltMedia :> fn) where
type Fn (AltMedia :> fn) = GBody -> Fn fn
buildClient :: Proxy (AltMedia :> fn) -> Request -> Fn (AltMedia :> fn)
buildClient Proxy (AltMedia :> fn)
Proxy Request
rq GBody
b =
Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn) (Request -> Fn fn) -> Request -> Fn fn
forall a b. (a -> b) -> a -> b
$
Request -> [GBody] -> Request
setBody Request
rq [GBody
b]
instance (KnownSymbol s, GoogleClient fn) => GoogleClient (s :> fn) where
type Fn (s :> fn) = Fn fn
buildClient :: Proxy (s :> fn) -> Request -> Fn (s :> fn)
buildClient Proxy (s :> fn)
Proxy Request
rq =
Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn) (Request -> Fn fn) -> Request -> Fn fn
forall a b. (a -> b) -> a -> b
$
Request -> Builder -> Request
appendPath Request
rq (Proxy s -> Builder
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> Builder
buildSymbol (Proxy s
forall {k} (t :: k). Proxy t
Proxy :: Proxy s))
instance (GoogleClient a, GoogleClient b) => GoogleClient (a :<|> b) where
type Fn (a :<|> b) = Fn a :<|> Fn b
buildClient :: Proxy (a :<|> b) -> Request -> Fn (a :<|> b)
buildClient Proxy (a :<|> b)
Proxy Request
rq =
Proxy a -> Request -> Fn a
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy a
forall {k} (t :: k). Proxy t
Proxy :: Proxy a) Request
rq
Fn a -> Fn b -> Fn a :<|> Fn b
forall a b. a -> b -> a :<|> b
:<|> Proxy b -> Request -> Fn b
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy b
forall {k} (t :: k). Proxy t
Proxy :: Proxy b) Request
rq
instance
( KnownSymbol s,
ToHttpApiData a,
GoogleClient fn
) =>
GoogleClient (Capture s a :> fn)
where
type Fn (Capture s a :> fn) = a -> Fn fn
buildClient :: Proxy (Capture s a :> fn) -> Request -> Fn (Capture s a :> fn)
buildClient Proxy (Capture s a :> fn)
Proxy Request
rq =
Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn)
(Request -> Fn fn) -> (a -> Request) -> a -> Fn fn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> Builder -> Request
appendPath Request
rq
(Builder -> Request) -> (a -> Builder) -> a -> Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
forall a. ToHttpApiData a => a -> Builder
buildText
instance
( KnownSymbol s,
ToHttpApiData a,
GoogleClient fn
) =>
GoogleClient (Captures s a :> fn)
where
type Fn (Captures s a :> fn) = [a] -> Fn fn
buildClient :: Proxy (Captures s a :> fn) -> Request -> Fn (Captures s a :> fn)
buildClient Proxy (Captures s a :> fn)
Proxy Request
rq =
Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn)
(Request -> Fn fn) -> ([a] -> Request) -> [a] -> Fn fn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> [a] -> Request
forall a. ToHttpApiData a => Request -> [a] -> Request
appendPaths Request
rq
instance
( KnownSymbol s,
KnownSymbol m,
ToHttpApiData a,
GoogleClient fn
) =>
GoogleClient (CaptureMode s m a :> fn)
where
type Fn (CaptureMode s m a :> fn) = a -> Fn fn
buildClient :: Proxy (CaptureMode s m a :> fn)
-> Request -> Fn (CaptureMode s m a :> fn)
buildClient Proxy (CaptureMode s m a :> fn)
Proxy Request
rq a
x =
Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn)
(Request -> Fn fn) -> (Builder -> Request) -> Builder -> Fn fn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> Builder -> Request
appendPath Request
rq
(Builder -> Fn fn) -> Builder -> Fn fn
forall a b. (a -> b) -> a -> b
$ a -> Builder
forall a. ToHttpApiData a => a -> Builder
buildText a
x Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
":" Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Proxy m -> Builder
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> Builder
buildSymbol (Proxy m
forall {k} (t :: k). Proxy t
Proxy :: Proxy m)
instance
( KnownSymbol s,
ToHttpApiData a,
GoogleClient fn
) =>
GoogleClient (QueryParam s a :> fn)
where
type Fn (QueryParam s a :> fn) = Maybe a -> Fn fn
buildClient :: Proxy (QueryParam s a :> fn)
-> Request -> Fn (QueryParam s a :> fn)
buildClient Proxy (QueryParam s a :> fn)
Proxy Request
rq Maybe a
mx = Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn) (Request -> Fn fn) -> Request -> Fn fn
forall a b. (a -> b) -> a -> b
$
case Maybe a
mx of
Maybe a
Nothing -> Request
rq
Just a
x -> Request -> ByteString -> Maybe Text -> Request
appendQuery Request
rq ByteString
k Maybe Text
v
where
k :: ByteString
k = Proxy s -> ByteString
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> ByteString
byteSymbol (Proxy s
forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
v :: Maybe Text
v = Text -> Maybe Text
forall a. a -> Maybe a
Just (a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam a
x)
instance
( KnownSymbol s,
ToHttpApiData a,
GoogleClient fn
) =>
GoogleClient (QueryParams s a :> fn)
where
type Fn (QueryParams s a :> fn) = [a] -> Fn fn
buildClient :: Proxy (QueryParams s a :> fn)
-> Request -> Fn (QueryParams s a :> fn)
buildClient Proxy (QueryParams s a :> fn)
Proxy Request
rq = Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn) (Request -> Fn fn) -> ([a] -> Request) -> [a] -> Fn fn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Request -> a -> Request) -> Request -> [a] -> Request
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl' Request -> a -> Request
go Request
rq
where
go :: Request -> a -> Request
go Request
r = Request -> ByteString -> Maybe Text -> Request
appendQuery Request
r ByteString
k (Maybe Text -> Request) -> (a -> Maybe Text) -> a -> Request
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> (a -> Text) -> a -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam
k :: ByteString
k = Proxy s -> ByteString
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> ByteString
byteSymbol (Proxy s
forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
instance
( KnownSymbol s,
ToHttpApiData a,
GoogleClient fn
) =>
GoogleClient (Header s a :> fn)
where
type Fn (Header s a :> fn) = Maybe a -> Fn fn
buildClient :: Proxy (Header s a :> fn) -> Request -> Fn (Header s a :> fn)
buildClient Proxy (Header s a :> fn)
Proxy Request
rq Maybe a
mx = Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn) (Request -> Fn fn) -> Request -> Fn fn
forall a b. (a -> b) -> a -> b
$
case Maybe a
mx of
Maybe a
Nothing -> Request
rq
Just a
x -> Request -> CI ByteString -> Maybe Text -> Request
appendHeader Request
rq (ByteString -> CI ByteString
forall s. FoldCase s => s -> CI s
CI.mk ByteString
k) Maybe Text
v
where
k :: ByteString
k = Proxy s -> ByteString
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> ByteString
byteSymbol (Proxy s
forall {k} (t :: k). Proxy t
Proxy :: Proxy s)
v :: Maybe Text
v = Text -> Maybe Text
forall a. a -> Maybe a
Just (a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam a
x)
instance
( ToBody c a,
GoogleClient fn
) =>
GoogleClient (ReqBody (c ': cs) a :> fn)
where
type Fn (ReqBody (c ': cs) a :> fn) = a -> Fn fn
buildClient :: Proxy (ReqBody (c : cs) a :> fn)
-> Request -> Fn (ReqBody (c : cs) a :> fn)
buildClient Proxy (ReqBody (c : cs) a :> fn)
Proxy Request
rq a
x =
Proxy fn -> Request -> Fn fn
forall {k} (fn :: k).
GoogleClient fn =>
Proxy fn -> Request -> Fn fn
buildClient (Proxy fn
forall {k} (t :: k). Proxy t
Proxy :: Proxy fn) (Request -> Fn fn) -> Request -> Fn fn
forall a b. (a -> b) -> a -> b
$
Request -> [GBody] -> Request
setBody Request
rq [Proxy c -> a -> GBody
forall {k} (c :: k) a. ToBody c a => Proxy c -> a -> GBody
toBody (Proxy c
forall {k} (t :: k). Proxy t
Proxy :: Proxy c) a
x]
instance {-# OVERLAPPABLE #-} (FromStream c a) => GoogleClient (Get (c ': cs) a) where
type Fn (Get (c ': cs) a) = ServiceConfig -> GClient a
buildClient :: Proxy (Get (c : cs) a) -> Request -> Fn (Get (c : cs) a)
buildClient Proxy (Get (c : cs) a)
Proxy = Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
forall {k} (c :: k) a.
FromStream c a =>
Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
mime (Proxy c
forall {k} (t :: k). Proxy t
Proxy :: Proxy c) ByteString
methodGet [Int
200, Int
203]
instance {-# OVERLAPPING #-} GoogleClient (Get (c ': cs) ()) where
type Fn (Get (c ': cs) ()) = ServiceConfig -> GClient ()
buildClient :: Proxy (Get (c : cs) ()) -> Request -> Fn (Get (c : cs) ())
buildClient Proxy (Get (c : cs) ())
Proxy = ByteString -> [Int] -> Request -> ServiceConfig -> GClient ()
discard ByteString
methodGet [Int
204]
instance {-# OVERLAPPABLE #-} (FromStream c a, cs' ~ (c ': cs)) => GoogleClient (Post cs' a) where
type Fn (Post cs' a) = ServiceConfig -> GClient a
buildClient :: Proxy (Post cs' a) -> Request -> Fn (Post cs' a)
buildClient Proxy (Post cs' a)
Proxy = Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
forall {k} (c :: k) a.
FromStream c a =>
Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
mime (Proxy c
forall {k} (t :: k). Proxy t
Proxy :: Proxy c) ByteString
methodPost [Int
200, Int
201]
instance {-# OVERLAPPING #-} GoogleClient (Post cs ()) where
type Fn (Post cs ()) = ServiceConfig -> GClient ()
buildClient :: Proxy (Post cs ()) -> Request -> Fn (Post cs ())
buildClient Proxy (Post cs ())
Proxy = ByteString -> [Int] -> Request -> ServiceConfig -> GClient ()
discard ByteString
methodPost [Int
204]
instance {-# OVERLAPPABLE #-} (FromStream c a) => GoogleClient (Put (c ': cs) a) where
type Fn (Put (c ': cs) a) = ServiceConfig -> GClient a
buildClient :: Proxy (Put (c : cs) a) -> Request -> Fn (Put (c : cs) a)
buildClient Proxy (Put (c : cs) a)
Proxy = Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
forall {k} (c :: k) a.
FromStream c a =>
Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
mime (Proxy c
forall {k} (t :: k). Proxy t
Proxy :: Proxy c) ByteString
methodPut [Int
200, Int
201]
instance {-# OVERLAPPING #-} GoogleClient (Put (c ': cs) ()) where
type Fn (Put (c ': cs) ()) = ServiceConfig -> GClient ()
buildClient :: Proxy (Put (c : cs) ()) -> Request -> Fn (Put (c : cs) ())
buildClient Proxy (Put (c : cs) ())
Proxy = ByteString -> [Int] -> Request -> ServiceConfig -> GClient ()
discard ByteString
methodPut [Int
204]
instance {-# OVERLAPPABLE #-} (FromStream c a) => GoogleClient (Patch (c ': cs) a) where
type Fn (Patch (c ': cs) a) = ServiceConfig -> GClient a
buildClient :: Proxy (Patch (c : cs) a) -> Request -> Fn (Patch (c : cs) a)
buildClient Proxy (Patch (c : cs) a)
Proxy = Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
forall {k} (c :: k) a.
FromStream c a =>
Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
mime (Proxy c
forall {k} (t :: k). Proxy t
Proxy :: Proxy c) ByteString
methodPatch [Int
200, Int
201]
instance {-# OVERLAPPING #-} GoogleClient (Patch (c ': cs) ()) where
type Fn (Patch (c ': cs) ()) = ServiceConfig -> GClient ()
buildClient :: Proxy (Patch (c : cs) ()) -> Request -> Fn (Patch (c : cs) ())
buildClient Proxy (Patch (c : cs) ())
Proxy = ByteString -> [Int] -> Request -> ServiceConfig -> GClient ()
discard ByteString
methodPatch [Int
204]
instance {-# OVERLAPPABLE #-} (FromStream c a) => GoogleClient (Delete (c ': cs) a) where
type Fn (Delete (c ': cs) a) = ServiceConfig -> GClient a
buildClient :: Proxy (Delete (c : cs) a) -> Request -> Fn (Delete (c : cs) a)
buildClient Proxy (Delete (c : cs) a)
Proxy = Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
forall {k} (c :: k) a.
FromStream c a =>
Proxy c
-> ByteString -> [Int] -> Request -> ServiceConfig -> GClient a
mime (Proxy c
forall {k} (t :: k). Proxy t
Proxy :: Proxy c) ByteString
methodDelete [Int
200, Int
202]
instance {-# OVERLAPPING #-} GoogleClient (Delete (c ': cs) ()) where
type Fn (Delete (c ': cs) ()) = ServiceConfig -> GClient ()
buildClient :: Proxy (Delete (c : cs) ()) -> Request -> Fn (Delete (c : cs) ())
buildClient Proxy (Delete (c : cs) ())
Proxy = ByteString -> [Int] -> Request -> ServiceConfig -> GClient ()
discard ByteString
methodDelete [Int
204]
sinkLBS :: Stream -> ResourceT IO LBS.ByteString
sinkLBS :: Stream -> ResourceT IO ByteString
sinkLBS = ConduitT () Void (ResourceT IO) ByteString
-> ResourceT IO ByteString
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void (ResourceT IO) ByteString
-> ResourceT IO ByteString)
-> (Stream -> ConduitT () Void (ResourceT IO) ByteString)
-> Stream
-> ResourceT IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Stream
-> ConduitT ByteString Void (ResourceT IO) ByteString
-> ConduitT () Void (ResourceT IO) ByteString
forall (m :: * -> *) a b c r.
Monad m =>
ConduitT a b m () -> ConduitT b c m r -> ConduitT a c m r
.| ConduitT ByteString Void (ResourceT IO) ByteString
forall (m :: * -> *) lazy strict o.
(Monad m, LazySequence lazy strict) =>
ConduitT strict o m lazy
Conduit.sinkLazy)
buildText :: (ToHttpApiData a) => a -> Builder
buildText :: forall a. ToHttpApiData a => a -> Builder
buildText = Text -> Builder
Build.fromText (Text -> Builder) -> (a -> Text) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam
buildSymbol :: forall n proxy. (KnownSymbol n) => proxy n -> Builder
buildSymbol :: forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> Builder
buildSymbol = String -> Builder
Build.fromString (String -> Builder) -> (proxy n -> String) -> proxy n -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. proxy n -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal
byteSymbol :: forall n proxy. (KnownSymbol n) => proxy n -> ByteString
byteSymbol :: forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> ByteString
byteSymbol = String -> ByteString
BS8.pack (String -> ByteString)
-> (proxy n -> String) -> proxy n -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. proxy n -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal
newtype Seconds = Seconds Int
deriving
( Seconds -> Seconds -> Bool
(Seconds -> Seconds -> Bool)
-> (Seconds -> Seconds -> Bool) -> Eq Seconds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Seconds -> Seconds -> Bool
== :: Seconds -> Seconds -> Bool
$c/= :: Seconds -> Seconds -> Bool
/= :: Seconds -> Seconds -> Bool
Eq,
Eq Seconds
Eq Seconds =>
(Seconds -> Seconds -> Ordering)
-> (Seconds -> Seconds -> Bool)
-> (Seconds -> Seconds -> Bool)
-> (Seconds -> Seconds -> Bool)
-> (Seconds -> Seconds -> Bool)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> Ord Seconds
Seconds -> Seconds -> Bool
Seconds -> Seconds -> Ordering
Seconds -> Seconds -> Seconds
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Seconds -> Seconds -> Ordering
compare :: Seconds -> Seconds -> Ordering
$c< :: Seconds -> Seconds -> Bool
< :: Seconds -> Seconds -> Bool
$c<= :: Seconds -> Seconds -> Bool
<= :: Seconds -> Seconds -> Bool
$c> :: Seconds -> Seconds -> Bool
> :: Seconds -> Seconds -> Bool
$c>= :: Seconds -> Seconds -> Bool
>= :: Seconds -> Seconds -> Bool
$cmax :: Seconds -> Seconds -> Seconds
max :: Seconds -> Seconds -> Seconds
$cmin :: Seconds -> Seconds -> Seconds
min :: Seconds -> Seconds -> Seconds
Ord,
ReadPrec [Seconds]
ReadPrec Seconds
Int -> ReadS Seconds
ReadS [Seconds]
(Int -> ReadS Seconds)
-> ReadS [Seconds]
-> ReadPrec Seconds
-> ReadPrec [Seconds]
-> Read Seconds
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Seconds
readsPrec :: Int -> ReadS Seconds
$creadList :: ReadS [Seconds]
readList :: ReadS [Seconds]
$creadPrec :: ReadPrec Seconds
readPrec :: ReadPrec Seconds
$creadListPrec :: ReadPrec [Seconds]
readListPrec :: ReadPrec [Seconds]
Read,
Int -> Seconds -> ShowS
[Seconds] -> ShowS
Seconds -> String
(Int -> Seconds -> ShowS)
-> (Seconds -> String) -> ([Seconds] -> ShowS) -> Show Seconds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Seconds -> ShowS
showsPrec :: Int -> Seconds -> ShowS
$cshow :: Seconds -> String
show :: Seconds -> String
$cshowList :: [Seconds] -> ShowS
showList :: [Seconds] -> ShowS
Show,
Int -> Seconds
Seconds -> Int
Seconds -> [Seconds]
Seconds -> Seconds
Seconds -> Seconds -> [Seconds]
Seconds -> Seconds -> Seconds -> [Seconds]
(Seconds -> Seconds)
-> (Seconds -> Seconds)
-> (Int -> Seconds)
-> (Seconds -> Int)
-> (Seconds -> [Seconds])
-> (Seconds -> Seconds -> [Seconds])
-> (Seconds -> Seconds -> [Seconds])
-> (Seconds -> Seconds -> Seconds -> [Seconds])
-> Enum Seconds
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Seconds -> Seconds
succ :: Seconds -> Seconds
$cpred :: Seconds -> Seconds
pred :: Seconds -> Seconds
$ctoEnum :: Int -> Seconds
toEnum :: Int -> Seconds
$cfromEnum :: Seconds -> Int
fromEnum :: Seconds -> Int
$cenumFrom :: Seconds -> [Seconds]
enumFrom :: Seconds -> [Seconds]
$cenumFromThen :: Seconds -> Seconds -> [Seconds]
enumFromThen :: Seconds -> Seconds -> [Seconds]
$cenumFromTo :: Seconds -> Seconds -> [Seconds]
enumFromTo :: Seconds -> Seconds -> [Seconds]
$cenumFromThenTo :: Seconds -> Seconds -> Seconds -> [Seconds]
enumFromThenTo :: Seconds -> Seconds -> Seconds -> [Seconds]
Enum,
Integer -> Seconds
Seconds -> Seconds
Seconds -> Seconds -> Seconds
(Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds)
-> (Seconds -> Seconds)
-> (Seconds -> Seconds)
-> (Integer -> Seconds)
-> Num Seconds
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Seconds -> Seconds -> Seconds
+ :: Seconds -> Seconds -> Seconds
$c- :: Seconds -> Seconds -> Seconds
- :: Seconds -> Seconds -> Seconds
$c* :: Seconds -> Seconds -> Seconds
* :: Seconds -> Seconds -> Seconds
$cnegate :: Seconds -> Seconds
negate :: Seconds -> Seconds
$cabs :: Seconds -> Seconds
abs :: Seconds -> Seconds
$csignum :: Seconds -> Seconds
signum :: Seconds -> Seconds
$cfromInteger :: Integer -> Seconds
fromInteger :: Integer -> Seconds
Num,
Seconds
Seconds -> Seconds -> Bounded Seconds
forall a. a -> a -> Bounded a
$cminBound :: Seconds
minBound :: Seconds
$cmaxBound :: Seconds
maxBound :: Seconds
Bounded,
Enum Seconds
Real Seconds
(Real Seconds, Enum Seconds) =>
(Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> (Seconds, Seconds))
-> (Seconds -> Seconds -> (Seconds, Seconds))
-> (Seconds -> Integer)
-> Integral Seconds
Seconds -> Integer
Seconds -> Seconds -> (Seconds, Seconds)
Seconds -> Seconds -> Seconds
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Seconds -> Seconds -> Seconds
quot :: Seconds -> Seconds -> Seconds
$crem :: Seconds -> Seconds -> Seconds
rem :: Seconds -> Seconds -> Seconds
$cdiv :: Seconds -> Seconds -> Seconds
div :: Seconds -> Seconds -> Seconds
$cmod :: Seconds -> Seconds -> Seconds
mod :: Seconds -> Seconds -> Seconds
$cquotRem :: Seconds -> Seconds -> (Seconds, Seconds)
quotRem :: Seconds -> Seconds -> (Seconds, Seconds)
$cdivMod :: Seconds -> Seconds -> (Seconds, Seconds)
divMod :: Seconds -> Seconds -> (Seconds, Seconds)
$ctoInteger :: Seconds -> Integer
toInteger :: Seconds -> Integer
Integral,
Num Seconds
Ord Seconds
(Num Seconds, Ord Seconds) => (Seconds -> Rational) -> Real Seconds
Seconds -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Seconds -> Rational
toRational :: Seconds -> Rational
Real,
(forall x. Seconds -> Rep Seconds x)
-> (forall x. Rep Seconds x -> Seconds) -> Generic Seconds
forall x. Rep Seconds x -> Seconds
forall x. Seconds -> Rep Seconds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Seconds -> Rep Seconds x
from :: forall x. Seconds -> Rep Seconds x
$cto :: forall x. Rep Seconds x -> Seconds
to :: forall x. Rep Seconds x -> Seconds
Generic
)
seconds :: Seconds -> Int
seconds :: Seconds -> Int
seconds (Seconds Int
n)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = Int
0
| Bool
otherwise = Int
n
microseconds :: Seconds -> Int
microseconds :: Seconds -> Int
microseconds = (Int
1000000 *) (Int -> Int) -> (Seconds -> Int) -> Seconds -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seconds -> Int
seconds
newtype FieldMask = FieldMask {FieldMask -> Text
fromFieldMask :: Text}
deriving
( FieldMask -> FieldMask -> Bool
(FieldMask -> FieldMask -> Bool)
-> (FieldMask -> FieldMask -> Bool) -> Eq FieldMask
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldMask -> FieldMask -> Bool
== :: FieldMask -> FieldMask -> Bool
$c/= :: FieldMask -> FieldMask -> Bool
/= :: FieldMask -> FieldMask -> Bool
Eq,
Eq FieldMask
Eq FieldMask =>
(FieldMask -> FieldMask -> Ordering)
-> (FieldMask -> FieldMask -> Bool)
-> (FieldMask -> FieldMask -> Bool)
-> (FieldMask -> FieldMask -> Bool)
-> (FieldMask -> FieldMask -> Bool)
-> (FieldMask -> FieldMask -> FieldMask)
-> (FieldMask -> FieldMask -> FieldMask)
-> Ord FieldMask
FieldMask -> FieldMask -> Bool
FieldMask -> FieldMask -> Ordering
FieldMask -> FieldMask -> FieldMask
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldMask -> FieldMask -> Ordering
compare :: FieldMask -> FieldMask -> Ordering
$c< :: FieldMask -> FieldMask -> Bool
< :: FieldMask -> FieldMask -> Bool
$c<= :: FieldMask -> FieldMask -> Bool
<= :: FieldMask -> FieldMask -> Bool
$c> :: FieldMask -> FieldMask -> Bool
> :: FieldMask -> FieldMask -> Bool
$c>= :: FieldMask -> FieldMask -> Bool
>= :: FieldMask -> FieldMask -> Bool
$cmax :: FieldMask -> FieldMask -> FieldMask
max :: FieldMask -> FieldMask -> FieldMask
$cmin :: FieldMask -> FieldMask -> FieldMask
min :: FieldMask -> FieldMask -> FieldMask
Ord,
Int -> FieldMask -> ShowS
[FieldMask] -> ShowS
FieldMask -> String
(Int -> FieldMask -> ShowS)
-> (FieldMask -> String)
-> ([FieldMask] -> ShowS)
-> Show FieldMask
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldMask -> ShowS
showsPrec :: Int -> FieldMask -> ShowS
$cshow :: FieldMask -> String
show :: FieldMask -> String
$cshowList :: [FieldMask] -> ShowS
showList :: [FieldMask] -> ShowS
Show,
ReadPrec [FieldMask]
ReadPrec FieldMask
Int -> ReadS FieldMask
ReadS [FieldMask]
(Int -> ReadS FieldMask)
-> ReadS [FieldMask]
-> ReadPrec FieldMask
-> ReadPrec [FieldMask]
-> Read FieldMask
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldMask
readsPrec :: Int -> ReadS FieldMask
$creadList :: ReadS [FieldMask]
readList :: ReadS [FieldMask]
$creadPrec :: ReadPrec FieldMask
readPrec :: ReadPrec FieldMask
$creadListPrec :: ReadPrec [FieldMask]
readListPrec :: ReadPrec [FieldMask]
Read,
String -> FieldMask
(String -> FieldMask) -> IsString FieldMask
forall a. (String -> a) -> IsString a
$cfromString :: String -> FieldMask
fromString :: String -> FieldMask
IsString,
(forall x. FieldMask -> Rep FieldMask x)
-> (forall x. Rep FieldMask x -> FieldMask) -> Generic FieldMask
forall x. Rep FieldMask x -> FieldMask
forall x. FieldMask -> Rep FieldMask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. FieldMask -> Rep FieldMask x
from :: forall x. FieldMask -> Rep FieldMask x
$cto :: forall x. Rep FieldMask x -> FieldMask
to :: forall x. Rep FieldMask x -> FieldMask
Generic,
Text -> Either Text FieldMask
ByteString -> Either Text FieldMask
(Text -> Either Text FieldMask)
-> (ByteString -> Either Text FieldMask)
-> (Text -> Either Text FieldMask)
-> FromHttpApiData FieldMask
forall a.
(Text -> Either Text a)
-> (ByteString -> Either Text a)
-> (Text -> Either Text a)
-> FromHttpApiData a
$cparseUrlPiece :: Text -> Either Text FieldMask
parseUrlPiece :: Text -> Either Text FieldMask
$cparseHeader :: ByteString -> Either Text FieldMask
parseHeader :: ByteString -> Either Text FieldMask
$cparseQueryParam :: Text -> Either Text FieldMask
parseQueryParam :: Text -> Either Text FieldMask
FromHttpApiData,
FieldMask -> Text
FieldMask -> ByteString
FieldMask -> Builder
(FieldMask -> Text)
-> (FieldMask -> Builder)
-> (FieldMask -> ByteString)
-> (FieldMask -> Text)
-> (FieldMask -> Builder)
-> ToHttpApiData FieldMask
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> (a -> Builder)
-> ToHttpApiData a
$ctoUrlPiece :: FieldMask -> Text
toUrlPiece :: FieldMask -> Text
$ctoEncodedUrlPiece :: FieldMask -> Builder
toEncodedUrlPiece :: FieldMask -> Builder
$ctoHeader :: FieldMask -> ByteString
toHeader :: FieldMask -> ByteString
$ctoQueryParam :: FieldMask -> Text
toQueryParam :: FieldMask -> Text
$ctoEncodedQueryParam :: FieldMask -> Builder
toEncodedQueryParam :: FieldMask -> Builder
ToHttpApiData,
Maybe FieldMask
Value -> Parser [FieldMask]
Value -> Parser FieldMask
(Value -> Parser FieldMask)
-> (Value -> Parser [FieldMask])
-> Maybe FieldMask
-> FromJSON FieldMask
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser FieldMask
parseJSON :: Value -> Parser FieldMask
$cparseJSONList :: Value -> Parser [FieldMask]
parseJSONList :: Value -> Parser [FieldMask]
$comittedField :: Maybe FieldMask
omittedField :: Maybe FieldMask
FromJSON,
[FieldMask] -> Value
[FieldMask] -> Encoding
FieldMask -> Bool
FieldMask -> Value
FieldMask -> Encoding
(FieldMask -> Value)
-> (FieldMask -> Encoding)
-> ([FieldMask] -> Value)
-> ([FieldMask] -> Encoding)
-> (FieldMask -> Bool)
-> ToJSON FieldMask
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: FieldMask -> Value
toJSON :: FieldMask -> Value
$ctoEncoding :: FieldMask -> Encoding
toEncoding :: FieldMask -> Encoding
$ctoJSONList :: [FieldMask] -> Value
toJSONList :: [FieldMask] -> Value
$ctoEncodingList :: [FieldMask] -> Encoding
toEncodingList :: [FieldMask] -> Encoding
$comitField :: FieldMask -> Bool
omitField :: FieldMask -> Bool
ToJSON
)