{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Circle.Types where
import Autodocodec
( Autodocodec (Autodocodec),
HasCodec (codec),
bimapCodec,
dimapCodec,
object,
optionalField',
requiredField,
requiredField',
shownBoundedEnumCodec,
stringConstCodec,
(.=),
)
import Control.Monad (guard)
import Country
( Country,
alphaTwoUpper,
)
import Data.Aeson
( FromJSON (parseJSON),
Result (Error, Success),
ToJSON (toEncoding, toJSON),
withObject,
withText,
(.:),
(.:?),
)
import Data.Aeson qualified as Aeson
import Data.Aeson.Types (fromJSON)
import Data.Bifunctor
import Data.ByteString.Char8 qualified as BS8
import Data.ByteString.Lazy.Char8 qualified as BSL
import Data.Coerce (coerce)
import Data.Foldable
import Data.List.NonEmpty qualified as NE
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Encoding qualified as TE
import Data.Time
import Data.UUID
import Data.UUID qualified as UUID
import GHC.Generics (Generic)
import Language.Haskell.TH (Exp, Q)
import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax (Lift)
import Network.HTTP.Client (Response)
import Network.HTTP.Types.Method qualified as NHTM
import Refined
import Refined.Unsafe (reallyUnsafeRefine)
import System.Environment (getEnv)
import Text.Regex.PCRE.Heavy
newtype ApiToken = ApiToken
{ ApiToken -> ByteString
unApiToken :: BS8.ByteString
}
deriving (ReadPrec [ApiToken]
ReadPrec ApiToken
Int -> ReadS ApiToken
ReadS [ApiToken]
(Int -> ReadS ApiToken)
-> ReadS [ApiToken]
-> ReadPrec ApiToken
-> ReadPrec [ApiToken]
-> Read ApiToken
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ApiToken]
$creadListPrec :: ReadPrec [ApiToken]
readPrec :: ReadPrec ApiToken
$creadPrec :: ReadPrec ApiToken
readList :: ReadS [ApiToken]
$creadList :: ReadS [ApiToken]
readsPrec :: Int -> ReadS ApiToken
$creadsPrec :: Int -> ReadS ApiToken
Read, Int -> ApiToken -> ShowS
[ApiToken] -> ShowS
ApiToken -> String
(Int -> ApiToken -> ShowS)
-> (ApiToken -> String) -> ([ApiToken] -> ShowS) -> Show ApiToken
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApiToken] -> ShowS
$cshowList :: [ApiToken] -> ShowS
show :: ApiToken -> String
$cshow :: ApiToken -> String
showsPrec :: Int -> ApiToken -> ShowS
$cshowsPrec :: Int -> ApiToken -> ShowS
Show, ApiToken -> ApiToken -> Bool
(ApiToken -> ApiToken -> Bool)
-> (ApiToken -> ApiToken -> Bool) -> Eq ApiToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ApiToken -> ApiToken -> Bool
$c/= :: ApiToken -> ApiToken -> Bool
== :: ApiToken -> ApiToken -> Bool
$c== :: ApiToken -> ApiToken -> Bool
Eq)
data CircleAPIRequest a b c = CircleAPIRequest
{
CircleAPIRequest a b c -> ByteString
rMethod :: !Method,
CircleAPIRequest a b c -> Text
endpoint :: !Text,
CircleAPIRequest a b c -> Params TupleBS8 ByteString
params :: !(Params TupleBS8 BSL.ByteString)
}
deriving (Int -> CircleAPIRequest a b c -> ShowS
[CircleAPIRequest a b c] -> ShowS
CircleAPIRequest a b c -> String
(Int -> CircleAPIRequest a b c -> ShowS)
-> (CircleAPIRequest a b c -> String)
-> ([CircleAPIRequest a b c] -> ShowS)
-> Show (CircleAPIRequest a b c)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b c. Int -> CircleAPIRequest a b c -> ShowS
forall a b c. [CircleAPIRequest a b c] -> ShowS
forall a b c. CircleAPIRequest a b c -> String
showList :: [CircleAPIRequest a b c] -> ShowS
$cshowList :: forall a b c. [CircleAPIRequest a b c] -> ShowS
show :: CircleAPIRequest a b c -> String
$cshow :: forall a b c. CircleAPIRequest a b c -> String
showsPrec :: Int -> CircleAPIRequest a b c -> ShowS
$cshowsPrec :: forall a b c. Int -> CircleAPIRequest a b c -> ShowS
Show)
mkCircleAPIRequest ::
Method ->
Text ->
Params TupleBS8 BSL.ByteString ->
CircleAPIRequest a b c
mkCircleAPIRequest :: ByteString
-> Text -> Params TupleBS8 ByteString -> CircleAPIRequest a b c
mkCircleAPIRequest = ByteString
-> Text -> Params TupleBS8 ByteString -> CircleAPIRequest a b c
forall a b c.
ByteString
-> Text -> Params TupleBS8 ByteString -> CircleAPIRequest a b c
CircleAPIRequest
type family CircleRequest a :: *
data CircleError = CircleError
{ CircleError -> Text
parseError :: !Text,
CircleError -> Reply
errorResponseBody :: !Reply
}
deriving (Int -> CircleError -> ShowS
[CircleError] -> ShowS
CircleError -> String
(Int -> CircleError -> ShowS)
-> (CircleError -> String)
-> ([CircleError] -> ShowS)
-> Show CircleError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CircleError] -> ShowS
$cshowList :: [CircleError] -> ShowS
show :: CircleError -> String
$cshow :: CircleError -> String
showsPrec :: Int -> CircleError -> ShowS
$cshowsPrec :: Int -> CircleError -> ShowS
Show)
data CircleResponseBody a = CircleResponseBody
{ CircleResponseBody a -> Maybe ResponseStatus
circleResponseCode :: !(Maybe ResponseStatus),
CircleResponseBody a -> Maybe ResponseMessage
circleResponseMessage :: !(Maybe ResponseMessage),
CircleResponseBody a -> Maybe a
circleResponseData :: !(Maybe a)
}
deriving (CircleResponseBody a -> CircleResponseBody a -> Bool
(CircleResponseBody a -> CircleResponseBody a -> Bool)
-> (CircleResponseBody a -> CircleResponseBody a -> Bool)
-> Eq (CircleResponseBody a)
forall a.
Eq a =>
CircleResponseBody a -> CircleResponseBody a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CircleResponseBody a -> CircleResponseBody a -> Bool
$c/= :: forall a.
Eq a =>
CircleResponseBody a -> CircleResponseBody a -> Bool
== :: CircleResponseBody a -> CircleResponseBody a -> Bool
$c== :: forall a.
Eq a =>
CircleResponseBody a -> CircleResponseBody a -> Bool
Eq, Int -> CircleResponseBody a -> ShowS
[CircleResponseBody a] -> ShowS
CircleResponseBody a -> String
(Int -> CircleResponseBody a -> ShowS)
-> (CircleResponseBody a -> String)
-> ([CircleResponseBody a] -> ShowS)
-> Show (CircleResponseBody a)
forall a. Show a => Int -> CircleResponseBody a -> ShowS
forall a. Show a => [CircleResponseBody a] -> ShowS
forall a. Show a => CircleResponseBody a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CircleResponseBody a] -> ShowS
$cshowList :: forall a. Show a => [CircleResponseBody a] -> ShowS
show :: CircleResponseBody a -> String
$cshow :: forall a. Show a => CircleResponseBody a -> String
showsPrec :: Int -> CircleResponseBody a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CircleResponseBody a -> ShowS
Show)
instance FromJSON a => FromJSON (CircleResponseBody a) where
parseJSON :: Value -> Parser (CircleResponseBody a)
parseJSON = String
-> (Object -> Parser (CircleResponseBody a))
-> Value
-> Parser (CircleResponseBody a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CircleResponseBody" Object -> Parser (CircleResponseBody a)
forall a. FromJSON a => Object -> Parser (CircleResponseBody a)
parse
where
parse :: Object -> Parser (CircleResponseBody a)
parse Object
o =
Maybe ResponseStatus
-> Maybe ResponseMessage -> Maybe a -> CircleResponseBody a
forall a.
Maybe ResponseStatus
-> Maybe ResponseMessage -> Maybe a -> CircleResponseBody a
CircleResponseBody
(Maybe ResponseStatus
-> Maybe ResponseMessage -> Maybe a -> CircleResponseBody a)
-> Parser (Maybe ResponseStatus)
-> Parser
(Maybe ResponseMessage -> Maybe a -> CircleResponseBody a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe ResponseStatus)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"status"
Parser (Maybe ResponseMessage -> Maybe a -> CircleResponseBody a)
-> Parser (Maybe ResponseMessage)
-> Parser (Maybe a -> CircleResponseBody a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe ResponseMessage)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"message"
Parser (Maybe a -> CircleResponseBody a)
-> Parser (Maybe a) -> Parser (CircleResponseBody a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe a)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"data"
newtype ResponseStatus = ResponseStatus
{ ResponseStatus -> Int
unResponseStatus :: Int
}
deriving (ResponseStatus -> ResponseStatus -> Bool
(ResponseStatus -> ResponseStatus -> Bool)
-> (ResponseStatus -> ResponseStatus -> Bool) -> Eq ResponseStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResponseStatus -> ResponseStatus -> Bool
$c/= :: ResponseStatus -> ResponseStatus -> Bool
== :: ResponseStatus -> ResponseStatus -> Bool
$c== :: ResponseStatus -> ResponseStatus -> Bool
Eq, Int -> ResponseStatus -> ShowS
[ResponseStatus] -> ShowS
ResponseStatus -> String
(Int -> ResponseStatus -> ShowS)
-> (ResponseStatus -> String)
-> ([ResponseStatus] -> ShowS)
-> Show ResponseStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResponseStatus] -> ShowS
$cshowList :: [ResponseStatus] -> ShowS
show :: ResponseStatus -> String
$cshow :: ResponseStatus -> String
showsPrec :: Int -> ResponseStatus -> ShowS
$cshowsPrec :: Int -> ResponseStatus -> ShowS
Show, Value -> Parser [ResponseStatus]
Value -> Parser ResponseStatus
(Value -> Parser ResponseStatus)
-> (Value -> Parser [ResponseStatus]) -> FromJSON ResponseStatus
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ResponseStatus]
$cparseJSONList :: Value -> Parser [ResponseStatus]
parseJSON :: Value -> Parser ResponseStatus
$cparseJSON :: Value -> Parser ResponseStatus
FromJSON)
instance HasCodec ResponseStatus where
codec :: JSONCodec ResponseStatus
codec = (Int -> ResponseStatus)
-> (ResponseStatus -> Int)
-> Codec Value Int Int
-> JSONCodec ResponseStatus
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Int -> ResponseStatus
ResponseStatus ResponseStatus -> Int
unResponseStatus Codec Value Int Int
forall value. HasCodec value => JSONCodec value
codec
newtype ResponseMessage = ResponseMessage
{ ResponseMessage -> Text
unResponseMessage :: Text
}
deriving (ResponseMessage -> ResponseMessage -> Bool
(ResponseMessage -> ResponseMessage -> Bool)
-> (ResponseMessage -> ResponseMessage -> Bool)
-> Eq ResponseMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResponseMessage -> ResponseMessage -> Bool
$c/= :: ResponseMessage -> ResponseMessage -> Bool
== :: ResponseMessage -> ResponseMessage -> Bool
$c== :: ResponseMessage -> ResponseMessage -> Bool
Eq, Int -> ResponseMessage -> ShowS
[ResponseMessage] -> ShowS
ResponseMessage -> String
(Int -> ResponseMessage -> ShowS)
-> (ResponseMessage -> String)
-> ([ResponseMessage] -> ShowS)
-> Show ResponseMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResponseMessage] -> ShowS
$cshowList :: [ResponseMessage] -> ShowS
show :: ResponseMessage -> String
$cshow :: ResponseMessage -> String
showsPrec :: Int -> ResponseMessage -> ShowS
$cshowsPrec :: Int -> ResponseMessage -> ShowS
Show, Value -> Parser [ResponseMessage]
Value -> Parser ResponseMessage
(Value -> Parser ResponseMessage)
-> (Value -> Parser [ResponseMessage]) -> FromJSON ResponseMessage
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ResponseMessage]
$cparseJSONList :: Value -> Parser [ResponseMessage]
parseJSON :: Value -> Parser ResponseMessage
$cparseJSON :: Value -> Parser ResponseMessage
FromJSON)
instance HasCodec ResponseMessage where
codec :: JSONCodec ResponseMessage
codec = (Text -> ResponseMessage)
-> (ResponseMessage -> Text)
-> Codec Value Text Text
-> JSONCodec ResponseMessage
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> ResponseMessage
ResponseMessage ResponseMessage -> Text
unResponseMessage Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
type Reply = Response BSL.ByteString
type Method = NHTM.Method
type Host = Text
data CircleHost
= CircleProduction
| CircleSandbox
deriving (CircleHost -> CircleHost -> Bool
(CircleHost -> CircleHost -> Bool)
-> (CircleHost -> CircleHost -> Bool) -> Eq CircleHost
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CircleHost -> CircleHost -> Bool
$c/= :: CircleHost -> CircleHost -> Bool
== :: CircleHost -> CircleHost -> Bool
$c== :: CircleHost -> CircleHost -> Bool
Eq, Int -> CircleHost -> ShowS
[CircleHost] -> ShowS
CircleHost -> String
(Int -> CircleHost -> ShowS)
-> (CircleHost -> String)
-> ([CircleHost] -> ShowS)
-> Show CircleHost
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CircleHost] -> ShowS
$cshowList :: [CircleHost] -> ShowS
show :: CircleHost -> String
$cshow :: CircleHost -> String
showsPrec :: Int -> CircleHost -> ShowS
$cshowsPrec :: Int -> CircleHost -> ShowS
Show)
hostUri :: CircleHost -> Text
hostUri :: CircleHost -> Text
hostUri CircleHost
CircleProduction = Text
"https://api.circle.com/v1/"
hostUri CircleHost
CircleSandbox = Text
"https://api-sandbox.circle.com/v1/"
data CircleConfig = CircleConfig
{ CircleConfig -> CircleHost
host :: !CircleHost,
CircleConfig -> ApiToken
token :: !ApiToken
}
deriving (CircleConfig -> CircleConfig -> Bool
(CircleConfig -> CircleConfig -> Bool)
-> (CircleConfig -> CircleConfig -> Bool) -> Eq CircleConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CircleConfig -> CircleConfig -> Bool
$c/= :: CircleConfig -> CircleConfig -> Bool
== :: CircleConfig -> CircleConfig -> Bool
$c== :: CircleConfig -> CircleConfig -> Bool
Eq, Int -> CircleConfig -> ShowS
[CircleConfig] -> ShowS
CircleConfig -> String
(Int -> CircleConfig -> ShowS)
-> (CircleConfig -> String)
-> ([CircleConfig] -> ShowS)
-> Show CircleConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CircleConfig] -> ShowS
$cshowList :: [CircleConfig] -> ShowS
show :: CircleConfig -> String
$cshow :: CircleConfig -> String
showsPrec :: Int -> CircleConfig -> ShowS
$cshowsPrec :: Int -> CircleConfig -> ShowS
Show)
credentialsEnv :: Maybe String -> IO ApiToken
credentialsEnv :: Maybe String -> IO ApiToken
credentialsEnv Maybe String
mKey = do
String
key <- case Maybe String
mKey of
Just String
k -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
k
Maybe String
Nothing -> String -> IO String
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
"CIRCLE_API_KEY"
String
token <- String -> IO String
getEnv String
key
ApiToken -> IO ApiToken
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> ApiToken
ApiToken (ByteString -> ApiToken) -> ByteString -> ApiToken
forall a b. (a -> b) -> a -> b
$ String -> ByteString
BS8.pack String
token)
prodEnvConfig :: Maybe String -> IO CircleConfig
prodEnvConfig :: Maybe String -> IO CircleConfig
prodEnvConfig Maybe String
key = do
CircleHost -> ApiToken -> CircleConfig
CircleConfig CircleHost
CircleProduction (ApiToken -> CircleConfig) -> IO ApiToken -> IO CircleConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String -> IO ApiToken
credentialsEnv Maybe String
key
sandboxEnvConfig :: Maybe String -> IO CircleConfig
sandboxEnvConfig :: Maybe String -> IO CircleConfig
sandboxEnvConfig Maybe String
key = do
CircleHost -> ApiToken -> CircleConfig
CircleConfig CircleHost
CircleSandbox (ApiToken -> CircleConfig) -> IO ApiToken -> IO CircleConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String -> IO ApiToken
credentialsEnv Maybe String
key
newtype Query = Query
{ Query -> TupleBS8
unQuery :: TupleBS8
}
deriving (Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c== :: Query -> Query -> Bool
Eq, Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
(Int -> Query -> ShowS)
-> (Query -> String) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Query] -> ShowS
$cshowList :: [Query] -> ShowS
show :: Query -> String
$cshow :: Query -> String
showsPrec :: Int -> Query -> ShowS
$cshowsPrec :: Int -> Query -> ShowS
Show)
newtype Body = Body
{ Body -> ByteString
unBody :: BSL.ByteString
}
deriving (Body -> Body -> Bool
(Body -> Body -> Bool) -> (Body -> Body -> Bool) -> Eq Body
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Body -> Body -> Bool
$c/= :: Body -> Body -> Bool
== :: Body -> Body -> Bool
$c== :: Body -> Body -> Bool
Eq, Int -> Body -> ShowS
[Body] -> ShowS
Body -> String
(Int -> Body -> ShowS)
-> (Body -> String) -> ([Body] -> ShowS) -> Show Body
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Body] -> ShowS
$cshowList :: [Body] -> ShowS
show :: Body -> String
$cshow :: Body -> String
showsPrec :: Int -> Body -> ShowS
$cshowsPrec :: Int -> Body -> ShowS
Show)
data Params b c = Params
{ Params b c -> Maybe Body
paramsBody :: Maybe Body,
Params b c -> [Query]
paramsQuery :: ![Query]
}
deriving (Int -> Params b c -> ShowS
[Params b c] -> ShowS
Params b c -> String
(Int -> Params b c -> ShowS)
-> (Params b c -> String)
-> ([Params b c] -> ShowS)
-> Show (Params b c)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall b c. Int -> Params b c -> ShowS
forall b c. [Params b c] -> ShowS
forall b c. Params b c -> String
showList :: [Params b c] -> ShowS
$cshowList :: forall b c. [Params b c] -> ShowS
show :: Params b c -> String
$cshow :: forall b c. Params b c -> String
showsPrec :: Int -> Params b c -> ShowS
$cshowsPrec :: forall b c. Int -> Params b c -> ShowS
Show)
joinQueryParams :: Params b c -> Params b c -> Params b c
joinQueryParams :: Params b c -> Params b c -> Params b c
joinQueryParams (Params Maybe Body
_ [Query]
xs) (Params Maybe Body
b [Query]
ys) = Maybe Body -> [Query] -> Params b c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
b ([Query]
xs [Query] -> [Query] -> [Query]
forall a. [a] -> [a] -> [a]
++ [Query]
ys)
type TupleBS8 = (BS8.ByteString, BS8.ByteString)
class ToCircleParam param where
toCircleParam :: param -> Params TupleBS8 c -> Params TupleBS8 c
class (ToCircleParam param) => CircleHasParam request param
(-&-) ::
CircleHasParam r param =>
CircleAPIRequest r b c ->
param ->
CircleAPIRequest r b c
CircleAPIRequest r b c
circleAPIRequest -&- :: CircleAPIRequest r b c -> param -> CircleAPIRequest r b c
-&- param
param =
CircleAPIRequest r b c
circleAPIRequest
{ params :: Params TupleBS8 ByteString
params = param -> Params TupleBS8 ByteString -> Params TupleBS8 ByteString
forall param c.
ToCircleParam param =>
param -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam param
param (CircleAPIRequest r b c -> Params TupleBS8 ByteString
forall a b c. CircleAPIRequest a b c -> Params TupleBS8 ByteString
params CircleAPIRequest r b c
circleAPIRequest)
}
newtype =
{ :: PaginationQueryParam
}
deriving (PaginationQueryParams -> PaginationQueryParams -> Bool
(PaginationQueryParams -> PaginationQueryParams -> Bool)
-> (PaginationQueryParams -> PaginationQueryParams -> Bool)
-> Eq PaginationQueryParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaginationQueryParams -> PaginationQueryParams -> Bool
$c/= :: PaginationQueryParams -> PaginationQueryParams -> Bool
== :: PaginationQueryParams -> PaginationQueryParams -> Bool
$c== :: PaginationQueryParams -> PaginationQueryParams -> Bool
Eq, Int -> PaginationQueryParams -> ShowS
[PaginationQueryParams] -> ShowS
PaginationQueryParams -> String
(Int -> PaginationQueryParams -> ShowS)
-> (PaginationQueryParams -> String)
-> ([PaginationQueryParams] -> ShowS)
-> Show PaginationQueryParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaginationQueryParams] -> ShowS
$cshowList :: [PaginationQueryParams] -> ShowS
show :: PaginationQueryParams -> String
$cshow :: PaginationQueryParams -> String
showsPrec :: Int -> PaginationQueryParams -> ShowS
$cshowsPrec :: Int -> PaginationQueryParams -> ShowS
Show)
data = PageBefore !Text | PageAfter !Text deriving (Int -> PaginationQueryParam -> ShowS
[PaginationQueryParam] -> ShowS
PaginationQueryParam -> String
(Int -> PaginationQueryParam -> ShowS)
-> (PaginationQueryParam -> String)
-> ([PaginationQueryParam] -> ShowS)
-> Show PaginationQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaginationQueryParam] -> ShowS
$cshowList :: [PaginationQueryParam] -> ShowS
show :: PaginationQueryParam -> String
$cshow :: PaginationQueryParam -> String
showsPrec :: Int -> PaginationQueryParam -> ShowS
$cshowsPrec :: Int -> PaginationQueryParam -> ShowS
Show, PaginationQueryParam -> PaginationQueryParam -> Bool
(PaginationQueryParam -> PaginationQueryParam -> Bool)
-> (PaginationQueryParam -> PaginationQueryParam -> Bool)
-> Eq PaginationQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaginationQueryParam -> PaginationQueryParam -> Bool
$c/= :: PaginationQueryParam -> PaginationQueryParam -> Bool
== :: PaginationQueryParam -> PaginationQueryParam -> Bool
$c== :: PaginationQueryParam -> PaginationQueryParam -> Bool
Eq)
instance ToCircleParam PaginationQueryParams where
toCircleParam :: PaginationQueryParams -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (PaginationQueryParams PaginationQueryParam
p) =
case PaginationQueryParam
p of
PageBefore Text
a ->
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"pageBefore", Text -> ByteString
TE.encodeUtf8 Text
a)]
PageAfter Text
a ->
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"pageAfter", Text -> ByteString
TE.encodeUtf8 Text
a)]
newtype FromQueryParam = FromQueryParam
{ FromQueryParam -> UTCTime
fromQueryParam :: UTCTime
}
deriving (FromQueryParam -> FromQueryParam -> Bool
(FromQueryParam -> FromQueryParam -> Bool)
-> (FromQueryParam -> FromQueryParam -> Bool) -> Eq FromQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FromQueryParam -> FromQueryParam -> Bool
$c/= :: FromQueryParam -> FromQueryParam -> Bool
== :: FromQueryParam -> FromQueryParam -> Bool
$c== :: FromQueryParam -> FromQueryParam -> Bool
Eq, Int -> FromQueryParam -> ShowS
[FromQueryParam] -> ShowS
FromQueryParam -> String
(Int -> FromQueryParam -> ShowS)
-> (FromQueryParam -> String)
-> ([FromQueryParam] -> ShowS)
-> Show FromQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FromQueryParam] -> ShowS
$cshowList :: [FromQueryParam] -> ShowS
show :: FromQueryParam -> String
$cshow :: FromQueryParam -> String
showsPrec :: Int -> FromQueryParam -> ShowS
$cshowsPrec :: Int -> FromQueryParam -> ShowS
Show)
instance ToCircleParam FromQueryParam where
toCircleParam :: FromQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (FromQueryParam UTCTime
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"from", Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ UTCTime -> Text
utcToCircle UTCTime
i)]
newtype ToQueryParam = ToQueryParam
{ ToQueryParam -> UTCTime
toQueryParam :: UTCTime
}
deriving (ToQueryParam -> ToQueryParam -> Bool
(ToQueryParam -> ToQueryParam -> Bool)
-> (ToQueryParam -> ToQueryParam -> Bool) -> Eq ToQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToQueryParam -> ToQueryParam -> Bool
$c/= :: ToQueryParam -> ToQueryParam -> Bool
== :: ToQueryParam -> ToQueryParam -> Bool
$c== :: ToQueryParam -> ToQueryParam -> Bool
Eq, Int -> ToQueryParam -> ShowS
[ToQueryParam] -> ShowS
ToQueryParam -> String
(Int -> ToQueryParam -> ShowS)
-> (ToQueryParam -> String)
-> ([ToQueryParam] -> ShowS)
-> Show ToQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToQueryParam] -> ShowS
$cshowList :: [ToQueryParam] -> ShowS
show :: ToQueryParam -> String
$cshow :: ToQueryParam -> String
showsPrec :: Int -> ToQueryParam -> ShowS
$cshowsPrec :: Int -> ToQueryParam -> ShowS
Show)
instance ToCircleParam ToQueryParam where
toCircleParam :: ToQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (ToQueryParam UTCTime
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"to", Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ UTCTime -> Text
utcToCircle UTCTime
i)]
newtype PageSizeQueryParam = PageSizeQueryParam
{ PageSizeQueryParam -> Integer
pageSizeQueryParam :: Integer
}
deriving (PageSizeQueryParam -> PageSizeQueryParam -> Bool
(PageSizeQueryParam -> PageSizeQueryParam -> Bool)
-> (PageSizeQueryParam -> PageSizeQueryParam -> Bool)
-> Eq PageSizeQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageSizeQueryParam -> PageSizeQueryParam -> Bool
$c/= :: PageSizeQueryParam -> PageSizeQueryParam -> Bool
== :: PageSizeQueryParam -> PageSizeQueryParam -> Bool
$c== :: PageSizeQueryParam -> PageSizeQueryParam -> Bool
Eq, Int -> PageSizeQueryParam -> ShowS
[PageSizeQueryParam] -> ShowS
PageSizeQueryParam -> String
(Int -> PageSizeQueryParam -> ShowS)
-> (PageSizeQueryParam -> String)
-> ([PageSizeQueryParam] -> ShowS)
-> Show PageSizeQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageSizeQueryParam] -> ShowS
$cshowList :: [PageSizeQueryParam] -> ShowS
show :: PageSizeQueryParam -> String
$cshow :: PageSizeQueryParam -> String
showsPrec :: Int -> PageSizeQueryParam -> ShowS
$cshowsPrec :: Int -> PageSizeQueryParam -> ShowS
Show)
instance ToCircleParam PageSizeQueryParam where
toCircleParam :: PageSizeQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (PageSizeQueryParam Integer
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"pageSize", Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ (String -> Text
T.pack (String -> Text) -> (Integer -> String) -> Integer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> String
forall a. Show a => a -> String
show) Integer
i)]
newtype StatusQueryParams = StatusQueryParams
{ StatusQueryParams -> [Status]
statusQueryParams :: [Status]
}
deriving (StatusQueryParams -> StatusQueryParams -> Bool
(StatusQueryParams -> StatusQueryParams -> Bool)
-> (StatusQueryParams -> StatusQueryParams -> Bool)
-> Eq StatusQueryParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatusQueryParams -> StatusQueryParams -> Bool
$c/= :: StatusQueryParams -> StatusQueryParams -> Bool
== :: StatusQueryParams -> StatusQueryParams -> Bool
$c== :: StatusQueryParams -> StatusQueryParams -> Bool
Eq, Int -> StatusQueryParams -> ShowS
[StatusQueryParams] -> ShowS
StatusQueryParams -> String
(Int -> StatusQueryParams -> ShowS)
-> (StatusQueryParams -> String)
-> ([StatusQueryParams] -> ShowS)
-> Show StatusQueryParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StatusQueryParams] -> ShowS
$cshowList :: [StatusQueryParams] -> ShowS
show :: StatusQueryParams -> String
$cshow :: StatusQueryParams -> String
showsPrec :: Int -> StatusQueryParams -> ShowS
$cshowsPrec :: Int -> StatusQueryParams -> ShowS
Show)
statusToBS8 :: Status -> BS8.ByteString
statusToBS8 :: Status -> ByteString
statusToBS8 Status
Pending = ByteString
"pending"
statusToBS8 Status
Complete = ByteString
"complete"
statusToBS8 Status
Failed = ByteString
"failed"
instance ToCircleParam StatusQueryParams where
toCircleParam :: StatusQueryParams -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (StatusQueryParams [Status]
xs) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"status", ByteString -> [ByteString] -> ByteString
BS8.intercalate ByteString
"," ((Status -> ByteString) -> [Status] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map Status -> ByteString
statusToBS8 [Status]
xs))]
newtype DestinationQueryParam = DestinationQueryParam
{ DestinationQueryParam -> UUID
destinationQueryParam :: UUID
}
deriving (DestinationQueryParam -> DestinationQueryParam -> Bool
(DestinationQueryParam -> DestinationQueryParam -> Bool)
-> (DestinationQueryParam -> DestinationQueryParam -> Bool)
-> Eq DestinationQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DestinationQueryParam -> DestinationQueryParam -> Bool
$c/= :: DestinationQueryParam -> DestinationQueryParam -> Bool
== :: DestinationQueryParam -> DestinationQueryParam -> Bool
$c== :: DestinationQueryParam -> DestinationQueryParam -> Bool
Eq, Int -> DestinationQueryParam -> ShowS
[DestinationQueryParam] -> ShowS
DestinationQueryParam -> String
(Int -> DestinationQueryParam -> ShowS)
-> (DestinationQueryParam -> String)
-> ([DestinationQueryParam] -> ShowS)
-> Show DestinationQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DestinationQueryParam] -> ShowS
$cshowList :: [DestinationQueryParam] -> ShowS
show :: DestinationQueryParam -> String
$cshow :: DestinationQueryParam -> String
showsPrec :: Int -> DestinationQueryParam -> ShowS
$cshowsPrec :: Int -> DestinationQueryParam -> ShowS
Show)
instance ToCircleParam DestinationQueryParam where
toCircleParam :: DestinationQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (DestinationQueryParam UUID
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"destination", Text -> ByteString
TE.encodeUtf8 (UUID -> Text
forall a. Show a => a -> Text
tshow UUID
i))]
newtype TypeQueryParam = TypeQueryParam
{ TypeQueryParam -> BankAccountType
typeQueryParam :: BankAccountType
}
deriving (TypeQueryParam -> TypeQueryParam -> Bool
(TypeQueryParam -> TypeQueryParam -> Bool)
-> (TypeQueryParam -> TypeQueryParam -> Bool) -> Eq TypeQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeQueryParam -> TypeQueryParam -> Bool
$c/= :: TypeQueryParam -> TypeQueryParam -> Bool
== :: TypeQueryParam -> TypeQueryParam -> Bool
$c== :: TypeQueryParam -> TypeQueryParam -> Bool
Eq, Int -> TypeQueryParam -> ShowS
[TypeQueryParam] -> ShowS
TypeQueryParam -> String
(Int -> TypeQueryParam -> ShowS)
-> (TypeQueryParam -> String)
-> ([TypeQueryParam] -> ShowS)
-> Show TypeQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeQueryParam] -> ShowS
$cshowList :: [TypeQueryParam] -> ShowS
show :: TypeQueryParam -> String
$cshow :: TypeQueryParam -> String
showsPrec :: Int -> TypeQueryParam -> ShowS
$cshowsPrec :: Int -> TypeQueryParam -> ShowS
Show)
bankAccountTypeToBS8 :: BankAccountType -> BS8.ByteString
bankAccountTypeToBS8 :: BankAccountType -> ByteString
bankAccountTypeToBS8 BankAccountType
Wire = ByteString
"wire"
bankAccountTypeToBS8 BankAccountType
Sen = ByteString
"sen"
instance ToCircleParam TypeQueryParam where
toCircleParam :: TypeQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (TypeQueryParam BankAccountType
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"type", BankAccountType -> ByteString
bankAccountTypeToBS8 BankAccountType
i)]
newtype CurrencyQueryParam = CurrencyQueryParam
{ CurrencyQueryParam -> SupportedCurrencies
currencyQueryParam :: SupportedCurrencies
}
deriving (CurrencyQueryParam -> CurrencyQueryParam -> Bool
(CurrencyQueryParam -> CurrencyQueryParam -> Bool)
-> (CurrencyQueryParam -> CurrencyQueryParam -> Bool)
-> Eq CurrencyQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CurrencyQueryParam -> CurrencyQueryParam -> Bool
$c/= :: CurrencyQueryParam -> CurrencyQueryParam -> Bool
== :: CurrencyQueryParam -> CurrencyQueryParam -> Bool
$c== :: CurrencyQueryParam -> CurrencyQueryParam -> Bool
Eq, Int -> CurrencyQueryParam -> ShowS
[CurrencyQueryParam] -> ShowS
CurrencyQueryParam -> String
(Int -> CurrencyQueryParam -> ShowS)
-> (CurrencyQueryParam -> String)
-> ([CurrencyQueryParam] -> ShowS)
-> Show CurrencyQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CurrencyQueryParam] -> ShowS
$cshowList :: [CurrencyQueryParam] -> ShowS
show :: CurrencyQueryParam -> String
$cshow :: CurrencyQueryParam -> String
showsPrec :: Int -> CurrencyQueryParam -> ShowS
$cshowsPrec :: Int -> CurrencyQueryParam -> ShowS
Show)
currencyToBS8 :: SupportedCurrencies -> BS8.ByteString
currencyToBS8 :: SupportedCurrencies -> ByteString
currencyToBS8 SupportedCurrencies
USD = ByteString
"USD"
currencyToBS8 SupportedCurrencies
EUR = ByteString
"EUR"
currencyToBS8 SupportedCurrencies
BTC = ByteString
"BTC"
currencyToBS8 SupportedCurrencies
ETH = ByteString
"ETH"
instance ToCircleParam CurrencyQueryParam where
toCircleParam :: CurrencyQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (CurrencyQueryParam SupportedCurrencies
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"currency", SupportedCurrencies -> ByteString
currencyToBS8 SupportedCurrencies
i)]
newtype SourceQueryParam = SourceQueryParam
{ SourceQueryParam -> UUID
sourceQueryParam :: UUID
}
deriving (SourceQueryParam -> SourceQueryParam -> Bool
(SourceQueryParam -> SourceQueryParam -> Bool)
-> (SourceQueryParam -> SourceQueryParam -> Bool)
-> Eq SourceQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceQueryParam -> SourceQueryParam -> Bool
$c/= :: SourceQueryParam -> SourceQueryParam -> Bool
== :: SourceQueryParam -> SourceQueryParam -> Bool
$c== :: SourceQueryParam -> SourceQueryParam -> Bool
Eq, Int -> SourceQueryParam -> ShowS
[SourceQueryParam] -> ShowS
SourceQueryParam -> String
(Int -> SourceQueryParam -> ShowS)
-> (SourceQueryParam -> String)
-> ([SourceQueryParam] -> ShowS)
-> Show SourceQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceQueryParam] -> ShowS
$cshowList :: [SourceQueryParam] -> ShowS
show :: SourceQueryParam -> String
$cshow :: SourceQueryParam -> String
showsPrec :: Int -> SourceQueryParam -> ShowS
$cshowsPrec :: Int -> SourceQueryParam -> ShowS
Show)
instance ToCircleParam SourceQueryParam where
toCircleParam :: SourceQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (SourceQueryParam UUID
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"source", Text -> ByteString
TE.encodeUtf8 (UUID -> Text
forall a. Show a => a -> Text
tshow UUID
i))]
newtype SettlementIdQueryParam = SettlementIdQueryParam
{ SettlementIdQueryParam -> UUID
settlementIdQueryParam :: UUID
}
deriving (SettlementIdQueryParam -> SettlementIdQueryParam -> Bool
(SettlementIdQueryParam -> SettlementIdQueryParam -> Bool)
-> (SettlementIdQueryParam -> SettlementIdQueryParam -> Bool)
-> Eq SettlementIdQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SettlementIdQueryParam -> SettlementIdQueryParam -> Bool
$c/= :: SettlementIdQueryParam -> SettlementIdQueryParam -> Bool
== :: SettlementIdQueryParam -> SettlementIdQueryParam -> Bool
$c== :: SettlementIdQueryParam -> SettlementIdQueryParam -> Bool
Eq, Int -> SettlementIdQueryParam -> ShowS
[SettlementIdQueryParam] -> ShowS
SettlementIdQueryParam -> String
(Int -> SettlementIdQueryParam -> ShowS)
-> (SettlementIdQueryParam -> String)
-> ([SettlementIdQueryParam] -> ShowS)
-> Show SettlementIdQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SettlementIdQueryParam] -> ShowS
$cshowList :: [SettlementIdQueryParam] -> ShowS
show :: SettlementIdQueryParam -> String
$cshow :: SettlementIdQueryParam -> String
showsPrec :: Int -> SettlementIdQueryParam -> ShowS
$cshowsPrec :: Int -> SettlementIdQueryParam -> ShowS
Show)
instance ToCircleParam SettlementIdQueryParam where
toCircleParam :: SettlementIdQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (SettlementIdQueryParam UUID
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"settlementId", Text -> ByteString
TE.encodeUtf8 (UUID -> Text
forall a. Show a => a -> Text
tshow UUID
i))]
newtype PaymentIntentIdQueryParam = PaymentIntentIdQueryParam
{ PaymentIntentIdQueryParam -> UUID
paymentIntentIdQueryParam :: UUID
}
deriving (PaymentIntentIdQueryParam -> PaymentIntentIdQueryParam -> Bool
(PaymentIntentIdQueryParam -> PaymentIntentIdQueryParam -> Bool)
-> (PaymentIntentIdQueryParam -> PaymentIntentIdQueryParam -> Bool)
-> Eq PaymentIntentIdQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentIntentIdQueryParam -> PaymentIntentIdQueryParam -> Bool
$c/= :: PaymentIntentIdQueryParam -> PaymentIntentIdQueryParam -> Bool
== :: PaymentIntentIdQueryParam -> PaymentIntentIdQueryParam -> Bool
$c== :: PaymentIntentIdQueryParam -> PaymentIntentIdQueryParam -> Bool
Eq, Int -> PaymentIntentIdQueryParam -> ShowS
[PaymentIntentIdQueryParam] -> ShowS
PaymentIntentIdQueryParam -> String
(Int -> PaymentIntentIdQueryParam -> ShowS)
-> (PaymentIntentIdQueryParam -> String)
-> ([PaymentIntentIdQueryParam] -> ShowS)
-> Show PaymentIntentIdQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentIntentIdQueryParam] -> ShowS
$cshowList :: [PaymentIntentIdQueryParam] -> ShowS
show :: PaymentIntentIdQueryParam -> String
$cshow :: PaymentIntentIdQueryParam -> String
showsPrec :: Int -> PaymentIntentIdQueryParam -> ShowS
$cshowsPrec :: Int -> PaymentIntentIdQueryParam -> ShowS
Show)
instance ToCircleParam PaymentIntentIdQueryParam where
toCircleParam :: PaymentIntentIdQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (PaymentIntentIdQueryParam UUID
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"paymentIntentId", Text -> ByteString
TE.encodeUtf8 (UUID -> Text
forall a. Show a => a -> Text
tshow UUID
i))]
newtype PaymentIdQueryParam = PaymentIdQueryParam
{ PaymentIdQueryParam -> UUID
paymentIdQueryParam :: UUID
}
deriving (PaymentIdQueryParam -> PaymentIdQueryParam -> Bool
(PaymentIdQueryParam -> PaymentIdQueryParam -> Bool)
-> (PaymentIdQueryParam -> PaymentIdQueryParam -> Bool)
-> Eq PaymentIdQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentIdQueryParam -> PaymentIdQueryParam -> Bool
$c/= :: PaymentIdQueryParam -> PaymentIdQueryParam -> Bool
== :: PaymentIdQueryParam -> PaymentIdQueryParam -> Bool
$c== :: PaymentIdQueryParam -> PaymentIdQueryParam -> Bool
Eq, Int -> PaymentIdQueryParam -> ShowS
[PaymentIdQueryParam] -> ShowS
PaymentIdQueryParam -> String
(Int -> PaymentIdQueryParam -> ShowS)
-> (PaymentIdQueryParam -> String)
-> ([PaymentIdQueryParam] -> ShowS)
-> Show PaymentIdQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentIdQueryParam] -> ShowS
$cshowList :: [PaymentIdQueryParam] -> ShowS
show :: PaymentIdQueryParam -> String
$cshow :: PaymentIdQueryParam -> String
showsPrec :: Int -> PaymentIdQueryParam -> ShowS
$cshowsPrec :: Int -> PaymentIdQueryParam -> ShowS
Show)
instance ToCircleParam PaymentIdQueryParam where
toCircleParam :: PaymentIdQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (PaymentIdQueryParam UUID
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"paymentId", Text -> ByteString
TE.encodeUtf8 (UUID -> Text
forall a. Show a => a -> Text
tshow UUID
i))]
newtype PaymentStatusQueryParams = PaymentStatusQueryParams
{ PaymentStatusQueryParams -> [PaymentStatus]
paymentStatusQueryParams :: [PaymentStatus]
}
deriving (PaymentStatusQueryParams -> PaymentStatusQueryParams -> Bool
(PaymentStatusQueryParams -> PaymentStatusQueryParams -> Bool)
-> (PaymentStatusQueryParams -> PaymentStatusQueryParams -> Bool)
-> Eq PaymentStatusQueryParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentStatusQueryParams -> PaymentStatusQueryParams -> Bool
$c/= :: PaymentStatusQueryParams -> PaymentStatusQueryParams -> Bool
== :: PaymentStatusQueryParams -> PaymentStatusQueryParams -> Bool
$c== :: PaymentStatusQueryParams -> PaymentStatusQueryParams -> Bool
Eq, Int -> PaymentStatusQueryParams -> ShowS
[PaymentStatusQueryParams] -> ShowS
PaymentStatusQueryParams -> String
(Int -> PaymentStatusQueryParams -> ShowS)
-> (PaymentStatusQueryParams -> String)
-> ([PaymentStatusQueryParams] -> ShowS)
-> Show PaymentStatusQueryParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentStatusQueryParams] -> ShowS
$cshowList :: [PaymentStatusQueryParams] -> ShowS
show :: PaymentStatusQueryParams -> String
$cshow :: PaymentStatusQueryParams -> String
showsPrec :: Int -> PaymentStatusQueryParams -> ShowS
$cshowsPrec :: Int -> PaymentStatusQueryParams -> ShowS
Show)
paymentStatusToBS8 :: PaymentStatus -> BS8.ByteString
paymentStatusToBS8 :: PaymentStatus -> ByteString
paymentStatusToBS8 PaymentStatus
PaymentPending = ByteString
"pending"
paymentStatusToBS8 PaymentStatus
Confirmed = ByteString
"confirmed"
paymentStatusToBS8 PaymentStatus
PaymentFailed = ByteString
"failed"
paymentStatusToBS8 PaymentStatus
Paid = ByteString
"paid"
paymentStatusToBS8 PaymentStatus
ActionRequired = ByteString
"action_required"
instance ToCircleParam PaymentStatusQueryParams where
toCircleParam :: PaymentStatusQueryParams -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (PaymentStatusQueryParams [PaymentStatus]
xs) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"status", ByteString -> [ByteString] -> ByteString
BS8.intercalate ByteString
"," ((PaymentStatus -> ByteString) -> [PaymentStatus] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map PaymentStatus -> ByteString
paymentStatusToBS8 [PaymentStatus]
xs))]
newtype PaymentIntentContextQueryParams = PaymentIntentContextQueryParams
{ PaymentIntentContextQueryParams -> [PaymentIntentContext]
paymentIntentContextQueryParams :: [PaymentIntentContext]
}
deriving (PaymentIntentContextQueryParams
-> PaymentIntentContextQueryParams -> Bool
(PaymentIntentContextQueryParams
-> PaymentIntentContextQueryParams -> Bool)
-> (PaymentIntentContextQueryParams
-> PaymentIntentContextQueryParams -> Bool)
-> Eq PaymentIntentContextQueryParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentIntentContextQueryParams
-> PaymentIntentContextQueryParams -> Bool
$c/= :: PaymentIntentContextQueryParams
-> PaymentIntentContextQueryParams -> Bool
== :: PaymentIntentContextQueryParams
-> PaymentIntentContextQueryParams -> Bool
$c== :: PaymentIntentContextQueryParams
-> PaymentIntentContextQueryParams -> Bool
Eq, Int -> PaymentIntentContextQueryParams -> ShowS
[PaymentIntentContextQueryParams] -> ShowS
PaymentIntentContextQueryParams -> String
(Int -> PaymentIntentContextQueryParams -> ShowS)
-> (PaymentIntentContextQueryParams -> String)
-> ([PaymentIntentContextQueryParams] -> ShowS)
-> Show PaymentIntentContextQueryParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentIntentContextQueryParams] -> ShowS
$cshowList :: [PaymentIntentContextQueryParams] -> ShowS
show :: PaymentIntentContextQueryParams -> String
$cshow :: PaymentIntentContextQueryParams -> String
showsPrec :: Int -> PaymentIntentContextQueryParams -> ShowS
$cshowsPrec :: Int -> PaymentIntentContextQueryParams -> ShowS
Show)
paymentIntentContextToBS8 :: PaymentIntentContext -> BS8.ByteString
paymentIntentContextToBS8 :: PaymentIntentContext -> ByteString
paymentIntentContextToBS8 PaymentIntentContext
ContextUnderpaid = ByteString
"underpaid"
paymentIntentContextToBS8 PaymentIntentContext
ContextPaid = ByteString
"paid"
paymentIntentContextToBS8 PaymentIntentContext
ContextOverpaid = ByteString
"overpaid"
instance ToCircleParam PaymentIntentContextQueryParams where
toCircleParam :: PaymentIntentContextQueryParams
-> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (PaymentIntentContextQueryParams [PaymentIntentContext]
xs) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"context", ByteString -> [ByteString] -> ByteString
BS8.intercalate ByteString
"," ((PaymentIntentContext -> ByteString)
-> [PaymentIntentContext] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map PaymentIntentContext -> ByteString
paymentIntentContextToBS8 [PaymentIntentContext]
xs))]
newtype WalletIdQueryParam = WalletIdQueryParam
{ WalletIdQueryParam -> WalletId
walletIdQueryParam :: WalletId
}
deriving (WalletIdQueryParam -> WalletIdQueryParam -> Bool
(WalletIdQueryParam -> WalletIdQueryParam -> Bool)
-> (WalletIdQueryParam -> WalletIdQueryParam -> Bool)
-> Eq WalletIdQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletIdQueryParam -> WalletIdQueryParam -> Bool
$c/= :: WalletIdQueryParam -> WalletIdQueryParam -> Bool
== :: WalletIdQueryParam -> WalletIdQueryParam -> Bool
$c== :: WalletIdQueryParam -> WalletIdQueryParam -> Bool
Eq, Int -> WalletIdQueryParam -> ShowS
[WalletIdQueryParam] -> ShowS
WalletIdQueryParam -> String
(Int -> WalletIdQueryParam -> ShowS)
-> (WalletIdQueryParam -> String)
-> ([WalletIdQueryParam] -> ShowS)
-> Show WalletIdQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletIdQueryParam] -> ShowS
$cshowList :: [WalletIdQueryParam] -> ShowS
show :: WalletIdQueryParam -> String
$cshow :: WalletIdQueryParam -> String
showsPrec :: Int -> WalletIdQueryParam -> ShowS
$cshowsPrec :: Int -> WalletIdQueryParam -> ShowS
Show)
instance ToCircleParam WalletIdQueryParam where
toCircleParam :: WalletIdQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (WalletIdQueryParam WalletId
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"walletId", Text -> ByteString
TE.encodeUtf8 (WalletId -> Text
unWalletId WalletId
i))]
newtype SourceWalletIdQueryParam = SourceWalletIdQueryParam
{ SourceWalletIdQueryParam -> WalletId
sourceWalletIdQueryParam :: WalletId
}
deriving (SourceWalletIdQueryParam -> SourceWalletIdQueryParam -> Bool
(SourceWalletIdQueryParam -> SourceWalletIdQueryParam -> Bool)
-> (SourceWalletIdQueryParam -> SourceWalletIdQueryParam -> Bool)
-> Eq SourceWalletIdQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceWalletIdQueryParam -> SourceWalletIdQueryParam -> Bool
$c/= :: SourceWalletIdQueryParam -> SourceWalletIdQueryParam -> Bool
== :: SourceWalletIdQueryParam -> SourceWalletIdQueryParam -> Bool
$c== :: SourceWalletIdQueryParam -> SourceWalletIdQueryParam -> Bool
Eq, Int -> SourceWalletIdQueryParam -> ShowS
[SourceWalletIdQueryParam] -> ShowS
SourceWalletIdQueryParam -> String
(Int -> SourceWalletIdQueryParam -> ShowS)
-> (SourceWalletIdQueryParam -> String)
-> ([SourceWalletIdQueryParam] -> ShowS)
-> Show SourceWalletIdQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceWalletIdQueryParam] -> ShowS
$cshowList :: [SourceWalletIdQueryParam] -> ShowS
show :: SourceWalletIdQueryParam -> String
$cshow :: SourceWalletIdQueryParam -> String
showsPrec :: Int -> SourceWalletIdQueryParam -> ShowS
$cshowsPrec :: Int -> SourceWalletIdQueryParam -> ShowS
Show)
instance ToCircleParam SourceWalletIdQueryParam where
toCircleParam :: SourceWalletIdQueryParam -> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (SourceWalletIdQueryParam WalletId
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"sourceWalletId", Text -> ByteString
TE.encodeUtf8 (WalletId -> Text
unWalletId WalletId
i))]
newtype DestinationWalletIdQueryParam = DestinationWalletIdQueryParam
{ DestinationWalletIdQueryParam -> WalletId
destinationWalletIdQueryParam :: WalletId
}
deriving (DestinationWalletIdQueryParam
-> DestinationWalletIdQueryParam -> Bool
(DestinationWalletIdQueryParam
-> DestinationWalletIdQueryParam -> Bool)
-> (DestinationWalletIdQueryParam
-> DestinationWalletIdQueryParam -> Bool)
-> Eq DestinationWalletIdQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DestinationWalletIdQueryParam
-> DestinationWalletIdQueryParam -> Bool
$c/= :: DestinationWalletIdQueryParam
-> DestinationWalletIdQueryParam -> Bool
== :: DestinationWalletIdQueryParam
-> DestinationWalletIdQueryParam -> Bool
$c== :: DestinationWalletIdQueryParam
-> DestinationWalletIdQueryParam -> Bool
Eq, Int -> DestinationWalletIdQueryParam -> ShowS
[DestinationWalletIdQueryParam] -> ShowS
DestinationWalletIdQueryParam -> String
(Int -> DestinationWalletIdQueryParam -> ShowS)
-> (DestinationWalletIdQueryParam -> String)
-> ([DestinationWalletIdQueryParam] -> ShowS)
-> Show DestinationWalletIdQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DestinationWalletIdQueryParam] -> ShowS
$cshowList :: [DestinationWalletIdQueryParam] -> ShowS
show :: DestinationWalletIdQueryParam -> String
$cshow :: DestinationWalletIdQueryParam -> String
showsPrec :: Int -> DestinationWalletIdQueryParam -> ShowS
$cshowsPrec :: Int -> DestinationWalletIdQueryParam -> ShowS
Show)
instance ToCircleParam DestinationWalletIdQueryParam where
toCircleParam :: DestinationWalletIdQueryParam
-> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (DestinationWalletIdQueryParam WalletId
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"destinationWalletId", Text -> ByteString
TE.encodeUtf8 (WalletId -> Text
unWalletId WalletId
i))]
newtype ReturnIdentitiesQueryParam = ReturnIdentitiesQueryParam
{ ReturnIdentitiesQueryParam -> Bool
returnIdentitiesQueryParam :: Bool
}
deriving (ReturnIdentitiesQueryParam -> ReturnIdentitiesQueryParam -> Bool
(ReturnIdentitiesQueryParam -> ReturnIdentitiesQueryParam -> Bool)
-> (ReturnIdentitiesQueryParam
-> ReturnIdentitiesQueryParam -> Bool)
-> Eq ReturnIdentitiesQueryParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReturnIdentitiesQueryParam -> ReturnIdentitiesQueryParam -> Bool
$c/= :: ReturnIdentitiesQueryParam -> ReturnIdentitiesQueryParam -> Bool
== :: ReturnIdentitiesQueryParam -> ReturnIdentitiesQueryParam -> Bool
$c== :: ReturnIdentitiesQueryParam -> ReturnIdentitiesQueryParam -> Bool
Eq, Int -> ReturnIdentitiesQueryParam -> ShowS
[ReturnIdentitiesQueryParam] -> ShowS
ReturnIdentitiesQueryParam -> String
(Int -> ReturnIdentitiesQueryParam -> ShowS)
-> (ReturnIdentitiesQueryParam -> String)
-> ([ReturnIdentitiesQueryParam] -> ShowS)
-> Show ReturnIdentitiesQueryParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReturnIdentitiesQueryParam] -> ShowS
$cshowList :: [ReturnIdentitiesQueryParam] -> ShowS
show :: ReturnIdentitiesQueryParam -> String
$cshow :: ReturnIdentitiesQueryParam -> String
showsPrec :: Int -> ReturnIdentitiesQueryParam -> ShowS
$cshowsPrec :: Int -> ReturnIdentitiesQueryParam -> ShowS
Show)
instance ToCircleParam ReturnIdentitiesQueryParam where
toCircleParam :: ReturnIdentitiesQueryParam
-> Params TupleBS8 c -> Params TupleBS8 c
toCircleParam (ReturnIdentitiesQueryParam Bool
i) =
Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall b c. Params b c -> Params b c -> Params b c
joinQueryParams (Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c)
-> Params TupleBS8 c -> Params TupleBS8 c -> Params TupleBS8 c
forall a b. (a -> b) -> a -> b
$ Maybe Body -> [Query] -> Params TupleBS8 c
forall b c. Maybe Body -> [Query] -> Params b c
Params Maybe Body
forall a. Maybe a
Nothing [TupleBS8 -> Query
Query (ByteString
"returnIdentities", Text -> ByteString
TE.encodeUtf8 (String -> Text
T.pack (Bool -> String
forall a. Show a => a -> String
show Bool
i)))]
data BalanceRequest
type instance CircleRequest BalanceRequest = CircleResponseBody BalanceResponseBody
data BalanceResponseBody = BalanceResponseBody
{ BalanceResponseBody -> [MoneyAmount]
balanceResponseBodyAvailable :: ![MoneyAmount],
BalanceResponseBody -> [MoneyAmount]
balanceResponseBodyUnsettled :: ![MoneyAmount]
}
deriving (BalanceResponseBody -> BalanceResponseBody -> Bool
(BalanceResponseBody -> BalanceResponseBody -> Bool)
-> (BalanceResponseBody -> BalanceResponseBody -> Bool)
-> Eq BalanceResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BalanceResponseBody -> BalanceResponseBody -> Bool
$c/= :: BalanceResponseBody -> BalanceResponseBody -> Bool
== :: BalanceResponseBody -> BalanceResponseBody -> Bool
$c== :: BalanceResponseBody -> BalanceResponseBody -> Bool
Eq, Int -> BalanceResponseBody -> ShowS
[BalanceResponseBody] -> ShowS
BalanceResponseBody -> String
(Int -> BalanceResponseBody -> ShowS)
-> (BalanceResponseBody -> String)
-> ([BalanceResponseBody] -> ShowS)
-> Show BalanceResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BalanceResponseBody] -> ShowS
$cshowList :: [BalanceResponseBody] -> ShowS
show :: BalanceResponseBody -> String
$cshow :: BalanceResponseBody -> String
showsPrec :: Int -> BalanceResponseBody -> ShowS
$cshowsPrec :: Int -> BalanceResponseBody -> ShowS
Show, (forall x. BalanceResponseBody -> Rep BalanceResponseBody x)
-> (forall x. Rep BalanceResponseBody x -> BalanceResponseBody)
-> Generic BalanceResponseBody
forall x. Rep BalanceResponseBody x -> BalanceResponseBody
forall x. BalanceResponseBody -> Rep BalanceResponseBody x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BalanceResponseBody x -> BalanceResponseBody
$cfrom :: forall x. BalanceResponseBody -> Rep BalanceResponseBody x
Generic)
deriving
( Value -> Parser [BalanceResponseBody]
Value -> Parser BalanceResponseBody
(Value -> Parser BalanceResponseBody)
-> (Value -> Parser [BalanceResponseBody])
-> FromJSON BalanceResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BalanceResponseBody]
$cparseJSONList :: Value -> Parser [BalanceResponseBody]
parseJSON :: Value -> Parser BalanceResponseBody
$cparseJSON :: Value -> Parser BalanceResponseBody
FromJSON,
[BalanceResponseBody] -> Encoding
[BalanceResponseBody] -> Value
BalanceResponseBody -> Encoding
BalanceResponseBody -> Value
(BalanceResponseBody -> Value)
-> (BalanceResponseBody -> Encoding)
-> ([BalanceResponseBody] -> Value)
-> ([BalanceResponseBody] -> Encoding)
-> ToJSON BalanceResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BalanceResponseBody] -> Encoding
$ctoEncodingList :: [BalanceResponseBody] -> Encoding
toJSONList :: [BalanceResponseBody] -> Value
$ctoJSONList :: [BalanceResponseBody] -> Value
toEncoding :: BalanceResponseBody -> Encoding
$ctoEncoding :: BalanceResponseBody -> Encoding
toJSON :: BalanceResponseBody -> Value
$ctoJSON :: BalanceResponseBody -> Value
ToJSON
)
via (Autodocodec BalanceResponseBody)
instance HasCodec BalanceResponseBody where
codec :: JSONCodec BalanceResponseBody
codec =
Text
-> ObjectCodec BalanceResponseBody BalanceResponseBody
-> JSONCodec BalanceResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BalanceResponseBody" (ObjectCodec BalanceResponseBody BalanceResponseBody
-> JSONCodec BalanceResponseBody)
-> ObjectCodec BalanceResponseBody BalanceResponseBody
-> JSONCodec BalanceResponseBody
forall a b. (a -> b) -> a -> b
$
[MoneyAmount] -> [MoneyAmount] -> BalanceResponseBody
BalanceResponseBody
([MoneyAmount] -> [MoneyAmount] -> BalanceResponseBody)
-> Codec Object BalanceResponseBody [MoneyAmount]
-> Codec
Object BalanceResponseBody ([MoneyAmount] -> BalanceResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec [MoneyAmount] [MoneyAmount]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"available" ObjectCodec [MoneyAmount] [MoneyAmount]
-> (BalanceResponseBody -> [MoneyAmount])
-> Codec Object BalanceResponseBody [MoneyAmount]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BalanceResponseBody -> [MoneyAmount]
balanceResponseBodyAvailable
Codec
Object BalanceResponseBody ([MoneyAmount] -> BalanceResponseBody)
-> Codec Object BalanceResponseBody [MoneyAmount]
-> ObjectCodec BalanceResponseBody BalanceResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [MoneyAmount] [MoneyAmount]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"unsettled" ObjectCodec [MoneyAmount] [MoneyAmount]
-> (BalanceResponseBody -> [MoneyAmount])
-> Codec Object BalanceResponseBody [MoneyAmount]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BalanceResponseBody -> [MoneyAmount]
balanceResponseBodyAvailable
data PayoutRequest
type instance CircleRequest PayoutRequest = CircleResponseBody PayoutResponseBody
data PayoutsRequest
type instance CircleRequest PayoutsRequest = CircleResponseBody [PayoutResponseBody]
instance CircleHasParam PayoutsRequest PaginationQueryParams
instance CircleHasParam PayoutsRequest FromQueryParam
instance CircleHasParam PayoutsRequest ToQueryParam
instance CircleHasParam PayoutsRequest PageSizeQueryParam
instance CircleHasParam PayoutsRequest StatusQueryParams
instance CircleHasParam PayoutsRequest TypeQueryParam
instance CircleHasParam PayoutsRequest DestinationQueryParam
data PayoutResponseBody = PayoutResponseBody
{ PayoutResponseBody -> UUID
payoutResponseBodyId :: !UUID,
PayoutResponseBody -> WalletId
payoutResponseBodySourceWalletId :: !WalletId,
PayoutResponseBody -> DestinationBankAccount
payoutResponseBodyDestinationBankAccount :: !DestinationBankAccount,
PayoutResponseBody -> MoneyAmount
payoutResponseBodyAmount :: !MoneyAmount,
PayoutResponseBody -> MoneyAmount
payoutResponseBodyFees :: !MoneyAmount,
PayoutResponseBody -> Status
payoutResponseBodyStatus :: !Status,
PayoutResponseBody -> TrackingReference
payoutResponseBodyTrackingRef :: !TrackingReference,
PayoutResponseBody -> PayoutErrorCode
payoutResponseBodyPayoutErrorCode :: !PayoutErrorCode,
PayoutResponseBody -> RiskEvaluation
payoutResponseBodyRiskEvaluation :: !RiskEvaluation,
PayoutResponseBody -> Adjustments
payoutResponseBodyAdjustments :: !Adjustments,
PayoutResponseBody -> PayoutReturnResponseBody
payoutResponseBodyPayoutReturn :: !PayoutReturnResponseBody,
PayoutResponseBody -> UTCTime
payoutResponseBodyCreateDate :: !UTCTime,
PayoutResponseBody -> UTCTime
payoutResponseBodyUpdateDate :: !UTCTime
}
deriving (PayoutResponseBody -> PayoutResponseBody -> Bool
(PayoutResponseBody -> PayoutResponseBody -> Bool)
-> (PayoutResponseBody -> PayoutResponseBody -> Bool)
-> Eq PayoutResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PayoutResponseBody -> PayoutResponseBody -> Bool
$c/= :: PayoutResponseBody -> PayoutResponseBody -> Bool
== :: PayoutResponseBody -> PayoutResponseBody -> Bool
$c== :: PayoutResponseBody -> PayoutResponseBody -> Bool
Eq, Int -> PayoutResponseBody -> ShowS
[PayoutResponseBody] -> ShowS
PayoutResponseBody -> String
(Int -> PayoutResponseBody -> ShowS)
-> (PayoutResponseBody -> String)
-> ([PayoutResponseBody] -> ShowS)
-> Show PayoutResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PayoutResponseBody] -> ShowS
$cshowList :: [PayoutResponseBody] -> ShowS
show :: PayoutResponseBody -> String
$cshow :: PayoutResponseBody -> String
showsPrec :: Int -> PayoutResponseBody -> ShowS
$cshowsPrec :: Int -> PayoutResponseBody -> ShowS
Show)
deriving
( [PayoutResponseBody] -> Encoding
[PayoutResponseBody] -> Value
PayoutResponseBody -> Encoding
PayoutResponseBody -> Value
(PayoutResponseBody -> Value)
-> (PayoutResponseBody -> Encoding)
-> ([PayoutResponseBody] -> Value)
-> ([PayoutResponseBody] -> Encoding)
-> ToJSON PayoutResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PayoutResponseBody] -> Encoding
$ctoEncodingList :: [PayoutResponseBody] -> Encoding
toJSONList :: [PayoutResponseBody] -> Value
$ctoJSONList :: [PayoutResponseBody] -> Value
toEncoding :: PayoutResponseBody -> Encoding
$ctoEncoding :: PayoutResponseBody -> Encoding
toJSON :: PayoutResponseBody -> Value
$ctoJSON :: PayoutResponseBody -> Value
ToJSON,
Value -> Parser [PayoutResponseBody]
Value -> Parser PayoutResponseBody
(Value -> Parser PayoutResponseBody)
-> (Value -> Parser [PayoutResponseBody])
-> FromJSON PayoutResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PayoutResponseBody]
$cparseJSONList :: Value -> Parser [PayoutResponseBody]
parseJSON :: Value -> Parser PayoutResponseBody
$cparseJSON :: Value -> Parser PayoutResponseBody
FromJSON
)
via (Autodocodec PayoutResponseBody)
instance HasCodec PayoutResponseBody where
codec :: JSONCodec PayoutResponseBody
codec =
Text
-> ObjectCodec PayoutResponseBody PayoutResponseBody
-> JSONCodec PayoutResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PayoutResponseBody" (ObjectCodec PayoutResponseBody PayoutResponseBody
-> JSONCodec PayoutResponseBody)
-> ObjectCodec PayoutResponseBody PayoutResponseBody
-> JSONCodec PayoutResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> WalletId
-> DestinationBankAccount
-> MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody
PayoutResponseBody
(UUID
-> WalletId
-> DestinationBankAccount
-> MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody UUID
-> Codec
Object
PayoutResponseBody
(WalletId
-> DestinationBankAccount
-> MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (PayoutResponseBody -> UUID)
-> Codec Object PayoutResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> UUID
payoutResponseBodyId
Codec
Object
PayoutResponseBody
(WalletId
-> DestinationBankAccount
-> MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody WalletId
-> Codec
Object
PayoutResponseBody
(DestinationBankAccount
-> MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec WalletId WalletId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"sourceWalletId" ObjectCodec WalletId WalletId
-> (PayoutResponseBody -> WalletId)
-> Codec Object PayoutResponseBody WalletId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> WalletId
payoutResponseBodySourceWalletId
Codec
Object
PayoutResponseBody
(DestinationBankAccount
-> MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody DestinationBankAccount
-> Codec
Object
PayoutResponseBody
(MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec DestinationBankAccount DestinationBankAccount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"destination" ObjectCodec DestinationBankAccount DestinationBankAccount
-> (PayoutResponseBody -> DestinationBankAccount)
-> Codec Object PayoutResponseBody DestinationBankAccount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> DestinationBankAccount
payoutResponseBodyDestinationBankAccount
Codec
Object
PayoutResponseBody
(MoneyAmount
-> MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody MoneyAmount
-> Codec
Object
PayoutResponseBody
(MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (PayoutResponseBody -> MoneyAmount)
-> Codec Object PayoutResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> MoneyAmount
payoutResponseBodyAmount
Codec
Object
PayoutResponseBody
(MoneyAmount
-> Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody MoneyAmount
-> Codec
Object
PayoutResponseBody
(Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fees" ObjectCodec MoneyAmount MoneyAmount
-> (PayoutResponseBody -> MoneyAmount)
-> Codec Object PayoutResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> MoneyAmount
payoutResponseBodyFees
Codec
Object
PayoutResponseBody
(Status
-> TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody Status
-> Codec
Object
PayoutResponseBody
(TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (PayoutResponseBody -> Status)
-> Codec Object PayoutResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> Status
payoutResponseBodyStatus
Codec
Object
PayoutResponseBody
(TrackingReference
-> PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody TrackingReference
-> Codec
Object
PayoutResponseBody
(PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (PayoutResponseBody -> TrackingReference)
-> Codec Object PayoutResponseBody TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> TrackingReference
payoutResponseBodyTrackingRef
Codec
Object
PayoutResponseBody
(PayoutErrorCode
-> RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody PayoutErrorCode
-> Codec
Object
PayoutResponseBody
(RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PayoutErrorCode PayoutErrorCode
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"errorCode" ObjectCodec PayoutErrorCode PayoutErrorCode
-> (PayoutResponseBody -> PayoutErrorCode)
-> Codec Object PayoutResponseBody PayoutErrorCode
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> PayoutErrorCode
payoutResponseBodyPayoutErrorCode
Codec
Object
PayoutResponseBody
(RiskEvaluation
-> Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody RiskEvaluation
-> Codec
Object
PayoutResponseBody
(Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RiskEvaluation RiskEvaluation
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"riskEvaluation" ObjectCodec RiskEvaluation RiskEvaluation
-> (PayoutResponseBody -> RiskEvaluation)
-> Codec Object PayoutResponseBody RiskEvaluation
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> RiskEvaluation
payoutResponseBodyRiskEvaluation
Codec
Object
PayoutResponseBody
(Adjustments
-> PayoutReturnResponseBody
-> UTCTime
-> UTCTime
-> PayoutResponseBody)
-> Codec Object PayoutResponseBody Adjustments
-> Codec
Object
PayoutResponseBody
(PayoutReturnResponseBody
-> UTCTime -> UTCTime -> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Adjustments Adjustments
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"adjustments" ObjectCodec Adjustments Adjustments
-> (PayoutResponseBody -> Adjustments)
-> Codec Object PayoutResponseBody Adjustments
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> Adjustments
payoutResponseBodyAdjustments
Codec
Object
PayoutResponseBody
(PayoutReturnResponseBody
-> UTCTime -> UTCTime -> PayoutResponseBody)
-> Codec Object PayoutResponseBody PayoutReturnResponseBody
-> Codec
Object
PayoutResponseBody
(UTCTime -> UTCTime -> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec PayoutReturnResponseBody PayoutReturnResponseBody
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"payoutReturn" ObjectCodec PayoutReturnResponseBody PayoutReturnResponseBody
-> (PayoutResponseBody -> PayoutReturnResponseBody)
-> Codec Object PayoutResponseBody PayoutReturnResponseBody
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> PayoutReturnResponseBody
payoutResponseBodyPayoutReturn
Codec
Object
PayoutResponseBody
(UTCTime -> UTCTime -> PayoutResponseBody)
-> Codec Object PayoutResponseBody UTCTime
-> Codec Object PayoutResponseBody (UTCTime -> PayoutResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (PayoutResponseBody -> UTCTime)
-> Codec Object PayoutResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> UTCTime
payoutResponseBodyCreateDate
Codec Object PayoutResponseBody (UTCTime -> PayoutResponseBody)
-> Codec Object PayoutResponseBody UTCTime
-> ObjectCodec PayoutResponseBody PayoutResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (PayoutResponseBody -> UTCTime)
-> Codec Object PayoutResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutResponseBody -> UTCTime
payoutResponseBodyUpdateDate
data BusinessPayoutRequestBody = BusinessPayoutRequestBody
{ BusinessPayoutRequestBody -> UUID
businessPayoutIdempotencyKey :: !UUID,
BusinessPayoutRequestBody -> DestinationBankAccount
businessPayoutDestination :: !DestinationBankAccount,
BusinessPayoutRequestBody -> MoneyAmount
businessPayoutAmount :: !MoneyAmount
}
deriving (BusinessPayoutRequestBody -> BusinessPayoutRequestBody -> Bool
(BusinessPayoutRequestBody -> BusinessPayoutRequestBody -> Bool)
-> (BusinessPayoutRequestBody -> BusinessPayoutRequestBody -> Bool)
-> Eq BusinessPayoutRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BusinessPayoutRequestBody -> BusinessPayoutRequestBody -> Bool
$c/= :: BusinessPayoutRequestBody -> BusinessPayoutRequestBody -> Bool
== :: BusinessPayoutRequestBody -> BusinessPayoutRequestBody -> Bool
$c== :: BusinessPayoutRequestBody -> BusinessPayoutRequestBody -> Bool
Eq, Int -> BusinessPayoutRequestBody -> ShowS
[BusinessPayoutRequestBody] -> ShowS
BusinessPayoutRequestBody -> String
(Int -> BusinessPayoutRequestBody -> ShowS)
-> (BusinessPayoutRequestBody -> String)
-> ([BusinessPayoutRequestBody] -> ShowS)
-> Show BusinessPayoutRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BusinessPayoutRequestBody] -> ShowS
$cshowList :: [BusinessPayoutRequestBody] -> ShowS
show :: BusinessPayoutRequestBody -> String
$cshow :: BusinessPayoutRequestBody -> String
showsPrec :: Int -> BusinessPayoutRequestBody -> ShowS
$cshowsPrec :: Int -> BusinessPayoutRequestBody -> ShowS
Show)
deriving
( [BusinessPayoutRequestBody] -> Encoding
[BusinessPayoutRequestBody] -> Value
BusinessPayoutRequestBody -> Encoding
BusinessPayoutRequestBody -> Value
(BusinessPayoutRequestBody -> Value)
-> (BusinessPayoutRequestBody -> Encoding)
-> ([BusinessPayoutRequestBody] -> Value)
-> ([BusinessPayoutRequestBody] -> Encoding)
-> ToJSON BusinessPayoutRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BusinessPayoutRequestBody] -> Encoding
$ctoEncodingList :: [BusinessPayoutRequestBody] -> Encoding
toJSONList :: [BusinessPayoutRequestBody] -> Value
$ctoJSONList :: [BusinessPayoutRequestBody] -> Value
toEncoding :: BusinessPayoutRequestBody -> Encoding
$ctoEncoding :: BusinessPayoutRequestBody -> Encoding
toJSON :: BusinessPayoutRequestBody -> Value
$ctoJSON :: BusinessPayoutRequestBody -> Value
ToJSON,
Value -> Parser [BusinessPayoutRequestBody]
Value -> Parser BusinessPayoutRequestBody
(Value -> Parser BusinessPayoutRequestBody)
-> (Value -> Parser [BusinessPayoutRequestBody])
-> FromJSON BusinessPayoutRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BusinessPayoutRequestBody]
$cparseJSONList :: Value -> Parser [BusinessPayoutRequestBody]
parseJSON :: Value -> Parser BusinessPayoutRequestBody
$cparseJSON :: Value -> Parser BusinessPayoutRequestBody
FromJSON
)
via (Autodocodec BusinessPayoutRequestBody)
instance HasCodec BusinessPayoutRequestBody where
codec :: JSONCodec BusinessPayoutRequestBody
codec =
Text
-> ObjectCodec BusinessPayoutRequestBody BusinessPayoutRequestBody
-> JSONCodec BusinessPayoutRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BusinessPayoutRequestBody" (ObjectCodec BusinessPayoutRequestBody BusinessPayoutRequestBody
-> JSONCodec BusinessPayoutRequestBody)
-> ObjectCodec BusinessPayoutRequestBody BusinessPayoutRequestBody
-> JSONCodec BusinessPayoutRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> DestinationBankAccount
-> MoneyAmount
-> BusinessPayoutRequestBody
BusinessPayoutRequestBody
(UUID
-> DestinationBankAccount
-> MoneyAmount
-> BusinessPayoutRequestBody)
-> Codec Object BusinessPayoutRequestBody UUID
-> Codec
Object
BusinessPayoutRequestBody
(DestinationBankAccount
-> MoneyAmount -> BusinessPayoutRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (BusinessPayoutRequestBody -> UUID)
-> Codec Object BusinessPayoutRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BusinessPayoutRequestBody -> UUID
businessPayoutIdempotencyKey
Codec
Object
BusinessPayoutRequestBody
(DestinationBankAccount
-> MoneyAmount -> BusinessPayoutRequestBody)
-> Codec Object BusinessPayoutRequestBody DestinationBankAccount
-> Codec
Object
BusinessPayoutRequestBody
(MoneyAmount -> BusinessPayoutRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec DestinationBankAccount DestinationBankAccount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"destination" ObjectCodec DestinationBankAccount DestinationBankAccount
-> (BusinessPayoutRequestBody -> DestinationBankAccount)
-> Codec Object BusinessPayoutRequestBody DestinationBankAccount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BusinessPayoutRequestBody -> DestinationBankAccount
businessPayoutDestination
Codec
Object
BusinessPayoutRequestBody
(MoneyAmount -> BusinessPayoutRequestBody)
-> Codec Object BusinessPayoutRequestBody MoneyAmount
-> ObjectCodec BusinessPayoutRequestBody BusinessPayoutRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (BusinessPayoutRequestBody -> MoneyAmount)
-> Codec Object BusinessPayoutRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BusinessPayoutRequestBody -> MoneyAmount
businessPayoutAmount
newtype PayoutMetadata = PayoutMetadata {PayoutMetadata -> Email
payoutMetadataBeneficiaryEmail :: Email}
deriving (PayoutMetadata -> PayoutMetadata -> Bool
(PayoutMetadata -> PayoutMetadata -> Bool)
-> (PayoutMetadata -> PayoutMetadata -> Bool) -> Eq PayoutMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PayoutMetadata -> PayoutMetadata -> Bool
$c/= :: PayoutMetadata -> PayoutMetadata -> Bool
== :: PayoutMetadata -> PayoutMetadata -> Bool
$c== :: PayoutMetadata -> PayoutMetadata -> Bool
Eq, Int -> PayoutMetadata -> ShowS
[PayoutMetadata] -> ShowS
PayoutMetadata -> String
(Int -> PayoutMetadata -> ShowS)
-> (PayoutMetadata -> String)
-> ([PayoutMetadata] -> ShowS)
-> Show PayoutMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PayoutMetadata] -> ShowS
$cshowList :: [PayoutMetadata] -> ShowS
show :: PayoutMetadata -> String
$cshow :: PayoutMetadata -> String
showsPrec :: Int -> PayoutMetadata -> ShowS
$cshowsPrec :: Int -> PayoutMetadata -> ShowS
Show)
deriving ([PayoutMetadata] -> Encoding
[PayoutMetadata] -> Value
PayoutMetadata -> Encoding
PayoutMetadata -> Value
(PayoutMetadata -> Value)
-> (PayoutMetadata -> Encoding)
-> ([PayoutMetadata] -> Value)
-> ([PayoutMetadata] -> Encoding)
-> ToJSON PayoutMetadata
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PayoutMetadata] -> Encoding
$ctoEncodingList :: [PayoutMetadata] -> Encoding
toJSONList :: [PayoutMetadata] -> Value
$ctoJSONList :: [PayoutMetadata] -> Value
toEncoding :: PayoutMetadata -> Encoding
$ctoEncoding :: PayoutMetadata -> Encoding
toJSON :: PayoutMetadata -> Value
$ctoJSON :: PayoutMetadata -> Value
ToJSON, Value -> Parser [PayoutMetadata]
Value -> Parser PayoutMetadata
(Value -> Parser PayoutMetadata)
-> (Value -> Parser [PayoutMetadata]) -> FromJSON PayoutMetadata
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PayoutMetadata]
$cparseJSONList :: Value -> Parser [PayoutMetadata]
parseJSON :: Value -> Parser PayoutMetadata
$cparseJSON :: Value -> Parser PayoutMetadata
FromJSON) via (Autodocodec PayoutMetadata)
instance HasCodec PayoutMetadata where
codec :: JSONCodec PayoutMetadata
codec =
Text
-> ObjectCodec PayoutMetadata PayoutMetadata
-> JSONCodec PayoutMetadata
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PayoutMetadata" (ObjectCodec PayoutMetadata PayoutMetadata
-> JSONCodec PayoutMetadata)
-> ObjectCodec PayoutMetadata PayoutMetadata
-> JSONCodec PayoutMetadata
forall a b. (a -> b) -> a -> b
$
Email -> PayoutMetadata
PayoutMetadata
(Email -> PayoutMetadata)
-> Codec Object PayoutMetadata Email
-> ObjectCodec PayoutMetadata PayoutMetadata
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Email Email
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"beneficiaryEmail" ObjectCodec Email Email
-> (PayoutMetadata -> Email) -> Codec Object PayoutMetadata Email
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutMetadata -> Email
payoutMetadataBeneficiaryEmail
data PayoutRequestBody = PayoutRequestBody
{ PayoutRequestBody -> UUID
payoutIdempotencyKey :: !UUID,
PayoutRequestBody -> Maybe PaymentSource
payoutSource :: !(Maybe PaymentSource),
PayoutRequestBody -> DestinationBankAccount
payoutDestination :: !DestinationBankAccount,
PayoutRequestBody -> MoneyAmount
payoutAmount :: !MoneyAmount,
PayoutRequestBody -> PayoutMetadata
payoutMetadata :: !PayoutMetadata
}
deriving (PayoutRequestBody -> PayoutRequestBody -> Bool
(PayoutRequestBody -> PayoutRequestBody -> Bool)
-> (PayoutRequestBody -> PayoutRequestBody -> Bool)
-> Eq PayoutRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PayoutRequestBody -> PayoutRequestBody -> Bool
$c/= :: PayoutRequestBody -> PayoutRequestBody -> Bool
== :: PayoutRequestBody -> PayoutRequestBody -> Bool
$c== :: PayoutRequestBody -> PayoutRequestBody -> Bool
Eq, Int -> PayoutRequestBody -> ShowS
[PayoutRequestBody] -> ShowS
PayoutRequestBody -> String
(Int -> PayoutRequestBody -> ShowS)
-> (PayoutRequestBody -> String)
-> ([PayoutRequestBody] -> ShowS)
-> Show PayoutRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PayoutRequestBody] -> ShowS
$cshowList :: [PayoutRequestBody] -> ShowS
show :: PayoutRequestBody -> String
$cshow :: PayoutRequestBody -> String
showsPrec :: Int -> PayoutRequestBody -> ShowS
$cshowsPrec :: Int -> PayoutRequestBody -> ShowS
Show)
deriving
( [PayoutRequestBody] -> Encoding
[PayoutRequestBody] -> Value
PayoutRequestBody -> Encoding
PayoutRequestBody -> Value
(PayoutRequestBody -> Value)
-> (PayoutRequestBody -> Encoding)
-> ([PayoutRequestBody] -> Value)
-> ([PayoutRequestBody] -> Encoding)
-> ToJSON PayoutRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PayoutRequestBody] -> Encoding
$ctoEncodingList :: [PayoutRequestBody] -> Encoding
toJSONList :: [PayoutRequestBody] -> Value
$ctoJSONList :: [PayoutRequestBody] -> Value
toEncoding :: PayoutRequestBody -> Encoding
$ctoEncoding :: PayoutRequestBody -> Encoding
toJSON :: PayoutRequestBody -> Value
$ctoJSON :: PayoutRequestBody -> Value
ToJSON,
Value -> Parser [PayoutRequestBody]
Value -> Parser PayoutRequestBody
(Value -> Parser PayoutRequestBody)
-> (Value -> Parser [PayoutRequestBody])
-> FromJSON PayoutRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PayoutRequestBody]
$cparseJSONList :: Value -> Parser [PayoutRequestBody]
parseJSON :: Value -> Parser PayoutRequestBody
$cparseJSON :: Value -> Parser PayoutRequestBody
FromJSON
)
via (Autodocodec PayoutRequestBody)
instance HasCodec PayoutRequestBody where
codec :: JSONCodec PayoutRequestBody
codec =
Text
-> ObjectCodec PayoutRequestBody PayoutRequestBody
-> JSONCodec PayoutRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PayoutRequestBody" (ObjectCodec PayoutRequestBody PayoutRequestBody
-> JSONCodec PayoutRequestBody)
-> ObjectCodec PayoutRequestBody PayoutRequestBody
-> JSONCodec PayoutRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Maybe PaymentSource
-> DestinationBankAccount
-> MoneyAmount
-> PayoutMetadata
-> PayoutRequestBody
PayoutRequestBody
(UUID
-> Maybe PaymentSource
-> DestinationBankAccount
-> MoneyAmount
-> PayoutMetadata
-> PayoutRequestBody)
-> Codec Object PayoutRequestBody UUID
-> Codec
Object
PayoutRequestBody
(Maybe PaymentSource
-> DestinationBankAccount
-> MoneyAmount
-> PayoutMetadata
-> PayoutRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (PayoutRequestBody -> UUID)
-> Codec Object PayoutRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutRequestBody -> UUID
payoutIdempotencyKey
Codec
Object
PayoutRequestBody
(Maybe PaymentSource
-> DestinationBankAccount
-> MoneyAmount
-> PayoutMetadata
-> PayoutRequestBody)
-> Codec Object PayoutRequestBody (Maybe PaymentSource)
-> Codec
Object
PayoutRequestBody
(DestinationBankAccount
-> MoneyAmount -> PayoutMetadata -> PayoutRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe PaymentSource) (Maybe PaymentSource)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"source" ObjectCodec (Maybe PaymentSource) (Maybe PaymentSource)
-> (PayoutRequestBody -> Maybe PaymentSource)
-> Codec Object PayoutRequestBody (Maybe PaymentSource)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutRequestBody -> Maybe PaymentSource
payoutSource
Codec
Object
PayoutRequestBody
(DestinationBankAccount
-> MoneyAmount -> PayoutMetadata -> PayoutRequestBody)
-> Codec Object PayoutRequestBody DestinationBankAccount
-> Codec
Object
PayoutRequestBody
(MoneyAmount -> PayoutMetadata -> PayoutRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec DestinationBankAccount DestinationBankAccount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"destination" ObjectCodec DestinationBankAccount DestinationBankAccount
-> (PayoutRequestBody -> DestinationBankAccount)
-> Codec Object PayoutRequestBody DestinationBankAccount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutRequestBody -> DestinationBankAccount
payoutDestination
Codec
Object
PayoutRequestBody
(MoneyAmount -> PayoutMetadata -> PayoutRequestBody)
-> Codec Object PayoutRequestBody MoneyAmount
-> Codec
Object PayoutRequestBody (PayoutMetadata -> PayoutRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (PayoutRequestBody -> MoneyAmount)
-> Codec Object PayoutRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutRequestBody -> MoneyAmount
payoutAmount
Codec
Object PayoutRequestBody (PayoutMetadata -> PayoutRequestBody)
-> Codec Object PayoutRequestBody PayoutMetadata
-> ObjectCodec PayoutRequestBody PayoutRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PayoutMetadata PayoutMetadata
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"metadata" ObjectCodec PayoutMetadata PayoutMetadata
-> (PayoutRequestBody -> PayoutMetadata)
-> Codec Object PayoutRequestBody PayoutMetadata
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutRequestBody -> PayoutMetadata
payoutMetadata
data PayoutReturnResponseBody = PayoutReturnResponseBody
{ PayoutReturnResponseBody -> UUID
payoutReturnResponseBodyId :: !UUID,
PayoutReturnResponseBody -> UUID
payoutReturnResponseBodyOriginalPayoutId :: !UUID,
PayoutReturnResponseBody -> MoneyAmount
payoutReturnResponseBodyAmount :: !MoneyAmount,
PayoutReturnResponseBody -> MoneyAmount
payoutReturnResponseBodyFees :: !MoneyAmount,
PayoutReturnResponseBody -> Text
payoutReturnResponseBodyReason :: !Text,
PayoutReturnResponseBody -> Status
payoutReturnResponseBodyStatus :: !Status,
PayoutReturnResponseBody -> UTCTime
payoutReturnResponseBodyCreateDate :: !UTCTime,
PayoutReturnResponseBody -> UTCTime
payoutReturnResponseBodyUpdateDate :: !UTCTime
}
deriving (PayoutReturnResponseBody -> PayoutReturnResponseBody -> Bool
(PayoutReturnResponseBody -> PayoutReturnResponseBody -> Bool)
-> (PayoutReturnResponseBody -> PayoutReturnResponseBody -> Bool)
-> Eq PayoutReturnResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PayoutReturnResponseBody -> PayoutReturnResponseBody -> Bool
$c/= :: PayoutReturnResponseBody -> PayoutReturnResponseBody -> Bool
== :: PayoutReturnResponseBody -> PayoutReturnResponseBody -> Bool
$c== :: PayoutReturnResponseBody -> PayoutReturnResponseBody -> Bool
Eq, Int -> PayoutReturnResponseBody -> ShowS
[PayoutReturnResponseBody] -> ShowS
PayoutReturnResponseBody -> String
(Int -> PayoutReturnResponseBody -> ShowS)
-> (PayoutReturnResponseBody -> String)
-> ([PayoutReturnResponseBody] -> ShowS)
-> Show PayoutReturnResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PayoutReturnResponseBody] -> ShowS
$cshowList :: [PayoutReturnResponseBody] -> ShowS
show :: PayoutReturnResponseBody -> String
$cshow :: PayoutReturnResponseBody -> String
showsPrec :: Int -> PayoutReturnResponseBody -> ShowS
$cshowsPrec :: Int -> PayoutReturnResponseBody -> ShowS
Show)
deriving
( [PayoutReturnResponseBody] -> Encoding
[PayoutReturnResponseBody] -> Value
PayoutReturnResponseBody -> Encoding
PayoutReturnResponseBody -> Value
(PayoutReturnResponseBody -> Value)
-> (PayoutReturnResponseBody -> Encoding)
-> ([PayoutReturnResponseBody] -> Value)
-> ([PayoutReturnResponseBody] -> Encoding)
-> ToJSON PayoutReturnResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PayoutReturnResponseBody] -> Encoding
$ctoEncodingList :: [PayoutReturnResponseBody] -> Encoding
toJSONList :: [PayoutReturnResponseBody] -> Value
$ctoJSONList :: [PayoutReturnResponseBody] -> Value
toEncoding :: PayoutReturnResponseBody -> Encoding
$ctoEncoding :: PayoutReturnResponseBody -> Encoding
toJSON :: PayoutReturnResponseBody -> Value
$ctoJSON :: PayoutReturnResponseBody -> Value
ToJSON,
Value -> Parser [PayoutReturnResponseBody]
Value -> Parser PayoutReturnResponseBody
(Value -> Parser PayoutReturnResponseBody)
-> (Value -> Parser [PayoutReturnResponseBody])
-> FromJSON PayoutReturnResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PayoutReturnResponseBody]
$cparseJSONList :: Value -> Parser [PayoutReturnResponseBody]
parseJSON :: Value -> Parser PayoutReturnResponseBody
$cparseJSON :: Value -> Parser PayoutReturnResponseBody
FromJSON
)
via (Autodocodec PayoutReturnResponseBody)
instance HasCodec PayoutReturnResponseBody where
codec :: JSONCodec PayoutReturnResponseBody
codec =
Text
-> ObjectCodec PayoutReturnResponseBody PayoutReturnResponseBody
-> JSONCodec PayoutReturnResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PayoutReturnResponseBody" (ObjectCodec PayoutReturnResponseBody PayoutReturnResponseBody
-> JSONCodec PayoutReturnResponseBody)
-> ObjectCodec PayoutReturnResponseBody PayoutReturnResponseBody
-> JSONCodec PayoutReturnResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody
PayoutReturnResponseBody
(UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody UUID
-> Codec
Object
PayoutReturnResponseBody
(UUID
-> MoneyAmount
-> MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (PayoutReturnResponseBody -> UUID)
-> Codec Object PayoutReturnResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> UUID
payoutReturnResponseBodyId
Codec
Object
PayoutReturnResponseBody
(UUID
-> MoneyAmount
-> MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody UUID
-> Codec
Object
PayoutReturnResponseBody
(MoneyAmount
-> MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"payoutId" ObjectCodec UUID UUID
-> (PayoutReturnResponseBody -> UUID)
-> Codec Object PayoutReturnResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> UUID
payoutReturnResponseBodyOriginalPayoutId
Codec
Object
PayoutReturnResponseBody
(MoneyAmount
-> MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody MoneyAmount
-> Codec
Object
PayoutReturnResponseBody
(MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (PayoutReturnResponseBody -> MoneyAmount)
-> Codec Object PayoutReturnResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> MoneyAmount
payoutReturnResponseBodyAmount
Codec
Object
PayoutReturnResponseBody
(MoneyAmount
-> Text
-> Status
-> UTCTime
-> UTCTime
-> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody MoneyAmount
-> Codec
Object
PayoutReturnResponseBody
(Text -> Status -> UTCTime -> UTCTime -> PayoutReturnResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fees" ObjectCodec MoneyAmount MoneyAmount
-> (PayoutReturnResponseBody -> MoneyAmount)
-> Codec Object PayoutReturnResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> MoneyAmount
payoutReturnResponseBodyFees
Codec
Object
PayoutReturnResponseBody
(Text -> Status -> UTCTime -> UTCTime -> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody Text
-> Codec
Object
PayoutReturnResponseBody
(Status -> UTCTime -> UTCTime -> PayoutReturnResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"reason" ObjectCodec Text Text
-> (PayoutReturnResponseBody -> Text)
-> Codec Object PayoutReturnResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> Text
payoutReturnResponseBodyReason
Codec
Object
PayoutReturnResponseBody
(Status -> UTCTime -> UTCTime -> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody Status
-> Codec
Object
PayoutReturnResponseBody
(UTCTime -> UTCTime -> PayoutReturnResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (PayoutReturnResponseBody -> Status)
-> Codec Object PayoutReturnResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> Status
payoutReturnResponseBodyStatus
Codec
Object
PayoutReturnResponseBody
(UTCTime -> UTCTime -> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody UTCTime
-> Codec
Object
PayoutReturnResponseBody
(UTCTime -> PayoutReturnResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (PayoutReturnResponseBody -> UTCTime)
-> Codec Object PayoutReturnResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> UTCTime
payoutReturnResponseBodyCreateDate
Codec
Object
PayoutReturnResponseBody
(UTCTime -> PayoutReturnResponseBody)
-> Codec Object PayoutReturnResponseBody UTCTime
-> ObjectCodec PayoutReturnResponseBody PayoutReturnResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (PayoutReturnResponseBody -> UTCTime)
-> Codec Object PayoutReturnResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PayoutReturnResponseBody -> UTCTime
payoutReturnResponseBodyUpdateDate
data PayoutErrorCode
= InsufficientFunds
| TransactionDenied
| TransactionFailed
| TransactionReturned
| BankTransactionError
| FiatAccountLimitExceeded
| InvalidBankAccountNumber
| InvalidACHRoutingTransitNumber
| InvalidWireRoutingTransitNumber
| VendorInactive
deriving (PayoutErrorCode -> PayoutErrorCode -> Bool
(PayoutErrorCode -> PayoutErrorCode -> Bool)
-> (PayoutErrorCode -> PayoutErrorCode -> Bool)
-> Eq PayoutErrorCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PayoutErrorCode -> PayoutErrorCode -> Bool
$c/= :: PayoutErrorCode -> PayoutErrorCode -> Bool
== :: PayoutErrorCode -> PayoutErrorCode -> Bool
$c== :: PayoutErrorCode -> PayoutErrorCode -> Bool
Eq, Int -> PayoutErrorCode -> ShowS
[PayoutErrorCode] -> ShowS
PayoutErrorCode -> String
(Int -> PayoutErrorCode -> ShowS)
-> (PayoutErrorCode -> String)
-> ([PayoutErrorCode] -> ShowS)
-> Show PayoutErrorCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PayoutErrorCode] -> ShowS
$cshowList :: [PayoutErrorCode] -> ShowS
show :: PayoutErrorCode -> String
$cshow :: PayoutErrorCode -> String
showsPrec :: Int -> PayoutErrorCode -> ShowS
$cshowsPrec :: Int -> PayoutErrorCode -> ShowS
Show)
deriving
( Value -> Parser [PayoutErrorCode]
Value -> Parser PayoutErrorCode
(Value -> Parser PayoutErrorCode)
-> (Value -> Parser [PayoutErrorCode]) -> FromJSON PayoutErrorCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PayoutErrorCode]
$cparseJSONList :: Value -> Parser [PayoutErrorCode]
parseJSON :: Value -> Parser PayoutErrorCode
$cparseJSON :: Value -> Parser PayoutErrorCode
FromJSON,
[PayoutErrorCode] -> Encoding
[PayoutErrorCode] -> Value
PayoutErrorCode -> Encoding
PayoutErrorCode -> Value
(PayoutErrorCode -> Value)
-> (PayoutErrorCode -> Encoding)
-> ([PayoutErrorCode] -> Value)
-> ([PayoutErrorCode] -> Encoding)
-> ToJSON PayoutErrorCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PayoutErrorCode] -> Encoding
$ctoEncodingList :: [PayoutErrorCode] -> Encoding
toJSONList :: [PayoutErrorCode] -> Value
$ctoJSONList :: [PayoutErrorCode] -> Value
toEncoding :: PayoutErrorCode -> Encoding
$ctoEncoding :: PayoutErrorCode -> Encoding
toJSON :: PayoutErrorCode -> Value
$ctoJSON :: PayoutErrorCode -> Value
ToJSON
)
via (Autodocodec PayoutErrorCode)
instance HasCodec PayoutErrorCode where
codec :: JSONCodec PayoutErrorCode
codec =
NonEmpty (PayoutErrorCode, Text) -> JSONCodec PayoutErrorCode
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (PayoutErrorCode, Text) -> JSONCodec PayoutErrorCode)
-> NonEmpty (PayoutErrorCode, Text) -> JSONCodec PayoutErrorCode
forall a b. (a -> b) -> a -> b
$
[(PayoutErrorCode, Text)] -> NonEmpty (PayoutErrorCode, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (PayoutErrorCode
InsufficientFunds, Text
"insufficient_funds"),
(PayoutErrorCode
TransactionDenied, Text
"transaction_denied"),
(PayoutErrorCode
TransactionFailed, Text
"transaction_failed"),
(PayoutErrorCode
TransactionReturned, Text
"transaction_returned"),
(PayoutErrorCode
BankTransactionError, Text
"bank_transaction_error"),
(PayoutErrorCode
FiatAccountLimitExceeded, Text
"fiat_account_limit_exceeded"),
(PayoutErrorCode
InvalidBankAccountNumber, Text
"invalid_bank_account_number"),
(PayoutErrorCode
InvalidACHRoutingTransitNumber, Text
"invalid_ach_rtn"),
(PayoutErrorCode
InvalidWireRoutingTransitNumber, Text
"invalid_wire_rtn"),
(PayoutErrorCode
VendorInactive, Text
"vendor_inactive")
]
data ConfigurationRequest
type instance CircleRequest ConfigurationRequest = CircleResponseBody ConfigurationResponseBody
newtype ConfigurationResponseBody = ConfigurationResponseBody {ConfigurationResponseBody -> WalletConfig
configurationResponseBodyPayments :: WalletConfig}
deriving (ConfigurationResponseBody -> ConfigurationResponseBody -> Bool
(ConfigurationResponseBody -> ConfigurationResponseBody -> Bool)
-> (ConfigurationResponseBody -> ConfigurationResponseBody -> Bool)
-> Eq ConfigurationResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfigurationResponseBody -> ConfigurationResponseBody -> Bool
$c/= :: ConfigurationResponseBody -> ConfigurationResponseBody -> Bool
== :: ConfigurationResponseBody -> ConfigurationResponseBody -> Bool
$c== :: ConfigurationResponseBody -> ConfigurationResponseBody -> Bool
Eq, Int -> ConfigurationResponseBody -> ShowS
[ConfigurationResponseBody] -> ShowS
ConfigurationResponseBody -> String
(Int -> ConfigurationResponseBody -> ShowS)
-> (ConfigurationResponseBody -> String)
-> ([ConfigurationResponseBody] -> ShowS)
-> Show ConfigurationResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfigurationResponseBody] -> ShowS
$cshowList :: [ConfigurationResponseBody] -> ShowS
show :: ConfigurationResponseBody -> String
$cshow :: ConfigurationResponseBody -> String
showsPrec :: Int -> ConfigurationResponseBody -> ShowS
$cshowsPrec :: Int -> ConfigurationResponseBody -> ShowS
Show)
deriving
( Value -> Parser [ConfigurationResponseBody]
Value -> Parser ConfigurationResponseBody
(Value -> Parser ConfigurationResponseBody)
-> (Value -> Parser [ConfigurationResponseBody])
-> FromJSON ConfigurationResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ConfigurationResponseBody]
$cparseJSONList :: Value -> Parser [ConfigurationResponseBody]
parseJSON :: Value -> Parser ConfigurationResponseBody
$cparseJSON :: Value -> Parser ConfigurationResponseBody
FromJSON,
[ConfigurationResponseBody] -> Encoding
[ConfigurationResponseBody] -> Value
ConfigurationResponseBody -> Encoding
ConfigurationResponseBody -> Value
(ConfigurationResponseBody -> Value)
-> (ConfigurationResponseBody -> Encoding)
-> ([ConfigurationResponseBody] -> Value)
-> ([ConfigurationResponseBody] -> Encoding)
-> ToJSON ConfigurationResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ConfigurationResponseBody] -> Encoding
$ctoEncodingList :: [ConfigurationResponseBody] -> Encoding
toJSONList :: [ConfigurationResponseBody] -> Value
$ctoJSONList :: [ConfigurationResponseBody] -> Value
toEncoding :: ConfigurationResponseBody -> Encoding
$ctoEncoding :: ConfigurationResponseBody -> Encoding
toJSON :: ConfigurationResponseBody -> Value
$ctoJSON :: ConfigurationResponseBody -> Value
ToJSON
)
via (Autodocodec ConfigurationResponseBody)
instance HasCodec ConfigurationResponseBody where
codec :: JSONCodec ConfigurationResponseBody
codec =
Text
-> ObjectCodec ConfigurationResponseBody ConfigurationResponseBody
-> JSONCodec ConfigurationResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ConfigurationResponseBody" (ObjectCodec ConfigurationResponseBody ConfigurationResponseBody
-> JSONCodec ConfigurationResponseBody)
-> ObjectCodec ConfigurationResponseBody ConfigurationResponseBody
-> JSONCodec ConfigurationResponseBody
forall a b. (a -> b) -> a -> b
$
WalletConfig -> ConfigurationResponseBody
ConfigurationResponseBody
(WalletConfig -> ConfigurationResponseBody)
-> Codec Object ConfigurationResponseBody WalletConfig
-> ObjectCodec ConfigurationResponseBody ConfigurationResponseBody
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec WalletConfig WalletConfig
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"payments" ObjectCodec WalletConfig WalletConfig
-> (ConfigurationResponseBody -> WalletConfig)
-> Codec Object ConfigurationResponseBody WalletConfig
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ConfigurationResponseBody -> WalletConfig
configurationResponseBodyPayments
newtype WalletConfig = WalletConfig {WalletConfig -> WalletId
masterWalletId :: WalletId}
deriving (WalletConfig -> WalletConfig -> Bool
(WalletConfig -> WalletConfig -> Bool)
-> (WalletConfig -> WalletConfig -> Bool) -> Eq WalletConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletConfig -> WalletConfig -> Bool
$c/= :: WalletConfig -> WalletConfig -> Bool
== :: WalletConfig -> WalletConfig -> Bool
$c== :: WalletConfig -> WalletConfig -> Bool
Eq, Int -> WalletConfig -> ShowS
[WalletConfig] -> ShowS
WalletConfig -> String
(Int -> WalletConfig -> ShowS)
-> (WalletConfig -> String)
-> ([WalletConfig] -> ShowS)
-> Show WalletConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletConfig] -> ShowS
$cshowList :: [WalletConfig] -> ShowS
show :: WalletConfig -> String
$cshow :: WalletConfig -> String
showsPrec :: Int -> WalletConfig -> ShowS
$cshowsPrec :: Int -> WalletConfig -> ShowS
Show)
deriving
( Value -> Parser [WalletConfig]
Value -> Parser WalletConfig
(Value -> Parser WalletConfig)
-> (Value -> Parser [WalletConfig]) -> FromJSON WalletConfig
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WalletConfig]
$cparseJSONList :: Value -> Parser [WalletConfig]
parseJSON :: Value -> Parser WalletConfig
$cparseJSON :: Value -> Parser WalletConfig
FromJSON,
[WalletConfig] -> Encoding
[WalletConfig] -> Value
WalletConfig -> Encoding
WalletConfig -> Value
(WalletConfig -> Value)
-> (WalletConfig -> Encoding)
-> ([WalletConfig] -> Value)
-> ([WalletConfig] -> Encoding)
-> ToJSON WalletConfig
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WalletConfig] -> Encoding
$ctoEncodingList :: [WalletConfig] -> Encoding
toJSONList :: [WalletConfig] -> Value
$ctoJSONList :: [WalletConfig] -> Value
toEncoding :: WalletConfig -> Encoding
$ctoEncoding :: WalletConfig -> Encoding
toJSON :: WalletConfig -> Value
$ctoJSON :: WalletConfig -> Value
ToJSON
)
via (Autodocodec WalletConfig)
instance HasCodec WalletConfig where
codec :: JSONCodec WalletConfig
codec =
Text
-> ObjectCodec WalletConfig WalletConfig -> JSONCodec WalletConfig
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"WalletConfig" (ObjectCodec WalletConfig WalletConfig -> JSONCodec WalletConfig)
-> ObjectCodec WalletConfig WalletConfig -> JSONCodec WalletConfig
forall a b. (a -> b) -> a -> b
$
WalletId -> WalletConfig
WalletConfig
(WalletId -> WalletConfig)
-> Codec Object WalletConfig WalletId
-> ObjectCodec WalletConfig WalletConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec WalletId WalletId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"masterWalletId" ObjectCodec WalletId WalletId
-> (WalletConfig -> WalletId) -> Codec Object WalletConfig WalletId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WalletConfig -> WalletId
masterWalletId
data EncryptionRequest
type instance CircleRequest EncryptionRequest = CircleResponseBody EncryptionResponseBody
data EncryptionResponseBody = EncryptionResponseBody
{ EncryptionResponseBody -> Text
encryptionResponseBodyKeyId :: !Text,
EncryptionResponseBody -> PGPKey
encryptionResponseBodyPublicKey :: !PGPKey
}
deriving (EncryptionResponseBody -> EncryptionResponseBody -> Bool
(EncryptionResponseBody -> EncryptionResponseBody -> Bool)
-> (EncryptionResponseBody -> EncryptionResponseBody -> Bool)
-> Eq EncryptionResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EncryptionResponseBody -> EncryptionResponseBody -> Bool
$c/= :: EncryptionResponseBody -> EncryptionResponseBody -> Bool
== :: EncryptionResponseBody -> EncryptionResponseBody -> Bool
$c== :: EncryptionResponseBody -> EncryptionResponseBody -> Bool
Eq, Int -> EncryptionResponseBody -> ShowS
[EncryptionResponseBody] -> ShowS
EncryptionResponseBody -> String
(Int -> EncryptionResponseBody -> ShowS)
-> (EncryptionResponseBody -> String)
-> ([EncryptionResponseBody] -> ShowS)
-> Show EncryptionResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EncryptionResponseBody] -> ShowS
$cshowList :: [EncryptionResponseBody] -> ShowS
show :: EncryptionResponseBody -> String
$cshow :: EncryptionResponseBody -> String
showsPrec :: Int -> EncryptionResponseBody -> ShowS
$cshowsPrec :: Int -> EncryptionResponseBody -> ShowS
Show)
deriving ([EncryptionResponseBody] -> Encoding
[EncryptionResponseBody] -> Value
EncryptionResponseBody -> Encoding
EncryptionResponseBody -> Value
(EncryptionResponseBody -> Value)
-> (EncryptionResponseBody -> Encoding)
-> ([EncryptionResponseBody] -> Value)
-> ([EncryptionResponseBody] -> Encoding)
-> ToJSON EncryptionResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [EncryptionResponseBody] -> Encoding
$ctoEncodingList :: [EncryptionResponseBody] -> Encoding
toJSONList :: [EncryptionResponseBody] -> Value
$ctoJSONList :: [EncryptionResponseBody] -> Value
toEncoding :: EncryptionResponseBody -> Encoding
$ctoEncoding :: EncryptionResponseBody -> Encoding
toJSON :: EncryptionResponseBody -> Value
$ctoJSON :: EncryptionResponseBody -> Value
ToJSON, Value -> Parser [EncryptionResponseBody]
Value -> Parser EncryptionResponseBody
(Value -> Parser EncryptionResponseBody)
-> (Value -> Parser [EncryptionResponseBody])
-> FromJSON EncryptionResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EncryptionResponseBody]
$cparseJSONList :: Value -> Parser [EncryptionResponseBody]
parseJSON :: Value -> Parser EncryptionResponseBody
$cparseJSON :: Value -> Parser EncryptionResponseBody
FromJSON) via (Autodocodec EncryptionResponseBody)
newtype PGPKey = PGPKey
{ PGPKey -> Text
unPGPKey :: Text
}
deriving (PGPKey -> PGPKey -> Bool
(PGPKey -> PGPKey -> Bool)
-> (PGPKey -> PGPKey -> Bool) -> Eq PGPKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PGPKey -> PGPKey -> Bool
$c/= :: PGPKey -> PGPKey -> Bool
== :: PGPKey -> PGPKey -> Bool
$c== :: PGPKey -> PGPKey -> Bool
Eq, Int -> PGPKey -> ShowS
[PGPKey] -> ShowS
PGPKey -> String
(Int -> PGPKey -> ShowS)
-> (PGPKey -> String) -> ([PGPKey] -> ShowS) -> Show PGPKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PGPKey] -> ShowS
$cshowList :: [PGPKey] -> ShowS
show :: PGPKey -> String
$cshow :: PGPKey -> String
showsPrec :: Int -> PGPKey -> ShowS
$cshowsPrec :: Int -> PGPKey -> ShowS
Show, [PGPKey] -> Encoding
[PGPKey] -> Value
PGPKey -> Encoding
PGPKey -> Value
(PGPKey -> Value)
-> (PGPKey -> Encoding)
-> ([PGPKey] -> Value)
-> ([PGPKey] -> Encoding)
-> ToJSON PGPKey
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PGPKey] -> Encoding
$ctoEncodingList :: [PGPKey] -> Encoding
toJSONList :: [PGPKey] -> Value
$ctoJSONList :: [PGPKey] -> Value
toEncoding :: PGPKey -> Encoding
$ctoEncoding :: PGPKey -> Encoding
toJSON :: PGPKey -> Value
$ctoJSON :: PGPKey -> Value
ToJSON, Value -> Parser [PGPKey]
Value -> Parser PGPKey
(Value -> Parser PGPKey)
-> (Value -> Parser [PGPKey]) -> FromJSON PGPKey
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PGPKey]
$cparseJSONList :: Value -> Parser [PGPKey]
parseJSON :: Value -> Parser PGPKey
$cparseJSON :: Value -> Parser PGPKey
FromJSON)
instance HasCodec PGPKey where
codec :: JSONCodec PGPKey
codec = (Text -> PGPKey)
-> (PGPKey -> Text) -> Codec Value Text Text -> JSONCodec PGPKey
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> PGPKey
PGPKey PGPKey -> Text
unPGPKey Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
instance HasCodec EncryptionResponseBody where
codec :: JSONCodec EncryptionResponseBody
codec =
Text
-> ObjectCodec EncryptionResponseBody EncryptionResponseBody
-> JSONCodec EncryptionResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"EncryptionResponseBody" (ObjectCodec EncryptionResponseBody EncryptionResponseBody
-> JSONCodec EncryptionResponseBody)
-> ObjectCodec EncryptionResponseBody EncryptionResponseBody
-> JSONCodec EncryptionResponseBody
forall a b. (a -> b) -> a -> b
$
Text -> PGPKey -> EncryptionResponseBody
EncryptionResponseBody
(Text -> PGPKey -> EncryptionResponseBody)
-> Codec Object EncryptionResponseBody Text
-> Codec
Object EncryptionResponseBody (PGPKey -> EncryptionResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"keyId" ObjectCodec Text Text
-> (EncryptionResponseBody -> Text)
-> Codec Object EncryptionResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= EncryptionResponseBody -> Text
encryptionResponseBodyKeyId
Codec
Object EncryptionResponseBody (PGPKey -> EncryptionResponseBody)
-> Codec Object EncryptionResponseBody PGPKey
-> ObjectCodec EncryptionResponseBody EncryptionResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PGPKey PGPKey
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"publicKey" ObjectCodec PGPKey PGPKey
-> (EncryptionResponseBody -> PGPKey)
-> Codec Object EncryptionResponseBody PGPKey
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= EncryptionResponseBody -> PGPKey
encryptionResponseBodyPublicKey
data ChannelsRequest
type instance CircleRequest ChannelsRequest = CircleResponseBody ChannelResponseBody
newtype ChannelResponseBody = ChannelResponseBody {ChannelResponseBody -> [Channel]
channels :: [Channel]}
deriving (ChannelResponseBody -> ChannelResponseBody -> Bool
(ChannelResponseBody -> ChannelResponseBody -> Bool)
-> (ChannelResponseBody -> ChannelResponseBody -> Bool)
-> Eq ChannelResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChannelResponseBody -> ChannelResponseBody -> Bool
$c/= :: ChannelResponseBody -> ChannelResponseBody -> Bool
== :: ChannelResponseBody -> ChannelResponseBody -> Bool
$c== :: ChannelResponseBody -> ChannelResponseBody -> Bool
Eq, Int -> ChannelResponseBody -> ShowS
[ChannelResponseBody] -> ShowS
ChannelResponseBody -> String
(Int -> ChannelResponseBody -> ShowS)
-> (ChannelResponseBody -> String)
-> ([ChannelResponseBody] -> ShowS)
-> Show ChannelResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelResponseBody] -> ShowS
$cshowList :: [ChannelResponseBody] -> ShowS
show :: ChannelResponseBody -> String
$cshow :: ChannelResponseBody -> String
showsPrec :: Int -> ChannelResponseBody -> ShowS
$cshowsPrec :: Int -> ChannelResponseBody -> ShowS
Show)
deriving
( Value -> Parser [ChannelResponseBody]
Value -> Parser ChannelResponseBody
(Value -> Parser ChannelResponseBody)
-> (Value -> Parser [ChannelResponseBody])
-> FromJSON ChannelResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ChannelResponseBody]
$cparseJSONList :: Value -> Parser [ChannelResponseBody]
parseJSON :: Value -> Parser ChannelResponseBody
$cparseJSON :: Value -> Parser ChannelResponseBody
FromJSON,
[ChannelResponseBody] -> Encoding
[ChannelResponseBody] -> Value
ChannelResponseBody -> Encoding
ChannelResponseBody -> Value
(ChannelResponseBody -> Value)
-> (ChannelResponseBody -> Encoding)
-> ([ChannelResponseBody] -> Value)
-> ([ChannelResponseBody] -> Encoding)
-> ToJSON ChannelResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ChannelResponseBody] -> Encoding
$ctoEncodingList :: [ChannelResponseBody] -> Encoding
toJSONList :: [ChannelResponseBody] -> Value
$ctoJSONList :: [ChannelResponseBody] -> Value
toEncoding :: ChannelResponseBody -> Encoding
$ctoEncoding :: ChannelResponseBody -> Encoding
toJSON :: ChannelResponseBody -> Value
$ctoJSON :: ChannelResponseBody -> Value
ToJSON
)
via (Autodocodec ChannelResponseBody)
instance HasCodec ChannelResponseBody where
codec :: JSONCodec ChannelResponseBody
codec =
Text
-> ObjectCodec ChannelResponseBody ChannelResponseBody
-> JSONCodec ChannelResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ChannelResponseBody" (ObjectCodec ChannelResponseBody ChannelResponseBody
-> JSONCodec ChannelResponseBody)
-> ObjectCodec ChannelResponseBody ChannelResponseBody
-> JSONCodec ChannelResponseBody
forall a b. (a -> b) -> a -> b
$
[Channel] -> ChannelResponseBody
ChannelResponseBody
([Channel] -> ChannelResponseBody)
-> Codec Object ChannelResponseBody [Channel]
-> ObjectCodec ChannelResponseBody ChannelResponseBody
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec [Channel] [Channel]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"channels" ObjectCodec [Channel] [Channel]
-> (ChannelResponseBody -> [Channel])
-> Codec Object ChannelResponseBody [Channel]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChannelResponseBody -> [Channel]
channels
data Channel = Channel
{ Channel -> UUID
channelId :: !UUID,
Channel -> Bool
channelDefault :: !Bool,
Channel -> Text
channelCardDescriptor :: !Text,
Channel -> Text
channelAchDescriptor :: !Text
}
deriving (Channel -> Channel -> Bool
(Channel -> Channel -> Bool)
-> (Channel -> Channel -> Bool) -> Eq Channel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Channel -> Channel -> Bool
$c/= :: Channel -> Channel -> Bool
== :: Channel -> Channel -> Bool
$c== :: Channel -> Channel -> Bool
Eq, Int -> Channel -> ShowS
[Channel] -> ShowS
Channel -> String
(Int -> Channel -> ShowS)
-> (Channel -> String) -> ([Channel] -> ShowS) -> Show Channel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Channel] -> ShowS
$cshowList :: [Channel] -> ShowS
show :: Channel -> String
$cshow :: Channel -> String
showsPrec :: Int -> Channel -> ShowS
$cshowsPrec :: Int -> Channel -> ShowS
Show)
deriving
( Value -> Parser [Channel]
Value -> Parser Channel
(Value -> Parser Channel)
-> (Value -> Parser [Channel]) -> FromJSON Channel
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Channel]
$cparseJSONList :: Value -> Parser [Channel]
parseJSON :: Value -> Parser Channel
$cparseJSON :: Value -> Parser Channel
FromJSON,
[Channel] -> Encoding
[Channel] -> Value
Channel -> Encoding
Channel -> Value
(Channel -> Value)
-> (Channel -> Encoding)
-> ([Channel] -> Value)
-> ([Channel] -> Encoding)
-> ToJSON Channel
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Channel] -> Encoding
$ctoEncodingList :: [Channel] -> Encoding
toJSONList :: [Channel] -> Value
$ctoJSONList :: [Channel] -> Value
toEncoding :: Channel -> Encoding
$ctoEncoding :: Channel -> Encoding
toJSON :: Channel -> Value
$ctoJSON :: Channel -> Value
ToJSON
)
via (Autodocodec Channel)
instance HasCodec Channel where
codec :: JSONCodec Channel
codec =
Text -> ObjectCodec Channel Channel -> JSONCodec Channel
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"Channel" (ObjectCodec Channel Channel -> JSONCodec Channel)
-> ObjectCodec Channel Channel -> JSONCodec Channel
forall a b. (a -> b) -> a -> b
$
UUID -> Bool -> Text -> Text -> Channel
Channel
(UUID -> Bool -> Text -> Text -> Channel)
-> Codec Object Channel UUID
-> Codec Object Channel (Bool -> Text -> Text -> Channel)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (Channel -> UUID) -> Codec Object Channel UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Channel -> UUID
channelId
Codec Object Channel (Bool -> Text -> Text -> Channel)
-> Codec Object Channel Bool
-> Codec Object Channel (Text -> Text -> Channel)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Bool Bool
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"default" ObjectCodec Bool Bool
-> (Channel -> Bool) -> Codec Object Channel Bool
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Channel -> Bool
channelDefault
Codec Object Channel (Text -> Text -> Channel)
-> Codec Object Channel Text
-> Codec Object Channel (Text -> Channel)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"cardDescriptor" ObjectCodec Text Text
-> (Channel -> Text) -> Codec Object Channel Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Channel -> Text
channelCardDescriptor
Codec Object Channel (Text -> Channel)
-> Codec Object Channel Text -> ObjectCodec Channel Channel
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"achDescriptor" ObjectCodec Text Text
-> (Channel -> Text) -> Codec Object Channel Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Channel -> Text
channelAchDescriptor
data StablecoinsRequest
type instance CircleRequest StablecoinsRequest = CircleResponseBody [StablecoinResponseBody]
data StablecoinResponseBody = StablecoinResponseBody
{ StablecoinResponseBody -> Text
stablecoinResponseBodyName :: !Text,
StablecoinResponseBody -> Stablecoin
stablecoinResponseBodySymbol :: !Stablecoin,
StablecoinResponseBody -> Text
stablecoinResponseBodyTotalAmount :: !Text,
StablecoinResponseBody -> [ChainAmount]
stablecoinResponseBodyChains :: ![ChainAmount]
}
deriving (StablecoinResponseBody -> StablecoinResponseBody -> Bool
(StablecoinResponseBody -> StablecoinResponseBody -> Bool)
-> (StablecoinResponseBody -> StablecoinResponseBody -> Bool)
-> Eq StablecoinResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StablecoinResponseBody -> StablecoinResponseBody -> Bool
$c/= :: StablecoinResponseBody -> StablecoinResponseBody -> Bool
== :: StablecoinResponseBody -> StablecoinResponseBody -> Bool
$c== :: StablecoinResponseBody -> StablecoinResponseBody -> Bool
Eq, Int -> StablecoinResponseBody -> ShowS
[StablecoinResponseBody] -> ShowS
StablecoinResponseBody -> String
(Int -> StablecoinResponseBody -> ShowS)
-> (StablecoinResponseBody -> String)
-> ([StablecoinResponseBody] -> ShowS)
-> Show StablecoinResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StablecoinResponseBody] -> ShowS
$cshowList :: [StablecoinResponseBody] -> ShowS
show :: StablecoinResponseBody -> String
$cshow :: StablecoinResponseBody -> String
showsPrec :: Int -> StablecoinResponseBody -> ShowS
$cshowsPrec :: Int -> StablecoinResponseBody -> ShowS
Show)
deriving
( Value -> Parser [StablecoinResponseBody]
Value -> Parser StablecoinResponseBody
(Value -> Parser StablecoinResponseBody)
-> (Value -> Parser [StablecoinResponseBody])
-> FromJSON StablecoinResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [StablecoinResponseBody]
$cparseJSONList :: Value -> Parser [StablecoinResponseBody]
parseJSON :: Value -> Parser StablecoinResponseBody
$cparseJSON :: Value -> Parser StablecoinResponseBody
FromJSON,
[StablecoinResponseBody] -> Encoding
[StablecoinResponseBody] -> Value
StablecoinResponseBody -> Encoding
StablecoinResponseBody -> Value
(StablecoinResponseBody -> Value)
-> (StablecoinResponseBody -> Encoding)
-> ([StablecoinResponseBody] -> Value)
-> ([StablecoinResponseBody] -> Encoding)
-> ToJSON StablecoinResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [StablecoinResponseBody] -> Encoding
$ctoEncodingList :: [StablecoinResponseBody] -> Encoding
toJSONList :: [StablecoinResponseBody] -> Value
$ctoJSONList :: [StablecoinResponseBody] -> Value
toEncoding :: StablecoinResponseBody -> Encoding
$ctoEncoding :: StablecoinResponseBody -> Encoding
toJSON :: StablecoinResponseBody -> Value
$ctoJSON :: StablecoinResponseBody -> Value
ToJSON
)
via (Autodocodec StablecoinResponseBody)
instance HasCodec StablecoinResponseBody where
codec :: JSONCodec StablecoinResponseBody
codec =
Text
-> ObjectCodec StablecoinResponseBody StablecoinResponseBody
-> JSONCodec StablecoinResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"StablecoinResponseBody" (ObjectCodec StablecoinResponseBody StablecoinResponseBody
-> JSONCodec StablecoinResponseBody)
-> ObjectCodec StablecoinResponseBody StablecoinResponseBody
-> JSONCodec StablecoinResponseBody
forall a b. (a -> b) -> a -> b
$
Text
-> Stablecoin -> Text -> [ChainAmount] -> StablecoinResponseBody
StablecoinResponseBody
(Text
-> Stablecoin -> Text -> [ChainAmount] -> StablecoinResponseBody)
-> Codec Object StablecoinResponseBody Text
-> Codec
Object
StablecoinResponseBody
(Stablecoin -> Text -> [ChainAmount] -> StablecoinResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"name" ObjectCodec Text Text
-> (StablecoinResponseBody -> Text)
-> Codec Object StablecoinResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= StablecoinResponseBody -> Text
stablecoinResponseBodyName
Codec
Object
StablecoinResponseBody
(Stablecoin -> Text -> [ChainAmount] -> StablecoinResponseBody)
-> Codec Object StablecoinResponseBody Stablecoin
-> Codec
Object
StablecoinResponseBody
(Text -> [ChainAmount] -> StablecoinResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Stablecoin Stablecoin
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"symbol" ObjectCodec Stablecoin Stablecoin
-> (StablecoinResponseBody -> Stablecoin)
-> Codec Object StablecoinResponseBody Stablecoin
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= StablecoinResponseBody -> Stablecoin
stablecoinResponseBodySymbol
Codec
Object
StablecoinResponseBody
(Text -> [ChainAmount] -> StablecoinResponseBody)
-> Codec Object StablecoinResponseBody Text
-> Codec
Object
StablecoinResponseBody
([ChainAmount] -> StablecoinResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"totalAmount" ObjectCodec Text Text
-> (StablecoinResponseBody -> Text)
-> Codec Object StablecoinResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= StablecoinResponseBody -> Text
stablecoinResponseBodyTotalAmount
Codec
Object
StablecoinResponseBody
([ChainAmount] -> StablecoinResponseBody)
-> Codec Object StablecoinResponseBody [ChainAmount]
-> ObjectCodec StablecoinResponseBody StablecoinResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [ChainAmount] [ChainAmount]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chains" ObjectCodec [ChainAmount] [ChainAmount]
-> (StablecoinResponseBody -> [ChainAmount])
-> Codec Object StablecoinResponseBody [ChainAmount]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= StablecoinResponseBody -> [ChainAmount]
stablecoinResponseBodyChains
data ChainAmount = ChainAmount
{ ChainAmount -> Text
chainAmountAmount :: !Text,
ChainAmount -> Chain
chainAmountChain :: !Chain,
ChainAmount -> UTCTime
chainAmountUpdateDate :: !UTCTime
}
deriving (ChainAmount -> ChainAmount -> Bool
(ChainAmount -> ChainAmount -> Bool)
-> (ChainAmount -> ChainAmount -> Bool) -> Eq ChainAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChainAmount -> ChainAmount -> Bool
$c/= :: ChainAmount -> ChainAmount -> Bool
== :: ChainAmount -> ChainAmount -> Bool
$c== :: ChainAmount -> ChainAmount -> Bool
Eq, Int -> ChainAmount -> ShowS
[ChainAmount] -> ShowS
ChainAmount -> String
(Int -> ChainAmount -> ShowS)
-> (ChainAmount -> String)
-> ([ChainAmount] -> ShowS)
-> Show ChainAmount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChainAmount] -> ShowS
$cshowList :: [ChainAmount] -> ShowS
show :: ChainAmount -> String
$cshow :: ChainAmount -> String
showsPrec :: Int -> ChainAmount -> ShowS
$cshowsPrec :: Int -> ChainAmount -> ShowS
Show)
deriving
( Value -> Parser [ChainAmount]
Value -> Parser ChainAmount
(Value -> Parser ChainAmount)
-> (Value -> Parser [ChainAmount]) -> FromJSON ChainAmount
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ChainAmount]
$cparseJSONList :: Value -> Parser [ChainAmount]
parseJSON :: Value -> Parser ChainAmount
$cparseJSON :: Value -> Parser ChainAmount
FromJSON,
[ChainAmount] -> Encoding
[ChainAmount] -> Value
ChainAmount -> Encoding
ChainAmount -> Value
(ChainAmount -> Value)
-> (ChainAmount -> Encoding)
-> ([ChainAmount] -> Value)
-> ([ChainAmount] -> Encoding)
-> ToJSON ChainAmount
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ChainAmount] -> Encoding
$ctoEncodingList :: [ChainAmount] -> Encoding
toJSONList :: [ChainAmount] -> Value
$ctoJSONList :: [ChainAmount] -> Value
toEncoding :: ChainAmount -> Encoding
$ctoEncoding :: ChainAmount -> Encoding
toJSON :: ChainAmount -> Value
$ctoJSON :: ChainAmount -> Value
ToJSON
)
via (Autodocodec ChainAmount)
instance HasCodec ChainAmount where
codec :: JSONCodec ChainAmount
codec =
Text
-> ObjectCodec ChainAmount ChainAmount -> JSONCodec ChainAmount
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ChainAmount" (ObjectCodec ChainAmount ChainAmount -> JSONCodec ChainAmount)
-> ObjectCodec ChainAmount ChainAmount -> JSONCodec ChainAmount
forall a b. (a -> b) -> a -> b
$
Text -> Chain -> UTCTime -> ChainAmount
ChainAmount
(Text -> Chain -> UTCTime -> ChainAmount)
-> Codec Object ChainAmount Text
-> Codec Object ChainAmount (Chain -> UTCTime -> ChainAmount)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec Text Text
-> (ChainAmount -> Text) -> Codec Object ChainAmount Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChainAmount -> Text
chainAmountAmount
Codec Object ChainAmount (Chain -> UTCTime -> ChainAmount)
-> Codec Object ChainAmount Chain
-> Codec Object ChainAmount (UTCTime -> ChainAmount)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (ChainAmount -> Chain) -> Codec Object ChainAmount Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChainAmount -> Chain
chainAmountChain
Codec Object ChainAmount (UTCTime -> ChainAmount)
-> Codec Object ChainAmount UTCTime
-> ObjectCodec ChainAmount ChainAmount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (ChainAmount -> UTCTime) -> Codec Object ChainAmount UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChainAmount -> UTCTime
chainAmountUpdateDate
data Chain = ALGO | ARB | AVAX | ChainBTC | ChainETH | FLOW | HBAR | MATIC | NEAR | OP | SOL | TRX | XLM
deriving (Chain -> Chain -> Bool
(Chain -> Chain -> Bool) -> (Chain -> Chain -> Bool) -> Eq Chain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chain -> Chain -> Bool
$c/= :: Chain -> Chain -> Bool
== :: Chain -> Chain -> Bool
$c== :: Chain -> Chain -> Bool
Eq, Int -> Chain -> ShowS
[Chain] -> ShowS
Chain -> String
(Int -> Chain -> ShowS)
-> (Chain -> String) -> ([Chain] -> ShowS) -> Show Chain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Chain] -> ShowS
$cshowList :: [Chain] -> ShowS
show :: Chain -> String
$cshow :: Chain -> String
showsPrec :: Int -> Chain -> ShowS
$cshowsPrec :: Int -> Chain -> ShowS
Show)
deriving
( Value -> Parser [Chain]
Value -> Parser Chain
(Value -> Parser Chain)
-> (Value -> Parser [Chain]) -> FromJSON Chain
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Chain]
$cparseJSONList :: Value -> Parser [Chain]
parseJSON :: Value -> Parser Chain
$cparseJSON :: Value -> Parser Chain
FromJSON,
[Chain] -> Encoding
[Chain] -> Value
Chain -> Encoding
Chain -> Value
(Chain -> Value)
-> (Chain -> Encoding)
-> ([Chain] -> Value)
-> ([Chain] -> Encoding)
-> ToJSON Chain
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Chain] -> Encoding
$ctoEncodingList :: [Chain] -> Encoding
toJSONList :: [Chain] -> Value
$ctoJSONList :: [Chain] -> Value
toEncoding :: Chain -> Encoding
$ctoEncoding :: Chain -> Encoding
toJSON :: Chain -> Value
$ctoJSON :: Chain -> Value
ToJSON
)
via (Autodocodec Chain)
instance HasCodec Chain where
codec :: JSONCodec Chain
codec =
NonEmpty (Chain, Text) -> JSONCodec Chain
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (Chain, Text) -> JSONCodec Chain)
-> NonEmpty (Chain, Text) -> JSONCodec Chain
forall a b. (a -> b) -> a -> b
$
[(Chain, Text)] -> NonEmpty (Chain, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (Chain
ALGO, Text
"ALGO"),
(Chain
ARB, Text
"ARB"),
(Chain
AVAX, Text
"AVAX"),
(Chain
ChainBTC, Text
"BTC"),
(Chain
ChainETH, Text
"ETH"),
(Chain
FLOW, Text
"FLOW"),
(Chain
HBAR, Text
"HBAR"),
(Chain
MATIC, Text
"MATIC"),
(Chain
NEAR, Text
"NEAR"),
(Chain
OP, Text
"OP"),
(Chain
SOL, Text
"SOL"),
(Chain
TRX, Text
"TRX"),
(Chain
XLM, Text
"XLM")
]
data Stablecoin = USDC | EUROC | USDT
deriving (Stablecoin -> Stablecoin -> Bool
(Stablecoin -> Stablecoin -> Bool)
-> (Stablecoin -> Stablecoin -> Bool) -> Eq Stablecoin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Stablecoin -> Stablecoin -> Bool
$c/= :: Stablecoin -> Stablecoin -> Bool
== :: Stablecoin -> Stablecoin -> Bool
$c== :: Stablecoin -> Stablecoin -> Bool
Eq, Int -> Stablecoin -> ShowS
[Stablecoin] -> ShowS
Stablecoin -> String
(Int -> Stablecoin -> ShowS)
-> (Stablecoin -> String)
-> ([Stablecoin] -> ShowS)
-> Show Stablecoin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Stablecoin] -> ShowS
$cshowList :: [Stablecoin] -> ShowS
show :: Stablecoin -> String
$cshow :: Stablecoin -> String
showsPrec :: Int -> Stablecoin -> ShowS
$cshowsPrec :: Int -> Stablecoin -> ShowS
Show)
deriving
( Value -> Parser [Stablecoin]
Value -> Parser Stablecoin
(Value -> Parser Stablecoin)
-> (Value -> Parser [Stablecoin]) -> FromJSON Stablecoin
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Stablecoin]
$cparseJSONList :: Value -> Parser [Stablecoin]
parseJSON :: Value -> Parser Stablecoin
$cparseJSON :: Value -> Parser Stablecoin
FromJSON,
[Stablecoin] -> Encoding
[Stablecoin] -> Value
Stablecoin -> Encoding
Stablecoin -> Value
(Stablecoin -> Value)
-> (Stablecoin -> Encoding)
-> ([Stablecoin] -> Value)
-> ([Stablecoin] -> Encoding)
-> ToJSON Stablecoin
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Stablecoin] -> Encoding
$ctoEncodingList :: [Stablecoin] -> Encoding
toJSONList :: [Stablecoin] -> Value
$ctoJSONList :: [Stablecoin] -> Value
toEncoding :: Stablecoin -> Encoding
$ctoEncoding :: Stablecoin -> Encoding
toJSON :: Stablecoin -> Value
$ctoJSON :: Stablecoin -> Value
ToJSON
)
via (Autodocodec Stablecoin)
instance HasCodec Stablecoin where
codec :: JSONCodec Stablecoin
codec =
NonEmpty (Stablecoin, Text) -> JSONCodec Stablecoin
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (Stablecoin, Text) -> JSONCodec Stablecoin)
-> NonEmpty (Stablecoin, Text) -> JSONCodec Stablecoin
forall a b. (a -> b) -> a -> b
$
[(Stablecoin, Text)] -> NonEmpty (Stablecoin, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (Stablecoin
USDC, Text
"USDC"),
(Stablecoin
EUROC, Text
"EUROC"),
(Stablecoin
USDT, Text
"USDT")
]
data SubscriptionsRequest
type instance CircleRequest SubscriptionsRequest = CircleResponseBody [SubscriptionResponseBody]
data SubscriptionRequest
type instance CircleRequest SubscriptionRequest = CircleResponseBody SubscriptionResponseBody
data SubscriptionResponseBody = SubscriptionResponseBody
{ SubscriptionResponseBody -> UUID
subscriptionResponseBodyId :: !UUID,
SubscriptionResponseBody -> URL
subscriptionResponseBodyEndpoint :: !URL,
SubscriptionResponseBody -> [SubscriptionDetails]
subscriptionResponseBodySubscriptionDetails :: ![SubscriptionDetails]
}
deriving (SubscriptionResponseBody -> SubscriptionResponseBody -> Bool
(SubscriptionResponseBody -> SubscriptionResponseBody -> Bool)
-> (SubscriptionResponseBody -> SubscriptionResponseBody -> Bool)
-> Eq SubscriptionResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionResponseBody -> SubscriptionResponseBody -> Bool
$c/= :: SubscriptionResponseBody -> SubscriptionResponseBody -> Bool
== :: SubscriptionResponseBody -> SubscriptionResponseBody -> Bool
$c== :: SubscriptionResponseBody -> SubscriptionResponseBody -> Bool
Eq, Int -> SubscriptionResponseBody -> ShowS
[SubscriptionResponseBody] -> ShowS
SubscriptionResponseBody -> String
(Int -> SubscriptionResponseBody -> ShowS)
-> (SubscriptionResponseBody -> String)
-> ([SubscriptionResponseBody] -> ShowS)
-> Show SubscriptionResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionResponseBody] -> ShowS
$cshowList :: [SubscriptionResponseBody] -> ShowS
show :: SubscriptionResponseBody -> String
$cshow :: SubscriptionResponseBody -> String
showsPrec :: Int -> SubscriptionResponseBody -> ShowS
$cshowsPrec :: Int -> SubscriptionResponseBody -> ShowS
Show)
deriving
( Value -> Parser [SubscriptionResponseBody]
Value -> Parser SubscriptionResponseBody
(Value -> Parser SubscriptionResponseBody)
-> (Value -> Parser [SubscriptionResponseBody])
-> FromJSON SubscriptionResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SubscriptionResponseBody]
$cparseJSONList :: Value -> Parser [SubscriptionResponseBody]
parseJSON :: Value -> Parser SubscriptionResponseBody
$cparseJSON :: Value -> Parser SubscriptionResponseBody
FromJSON,
[SubscriptionResponseBody] -> Encoding
[SubscriptionResponseBody] -> Value
SubscriptionResponseBody -> Encoding
SubscriptionResponseBody -> Value
(SubscriptionResponseBody -> Value)
-> (SubscriptionResponseBody -> Encoding)
-> ([SubscriptionResponseBody] -> Value)
-> ([SubscriptionResponseBody] -> Encoding)
-> ToJSON SubscriptionResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SubscriptionResponseBody] -> Encoding
$ctoEncodingList :: [SubscriptionResponseBody] -> Encoding
toJSONList :: [SubscriptionResponseBody] -> Value
$ctoJSONList :: [SubscriptionResponseBody] -> Value
toEncoding :: SubscriptionResponseBody -> Encoding
$ctoEncoding :: SubscriptionResponseBody -> Encoding
toJSON :: SubscriptionResponseBody -> Value
$ctoJSON :: SubscriptionResponseBody -> Value
ToJSON
)
via (Autodocodec SubscriptionResponseBody)
instance HasCodec SubscriptionResponseBody where
codec :: JSONCodec SubscriptionResponseBody
codec =
Text
-> ObjectCodec SubscriptionResponseBody SubscriptionResponseBody
-> JSONCodec SubscriptionResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SubscriptionResponseBody" (ObjectCodec SubscriptionResponseBody SubscriptionResponseBody
-> JSONCodec SubscriptionResponseBody)
-> ObjectCodec SubscriptionResponseBody SubscriptionResponseBody
-> JSONCodec SubscriptionResponseBody
forall a b. (a -> b) -> a -> b
$
UUID -> URL -> [SubscriptionDetails] -> SubscriptionResponseBody
SubscriptionResponseBody
(UUID -> URL -> [SubscriptionDetails] -> SubscriptionResponseBody)
-> Codec Object SubscriptionResponseBody UUID
-> Codec
Object
SubscriptionResponseBody
(URL -> [SubscriptionDetails] -> SubscriptionResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (SubscriptionResponseBody -> UUID)
-> Codec Object SubscriptionResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SubscriptionResponseBody -> UUID
subscriptionResponseBodyId
Codec
Object
SubscriptionResponseBody
(URL -> [SubscriptionDetails] -> SubscriptionResponseBody)
-> Codec Object SubscriptionResponseBody URL
-> Codec
Object
SubscriptionResponseBody
([SubscriptionDetails] -> SubscriptionResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec URL URL
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"endpoint" ObjectCodec URL URL
-> (SubscriptionResponseBody -> URL)
-> Codec Object SubscriptionResponseBody URL
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SubscriptionResponseBody -> URL
subscriptionResponseBodyEndpoint
Codec
Object
SubscriptionResponseBody
([SubscriptionDetails] -> SubscriptionResponseBody)
-> Codec Object SubscriptionResponseBody [SubscriptionDetails]
-> ObjectCodec SubscriptionResponseBody SubscriptionResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [SubscriptionDetails] [SubscriptionDetails]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"subscriptionDetails" ObjectCodec [SubscriptionDetails] [SubscriptionDetails]
-> (SubscriptionResponseBody -> [SubscriptionDetails])
-> Codec Object SubscriptionResponseBody [SubscriptionDetails]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SubscriptionResponseBody -> [SubscriptionDetails]
subscriptionResponseBodySubscriptionDetails
data SubscriptionDetails = SubscriptionDetails
{ SubscriptionDetails -> URL
subscriptionDetailsUrl :: !URL,
SubscriptionDetails -> Status
subscriptionDetailsStatus :: !Status
}
deriving (SubscriptionDetails -> SubscriptionDetails -> Bool
(SubscriptionDetails -> SubscriptionDetails -> Bool)
-> (SubscriptionDetails -> SubscriptionDetails -> Bool)
-> Eq SubscriptionDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionDetails -> SubscriptionDetails -> Bool
$c/= :: SubscriptionDetails -> SubscriptionDetails -> Bool
== :: SubscriptionDetails -> SubscriptionDetails -> Bool
$c== :: SubscriptionDetails -> SubscriptionDetails -> Bool
Eq, Int -> SubscriptionDetails -> ShowS
[SubscriptionDetails] -> ShowS
SubscriptionDetails -> String
(Int -> SubscriptionDetails -> ShowS)
-> (SubscriptionDetails -> String)
-> ([SubscriptionDetails] -> ShowS)
-> Show SubscriptionDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionDetails] -> ShowS
$cshowList :: [SubscriptionDetails] -> ShowS
show :: SubscriptionDetails -> String
$cshow :: SubscriptionDetails -> String
showsPrec :: Int -> SubscriptionDetails -> ShowS
$cshowsPrec :: Int -> SubscriptionDetails -> ShowS
Show)
deriving
( Value -> Parser [SubscriptionDetails]
Value -> Parser SubscriptionDetails
(Value -> Parser SubscriptionDetails)
-> (Value -> Parser [SubscriptionDetails])
-> FromJSON SubscriptionDetails
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SubscriptionDetails]
$cparseJSONList :: Value -> Parser [SubscriptionDetails]
parseJSON :: Value -> Parser SubscriptionDetails
$cparseJSON :: Value -> Parser SubscriptionDetails
FromJSON,
[SubscriptionDetails] -> Encoding
[SubscriptionDetails] -> Value
SubscriptionDetails -> Encoding
SubscriptionDetails -> Value
(SubscriptionDetails -> Value)
-> (SubscriptionDetails -> Encoding)
-> ([SubscriptionDetails] -> Value)
-> ([SubscriptionDetails] -> Encoding)
-> ToJSON SubscriptionDetails
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SubscriptionDetails] -> Encoding
$ctoEncodingList :: [SubscriptionDetails] -> Encoding
toJSONList :: [SubscriptionDetails] -> Value
$ctoJSONList :: [SubscriptionDetails] -> Value
toEncoding :: SubscriptionDetails -> Encoding
$ctoEncoding :: SubscriptionDetails -> Encoding
toJSON :: SubscriptionDetails -> Value
$ctoJSON :: SubscriptionDetails -> Value
ToJSON
)
via (Autodocodec SubscriptionDetails)
instance HasCodec SubscriptionDetails where
codec :: JSONCodec SubscriptionDetails
codec =
Text
-> ObjectCodec SubscriptionDetails SubscriptionDetails
-> JSONCodec SubscriptionDetails
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SubscriptionDetails" (ObjectCodec SubscriptionDetails SubscriptionDetails
-> JSONCodec SubscriptionDetails)
-> ObjectCodec SubscriptionDetails SubscriptionDetails
-> JSONCodec SubscriptionDetails
forall a b. (a -> b) -> a -> b
$
URL -> Status -> SubscriptionDetails
SubscriptionDetails
(URL -> Status -> SubscriptionDetails)
-> Codec Object SubscriptionDetails URL
-> Codec Object SubscriptionDetails (Status -> SubscriptionDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec URL URL
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"url" ObjectCodec URL URL
-> (SubscriptionDetails -> URL)
-> Codec Object SubscriptionDetails URL
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SubscriptionDetails -> URL
subscriptionDetailsUrl
Codec Object SubscriptionDetails (Status -> SubscriptionDetails)
-> Codec Object SubscriptionDetails Status
-> ObjectCodec SubscriptionDetails SubscriptionDetails
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (SubscriptionDetails -> Status)
-> Codec Object SubscriptionDetails Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SubscriptionDetails -> Status
subscriptionDetailsStatus
newtype SubscriptionRequestBody = SubscriptionRequestBody
{ SubscriptionRequestBody -> Text
subscriptionRequestBodyEndpoint :: Text
}
deriving (SubscriptionRequestBody -> SubscriptionRequestBody -> Bool
(SubscriptionRequestBody -> SubscriptionRequestBody -> Bool)
-> (SubscriptionRequestBody -> SubscriptionRequestBody -> Bool)
-> Eq SubscriptionRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionRequestBody -> SubscriptionRequestBody -> Bool
$c/= :: SubscriptionRequestBody -> SubscriptionRequestBody -> Bool
== :: SubscriptionRequestBody -> SubscriptionRequestBody -> Bool
$c== :: SubscriptionRequestBody -> SubscriptionRequestBody -> Bool
Eq, Int -> SubscriptionRequestBody -> ShowS
[SubscriptionRequestBody] -> ShowS
SubscriptionRequestBody -> String
(Int -> SubscriptionRequestBody -> ShowS)
-> (SubscriptionRequestBody -> String)
-> ([SubscriptionRequestBody] -> ShowS)
-> Show SubscriptionRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionRequestBody] -> ShowS
$cshowList :: [SubscriptionRequestBody] -> ShowS
show :: SubscriptionRequestBody -> String
$cshow :: SubscriptionRequestBody -> String
showsPrec :: Int -> SubscriptionRequestBody -> ShowS
$cshowsPrec :: Int -> SubscriptionRequestBody -> ShowS
Show)
deriving
( Value -> Parser [SubscriptionRequestBody]
Value -> Parser SubscriptionRequestBody
(Value -> Parser SubscriptionRequestBody)
-> (Value -> Parser [SubscriptionRequestBody])
-> FromJSON SubscriptionRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SubscriptionRequestBody]
$cparseJSONList :: Value -> Parser [SubscriptionRequestBody]
parseJSON :: Value -> Parser SubscriptionRequestBody
$cparseJSON :: Value -> Parser SubscriptionRequestBody
FromJSON,
[SubscriptionRequestBody] -> Encoding
[SubscriptionRequestBody] -> Value
SubscriptionRequestBody -> Encoding
SubscriptionRequestBody -> Value
(SubscriptionRequestBody -> Value)
-> (SubscriptionRequestBody -> Encoding)
-> ([SubscriptionRequestBody] -> Value)
-> ([SubscriptionRequestBody] -> Encoding)
-> ToJSON SubscriptionRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SubscriptionRequestBody] -> Encoding
$ctoEncodingList :: [SubscriptionRequestBody] -> Encoding
toJSONList :: [SubscriptionRequestBody] -> Value
$ctoJSONList :: [SubscriptionRequestBody] -> Value
toEncoding :: SubscriptionRequestBody -> Encoding
$ctoEncoding :: SubscriptionRequestBody -> Encoding
toJSON :: SubscriptionRequestBody -> Value
$ctoJSON :: SubscriptionRequestBody -> Value
ToJSON
)
via (Autodocodec SubscriptionRequestBody)
instance HasCodec SubscriptionRequestBody where
codec :: JSONCodec SubscriptionRequestBody
codec =
Text
-> ObjectCodec SubscriptionRequestBody SubscriptionRequestBody
-> JSONCodec SubscriptionRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SubscriptionRequestBody" (ObjectCodec SubscriptionRequestBody SubscriptionRequestBody
-> JSONCodec SubscriptionRequestBody)
-> ObjectCodec SubscriptionRequestBody SubscriptionRequestBody
-> JSONCodec SubscriptionRequestBody
forall a b. (a -> b) -> a -> b
$
Text -> SubscriptionRequestBody
SubscriptionRequestBody
(Text -> SubscriptionRequestBody)
-> Codec Object SubscriptionRequestBody Text
-> ObjectCodec SubscriptionRequestBody SubscriptionRequestBody
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"endpoint" ObjectCodec Text Text
-> (SubscriptionRequestBody -> Text)
-> Codec Object SubscriptionRequestBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SubscriptionRequestBody -> Text
subscriptionRequestBodyEndpoint
data TransfersRequest
type instance CircleRequest TransfersRequest = CircleResponseBody [TransferResponseBody]
instance CircleHasParam TransfersRequest PaginationQueryParams
instance CircleHasParam TransfersRequest FromQueryParam
instance CircleHasParam TransfersRequest ToQueryParam
instance CircleHasParam TransfersRequest PageSizeQueryParam
instance CircleHasParam TransfersRequest WalletIdQueryParam
instance CircleHasParam TransfersRequest SourceWalletIdQueryParam
instance CircleHasParam TransfersRequest DestinationWalletIdQueryParam
instance CircleHasParam TransfersRequest ReturnIdentitiesQueryParam
data TransferRequest
type instance CircleRequest TransferRequest = CircleResponseBody TransferResponseBody
instance CircleHasParam TransferRequest ReturnIdentitiesQueryParam
data BusinessTransferRequestBody = BusinessTransferRequestBody
{ BusinessTransferRequestBody -> UUID
businessTransferRequestBodyIdempotencyKey :: !UUID,
BusinessTransferRequestBody -> TransferDestination
businessTransferRequestBodyDestination :: !TransferDestination,
BusinessTransferRequestBody -> MoneyAmount
businessTransferRequestBodyAmount :: !MoneyAmount
}
deriving (BusinessTransferRequestBody -> BusinessTransferRequestBody -> Bool
(BusinessTransferRequestBody
-> BusinessTransferRequestBody -> Bool)
-> (BusinessTransferRequestBody
-> BusinessTransferRequestBody -> Bool)
-> Eq BusinessTransferRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BusinessTransferRequestBody -> BusinessTransferRequestBody -> Bool
$c/= :: BusinessTransferRequestBody -> BusinessTransferRequestBody -> Bool
== :: BusinessTransferRequestBody -> BusinessTransferRequestBody -> Bool
$c== :: BusinessTransferRequestBody -> BusinessTransferRequestBody -> Bool
Eq, Int -> BusinessTransferRequestBody -> ShowS
[BusinessTransferRequestBody] -> ShowS
BusinessTransferRequestBody -> String
(Int -> BusinessTransferRequestBody -> ShowS)
-> (BusinessTransferRequestBody -> String)
-> ([BusinessTransferRequestBody] -> ShowS)
-> Show BusinessTransferRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BusinessTransferRequestBody] -> ShowS
$cshowList :: [BusinessTransferRequestBody] -> ShowS
show :: BusinessTransferRequestBody -> String
$cshow :: BusinessTransferRequestBody -> String
showsPrec :: Int -> BusinessTransferRequestBody -> ShowS
$cshowsPrec :: Int -> BusinessTransferRequestBody -> ShowS
Show)
deriving
( Value -> Parser [BusinessTransferRequestBody]
Value -> Parser BusinessTransferRequestBody
(Value -> Parser BusinessTransferRequestBody)
-> (Value -> Parser [BusinessTransferRequestBody])
-> FromJSON BusinessTransferRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BusinessTransferRequestBody]
$cparseJSONList :: Value -> Parser [BusinessTransferRequestBody]
parseJSON :: Value -> Parser BusinessTransferRequestBody
$cparseJSON :: Value -> Parser BusinessTransferRequestBody
FromJSON,
[BusinessTransferRequestBody] -> Encoding
[BusinessTransferRequestBody] -> Value
BusinessTransferRequestBody -> Encoding
BusinessTransferRequestBody -> Value
(BusinessTransferRequestBody -> Value)
-> (BusinessTransferRequestBody -> Encoding)
-> ([BusinessTransferRequestBody] -> Value)
-> ([BusinessTransferRequestBody] -> Encoding)
-> ToJSON BusinessTransferRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BusinessTransferRequestBody] -> Encoding
$ctoEncodingList :: [BusinessTransferRequestBody] -> Encoding
toJSONList :: [BusinessTransferRequestBody] -> Value
$ctoJSONList :: [BusinessTransferRequestBody] -> Value
toEncoding :: BusinessTransferRequestBody -> Encoding
$ctoEncoding :: BusinessTransferRequestBody -> Encoding
toJSON :: BusinessTransferRequestBody -> Value
$ctoJSON :: BusinessTransferRequestBody -> Value
ToJSON
)
via (Autodocodec BusinessTransferRequestBody)
instance HasCodec BusinessTransferRequestBody where
codec :: JSONCodec BusinessTransferRequestBody
codec =
Text
-> ObjectCodec
BusinessTransferRequestBody BusinessTransferRequestBody
-> JSONCodec BusinessTransferRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BusinessTransferRequestBody" (ObjectCodec
BusinessTransferRequestBody BusinessTransferRequestBody
-> JSONCodec BusinessTransferRequestBody)
-> ObjectCodec
BusinessTransferRequestBody BusinessTransferRequestBody
-> JSONCodec BusinessTransferRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> TransferDestination
-> MoneyAmount
-> BusinessTransferRequestBody
BusinessTransferRequestBody
(UUID
-> TransferDestination
-> MoneyAmount
-> BusinessTransferRequestBody)
-> Codec Object BusinessTransferRequestBody UUID
-> Codec
Object
BusinessTransferRequestBody
(TransferDestination -> MoneyAmount -> BusinessTransferRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (BusinessTransferRequestBody -> UUID)
-> Codec Object BusinessTransferRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BusinessTransferRequestBody -> UUID
businessTransferRequestBodyIdempotencyKey
Codec
Object
BusinessTransferRequestBody
(TransferDestination -> MoneyAmount -> BusinessTransferRequestBody)
-> Codec Object BusinessTransferRequestBody TransferDestination
-> Codec
Object
BusinessTransferRequestBody
(MoneyAmount -> BusinessTransferRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec TransferDestination TransferDestination
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"destination" ObjectCodec TransferDestination TransferDestination
-> (BusinessTransferRequestBody -> TransferDestination)
-> Codec Object BusinessTransferRequestBody TransferDestination
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BusinessTransferRequestBody -> TransferDestination
businessTransferRequestBodyDestination
Codec
Object
BusinessTransferRequestBody
(MoneyAmount -> BusinessTransferRequestBody)
-> Codec Object BusinessTransferRequestBody MoneyAmount
-> ObjectCodec
BusinessTransferRequestBody BusinessTransferRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (BusinessTransferRequestBody -> MoneyAmount)
-> Codec Object BusinessTransferRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BusinessTransferRequestBody -> MoneyAmount
businessTransferRequestBodyAmount
data TransferRequestBody = TransferRequestBody
{ TransferRequestBody -> UUID
transferRequestBodyIdempotencyKey :: !UUID,
TransferRequestBody -> PaymentSource
transferRequestBodySource :: !PaymentSource,
TransferRequestBody -> TransferDestination
transferRequestBodyDestination :: !TransferDestination,
TransferRequestBody -> MoneyAmount
transferRequestBodyAmount :: !MoneyAmount
}
deriving (TransferRequestBody -> TransferRequestBody -> Bool
(TransferRequestBody -> TransferRequestBody -> Bool)
-> (TransferRequestBody -> TransferRequestBody -> Bool)
-> Eq TransferRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferRequestBody -> TransferRequestBody -> Bool
$c/= :: TransferRequestBody -> TransferRequestBody -> Bool
== :: TransferRequestBody -> TransferRequestBody -> Bool
$c== :: TransferRequestBody -> TransferRequestBody -> Bool
Eq, Int -> TransferRequestBody -> ShowS
[TransferRequestBody] -> ShowS
TransferRequestBody -> String
(Int -> TransferRequestBody -> ShowS)
-> (TransferRequestBody -> String)
-> ([TransferRequestBody] -> ShowS)
-> Show TransferRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferRequestBody] -> ShowS
$cshowList :: [TransferRequestBody] -> ShowS
show :: TransferRequestBody -> String
$cshow :: TransferRequestBody -> String
showsPrec :: Int -> TransferRequestBody -> ShowS
$cshowsPrec :: Int -> TransferRequestBody -> ShowS
Show)
deriving
( Value -> Parser [TransferRequestBody]
Value -> Parser TransferRequestBody
(Value -> Parser TransferRequestBody)
-> (Value -> Parser [TransferRequestBody])
-> FromJSON TransferRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransferRequestBody]
$cparseJSONList :: Value -> Parser [TransferRequestBody]
parseJSON :: Value -> Parser TransferRequestBody
$cparseJSON :: Value -> Parser TransferRequestBody
FromJSON,
[TransferRequestBody] -> Encoding
[TransferRequestBody] -> Value
TransferRequestBody -> Encoding
TransferRequestBody -> Value
(TransferRequestBody -> Value)
-> (TransferRequestBody -> Encoding)
-> ([TransferRequestBody] -> Value)
-> ([TransferRequestBody] -> Encoding)
-> ToJSON TransferRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransferRequestBody] -> Encoding
$ctoEncodingList :: [TransferRequestBody] -> Encoding
toJSONList :: [TransferRequestBody] -> Value
$ctoJSONList :: [TransferRequestBody] -> Value
toEncoding :: TransferRequestBody -> Encoding
$ctoEncoding :: TransferRequestBody -> Encoding
toJSON :: TransferRequestBody -> Value
$ctoJSON :: TransferRequestBody -> Value
ToJSON
)
via (Autodocodec TransferRequestBody)
instance HasCodec TransferRequestBody where
codec :: JSONCodec TransferRequestBody
codec =
Text
-> ObjectCodec TransferRequestBody TransferRequestBody
-> JSONCodec TransferRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"TransferRequestBody" (ObjectCodec TransferRequestBody TransferRequestBody
-> JSONCodec TransferRequestBody)
-> ObjectCodec TransferRequestBody TransferRequestBody
-> JSONCodec TransferRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> PaymentSource
-> TransferDestination
-> MoneyAmount
-> TransferRequestBody
TransferRequestBody
(UUID
-> PaymentSource
-> TransferDestination
-> MoneyAmount
-> TransferRequestBody)
-> Codec Object TransferRequestBody UUID
-> Codec
Object
TransferRequestBody
(PaymentSource
-> TransferDestination -> MoneyAmount -> TransferRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (TransferRequestBody -> UUID)
-> Codec Object TransferRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferRequestBody -> UUID
transferRequestBodyIdempotencyKey
Codec
Object
TransferRequestBody
(PaymentSource
-> TransferDestination -> MoneyAmount -> TransferRequestBody)
-> Codec Object TransferRequestBody PaymentSource
-> Codec
Object
TransferRequestBody
(TransferDestination -> MoneyAmount -> TransferRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentSource PaymentSource
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"source" ObjectCodec PaymentSource PaymentSource
-> (TransferRequestBody -> PaymentSource)
-> Codec Object TransferRequestBody PaymentSource
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferRequestBody -> PaymentSource
transferRequestBodySource
Codec
Object
TransferRequestBody
(TransferDestination -> MoneyAmount -> TransferRequestBody)
-> Codec Object TransferRequestBody TransferDestination
-> Codec
Object TransferRequestBody (MoneyAmount -> TransferRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec TransferDestination TransferDestination
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"destination" ObjectCodec TransferDestination TransferDestination
-> (TransferRequestBody -> TransferDestination)
-> Codec Object TransferRequestBody TransferDestination
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferRequestBody -> TransferDestination
transferRequestBodyDestination
Codec
Object TransferRequestBody (MoneyAmount -> TransferRequestBody)
-> Codec Object TransferRequestBody MoneyAmount
-> ObjectCodec TransferRequestBody TransferRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (TransferRequestBody -> MoneyAmount)
-> Codec Object TransferRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferRequestBody -> MoneyAmount
transferRequestBodyAmount
data TransferDestination = TransferDestination
{ TransferDestination -> DestinationType
transferDestinationType :: !DestinationType,
TransferDestination -> UUID
transferDestinationAddressId :: !UUID
}
deriving (TransferDestination -> TransferDestination -> Bool
(TransferDestination -> TransferDestination -> Bool)
-> (TransferDestination -> TransferDestination -> Bool)
-> Eq TransferDestination
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferDestination -> TransferDestination -> Bool
$c/= :: TransferDestination -> TransferDestination -> Bool
== :: TransferDestination -> TransferDestination -> Bool
$c== :: TransferDestination -> TransferDestination -> Bool
Eq, Int -> TransferDestination -> ShowS
[TransferDestination] -> ShowS
TransferDestination -> String
(Int -> TransferDestination -> ShowS)
-> (TransferDestination -> String)
-> ([TransferDestination] -> ShowS)
-> Show TransferDestination
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferDestination] -> ShowS
$cshowList :: [TransferDestination] -> ShowS
show :: TransferDestination -> String
$cshow :: TransferDestination -> String
showsPrec :: Int -> TransferDestination -> ShowS
$cshowsPrec :: Int -> TransferDestination -> ShowS
Show)
deriving
( Value -> Parser [TransferDestination]
Value -> Parser TransferDestination
(Value -> Parser TransferDestination)
-> (Value -> Parser [TransferDestination])
-> FromJSON TransferDestination
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransferDestination]
$cparseJSONList :: Value -> Parser [TransferDestination]
parseJSON :: Value -> Parser TransferDestination
$cparseJSON :: Value -> Parser TransferDestination
FromJSON,
[TransferDestination] -> Encoding
[TransferDestination] -> Value
TransferDestination -> Encoding
TransferDestination -> Value
(TransferDestination -> Value)
-> (TransferDestination -> Encoding)
-> ([TransferDestination] -> Value)
-> ([TransferDestination] -> Encoding)
-> ToJSON TransferDestination
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransferDestination] -> Encoding
$ctoEncodingList :: [TransferDestination] -> Encoding
toJSONList :: [TransferDestination] -> Value
$ctoJSONList :: [TransferDestination] -> Value
toEncoding :: TransferDestination -> Encoding
$ctoEncoding :: TransferDestination -> Encoding
toJSON :: TransferDestination -> Value
$ctoJSON :: TransferDestination -> Value
ToJSON
)
via (Autodocodec TransferDestination)
instance HasCodec TransferDestination where
codec :: JSONCodec TransferDestination
codec =
Text
-> ObjectCodec TransferDestination TransferDestination
-> JSONCodec TransferDestination
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"TransferDestination" (ObjectCodec TransferDestination TransferDestination
-> JSONCodec TransferDestination)
-> ObjectCodec TransferDestination TransferDestination
-> JSONCodec TransferDestination
forall a b. (a -> b) -> a -> b
$
DestinationType -> UUID -> TransferDestination
TransferDestination
(DestinationType -> UUID -> TransferDestination)
-> Codec Object TransferDestination DestinationType
-> Codec Object TransferDestination (UUID -> TransferDestination)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec DestinationType DestinationType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec DestinationType DestinationType
-> (TransferDestination -> DestinationType)
-> Codec Object TransferDestination DestinationType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferDestination -> DestinationType
transferDestinationType
Codec Object TransferDestination (UUID -> TransferDestination)
-> Codec Object TransferDestination UUID
-> ObjectCodec TransferDestination TransferDestination
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"addressId" ObjectCodec UUID UUID
-> (TransferDestination -> UUID)
-> Codec Object TransferDestination UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferDestination -> UUID
transferDestinationAddressId
data DestinationType = VerifiedBlockchain
deriving (DestinationType -> DestinationType -> Bool
(DestinationType -> DestinationType -> Bool)
-> (DestinationType -> DestinationType -> Bool)
-> Eq DestinationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DestinationType -> DestinationType -> Bool
$c/= :: DestinationType -> DestinationType -> Bool
== :: DestinationType -> DestinationType -> Bool
$c== :: DestinationType -> DestinationType -> Bool
Eq, Int -> DestinationType -> ShowS
[DestinationType] -> ShowS
DestinationType -> String
(Int -> DestinationType -> ShowS)
-> (DestinationType -> String)
-> ([DestinationType] -> ShowS)
-> Show DestinationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DestinationType] -> ShowS
$cshowList :: [DestinationType] -> ShowS
show :: DestinationType -> String
$cshow :: DestinationType -> String
showsPrec :: Int -> DestinationType -> ShowS
$cshowsPrec :: Int -> DestinationType -> ShowS
Show)
deriving
( Value -> Parser [DestinationType]
Value -> Parser DestinationType
(Value -> Parser DestinationType)
-> (Value -> Parser [DestinationType]) -> FromJSON DestinationType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DestinationType]
$cparseJSONList :: Value -> Parser [DestinationType]
parseJSON :: Value -> Parser DestinationType
$cparseJSON :: Value -> Parser DestinationType
FromJSON,
[DestinationType] -> Encoding
[DestinationType] -> Value
DestinationType -> Encoding
DestinationType -> Value
(DestinationType -> Value)
-> (DestinationType -> Encoding)
-> ([DestinationType] -> Value)
-> ([DestinationType] -> Encoding)
-> ToJSON DestinationType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DestinationType] -> Encoding
$ctoEncodingList :: [DestinationType] -> Encoding
toJSONList :: [DestinationType] -> Value
$ctoJSONList :: [DestinationType] -> Value
toEncoding :: DestinationType -> Encoding
$ctoEncoding :: DestinationType -> Encoding
toJSON :: DestinationType -> Value
$ctoJSON :: DestinationType -> Value
ToJSON
)
via (Autodocodec DestinationType)
instance HasCodec DestinationType where
codec :: JSONCodec DestinationType
codec =
NonEmpty (DestinationType, Text) -> JSONCodec DestinationType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (DestinationType, Text) -> JSONCodec DestinationType)
-> NonEmpty (DestinationType, Text) -> JSONCodec DestinationType
forall a b. (a -> b) -> a -> b
$
[(DestinationType, Text)] -> NonEmpty (DestinationType, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (DestinationType
VerifiedBlockchain, Text
"verified_blockchain")
]
data TransferResponseBody = TransferResponseBody
{ TransferResponseBody -> UUID
transferResponseBodyId :: !UUID,
TransferResponseBody -> ThisOrThat SourceWallet SourceBlockchain
transferResponseBodySource :: !(ThisOrThat SourceWallet SourceBlockchain),
TransferResponseBody
-> ThisOrThat DestinationWallet DestinationBlockchain
transferResponseBodyDestination :: !(ThisOrThat DestinationWallet DestinationBlockchain),
TransferResponseBody -> MoneyAmount
transferResponseBodyAmount :: !MoneyAmount,
TransferResponseBody -> TransferFeeAmount
transferResponseBodyFees :: !TransferFeeAmount,
TransferResponseBody -> Maybe HexString
transferResponseBodyTransactionHash :: !(Maybe HexString),
TransferResponseBody -> Status
transferResponseBodyStatus :: !Status,
TransferResponseBody -> Maybe TransferErrorCode
transferResponseBodyTransferErrorCode :: !(Maybe TransferErrorCode),
TransferResponseBody -> Maybe RiskEvaluation
transferResponseBodyRiskEvaluation :: !(Maybe RiskEvaluation),
TransferResponseBody -> Maybe UTCTime
transferResponseBodyCreateDate :: !(Maybe UTCTime)
}
deriving (TransferResponseBody -> TransferResponseBody -> Bool
(TransferResponseBody -> TransferResponseBody -> Bool)
-> (TransferResponseBody -> TransferResponseBody -> Bool)
-> Eq TransferResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferResponseBody -> TransferResponseBody -> Bool
$c/= :: TransferResponseBody -> TransferResponseBody -> Bool
== :: TransferResponseBody -> TransferResponseBody -> Bool
$c== :: TransferResponseBody -> TransferResponseBody -> Bool
Eq, Int -> TransferResponseBody -> ShowS
[TransferResponseBody] -> ShowS
TransferResponseBody -> String
(Int -> TransferResponseBody -> ShowS)
-> (TransferResponseBody -> String)
-> ([TransferResponseBody] -> ShowS)
-> Show TransferResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferResponseBody] -> ShowS
$cshowList :: [TransferResponseBody] -> ShowS
show :: TransferResponseBody -> String
$cshow :: TransferResponseBody -> String
showsPrec :: Int -> TransferResponseBody -> ShowS
$cshowsPrec :: Int -> TransferResponseBody -> ShowS
Show)
instance FromJSON TransferResponseBody where
parseJSON :: Value -> Parser TransferResponseBody
parseJSON = String
-> (Object -> Parser TransferResponseBody)
-> Value
-> Parser TransferResponseBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TransferResponseBody" Object -> Parser TransferResponseBody
parse
where
parse :: Object -> Parser TransferResponseBody
parse Object
o =
UUID
-> ThisOrThat SourceWallet SourceBlockchain
-> ThisOrThat DestinationWallet DestinationBlockchain
-> MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody
TransferResponseBody
(UUID
-> ThisOrThat SourceWallet SourceBlockchain
-> ThisOrThat DestinationWallet DestinationBlockchain
-> MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
-> Parser UUID
-> Parser
(ThisOrThat SourceWallet SourceBlockchain
-> ThisOrThat DestinationWallet DestinationBlockchain
-> MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser UUID
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id"
Parser
(ThisOrThat SourceWallet SourceBlockchain
-> ThisOrThat DestinationWallet DestinationBlockchain
-> MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
-> Parser (ThisOrThat SourceWallet SourceBlockchain)
-> Parser
(ThisOrThat DestinationWallet DestinationBlockchain
-> MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (ThisOrThat SourceWallet SourceBlockchain)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"source"
Parser
(ThisOrThat DestinationWallet DestinationBlockchain
-> MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
-> Parser (ThisOrThat DestinationWallet DestinationBlockchain)
-> Parser
(MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object
-> Text
-> Parser (ThisOrThat DestinationWallet DestinationBlockchain)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"destination"
Parser
(MoneyAmount
-> TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
-> Parser MoneyAmount
-> Parser
(TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser MoneyAmount
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"amount"
Parser
(TransferFeeAmount
-> Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
-> Parser TransferFeeAmount
-> Parser
(Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser TransferFeeAmount
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"fees"
Parser
(Maybe HexString
-> Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
-> Parser (Maybe HexString)
-> Parser
(Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe HexString)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"transactionHash"
Parser
(Status
-> Maybe TransferErrorCode
-> Maybe RiskEvaluation
-> Maybe UTCTime
-> TransferResponseBody)
-> Parser Status
-> Parser
(Maybe TransferErrorCode
-> Maybe RiskEvaluation -> Maybe UTCTime -> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser Status
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"status"
Parser
(Maybe TransferErrorCode
-> Maybe RiskEvaluation -> Maybe UTCTime -> TransferResponseBody)
-> Parser (Maybe TransferErrorCode)
-> Parser
(Maybe RiskEvaluation -> Maybe UTCTime -> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe TransferErrorCode)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"errorCode"
Parser
(Maybe RiskEvaluation -> Maybe UTCTime -> TransferResponseBody)
-> Parser (Maybe RiskEvaluation)
-> Parser (Maybe UTCTime -> TransferResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe RiskEvaluation)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"riskEvaluation"
Parser (Maybe UTCTime -> TransferResponseBody)
-> Parser (Maybe UTCTime) -> Parser TransferResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe UTCTime)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"createDate"
data SourceWallet = SourceWallet
{ SourceWallet -> TransferType
sourceWalletType :: !TransferType,
SourceWallet -> WalletId
sourceWalletId :: !WalletId,
SourceWallet -> [Identity]
sourceWalletIdentities :: ![Identity]
}
deriving (SourceWallet -> SourceWallet -> Bool
(SourceWallet -> SourceWallet -> Bool)
-> (SourceWallet -> SourceWallet -> Bool) -> Eq SourceWallet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceWallet -> SourceWallet -> Bool
$c/= :: SourceWallet -> SourceWallet -> Bool
== :: SourceWallet -> SourceWallet -> Bool
$c== :: SourceWallet -> SourceWallet -> Bool
Eq, Int -> SourceWallet -> ShowS
[SourceWallet] -> ShowS
SourceWallet -> String
(Int -> SourceWallet -> ShowS)
-> (SourceWallet -> String)
-> ([SourceWallet] -> ShowS)
-> Show SourceWallet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceWallet] -> ShowS
$cshowList :: [SourceWallet] -> ShowS
show :: SourceWallet -> String
$cshow :: SourceWallet -> String
showsPrec :: Int -> SourceWallet -> ShowS
$cshowsPrec :: Int -> SourceWallet -> ShowS
Show)
deriving
( Value -> Parser [SourceWallet]
Value -> Parser SourceWallet
(Value -> Parser SourceWallet)
-> (Value -> Parser [SourceWallet]) -> FromJSON SourceWallet
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SourceWallet]
$cparseJSONList :: Value -> Parser [SourceWallet]
parseJSON :: Value -> Parser SourceWallet
$cparseJSON :: Value -> Parser SourceWallet
FromJSON,
[SourceWallet] -> Encoding
[SourceWallet] -> Value
SourceWallet -> Encoding
SourceWallet -> Value
(SourceWallet -> Value)
-> (SourceWallet -> Encoding)
-> ([SourceWallet] -> Value)
-> ([SourceWallet] -> Encoding)
-> ToJSON SourceWallet
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SourceWallet] -> Encoding
$ctoEncodingList :: [SourceWallet] -> Encoding
toJSONList :: [SourceWallet] -> Value
$ctoJSONList :: [SourceWallet] -> Value
toEncoding :: SourceWallet -> Encoding
$ctoEncoding :: SourceWallet -> Encoding
toJSON :: SourceWallet -> Value
$ctoJSON :: SourceWallet -> Value
ToJSON
)
via (Autodocodec SourceWallet)
instance HasCodec SourceWallet where
codec :: JSONCodec SourceWallet
codec =
Text
-> ObjectCodec SourceWallet SourceWallet -> JSONCodec SourceWallet
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SourceWallet" (ObjectCodec SourceWallet SourceWallet -> JSONCodec SourceWallet)
-> ObjectCodec SourceWallet SourceWallet -> JSONCodec SourceWallet
forall a b. (a -> b) -> a -> b
$
TransferType -> WalletId -> [Identity] -> SourceWallet
SourceWallet
(TransferType -> WalletId -> [Identity] -> SourceWallet)
-> Codec Object SourceWallet TransferType
-> Codec
Object SourceWallet (WalletId -> [Identity] -> SourceWallet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TransferType TransferType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec TransferType TransferType
-> (SourceWallet -> TransferType)
-> Codec Object SourceWallet TransferType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SourceWallet -> TransferType
sourceWalletType
Codec Object SourceWallet (WalletId -> [Identity] -> SourceWallet)
-> Codec Object SourceWallet WalletId
-> Codec Object SourceWallet ([Identity] -> SourceWallet)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec WalletId WalletId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec WalletId WalletId
-> (SourceWallet -> WalletId) -> Codec Object SourceWallet WalletId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SourceWallet -> WalletId
sourceWalletId
Codec Object SourceWallet ([Identity] -> SourceWallet)
-> Codec Object SourceWallet [Identity]
-> ObjectCodec SourceWallet SourceWallet
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [Identity] [Identity]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"identities" ObjectCodec [Identity] [Identity]
-> (SourceWallet -> [Identity])
-> Codec Object SourceWallet [Identity]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SourceWallet -> [Identity]
sourceWalletIdentities
data SourceBlockchain = SourceBlockchain
{ SourceBlockchain -> TransferType
sourceBlockchainType :: !TransferType,
SourceBlockchain -> Chain
sourceBlockchainChain :: !Chain,
SourceBlockchain -> [Identity]
sourceBlockChainIdentities :: ![Identity]
}
deriving (SourceBlockchain -> SourceBlockchain -> Bool
(SourceBlockchain -> SourceBlockchain -> Bool)
-> (SourceBlockchain -> SourceBlockchain -> Bool)
-> Eq SourceBlockchain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceBlockchain -> SourceBlockchain -> Bool
$c/= :: SourceBlockchain -> SourceBlockchain -> Bool
== :: SourceBlockchain -> SourceBlockchain -> Bool
$c== :: SourceBlockchain -> SourceBlockchain -> Bool
Eq, Int -> SourceBlockchain -> ShowS
[SourceBlockchain] -> ShowS
SourceBlockchain -> String
(Int -> SourceBlockchain -> ShowS)
-> (SourceBlockchain -> String)
-> ([SourceBlockchain] -> ShowS)
-> Show SourceBlockchain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceBlockchain] -> ShowS
$cshowList :: [SourceBlockchain] -> ShowS
show :: SourceBlockchain -> String
$cshow :: SourceBlockchain -> String
showsPrec :: Int -> SourceBlockchain -> ShowS
$cshowsPrec :: Int -> SourceBlockchain -> ShowS
Show)
deriving
( Value -> Parser [SourceBlockchain]
Value -> Parser SourceBlockchain
(Value -> Parser SourceBlockchain)
-> (Value -> Parser [SourceBlockchain])
-> FromJSON SourceBlockchain
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SourceBlockchain]
$cparseJSONList :: Value -> Parser [SourceBlockchain]
parseJSON :: Value -> Parser SourceBlockchain
$cparseJSON :: Value -> Parser SourceBlockchain
FromJSON,
[SourceBlockchain] -> Encoding
[SourceBlockchain] -> Value
SourceBlockchain -> Encoding
SourceBlockchain -> Value
(SourceBlockchain -> Value)
-> (SourceBlockchain -> Encoding)
-> ([SourceBlockchain] -> Value)
-> ([SourceBlockchain] -> Encoding)
-> ToJSON SourceBlockchain
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SourceBlockchain] -> Encoding
$ctoEncodingList :: [SourceBlockchain] -> Encoding
toJSONList :: [SourceBlockchain] -> Value
$ctoJSONList :: [SourceBlockchain] -> Value
toEncoding :: SourceBlockchain -> Encoding
$ctoEncoding :: SourceBlockchain -> Encoding
toJSON :: SourceBlockchain -> Value
$ctoJSON :: SourceBlockchain -> Value
ToJSON
)
via (Autodocodec SourceBlockchain)
instance HasCodec SourceBlockchain where
codec :: JSONCodec SourceBlockchain
codec =
Text
-> ObjectCodec SourceBlockchain SourceBlockchain
-> JSONCodec SourceBlockchain
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SourceBlockchain" (ObjectCodec SourceBlockchain SourceBlockchain
-> JSONCodec SourceBlockchain)
-> ObjectCodec SourceBlockchain SourceBlockchain
-> JSONCodec SourceBlockchain
forall a b. (a -> b) -> a -> b
$
TransferType -> Chain -> [Identity] -> SourceBlockchain
SourceBlockchain
(TransferType -> Chain -> [Identity] -> SourceBlockchain)
-> Codec Object SourceBlockchain TransferType
-> Codec
Object SourceBlockchain (Chain -> [Identity] -> SourceBlockchain)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TransferType TransferType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec TransferType TransferType
-> (SourceBlockchain -> TransferType)
-> Codec Object SourceBlockchain TransferType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SourceBlockchain -> TransferType
sourceBlockchainType
Codec
Object SourceBlockchain (Chain -> [Identity] -> SourceBlockchain)
-> Codec Object SourceBlockchain Chain
-> Codec Object SourceBlockchain ([Identity] -> SourceBlockchain)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (SourceBlockchain -> Chain)
-> Codec Object SourceBlockchain Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SourceBlockchain -> Chain
sourceBlockchainChain
Codec Object SourceBlockchain ([Identity] -> SourceBlockchain)
-> Codec Object SourceBlockchain [Identity]
-> ObjectCodec SourceBlockchain SourceBlockchain
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [Identity] [Identity]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"identities" ObjectCodec [Identity] [Identity]
-> (SourceBlockchain -> [Identity])
-> Codec Object SourceBlockchain [Identity]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SourceBlockchain -> [Identity]
sourceBlockChainIdentities
data DestinationWallet = DestinationWallet
{ DestinationWallet -> TransferType
destinationWalletType :: !TransferType,
DestinationWallet -> WalletId
destinationWalletId :: !WalletId,
DestinationWallet -> Maybe Text
destinationWalletAddress :: !(Maybe Text),
DestinationWallet -> Maybe Text
destinationWalletAddressTag :: !(Maybe Text)
}
deriving (DestinationWallet -> DestinationWallet -> Bool
(DestinationWallet -> DestinationWallet -> Bool)
-> (DestinationWallet -> DestinationWallet -> Bool)
-> Eq DestinationWallet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DestinationWallet -> DestinationWallet -> Bool
$c/= :: DestinationWallet -> DestinationWallet -> Bool
== :: DestinationWallet -> DestinationWallet -> Bool
$c== :: DestinationWallet -> DestinationWallet -> Bool
Eq, Int -> DestinationWallet -> ShowS
[DestinationWallet] -> ShowS
DestinationWallet -> String
(Int -> DestinationWallet -> ShowS)
-> (DestinationWallet -> String)
-> ([DestinationWallet] -> ShowS)
-> Show DestinationWallet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DestinationWallet] -> ShowS
$cshowList :: [DestinationWallet] -> ShowS
show :: DestinationWallet -> String
$cshow :: DestinationWallet -> String
showsPrec :: Int -> DestinationWallet -> ShowS
$cshowsPrec :: Int -> DestinationWallet -> ShowS
Show)
deriving
( Value -> Parser [DestinationWallet]
Value -> Parser DestinationWallet
(Value -> Parser DestinationWallet)
-> (Value -> Parser [DestinationWallet])
-> FromJSON DestinationWallet
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DestinationWallet]
$cparseJSONList :: Value -> Parser [DestinationWallet]
parseJSON :: Value -> Parser DestinationWallet
$cparseJSON :: Value -> Parser DestinationWallet
FromJSON,
[DestinationWallet] -> Encoding
[DestinationWallet] -> Value
DestinationWallet -> Encoding
DestinationWallet -> Value
(DestinationWallet -> Value)
-> (DestinationWallet -> Encoding)
-> ([DestinationWallet] -> Value)
-> ([DestinationWallet] -> Encoding)
-> ToJSON DestinationWallet
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DestinationWallet] -> Encoding
$ctoEncodingList :: [DestinationWallet] -> Encoding
toJSONList :: [DestinationWallet] -> Value
$ctoJSONList :: [DestinationWallet] -> Value
toEncoding :: DestinationWallet -> Encoding
$ctoEncoding :: DestinationWallet -> Encoding
toJSON :: DestinationWallet -> Value
$ctoJSON :: DestinationWallet -> Value
ToJSON
)
via (Autodocodec DestinationWallet)
instance HasCodec DestinationWallet where
codec :: JSONCodec DestinationWallet
codec =
Text
-> ObjectCodec DestinationWallet DestinationWallet
-> JSONCodec DestinationWallet
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"DestinationWallet" (ObjectCodec DestinationWallet DestinationWallet
-> JSONCodec DestinationWallet)
-> ObjectCodec DestinationWallet DestinationWallet
-> JSONCodec DestinationWallet
forall a b. (a -> b) -> a -> b
$
TransferType
-> WalletId -> Maybe Text -> Maybe Text -> DestinationWallet
DestinationWallet
(TransferType
-> WalletId -> Maybe Text -> Maybe Text -> DestinationWallet)
-> Codec Object DestinationWallet TransferType
-> Codec
Object
DestinationWallet
(WalletId -> Maybe Text -> Maybe Text -> DestinationWallet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TransferType TransferType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec TransferType TransferType
-> (DestinationWallet -> TransferType)
-> Codec Object DestinationWallet TransferType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationWallet -> TransferType
destinationWalletType
Codec
Object
DestinationWallet
(WalletId -> Maybe Text -> Maybe Text -> DestinationWallet)
-> Codec Object DestinationWallet WalletId
-> Codec
Object
DestinationWallet
(Maybe Text -> Maybe Text -> DestinationWallet)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec WalletId WalletId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec WalletId WalletId
-> (DestinationWallet -> WalletId)
-> Codec Object DestinationWallet WalletId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationWallet -> WalletId
destinationWalletId
Codec
Object
DestinationWallet
(Maybe Text -> Maybe Text -> DestinationWallet)
-> Codec Object DestinationWallet (Maybe Text)
-> Codec Object DestinationWallet (Maybe Text -> DestinationWallet)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"address" ObjectCodec (Maybe Text) (Maybe Text)
-> (DestinationWallet -> Maybe Text)
-> Codec Object DestinationWallet (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationWallet -> Maybe Text
destinationWalletAddress
Codec Object DestinationWallet (Maybe Text -> DestinationWallet)
-> Codec Object DestinationWallet (Maybe Text)
-> ObjectCodec DestinationWallet DestinationWallet
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"addressTag" ObjectCodec (Maybe Text) (Maybe Text)
-> (DestinationWallet -> Maybe Text)
-> Codec Object DestinationWallet (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationWallet -> Maybe Text
destinationWalletAddressTag
data DestinationBlockchain = DestinationBlockchain
{ DestinationBlockchain -> TransferType
destinationBlockchainType :: !TransferType,
DestinationBlockchain -> HexString
destinationBlockchainAddress :: !HexString,
DestinationBlockchain -> Maybe Text
destinationBlockchainAddressTag :: !(Maybe Text),
DestinationBlockchain -> Chain
destinationBlockchainAddressChain :: !Chain
}
deriving (DestinationBlockchain -> DestinationBlockchain -> Bool
(DestinationBlockchain -> DestinationBlockchain -> Bool)
-> (DestinationBlockchain -> DestinationBlockchain -> Bool)
-> Eq DestinationBlockchain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DestinationBlockchain -> DestinationBlockchain -> Bool
$c/= :: DestinationBlockchain -> DestinationBlockchain -> Bool
== :: DestinationBlockchain -> DestinationBlockchain -> Bool
$c== :: DestinationBlockchain -> DestinationBlockchain -> Bool
Eq, Int -> DestinationBlockchain -> ShowS
[DestinationBlockchain] -> ShowS
DestinationBlockchain -> String
(Int -> DestinationBlockchain -> ShowS)
-> (DestinationBlockchain -> String)
-> ([DestinationBlockchain] -> ShowS)
-> Show DestinationBlockchain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DestinationBlockchain] -> ShowS
$cshowList :: [DestinationBlockchain] -> ShowS
show :: DestinationBlockchain -> String
$cshow :: DestinationBlockchain -> String
showsPrec :: Int -> DestinationBlockchain -> ShowS
$cshowsPrec :: Int -> DestinationBlockchain -> ShowS
Show)
deriving
( Value -> Parser [DestinationBlockchain]
Value -> Parser DestinationBlockchain
(Value -> Parser DestinationBlockchain)
-> (Value -> Parser [DestinationBlockchain])
-> FromJSON DestinationBlockchain
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DestinationBlockchain]
$cparseJSONList :: Value -> Parser [DestinationBlockchain]
parseJSON :: Value -> Parser DestinationBlockchain
$cparseJSON :: Value -> Parser DestinationBlockchain
FromJSON,
[DestinationBlockchain] -> Encoding
[DestinationBlockchain] -> Value
DestinationBlockchain -> Encoding
DestinationBlockchain -> Value
(DestinationBlockchain -> Value)
-> (DestinationBlockchain -> Encoding)
-> ([DestinationBlockchain] -> Value)
-> ([DestinationBlockchain] -> Encoding)
-> ToJSON DestinationBlockchain
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DestinationBlockchain] -> Encoding
$ctoEncodingList :: [DestinationBlockchain] -> Encoding
toJSONList :: [DestinationBlockchain] -> Value
$ctoJSONList :: [DestinationBlockchain] -> Value
toEncoding :: DestinationBlockchain -> Encoding
$ctoEncoding :: DestinationBlockchain -> Encoding
toJSON :: DestinationBlockchain -> Value
$ctoJSON :: DestinationBlockchain -> Value
ToJSON
)
via (Autodocodec DestinationBlockchain)
instance HasCodec DestinationBlockchain where
codec :: JSONCodec DestinationBlockchain
codec =
Text
-> ObjectCodec DestinationBlockchain DestinationBlockchain
-> JSONCodec DestinationBlockchain
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"DestinationBlockchain" (ObjectCodec DestinationBlockchain DestinationBlockchain
-> JSONCodec DestinationBlockchain)
-> ObjectCodec DestinationBlockchain DestinationBlockchain
-> JSONCodec DestinationBlockchain
forall a b. (a -> b) -> a -> b
$
TransferType
-> HexString -> Maybe Text -> Chain -> DestinationBlockchain
DestinationBlockchain
(TransferType
-> HexString -> Maybe Text -> Chain -> DestinationBlockchain)
-> Codec Object DestinationBlockchain TransferType
-> Codec
Object
DestinationBlockchain
(HexString -> Maybe Text -> Chain -> DestinationBlockchain)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TransferType TransferType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec TransferType TransferType
-> (DestinationBlockchain -> TransferType)
-> Codec Object DestinationBlockchain TransferType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationBlockchain -> TransferType
destinationBlockchainType
Codec
Object
DestinationBlockchain
(HexString -> Maybe Text -> Chain -> DestinationBlockchain)
-> Codec Object DestinationBlockchain HexString
-> Codec
Object
DestinationBlockchain
(Maybe Text -> Chain -> DestinationBlockchain)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec HexString HexString
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"address" ObjectCodec HexString HexString
-> (DestinationBlockchain -> HexString)
-> Codec Object DestinationBlockchain HexString
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationBlockchain -> HexString
destinationBlockchainAddress
Codec
Object
DestinationBlockchain
(Maybe Text -> Chain -> DestinationBlockchain)
-> Codec Object DestinationBlockchain (Maybe Text)
-> Codec
Object DestinationBlockchain (Chain -> DestinationBlockchain)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"addressTag" ObjectCodec (Maybe Text) (Maybe Text)
-> (DestinationBlockchain -> Maybe Text)
-> Codec Object DestinationBlockchain (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationBlockchain -> Maybe Text
destinationBlockchainAddressTag
Codec Object DestinationBlockchain (Chain -> DestinationBlockchain)
-> Codec Object DestinationBlockchain Chain
-> ObjectCodec DestinationBlockchain DestinationBlockchain
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (DestinationBlockchain -> Chain)
-> Codec Object DestinationBlockchain Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationBlockchain -> Chain
destinationBlockchainAddressChain
data Identity = Identity
{ Identity -> IdentityType
identityType :: !IdentityType,
Identity -> Text
identityName :: !Text,
Identity -> [Address]
identityAddresses :: ![Address]
}
deriving (Identity -> Identity -> Bool
(Identity -> Identity -> Bool)
-> (Identity -> Identity -> Bool) -> Eq Identity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identity -> Identity -> Bool
$c/= :: Identity -> Identity -> Bool
== :: Identity -> Identity -> Bool
$c== :: Identity -> Identity -> Bool
Eq, Int -> Identity -> ShowS
[Identity] -> ShowS
Identity -> String
(Int -> Identity -> ShowS)
-> (Identity -> String) -> ([Identity] -> ShowS) -> Show Identity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identity] -> ShowS
$cshowList :: [Identity] -> ShowS
show :: Identity -> String
$cshow :: Identity -> String
showsPrec :: Int -> Identity -> ShowS
$cshowsPrec :: Int -> Identity -> ShowS
Show)
deriving
( Value -> Parser [Identity]
Value -> Parser Identity
(Value -> Parser Identity)
-> (Value -> Parser [Identity]) -> FromJSON Identity
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Identity]
$cparseJSONList :: Value -> Parser [Identity]
parseJSON :: Value -> Parser Identity
$cparseJSON :: Value -> Parser Identity
FromJSON,
[Identity] -> Encoding
[Identity] -> Value
Identity -> Encoding
Identity -> Value
(Identity -> Value)
-> (Identity -> Encoding)
-> ([Identity] -> Value)
-> ([Identity] -> Encoding)
-> ToJSON Identity
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Identity] -> Encoding
$ctoEncodingList :: [Identity] -> Encoding
toJSONList :: [Identity] -> Value
$ctoJSONList :: [Identity] -> Value
toEncoding :: Identity -> Encoding
$ctoEncoding :: Identity -> Encoding
toJSON :: Identity -> Value
$ctoJSON :: Identity -> Value
ToJSON
)
via (Autodocodec Identity)
instance HasCodec Identity where
codec :: JSONCodec Identity
codec =
Text -> ObjectCodec Identity Identity -> JSONCodec Identity
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"Identity" (ObjectCodec Identity Identity -> JSONCodec Identity)
-> ObjectCodec Identity Identity -> JSONCodec Identity
forall a b. (a -> b) -> a -> b
$
IdentityType -> Text -> [Address] -> Identity
Identity
(IdentityType -> Text -> [Address] -> Identity)
-> Codec Object Identity IdentityType
-> Codec Object Identity (Text -> [Address] -> Identity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec IdentityType IdentityType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec IdentityType IdentityType
-> (Identity -> IdentityType) -> Codec Object Identity IdentityType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Identity -> IdentityType
identityType
Codec Object Identity (Text -> [Address] -> Identity)
-> Codec Object Identity Text
-> Codec Object Identity ([Address] -> Identity)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"name" ObjectCodec Text Text
-> (Identity -> Text) -> Codec Object Identity Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Identity -> Text
identityName
Codec Object Identity ([Address] -> Identity)
-> Codec Object Identity [Address] -> ObjectCodec Identity Identity
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [Address] [Address]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"addresses" ObjectCodec [Address] [Address]
-> (Identity -> [Address]) -> Codec Object Identity [Address]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Identity -> [Address]
identityAddresses
data IdentityType = Individual | Business
deriving (IdentityType -> IdentityType -> Bool
(IdentityType -> IdentityType -> Bool)
-> (IdentityType -> IdentityType -> Bool) -> Eq IdentityType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IdentityType -> IdentityType -> Bool
$c/= :: IdentityType -> IdentityType -> Bool
== :: IdentityType -> IdentityType -> Bool
$c== :: IdentityType -> IdentityType -> Bool
Eq, Int -> IdentityType -> ShowS
[IdentityType] -> ShowS
IdentityType -> String
(Int -> IdentityType -> ShowS)
-> (IdentityType -> String)
-> ([IdentityType] -> ShowS)
-> Show IdentityType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IdentityType] -> ShowS
$cshowList :: [IdentityType] -> ShowS
show :: IdentityType -> String
$cshow :: IdentityType -> String
showsPrec :: Int -> IdentityType -> ShowS
$cshowsPrec :: Int -> IdentityType -> ShowS
Show)
deriving
( Value -> Parser [IdentityType]
Value -> Parser IdentityType
(Value -> Parser IdentityType)
-> (Value -> Parser [IdentityType]) -> FromJSON IdentityType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [IdentityType]
$cparseJSONList :: Value -> Parser [IdentityType]
parseJSON :: Value -> Parser IdentityType
$cparseJSON :: Value -> Parser IdentityType
FromJSON,
[IdentityType] -> Encoding
[IdentityType] -> Value
IdentityType -> Encoding
IdentityType -> Value
(IdentityType -> Value)
-> (IdentityType -> Encoding)
-> ([IdentityType] -> Value)
-> ([IdentityType] -> Encoding)
-> ToJSON IdentityType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [IdentityType] -> Encoding
$ctoEncodingList :: [IdentityType] -> Encoding
toJSONList :: [IdentityType] -> Value
$ctoJSONList :: [IdentityType] -> Value
toEncoding :: IdentityType -> Encoding
$ctoEncoding :: IdentityType -> Encoding
toJSON :: IdentityType -> Value
$ctoJSON :: IdentityType -> Value
ToJSON
)
via (Autodocodec IdentityType)
instance HasCodec IdentityType where
codec :: JSONCodec IdentityType
codec = NonEmpty (IdentityType, Text) -> JSONCodec IdentityType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (IdentityType, Text) -> JSONCodec IdentityType)
-> NonEmpty (IdentityType, Text) -> JSONCodec IdentityType
forall a b. (a -> b) -> a -> b
$ [(IdentityType, Text)] -> NonEmpty (IdentityType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(IdentityType
Individual, Text
"individual"), (IdentityType
Business, Text
"business")]
data TransferType = Wallet | Blockchain
deriving (TransferType -> TransferType -> Bool
(TransferType -> TransferType -> Bool)
-> (TransferType -> TransferType -> Bool) -> Eq TransferType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferType -> TransferType -> Bool
$c/= :: TransferType -> TransferType -> Bool
== :: TransferType -> TransferType -> Bool
$c== :: TransferType -> TransferType -> Bool
Eq, Int -> TransferType -> ShowS
[TransferType] -> ShowS
TransferType -> String
(Int -> TransferType -> ShowS)
-> (TransferType -> String)
-> ([TransferType] -> ShowS)
-> Show TransferType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferType] -> ShowS
$cshowList :: [TransferType] -> ShowS
show :: TransferType -> String
$cshow :: TransferType -> String
showsPrec :: Int -> TransferType -> ShowS
$cshowsPrec :: Int -> TransferType -> ShowS
Show)
deriving
( Value -> Parser [TransferType]
Value -> Parser TransferType
(Value -> Parser TransferType)
-> (Value -> Parser [TransferType]) -> FromJSON TransferType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransferType]
$cparseJSONList :: Value -> Parser [TransferType]
parseJSON :: Value -> Parser TransferType
$cparseJSON :: Value -> Parser TransferType
FromJSON,
[TransferType] -> Encoding
[TransferType] -> Value
TransferType -> Encoding
TransferType -> Value
(TransferType -> Value)
-> (TransferType -> Encoding)
-> ([TransferType] -> Value)
-> ([TransferType] -> Encoding)
-> ToJSON TransferType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransferType] -> Encoding
$ctoEncodingList :: [TransferType] -> Encoding
toJSONList :: [TransferType] -> Value
$ctoJSONList :: [TransferType] -> Value
toEncoding :: TransferType -> Encoding
$ctoEncoding :: TransferType -> Encoding
toJSON :: TransferType -> Value
$ctoJSON :: TransferType -> Value
ToJSON
)
via (Autodocodec TransferType)
instance HasCodec TransferType where
codec :: JSONCodec TransferType
codec = NonEmpty (TransferType, Text) -> JSONCodec TransferType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (TransferType, Text) -> JSONCodec TransferType)
-> NonEmpty (TransferType, Text) -> JSONCodec TransferType
forall a b. (a -> b) -> a -> b
$ [(TransferType, Text)] -> NonEmpty (TransferType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(TransferType
Wallet, Text
"wallet"), (TransferType
Blockchain, Text
"blockchain")]
data TransferErrorCode
= TransferInsufficientFunds
| BlockchainError
| TransferDenied
| TransferFailed
deriving (TransferErrorCode -> TransferErrorCode -> Bool
(TransferErrorCode -> TransferErrorCode -> Bool)
-> (TransferErrorCode -> TransferErrorCode -> Bool)
-> Eq TransferErrorCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferErrorCode -> TransferErrorCode -> Bool
$c/= :: TransferErrorCode -> TransferErrorCode -> Bool
== :: TransferErrorCode -> TransferErrorCode -> Bool
$c== :: TransferErrorCode -> TransferErrorCode -> Bool
Eq, Int -> TransferErrorCode -> ShowS
[TransferErrorCode] -> ShowS
TransferErrorCode -> String
(Int -> TransferErrorCode -> ShowS)
-> (TransferErrorCode -> String)
-> ([TransferErrorCode] -> ShowS)
-> Show TransferErrorCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferErrorCode] -> ShowS
$cshowList :: [TransferErrorCode] -> ShowS
show :: TransferErrorCode -> String
$cshow :: TransferErrorCode -> String
showsPrec :: Int -> TransferErrorCode -> ShowS
$cshowsPrec :: Int -> TransferErrorCode -> ShowS
Show)
deriving
( Value -> Parser [TransferErrorCode]
Value -> Parser TransferErrorCode
(Value -> Parser TransferErrorCode)
-> (Value -> Parser [TransferErrorCode])
-> FromJSON TransferErrorCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransferErrorCode]
$cparseJSONList :: Value -> Parser [TransferErrorCode]
parseJSON :: Value -> Parser TransferErrorCode
$cparseJSON :: Value -> Parser TransferErrorCode
FromJSON,
[TransferErrorCode] -> Encoding
[TransferErrorCode] -> Value
TransferErrorCode -> Encoding
TransferErrorCode -> Value
(TransferErrorCode -> Value)
-> (TransferErrorCode -> Encoding)
-> ([TransferErrorCode] -> Value)
-> ([TransferErrorCode] -> Encoding)
-> ToJSON TransferErrorCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransferErrorCode] -> Encoding
$ctoEncodingList :: [TransferErrorCode] -> Encoding
toJSONList :: [TransferErrorCode] -> Value
$ctoJSONList :: [TransferErrorCode] -> Value
toEncoding :: TransferErrorCode -> Encoding
$ctoEncoding :: TransferErrorCode -> Encoding
toJSON :: TransferErrorCode -> Value
$ctoJSON :: TransferErrorCode -> Value
ToJSON
)
via (Autodocodec TransferErrorCode)
instance HasCodec TransferErrorCode where
codec :: JSONCodec TransferErrorCode
codec =
NonEmpty (TransferErrorCode, Text) -> JSONCodec TransferErrorCode
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (TransferErrorCode, Text) -> JSONCodec TransferErrorCode)
-> NonEmpty (TransferErrorCode, Text)
-> JSONCodec TransferErrorCode
forall a b. (a -> b) -> a -> b
$
[(TransferErrorCode, Text)] -> NonEmpty (TransferErrorCode, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (TransferErrorCode
TransferInsufficientFunds, Text
"insufficient_funds"),
(TransferErrorCode
BlockchainError, Text
"blockchain_error"),
(TransferErrorCode
TransferDenied, Text
"transfer_denied"),
(TransferErrorCode
TransferFailed, Text
"transfer_failed")
]
data DepositAddressesRequest
type instance CircleRequest DepositAddressesRequest = CircleResponseBody [DepositAddressResponseBody]
data DepositAddressRequest
type instance CircleRequest DepositAddressRequest = CircleResponseBody DepositAddressResponseBody
data DepositAddressResponseBody = DepositAddressResponseBody
{ DepositAddressResponseBody -> HexString
depositAddressResponseBodyAddress :: !HexString,
DepositAddressResponseBody -> Maybe Text
depositAddressResponseBodyAddressTag :: !(Maybe Text),
DepositAddressResponseBody -> SupportedCurrencies
depositAddressResponseBodyCurrency :: !SupportedCurrencies,
DepositAddressResponseBody -> Chain
depositAddressResponseBodyChain :: !Chain
}
deriving (DepositAddressResponseBody -> DepositAddressResponseBody -> Bool
(DepositAddressResponseBody -> DepositAddressResponseBody -> Bool)
-> (DepositAddressResponseBody
-> DepositAddressResponseBody -> Bool)
-> Eq DepositAddressResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DepositAddressResponseBody -> DepositAddressResponseBody -> Bool
$c/= :: DepositAddressResponseBody -> DepositAddressResponseBody -> Bool
== :: DepositAddressResponseBody -> DepositAddressResponseBody -> Bool
$c== :: DepositAddressResponseBody -> DepositAddressResponseBody -> Bool
Eq, Int -> DepositAddressResponseBody -> ShowS
[DepositAddressResponseBody] -> ShowS
DepositAddressResponseBody -> String
(Int -> DepositAddressResponseBody -> ShowS)
-> (DepositAddressResponseBody -> String)
-> ([DepositAddressResponseBody] -> ShowS)
-> Show DepositAddressResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DepositAddressResponseBody] -> ShowS
$cshowList :: [DepositAddressResponseBody] -> ShowS
show :: DepositAddressResponseBody -> String
$cshow :: DepositAddressResponseBody -> String
showsPrec :: Int -> DepositAddressResponseBody -> ShowS
$cshowsPrec :: Int -> DepositAddressResponseBody -> ShowS
Show)
deriving
( Value -> Parser [DepositAddressResponseBody]
Value -> Parser DepositAddressResponseBody
(Value -> Parser DepositAddressResponseBody)
-> (Value -> Parser [DepositAddressResponseBody])
-> FromJSON DepositAddressResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DepositAddressResponseBody]
$cparseJSONList :: Value -> Parser [DepositAddressResponseBody]
parseJSON :: Value -> Parser DepositAddressResponseBody
$cparseJSON :: Value -> Parser DepositAddressResponseBody
FromJSON,
[DepositAddressResponseBody] -> Encoding
[DepositAddressResponseBody] -> Value
DepositAddressResponseBody -> Encoding
DepositAddressResponseBody -> Value
(DepositAddressResponseBody -> Value)
-> (DepositAddressResponseBody -> Encoding)
-> ([DepositAddressResponseBody] -> Value)
-> ([DepositAddressResponseBody] -> Encoding)
-> ToJSON DepositAddressResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DepositAddressResponseBody] -> Encoding
$ctoEncodingList :: [DepositAddressResponseBody] -> Encoding
toJSONList :: [DepositAddressResponseBody] -> Value
$ctoJSONList :: [DepositAddressResponseBody] -> Value
toEncoding :: DepositAddressResponseBody -> Encoding
$ctoEncoding :: DepositAddressResponseBody -> Encoding
toJSON :: DepositAddressResponseBody -> Value
$ctoJSON :: DepositAddressResponseBody -> Value
ToJSON
)
via (Autodocodec DepositAddressResponseBody)
instance HasCodec DepositAddressResponseBody where
codec :: JSONCodec DepositAddressResponseBody
codec =
Text
-> ObjectCodec
DepositAddressResponseBody DepositAddressResponseBody
-> JSONCodec DepositAddressResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"DepositAddressResponseBody" (ObjectCodec DepositAddressResponseBody DepositAddressResponseBody
-> JSONCodec DepositAddressResponseBody)
-> ObjectCodec
DepositAddressResponseBody DepositAddressResponseBody
-> JSONCodec DepositAddressResponseBody
forall a b. (a -> b) -> a -> b
$
HexString
-> Maybe Text
-> SupportedCurrencies
-> Chain
-> DepositAddressResponseBody
DepositAddressResponseBody
(HexString
-> Maybe Text
-> SupportedCurrencies
-> Chain
-> DepositAddressResponseBody)
-> Codec Object DepositAddressResponseBody HexString
-> Codec
Object
DepositAddressResponseBody
(Maybe Text
-> SupportedCurrencies -> Chain -> DepositAddressResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec HexString HexString
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"address" ObjectCodec HexString HexString
-> (DepositAddressResponseBody -> HexString)
-> Codec Object DepositAddressResponseBody HexString
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositAddressResponseBody -> HexString
depositAddressResponseBodyAddress
Codec
Object
DepositAddressResponseBody
(Maybe Text
-> SupportedCurrencies -> Chain -> DepositAddressResponseBody)
-> Codec Object DepositAddressResponseBody (Maybe Text)
-> Codec
Object
DepositAddressResponseBody
(SupportedCurrencies -> Chain -> DepositAddressResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"addressTag" ObjectCodec (Maybe Text) (Maybe Text)
-> (DepositAddressResponseBody -> Maybe Text)
-> Codec Object DepositAddressResponseBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositAddressResponseBody -> Maybe Text
depositAddressResponseBodyAddressTag
Codec
Object
DepositAddressResponseBody
(SupportedCurrencies -> Chain -> DepositAddressResponseBody)
-> Codec Object DepositAddressResponseBody SupportedCurrencies
-> Codec
Object
DepositAddressResponseBody
(Chain -> DepositAddressResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (DepositAddressResponseBody -> SupportedCurrencies)
-> Codec Object DepositAddressResponseBody SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositAddressResponseBody -> SupportedCurrencies
depositAddressResponseBodyCurrency
Codec
Object
DepositAddressResponseBody
(Chain -> DepositAddressResponseBody)
-> Codec Object DepositAddressResponseBody Chain
-> ObjectCodec
DepositAddressResponseBody DepositAddressResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (DepositAddressResponseBody -> Chain)
-> Codec Object DepositAddressResponseBody Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositAddressResponseBody -> Chain
depositAddressResponseBodyChain
data DepositAddressRequestBody = DepositAddressRequestBody
{ DepositAddressRequestBody -> UUID
depositAddressRequestBodyIdempotencyKey :: !UUID,
DepositAddressRequestBody -> SupportedCurrencies
depositAddressRequestBodyCurrency :: !SupportedCurrencies,
DepositAddressRequestBody -> Chain
depositAddressRequestBodyChain :: !Chain
}
deriving (DepositAddressRequestBody -> DepositAddressRequestBody -> Bool
(DepositAddressRequestBody -> DepositAddressRequestBody -> Bool)
-> (DepositAddressRequestBody -> DepositAddressRequestBody -> Bool)
-> Eq DepositAddressRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DepositAddressRequestBody -> DepositAddressRequestBody -> Bool
$c/= :: DepositAddressRequestBody -> DepositAddressRequestBody -> Bool
== :: DepositAddressRequestBody -> DepositAddressRequestBody -> Bool
$c== :: DepositAddressRequestBody -> DepositAddressRequestBody -> Bool
Eq, Int -> DepositAddressRequestBody -> ShowS
[DepositAddressRequestBody] -> ShowS
DepositAddressRequestBody -> String
(Int -> DepositAddressRequestBody -> ShowS)
-> (DepositAddressRequestBody -> String)
-> ([DepositAddressRequestBody] -> ShowS)
-> Show DepositAddressRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DepositAddressRequestBody] -> ShowS
$cshowList :: [DepositAddressRequestBody] -> ShowS
show :: DepositAddressRequestBody -> String
$cshow :: DepositAddressRequestBody -> String
showsPrec :: Int -> DepositAddressRequestBody -> ShowS
$cshowsPrec :: Int -> DepositAddressRequestBody -> ShowS
Show)
deriving
( Value -> Parser [DepositAddressRequestBody]
Value -> Parser DepositAddressRequestBody
(Value -> Parser DepositAddressRequestBody)
-> (Value -> Parser [DepositAddressRequestBody])
-> FromJSON DepositAddressRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DepositAddressRequestBody]
$cparseJSONList :: Value -> Parser [DepositAddressRequestBody]
parseJSON :: Value -> Parser DepositAddressRequestBody
$cparseJSON :: Value -> Parser DepositAddressRequestBody
FromJSON,
[DepositAddressRequestBody] -> Encoding
[DepositAddressRequestBody] -> Value
DepositAddressRequestBody -> Encoding
DepositAddressRequestBody -> Value
(DepositAddressRequestBody -> Value)
-> (DepositAddressRequestBody -> Encoding)
-> ([DepositAddressRequestBody] -> Value)
-> ([DepositAddressRequestBody] -> Encoding)
-> ToJSON DepositAddressRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DepositAddressRequestBody] -> Encoding
$ctoEncodingList :: [DepositAddressRequestBody] -> Encoding
toJSONList :: [DepositAddressRequestBody] -> Value
$ctoJSONList :: [DepositAddressRequestBody] -> Value
toEncoding :: DepositAddressRequestBody -> Encoding
$ctoEncoding :: DepositAddressRequestBody -> Encoding
toJSON :: DepositAddressRequestBody -> Value
$ctoJSON :: DepositAddressRequestBody -> Value
ToJSON
)
via (Autodocodec DepositAddressRequestBody)
instance HasCodec DepositAddressRequestBody where
codec :: JSONCodec DepositAddressRequestBody
codec =
Text
-> ObjectCodec DepositAddressRequestBody DepositAddressRequestBody
-> JSONCodec DepositAddressRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"DepositAddressRequestBody" (ObjectCodec DepositAddressRequestBody DepositAddressRequestBody
-> JSONCodec DepositAddressRequestBody)
-> ObjectCodec DepositAddressRequestBody DepositAddressRequestBody
-> JSONCodec DepositAddressRequestBody
forall a b. (a -> b) -> a -> b
$
UUID -> SupportedCurrencies -> Chain -> DepositAddressRequestBody
DepositAddressRequestBody
(UUID -> SupportedCurrencies -> Chain -> DepositAddressRequestBody)
-> Codec Object DepositAddressRequestBody UUID
-> Codec
Object
DepositAddressRequestBody
(SupportedCurrencies -> Chain -> DepositAddressRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (DepositAddressRequestBody -> UUID)
-> Codec Object DepositAddressRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositAddressRequestBody -> UUID
depositAddressRequestBodyIdempotencyKey
Codec
Object
DepositAddressRequestBody
(SupportedCurrencies -> Chain -> DepositAddressRequestBody)
-> Codec Object DepositAddressRequestBody SupportedCurrencies
-> Codec
Object
DepositAddressRequestBody
(Chain -> DepositAddressRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (DepositAddressRequestBody -> SupportedCurrencies)
-> Codec Object DepositAddressRequestBody SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositAddressRequestBody -> SupportedCurrencies
depositAddressRequestBodyCurrency
Codec
Object
DepositAddressRequestBody
(Chain -> DepositAddressRequestBody)
-> Codec Object DepositAddressRequestBody Chain
-> ObjectCodec DepositAddressRequestBody DepositAddressRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (DepositAddressRequestBody -> Chain)
-> Codec Object DepositAddressRequestBody Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositAddressRequestBody -> Chain
depositAddressRequestBodyChain
data RecipientAddressesRequest
type instance CircleRequest RecipientAddressesRequest = CircleResponseBody [RecipientAddressResponseBody]
instance CircleHasParam RecipientAddressesRequest PaginationQueryParams
instance CircleHasParam RecipientAddressesRequest FromQueryParam
instance CircleHasParam RecipientAddressesRequest ToQueryParam
instance CircleHasParam RecipientAddressesRequest PageSizeQueryParam
data RecipientAddressRequest
type instance CircleRequest RecipientAddressRequest = CircleResponseBody RecipientAddressResponseBody
data RecipientAddressResponseBody = RecipientAddressResponseBody
{ RecipientAddressResponseBody -> UUID
recipientAddressResponseBodyId :: !UUID,
RecipientAddressResponseBody -> HexString
recipientAddressResponseBodyAddress :: !HexString,
RecipientAddressResponseBody -> Maybe Text
recipientAddressResponseBodyAddressTag :: !(Maybe Text),
RecipientAddressResponseBody -> Chain
recipientAddressResponseBodyChain :: !Chain,
RecipientAddressResponseBody -> SupportedCurrencies
recipientAddressResponseBodyCurrency :: !SupportedCurrencies,
RecipientAddressResponseBody -> Text
recipientAddressResponseBodyDescription :: !Text
}
deriving (RecipientAddressResponseBody
-> RecipientAddressResponseBody -> Bool
(RecipientAddressResponseBody
-> RecipientAddressResponseBody -> Bool)
-> (RecipientAddressResponseBody
-> RecipientAddressResponseBody -> Bool)
-> Eq RecipientAddressResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecipientAddressResponseBody
-> RecipientAddressResponseBody -> Bool
$c/= :: RecipientAddressResponseBody
-> RecipientAddressResponseBody -> Bool
== :: RecipientAddressResponseBody
-> RecipientAddressResponseBody -> Bool
$c== :: RecipientAddressResponseBody
-> RecipientAddressResponseBody -> Bool
Eq, Int -> RecipientAddressResponseBody -> ShowS
[RecipientAddressResponseBody] -> ShowS
RecipientAddressResponseBody -> String
(Int -> RecipientAddressResponseBody -> ShowS)
-> (RecipientAddressResponseBody -> String)
-> ([RecipientAddressResponseBody] -> ShowS)
-> Show RecipientAddressResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecipientAddressResponseBody] -> ShowS
$cshowList :: [RecipientAddressResponseBody] -> ShowS
show :: RecipientAddressResponseBody -> String
$cshow :: RecipientAddressResponseBody -> String
showsPrec :: Int -> RecipientAddressResponseBody -> ShowS
$cshowsPrec :: Int -> RecipientAddressResponseBody -> ShowS
Show)
deriving
( Value -> Parser [RecipientAddressResponseBody]
Value -> Parser RecipientAddressResponseBody
(Value -> Parser RecipientAddressResponseBody)
-> (Value -> Parser [RecipientAddressResponseBody])
-> FromJSON RecipientAddressResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RecipientAddressResponseBody]
$cparseJSONList :: Value -> Parser [RecipientAddressResponseBody]
parseJSON :: Value -> Parser RecipientAddressResponseBody
$cparseJSON :: Value -> Parser RecipientAddressResponseBody
FromJSON,
[RecipientAddressResponseBody] -> Encoding
[RecipientAddressResponseBody] -> Value
RecipientAddressResponseBody -> Encoding
RecipientAddressResponseBody -> Value
(RecipientAddressResponseBody -> Value)
-> (RecipientAddressResponseBody -> Encoding)
-> ([RecipientAddressResponseBody] -> Value)
-> ([RecipientAddressResponseBody] -> Encoding)
-> ToJSON RecipientAddressResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RecipientAddressResponseBody] -> Encoding
$ctoEncodingList :: [RecipientAddressResponseBody] -> Encoding
toJSONList :: [RecipientAddressResponseBody] -> Value
$ctoJSONList :: [RecipientAddressResponseBody] -> Value
toEncoding :: RecipientAddressResponseBody -> Encoding
$ctoEncoding :: RecipientAddressResponseBody -> Encoding
toJSON :: RecipientAddressResponseBody -> Value
$ctoJSON :: RecipientAddressResponseBody -> Value
ToJSON
)
via (Autodocodec RecipientAddressResponseBody)
instance HasCodec RecipientAddressResponseBody where
codec :: JSONCodec RecipientAddressResponseBody
codec =
Text
-> ObjectCodec
RecipientAddressResponseBody RecipientAddressResponseBody
-> JSONCodec RecipientAddressResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"RecipientAddressResponseBody" (ObjectCodec
RecipientAddressResponseBody RecipientAddressResponseBody
-> JSONCodec RecipientAddressResponseBody)
-> ObjectCodec
RecipientAddressResponseBody RecipientAddressResponseBody
-> JSONCodec RecipientAddressResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressResponseBody
RecipientAddressResponseBody
(UUID
-> HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressResponseBody)
-> Codec Object RecipientAddressResponseBody UUID
-> Codec
Object
RecipientAddressResponseBody
(HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (RecipientAddressResponseBody -> UUID)
-> Codec Object RecipientAddressResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressResponseBody -> UUID
recipientAddressResponseBodyId
Codec
Object
RecipientAddressResponseBody
(HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressResponseBody)
-> Codec Object RecipientAddressResponseBody HexString
-> Codec
Object
RecipientAddressResponseBody
(Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec HexString HexString
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"address" ObjectCodec HexString HexString
-> (RecipientAddressResponseBody -> HexString)
-> Codec Object RecipientAddressResponseBody HexString
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressResponseBody -> HexString
recipientAddressResponseBodyAddress
Codec
Object
RecipientAddressResponseBody
(Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressResponseBody)
-> Codec Object RecipientAddressResponseBody (Maybe Text)
-> Codec
Object
RecipientAddressResponseBody
(Chain
-> SupportedCurrencies -> Text -> RecipientAddressResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"addressTag" ObjectCodec (Maybe Text) (Maybe Text)
-> (RecipientAddressResponseBody -> Maybe Text)
-> Codec Object RecipientAddressResponseBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressResponseBody -> Maybe Text
recipientAddressResponseBodyAddressTag
Codec
Object
RecipientAddressResponseBody
(Chain
-> SupportedCurrencies -> Text -> RecipientAddressResponseBody)
-> Codec Object RecipientAddressResponseBody Chain
-> Codec
Object
RecipientAddressResponseBody
(SupportedCurrencies -> Text -> RecipientAddressResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (RecipientAddressResponseBody -> Chain)
-> Codec Object RecipientAddressResponseBody Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressResponseBody -> Chain
recipientAddressResponseBodyChain
Codec
Object
RecipientAddressResponseBody
(SupportedCurrencies -> Text -> RecipientAddressResponseBody)
-> Codec Object RecipientAddressResponseBody SupportedCurrencies
-> Codec
Object
RecipientAddressResponseBody
(Text -> RecipientAddressResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (RecipientAddressResponseBody -> SupportedCurrencies)
-> Codec Object RecipientAddressResponseBody SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressResponseBody -> SupportedCurrencies
recipientAddressResponseBodyCurrency
Codec
Object
RecipientAddressResponseBody
(Text -> RecipientAddressResponseBody)
-> Codec Object RecipientAddressResponseBody Text
-> ObjectCodec
RecipientAddressResponseBody RecipientAddressResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (RecipientAddressResponseBody -> Text)
-> Codec Object RecipientAddressResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressResponseBody -> Text
recipientAddressResponseBodyDescription
data RecipientAddressRequestBody = RecipientAddressRequestBody
{ RecipientAddressRequestBody -> UUID
recipientAddressRequestBodyIdempotencyKey :: !UUID,
RecipientAddressRequestBody -> HexString
recipientAddressRequestBodyAddress :: !HexString,
RecipientAddressRequestBody -> Maybe Text
recipientAddressRequestBodyAddressTag :: !(Maybe Text),
RecipientAddressRequestBody -> Chain
recipientAddressRequestBodyChain :: !Chain,
RecipientAddressRequestBody -> SupportedCurrencies
recipientAddressRequestBodyCurrency :: !SupportedCurrencies,
RecipientAddressRequestBody -> Text
recipientAddressRequestBodyDescription :: !Text
}
deriving (RecipientAddressRequestBody -> RecipientAddressRequestBody -> Bool
(RecipientAddressRequestBody
-> RecipientAddressRequestBody -> Bool)
-> (RecipientAddressRequestBody
-> RecipientAddressRequestBody -> Bool)
-> Eq RecipientAddressRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecipientAddressRequestBody -> RecipientAddressRequestBody -> Bool
$c/= :: RecipientAddressRequestBody -> RecipientAddressRequestBody -> Bool
== :: RecipientAddressRequestBody -> RecipientAddressRequestBody -> Bool
$c== :: RecipientAddressRequestBody -> RecipientAddressRequestBody -> Bool
Eq, Int -> RecipientAddressRequestBody -> ShowS
[RecipientAddressRequestBody] -> ShowS
RecipientAddressRequestBody -> String
(Int -> RecipientAddressRequestBody -> ShowS)
-> (RecipientAddressRequestBody -> String)
-> ([RecipientAddressRequestBody] -> ShowS)
-> Show RecipientAddressRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecipientAddressRequestBody] -> ShowS
$cshowList :: [RecipientAddressRequestBody] -> ShowS
show :: RecipientAddressRequestBody -> String
$cshow :: RecipientAddressRequestBody -> String
showsPrec :: Int -> RecipientAddressRequestBody -> ShowS
$cshowsPrec :: Int -> RecipientAddressRequestBody -> ShowS
Show)
deriving
( Value -> Parser [RecipientAddressRequestBody]
Value -> Parser RecipientAddressRequestBody
(Value -> Parser RecipientAddressRequestBody)
-> (Value -> Parser [RecipientAddressRequestBody])
-> FromJSON RecipientAddressRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RecipientAddressRequestBody]
$cparseJSONList :: Value -> Parser [RecipientAddressRequestBody]
parseJSON :: Value -> Parser RecipientAddressRequestBody
$cparseJSON :: Value -> Parser RecipientAddressRequestBody
FromJSON,
[RecipientAddressRequestBody] -> Encoding
[RecipientAddressRequestBody] -> Value
RecipientAddressRequestBody -> Encoding
RecipientAddressRequestBody -> Value
(RecipientAddressRequestBody -> Value)
-> (RecipientAddressRequestBody -> Encoding)
-> ([RecipientAddressRequestBody] -> Value)
-> ([RecipientAddressRequestBody] -> Encoding)
-> ToJSON RecipientAddressRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RecipientAddressRequestBody] -> Encoding
$ctoEncodingList :: [RecipientAddressRequestBody] -> Encoding
toJSONList :: [RecipientAddressRequestBody] -> Value
$ctoJSONList :: [RecipientAddressRequestBody] -> Value
toEncoding :: RecipientAddressRequestBody -> Encoding
$ctoEncoding :: RecipientAddressRequestBody -> Encoding
toJSON :: RecipientAddressRequestBody -> Value
$ctoJSON :: RecipientAddressRequestBody -> Value
ToJSON
)
via (Autodocodec RecipientAddressRequestBody)
instance HasCodec RecipientAddressRequestBody where
codec :: JSONCodec RecipientAddressRequestBody
codec =
Text
-> ObjectCodec
RecipientAddressRequestBody RecipientAddressRequestBody
-> JSONCodec RecipientAddressRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"RecipientAddressRequestBody" (ObjectCodec
RecipientAddressRequestBody RecipientAddressRequestBody
-> JSONCodec RecipientAddressRequestBody)
-> ObjectCodec
RecipientAddressRequestBody RecipientAddressRequestBody
-> JSONCodec RecipientAddressRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressRequestBody
RecipientAddressRequestBody
(UUID
-> HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressRequestBody)
-> Codec Object RecipientAddressRequestBody UUID
-> Codec
Object
RecipientAddressRequestBody
(HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (RecipientAddressRequestBody -> UUID)
-> Codec Object RecipientAddressRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressRequestBody -> UUID
recipientAddressRequestBodyIdempotencyKey
Codec
Object
RecipientAddressRequestBody
(HexString
-> Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressRequestBody)
-> Codec Object RecipientAddressRequestBody HexString
-> Codec
Object
RecipientAddressRequestBody
(Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec HexString HexString
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"address" ObjectCodec HexString HexString
-> (RecipientAddressRequestBody -> HexString)
-> Codec Object RecipientAddressRequestBody HexString
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressRequestBody -> HexString
recipientAddressRequestBodyAddress
Codec
Object
RecipientAddressRequestBody
(Maybe Text
-> Chain
-> SupportedCurrencies
-> Text
-> RecipientAddressRequestBody)
-> Codec Object RecipientAddressRequestBody (Maybe Text)
-> Codec
Object
RecipientAddressRequestBody
(Chain
-> SupportedCurrencies -> Text -> RecipientAddressRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"addressTag" ObjectCodec (Maybe Text) (Maybe Text)
-> (RecipientAddressRequestBody -> Maybe Text)
-> Codec Object RecipientAddressRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressRequestBody -> Maybe Text
recipientAddressRequestBodyAddressTag
Codec
Object
RecipientAddressRequestBody
(Chain
-> SupportedCurrencies -> Text -> RecipientAddressRequestBody)
-> Codec Object RecipientAddressRequestBody Chain
-> Codec
Object
RecipientAddressRequestBody
(SupportedCurrencies -> Text -> RecipientAddressRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (RecipientAddressRequestBody -> Chain)
-> Codec Object RecipientAddressRequestBody Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressRequestBody -> Chain
recipientAddressRequestBodyChain
Codec
Object
RecipientAddressRequestBody
(SupportedCurrencies -> Text -> RecipientAddressRequestBody)
-> Codec Object RecipientAddressRequestBody SupportedCurrencies
-> Codec
Object
RecipientAddressRequestBody
(Text -> RecipientAddressRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (RecipientAddressRequestBody -> SupportedCurrencies)
-> Codec Object RecipientAddressRequestBody SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressRequestBody -> SupportedCurrencies
recipientAddressRequestBodyCurrency
Codec
Object
RecipientAddressRequestBody
(Text -> RecipientAddressRequestBody)
-> Codec Object RecipientAddressRequestBody Text
-> ObjectCodec
RecipientAddressRequestBody RecipientAddressRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (RecipientAddressRequestBody -> Text)
-> Codec Object RecipientAddressRequestBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RecipientAddressRequestBody -> Text
recipientAddressRequestBodyDescription
data DepositsRequest
type instance CircleRequest DepositsRequest = CircleResponseBody [DepositResponseBody]
instance CircleHasParam DepositsRequest TypeQueryParam
instance CircleHasParam DepositsRequest PaginationQueryParams
instance CircleHasParam DepositsRequest FromQueryParam
instance CircleHasParam DepositsRequest ToQueryParam
instance CircleHasParam DepositsRequest PageSizeQueryParam
data DepositResponseBody = DepositResponseBody
{ DepositResponseBody -> UUID
depositResponseBodyId :: !UUID,
DepositResponseBody -> Maybe WalletId
depositResponseBodySourceWalletId :: !(Maybe WalletId),
DepositResponseBody -> DestinationWallet
depositResponseBodyDestination :: !DestinationWallet,
DepositResponseBody -> MoneyAmount
depositResponseBodyAmount :: !MoneyAmount,
DepositResponseBody -> MoneyAmount
depositResponseBodyFee :: !MoneyAmount,
DepositResponseBody -> Status
depositResponseBodyStatus :: !Status,
DepositResponseBody -> Maybe RiskEvaluation
depositResponseBodyRiskEvaluation :: !(Maybe RiskEvaluation),
DepositResponseBody -> UTCTime
depositResponseBodyCreateDate :: !UTCTime,
DepositResponseBody -> Maybe UTCTime
depositResponseBodyUpdateDate :: !(Maybe UTCTime)
}
deriving (DepositResponseBody -> DepositResponseBody -> Bool
(DepositResponseBody -> DepositResponseBody -> Bool)
-> (DepositResponseBody -> DepositResponseBody -> Bool)
-> Eq DepositResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DepositResponseBody -> DepositResponseBody -> Bool
$c/= :: DepositResponseBody -> DepositResponseBody -> Bool
== :: DepositResponseBody -> DepositResponseBody -> Bool
$c== :: DepositResponseBody -> DepositResponseBody -> Bool
Eq, Int -> DepositResponseBody -> ShowS
[DepositResponseBody] -> ShowS
DepositResponseBody -> String
(Int -> DepositResponseBody -> ShowS)
-> (DepositResponseBody -> String)
-> ([DepositResponseBody] -> ShowS)
-> Show DepositResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DepositResponseBody] -> ShowS
$cshowList :: [DepositResponseBody] -> ShowS
show :: DepositResponseBody -> String
$cshow :: DepositResponseBody -> String
showsPrec :: Int -> DepositResponseBody -> ShowS
$cshowsPrec :: Int -> DepositResponseBody -> ShowS
Show)
deriving
( Value -> Parser [DepositResponseBody]
Value -> Parser DepositResponseBody
(Value -> Parser DepositResponseBody)
-> (Value -> Parser [DepositResponseBody])
-> FromJSON DepositResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DepositResponseBody]
$cparseJSONList :: Value -> Parser [DepositResponseBody]
parseJSON :: Value -> Parser DepositResponseBody
$cparseJSON :: Value -> Parser DepositResponseBody
FromJSON,
[DepositResponseBody] -> Encoding
[DepositResponseBody] -> Value
DepositResponseBody -> Encoding
DepositResponseBody -> Value
(DepositResponseBody -> Value)
-> (DepositResponseBody -> Encoding)
-> ([DepositResponseBody] -> Value)
-> ([DepositResponseBody] -> Encoding)
-> ToJSON DepositResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DepositResponseBody] -> Encoding
$ctoEncodingList :: [DepositResponseBody] -> Encoding
toJSONList :: [DepositResponseBody] -> Value
$ctoJSONList :: [DepositResponseBody] -> Value
toEncoding :: DepositResponseBody -> Encoding
$ctoEncoding :: DepositResponseBody -> Encoding
toJSON :: DepositResponseBody -> Value
$ctoJSON :: DepositResponseBody -> Value
ToJSON
)
via (Autodocodec DepositResponseBody)
instance HasCodec DepositResponseBody where
codec :: JSONCodec DepositResponseBody
codec =
Text
-> ObjectCodec DepositResponseBody DepositResponseBody
-> JSONCodec DepositResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"DepositResponseBody" (ObjectCodec DepositResponseBody DepositResponseBody
-> JSONCodec DepositResponseBody)
-> ObjectCodec DepositResponseBody DepositResponseBody
-> JSONCodec DepositResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Maybe WalletId
-> DestinationWallet
-> MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody
DepositResponseBody
(UUID
-> Maybe WalletId
-> DestinationWallet
-> MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
-> Codec Object DepositResponseBody UUID
-> Codec
Object
DepositResponseBody
(Maybe WalletId
-> DestinationWallet
-> MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (DepositResponseBody -> UUID)
-> Codec Object DepositResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> UUID
depositResponseBodyId
Codec
Object
DepositResponseBody
(Maybe WalletId
-> DestinationWallet
-> MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
-> Codec Object DepositResponseBody (Maybe WalletId)
-> Codec
Object
DepositResponseBody
(DestinationWallet
-> MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe WalletId) (Maybe WalletId)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"sourceWalletId" ObjectCodec (Maybe WalletId) (Maybe WalletId)
-> (DepositResponseBody -> Maybe WalletId)
-> Codec Object DepositResponseBody (Maybe WalletId)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> Maybe WalletId
depositResponseBodySourceWalletId
Codec
Object
DepositResponseBody
(DestinationWallet
-> MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
-> Codec Object DepositResponseBody DestinationWallet
-> Codec
Object
DepositResponseBody
(MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec DestinationWallet DestinationWallet
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"destination" ObjectCodec DestinationWallet DestinationWallet
-> (DepositResponseBody -> DestinationWallet)
-> Codec Object DepositResponseBody DestinationWallet
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> DestinationWallet
depositResponseBodyDestination
Codec
Object
DepositResponseBody
(MoneyAmount
-> MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
-> Codec Object DepositResponseBody MoneyAmount
-> Codec
Object
DepositResponseBody
(MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (DepositResponseBody -> MoneyAmount)
-> Codec Object DepositResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> MoneyAmount
depositResponseBodyAmount
Codec
Object
DepositResponseBody
(MoneyAmount
-> Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
-> Codec Object DepositResponseBody MoneyAmount
-> Codec
Object
DepositResponseBody
(Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fee" ObjectCodec MoneyAmount MoneyAmount
-> (DepositResponseBody -> MoneyAmount)
-> Codec Object DepositResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> MoneyAmount
depositResponseBodyFee
Codec
Object
DepositResponseBody
(Status
-> Maybe RiskEvaluation
-> UTCTime
-> Maybe UTCTime
-> DepositResponseBody)
-> Codec Object DepositResponseBody Status
-> Codec
Object
DepositResponseBody
(Maybe RiskEvaluation
-> UTCTime -> Maybe UTCTime -> DepositResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (DepositResponseBody -> Status)
-> Codec Object DepositResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> Status
depositResponseBodyStatus
Codec
Object
DepositResponseBody
(Maybe RiskEvaluation
-> UTCTime -> Maybe UTCTime -> DepositResponseBody)
-> Codec Object DepositResponseBody (Maybe RiskEvaluation)
-> Codec
Object
DepositResponseBody
(UTCTime -> Maybe UTCTime -> DepositResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"riskEvaluation" ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
-> (DepositResponseBody -> Maybe RiskEvaluation)
-> Codec Object DepositResponseBody (Maybe RiskEvaluation)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> Maybe RiskEvaluation
depositResponseBodyRiskEvaluation
Codec
Object
DepositResponseBody
(UTCTime -> Maybe UTCTime -> DepositResponseBody)
-> Codec Object DepositResponseBody UTCTime
-> Codec
Object DepositResponseBody (Maybe UTCTime -> DepositResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (DepositResponseBody -> UTCTime)
-> Codec Object DepositResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> UTCTime
depositResponseBodyCreateDate
Codec
Object DepositResponseBody (Maybe UTCTime -> DepositResponseBody)
-> Codec Object DepositResponseBody (Maybe UTCTime)
-> ObjectCodec DepositResponseBody DepositResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
-> (DepositResponseBody -> Maybe UTCTime)
-> Codec Object DepositResponseBody (Maybe UTCTime)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DepositResponseBody -> Maybe UTCTime
depositResponseBodyUpdateDate
data MockPaymentRequest
type instance CircleRequest MockPaymentRequest = CircleResponseBody MockPaymentResponseBody
data MockPaymentResponseBody = MockPaymentResponseBody
{ MockPaymentResponseBody -> Maybe TrackingReference
mockPaymentResponseBodyTrackingRef :: !(Maybe TrackingReference),
MockPaymentResponseBody -> Maybe MoneyAmount
mockPaymentResponseBodyAmount :: !(Maybe MoneyAmount),
MockPaymentResponseBody -> Maybe BeneficiaryBankDetails
mockPaymentResponseBodyBeneficiaryBank :: !(Maybe BeneficiaryBankDetails),
MockPaymentResponseBody -> Maybe Status
mockPaymentResponseBodyStatus :: !(Maybe Status)
}
deriving (MockPaymentResponseBody -> MockPaymentResponseBody -> Bool
(MockPaymentResponseBody -> MockPaymentResponseBody -> Bool)
-> (MockPaymentResponseBody -> MockPaymentResponseBody -> Bool)
-> Eq MockPaymentResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MockPaymentResponseBody -> MockPaymentResponseBody -> Bool
$c/= :: MockPaymentResponseBody -> MockPaymentResponseBody -> Bool
== :: MockPaymentResponseBody -> MockPaymentResponseBody -> Bool
$c== :: MockPaymentResponseBody -> MockPaymentResponseBody -> Bool
Eq, Int -> MockPaymentResponseBody -> ShowS
[MockPaymentResponseBody] -> ShowS
MockPaymentResponseBody -> String
(Int -> MockPaymentResponseBody -> ShowS)
-> (MockPaymentResponseBody -> String)
-> ([MockPaymentResponseBody] -> ShowS)
-> Show MockPaymentResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MockPaymentResponseBody] -> ShowS
$cshowList :: [MockPaymentResponseBody] -> ShowS
show :: MockPaymentResponseBody -> String
$cshow :: MockPaymentResponseBody -> String
showsPrec :: Int -> MockPaymentResponseBody -> ShowS
$cshowsPrec :: Int -> MockPaymentResponseBody -> ShowS
Show)
deriving
( Value -> Parser [MockPaymentResponseBody]
Value -> Parser MockPaymentResponseBody
(Value -> Parser MockPaymentResponseBody)
-> (Value -> Parser [MockPaymentResponseBody])
-> FromJSON MockPaymentResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MockPaymentResponseBody]
$cparseJSONList :: Value -> Parser [MockPaymentResponseBody]
parseJSON :: Value -> Parser MockPaymentResponseBody
$cparseJSON :: Value -> Parser MockPaymentResponseBody
FromJSON,
[MockPaymentResponseBody] -> Encoding
[MockPaymentResponseBody] -> Value
MockPaymentResponseBody -> Encoding
MockPaymentResponseBody -> Value
(MockPaymentResponseBody -> Value)
-> (MockPaymentResponseBody -> Encoding)
-> ([MockPaymentResponseBody] -> Value)
-> ([MockPaymentResponseBody] -> Encoding)
-> ToJSON MockPaymentResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MockPaymentResponseBody] -> Encoding
$ctoEncodingList :: [MockPaymentResponseBody] -> Encoding
toJSONList :: [MockPaymentResponseBody] -> Value
$ctoJSONList :: [MockPaymentResponseBody] -> Value
toEncoding :: MockPaymentResponseBody -> Encoding
$ctoEncoding :: MockPaymentResponseBody -> Encoding
toJSON :: MockPaymentResponseBody -> Value
$ctoJSON :: MockPaymentResponseBody -> Value
ToJSON
)
via (Autodocodec MockPaymentResponseBody)
instance HasCodec MockPaymentResponseBody where
codec :: JSONCodec MockPaymentResponseBody
codec =
Text
-> ObjectCodec MockPaymentResponseBody MockPaymentResponseBody
-> JSONCodec MockPaymentResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"MockPaymentResponseBody" (ObjectCodec MockPaymentResponseBody MockPaymentResponseBody
-> JSONCodec MockPaymentResponseBody)
-> ObjectCodec MockPaymentResponseBody MockPaymentResponseBody
-> JSONCodec MockPaymentResponseBody
forall a b. (a -> b) -> a -> b
$
Maybe TrackingReference
-> Maybe MoneyAmount
-> Maybe BeneficiaryBankDetails
-> Maybe Status
-> MockPaymentResponseBody
MockPaymentResponseBody
(Maybe TrackingReference
-> Maybe MoneyAmount
-> Maybe BeneficiaryBankDetails
-> Maybe Status
-> MockPaymentResponseBody)
-> Codec Object MockPaymentResponseBody (Maybe TrackingReference)
-> Codec
Object
MockPaymentResponseBody
(Maybe MoneyAmount
-> Maybe BeneficiaryBankDetails
-> Maybe Status
-> MockPaymentResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"trackingRef" ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
-> (MockPaymentResponseBody -> Maybe TrackingReference)
-> Codec Object MockPaymentResponseBody (Maybe TrackingReference)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockPaymentResponseBody -> Maybe TrackingReference
mockPaymentResponseBodyTrackingRef
Codec
Object
MockPaymentResponseBody
(Maybe MoneyAmount
-> Maybe BeneficiaryBankDetails
-> Maybe Status
-> MockPaymentResponseBody)
-> Codec Object MockPaymentResponseBody (Maybe MoneyAmount)
-> Codec
Object
MockPaymentResponseBody
(Maybe BeneficiaryBankDetails
-> Maybe Status -> MockPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"amount" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (MockPaymentResponseBody -> Maybe MoneyAmount)
-> Codec Object MockPaymentResponseBody (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockPaymentResponseBody -> Maybe MoneyAmount
mockPaymentResponseBodyAmount
Codec
Object
MockPaymentResponseBody
(Maybe BeneficiaryBankDetails
-> Maybe Status -> MockPaymentResponseBody)
-> Codec
Object MockPaymentResponseBody (Maybe BeneficiaryBankDetails)
-> Codec
Object
MockPaymentResponseBody
(Maybe Status -> MockPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe BeneficiaryBankDetails) (Maybe BeneficiaryBankDetails)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"beneficiaryBank" ObjectCodec
(Maybe BeneficiaryBankDetails) (Maybe BeneficiaryBankDetails)
-> (MockPaymentResponseBody -> Maybe BeneficiaryBankDetails)
-> Codec
Object MockPaymentResponseBody (Maybe BeneficiaryBankDetails)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockPaymentResponseBody -> Maybe BeneficiaryBankDetails
mockPaymentResponseBodyBeneficiaryBank
Codec
Object
MockPaymentResponseBody
(Maybe Status -> MockPaymentResponseBody)
-> Codec Object MockPaymentResponseBody (Maybe Status)
-> ObjectCodec MockPaymentResponseBody MockPaymentResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Status) (Maybe Status)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"status" ObjectCodec (Maybe Status) (Maybe Status)
-> (MockPaymentResponseBody -> Maybe Status)
-> Codec Object MockPaymentResponseBody (Maybe Status)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockPaymentResponseBody -> Maybe Status
mockPaymentResponseBodyStatus
data MockSenOrWirePaymentRequestBody = MockSenOrWirePaymentRequestBody
{ MockSenOrWirePaymentRequestBody -> TrackingReference
mockSenOrWirePaymentRequestBodyTrackingRef :: !TrackingReference,
MockSenOrWirePaymentRequestBody -> MoneyAmount
mockSenOrWirePaymentRequestBodyAmount :: !MoneyAmount,
MockSenOrWirePaymentRequestBody -> MockBeneficiaryBankDetails
mockSenOrWirePaymentRequestBodyBeneficiaryBank :: !MockBeneficiaryBankDetails
}
deriving (MockSenOrWirePaymentRequestBody
-> MockSenOrWirePaymentRequestBody -> Bool
(MockSenOrWirePaymentRequestBody
-> MockSenOrWirePaymentRequestBody -> Bool)
-> (MockSenOrWirePaymentRequestBody
-> MockSenOrWirePaymentRequestBody -> Bool)
-> Eq MockSenOrWirePaymentRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MockSenOrWirePaymentRequestBody
-> MockSenOrWirePaymentRequestBody -> Bool
$c/= :: MockSenOrWirePaymentRequestBody
-> MockSenOrWirePaymentRequestBody -> Bool
== :: MockSenOrWirePaymentRequestBody
-> MockSenOrWirePaymentRequestBody -> Bool
$c== :: MockSenOrWirePaymentRequestBody
-> MockSenOrWirePaymentRequestBody -> Bool
Eq, Int -> MockSenOrWirePaymentRequestBody -> ShowS
[MockSenOrWirePaymentRequestBody] -> ShowS
MockSenOrWirePaymentRequestBody -> String
(Int -> MockSenOrWirePaymentRequestBody -> ShowS)
-> (MockSenOrWirePaymentRequestBody -> String)
-> ([MockSenOrWirePaymentRequestBody] -> ShowS)
-> Show MockSenOrWirePaymentRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MockSenOrWirePaymentRequestBody] -> ShowS
$cshowList :: [MockSenOrWirePaymentRequestBody] -> ShowS
show :: MockSenOrWirePaymentRequestBody -> String
$cshow :: MockSenOrWirePaymentRequestBody -> String
showsPrec :: Int -> MockSenOrWirePaymentRequestBody -> ShowS
$cshowsPrec :: Int -> MockSenOrWirePaymentRequestBody -> ShowS
Show)
deriving
( Value -> Parser [MockSenOrWirePaymentRequestBody]
Value -> Parser MockSenOrWirePaymentRequestBody
(Value -> Parser MockSenOrWirePaymentRequestBody)
-> (Value -> Parser [MockSenOrWirePaymentRequestBody])
-> FromJSON MockSenOrWirePaymentRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MockSenOrWirePaymentRequestBody]
$cparseJSONList :: Value -> Parser [MockSenOrWirePaymentRequestBody]
parseJSON :: Value -> Parser MockSenOrWirePaymentRequestBody
$cparseJSON :: Value -> Parser MockSenOrWirePaymentRequestBody
FromJSON,
[MockSenOrWirePaymentRequestBody] -> Encoding
[MockSenOrWirePaymentRequestBody] -> Value
MockSenOrWirePaymentRequestBody -> Encoding
MockSenOrWirePaymentRequestBody -> Value
(MockSenOrWirePaymentRequestBody -> Value)
-> (MockSenOrWirePaymentRequestBody -> Encoding)
-> ([MockSenOrWirePaymentRequestBody] -> Value)
-> ([MockSenOrWirePaymentRequestBody] -> Encoding)
-> ToJSON MockSenOrWirePaymentRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MockSenOrWirePaymentRequestBody] -> Encoding
$ctoEncodingList :: [MockSenOrWirePaymentRequestBody] -> Encoding
toJSONList :: [MockSenOrWirePaymentRequestBody] -> Value
$ctoJSONList :: [MockSenOrWirePaymentRequestBody] -> Value
toEncoding :: MockSenOrWirePaymentRequestBody -> Encoding
$ctoEncoding :: MockSenOrWirePaymentRequestBody -> Encoding
toJSON :: MockSenOrWirePaymentRequestBody -> Value
$ctoJSON :: MockSenOrWirePaymentRequestBody -> Value
ToJSON
)
via (Autodocodec MockSenOrWirePaymentRequestBody)
instance HasCodec MockSenOrWirePaymentRequestBody where
codec :: JSONCodec MockSenOrWirePaymentRequestBody
codec =
Text
-> ObjectCodec
MockSenOrWirePaymentRequestBody MockSenOrWirePaymentRequestBody
-> JSONCodec MockSenOrWirePaymentRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"MockSenOrWirePaymentRequestBody" (ObjectCodec
MockSenOrWirePaymentRequestBody MockSenOrWirePaymentRequestBody
-> JSONCodec MockSenOrWirePaymentRequestBody)
-> ObjectCodec
MockSenOrWirePaymentRequestBody MockSenOrWirePaymentRequestBody
-> JSONCodec MockSenOrWirePaymentRequestBody
forall a b. (a -> b) -> a -> b
$
TrackingReference
-> MoneyAmount
-> MockBeneficiaryBankDetails
-> MockSenOrWirePaymentRequestBody
MockSenOrWirePaymentRequestBody
(TrackingReference
-> MoneyAmount
-> MockBeneficiaryBankDetails
-> MockSenOrWirePaymentRequestBody)
-> Codec Object MockSenOrWirePaymentRequestBody TrackingReference
-> Codec
Object
MockSenOrWirePaymentRequestBody
(MoneyAmount
-> MockBeneficiaryBankDetails -> MockSenOrWirePaymentRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (MockSenOrWirePaymentRequestBody -> TrackingReference)
-> Codec Object MockSenOrWirePaymentRequestBody TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockSenOrWirePaymentRequestBody -> TrackingReference
mockSenOrWirePaymentRequestBodyTrackingRef
Codec
Object
MockSenOrWirePaymentRequestBody
(MoneyAmount
-> MockBeneficiaryBankDetails -> MockSenOrWirePaymentRequestBody)
-> Codec Object MockSenOrWirePaymentRequestBody MoneyAmount
-> Codec
Object
MockSenOrWirePaymentRequestBody
(MockBeneficiaryBankDetails -> MockSenOrWirePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (MockSenOrWirePaymentRequestBody -> MoneyAmount)
-> Codec Object MockSenOrWirePaymentRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockSenOrWirePaymentRequestBody -> MoneyAmount
mockSenOrWirePaymentRequestBodyAmount
Codec
Object
MockSenOrWirePaymentRequestBody
(MockBeneficiaryBankDetails -> MockSenOrWirePaymentRequestBody)
-> Codec
Object MockSenOrWirePaymentRequestBody MockBeneficiaryBankDetails
-> ObjectCodec
MockSenOrWirePaymentRequestBody MockSenOrWirePaymentRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
MockBeneficiaryBankDetails MockBeneficiaryBankDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"beneficiaryBank" ObjectCodec MockBeneficiaryBankDetails MockBeneficiaryBankDetails
-> (MockSenOrWirePaymentRequestBody -> MockBeneficiaryBankDetails)
-> Codec
Object MockSenOrWirePaymentRequestBody MockBeneficiaryBankDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockSenOrWirePaymentRequestBody -> MockBeneficiaryBankDetails
mockSenOrWirePaymentRequestBodyBeneficiaryBank
data MockSEPAPaymentRequestBody = MockSEPAPaymentRequestBody
{ MockSEPAPaymentRequestBody -> TrackingReference
mockSEPAPaymentRequestBodyTrackingRef :: !TrackingReference,
MockSEPAPaymentRequestBody -> MoneyAmount
mockSEPAPaymentRequestBodyAmount :: !MoneyAmount
}
deriving (MockSEPAPaymentRequestBody -> MockSEPAPaymentRequestBody -> Bool
(MockSEPAPaymentRequestBody -> MockSEPAPaymentRequestBody -> Bool)
-> (MockSEPAPaymentRequestBody
-> MockSEPAPaymentRequestBody -> Bool)
-> Eq MockSEPAPaymentRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MockSEPAPaymentRequestBody -> MockSEPAPaymentRequestBody -> Bool
$c/= :: MockSEPAPaymentRequestBody -> MockSEPAPaymentRequestBody -> Bool
== :: MockSEPAPaymentRequestBody -> MockSEPAPaymentRequestBody -> Bool
$c== :: MockSEPAPaymentRequestBody -> MockSEPAPaymentRequestBody -> Bool
Eq, Int -> MockSEPAPaymentRequestBody -> ShowS
[MockSEPAPaymentRequestBody] -> ShowS
MockSEPAPaymentRequestBody -> String
(Int -> MockSEPAPaymentRequestBody -> ShowS)
-> (MockSEPAPaymentRequestBody -> String)
-> ([MockSEPAPaymentRequestBody] -> ShowS)
-> Show MockSEPAPaymentRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MockSEPAPaymentRequestBody] -> ShowS
$cshowList :: [MockSEPAPaymentRequestBody] -> ShowS
show :: MockSEPAPaymentRequestBody -> String
$cshow :: MockSEPAPaymentRequestBody -> String
showsPrec :: Int -> MockSEPAPaymentRequestBody -> ShowS
$cshowsPrec :: Int -> MockSEPAPaymentRequestBody -> ShowS
Show)
deriving
( Value -> Parser [MockSEPAPaymentRequestBody]
Value -> Parser MockSEPAPaymentRequestBody
(Value -> Parser MockSEPAPaymentRequestBody)
-> (Value -> Parser [MockSEPAPaymentRequestBody])
-> FromJSON MockSEPAPaymentRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MockSEPAPaymentRequestBody]
$cparseJSONList :: Value -> Parser [MockSEPAPaymentRequestBody]
parseJSON :: Value -> Parser MockSEPAPaymentRequestBody
$cparseJSON :: Value -> Parser MockSEPAPaymentRequestBody
FromJSON,
[MockSEPAPaymentRequestBody] -> Encoding
[MockSEPAPaymentRequestBody] -> Value
MockSEPAPaymentRequestBody -> Encoding
MockSEPAPaymentRequestBody -> Value
(MockSEPAPaymentRequestBody -> Value)
-> (MockSEPAPaymentRequestBody -> Encoding)
-> ([MockSEPAPaymentRequestBody] -> Value)
-> ([MockSEPAPaymentRequestBody] -> Encoding)
-> ToJSON MockSEPAPaymentRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MockSEPAPaymentRequestBody] -> Encoding
$ctoEncodingList :: [MockSEPAPaymentRequestBody] -> Encoding
toJSONList :: [MockSEPAPaymentRequestBody] -> Value
$ctoJSONList :: [MockSEPAPaymentRequestBody] -> Value
toEncoding :: MockSEPAPaymentRequestBody -> Encoding
$ctoEncoding :: MockSEPAPaymentRequestBody -> Encoding
toJSON :: MockSEPAPaymentRequestBody -> Value
$ctoJSON :: MockSEPAPaymentRequestBody -> Value
ToJSON
)
via (Autodocodec MockSEPAPaymentRequestBody)
instance HasCodec MockSEPAPaymentRequestBody where
codec :: JSONCodec MockSEPAPaymentRequestBody
codec =
Text
-> ObjectCodec
MockSEPAPaymentRequestBody MockSEPAPaymentRequestBody
-> JSONCodec MockSEPAPaymentRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"MockSEPAPaymentRequestBody" (ObjectCodec MockSEPAPaymentRequestBody MockSEPAPaymentRequestBody
-> JSONCodec MockSEPAPaymentRequestBody)
-> ObjectCodec
MockSEPAPaymentRequestBody MockSEPAPaymentRequestBody
-> JSONCodec MockSEPAPaymentRequestBody
forall a b. (a -> b) -> a -> b
$
TrackingReference -> MoneyAmount -> MockSEPAPaymentRequestBody
MockSEPAPaymentRequestBody
(TrackingReference -> MoneyAmount -> MockSEPAPaymentRequestBody)
-> Codec Object MockSEPAPaymentRequestBody TrackingReference
-> Codec
Object
MockSEPAPaymentRequestBody
(MoneyAmount -> MockSEPAPaymentRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (MockSEPAPaymentRequestBody -> TrackingReference)
-> Codec Object MockSEPAPaymentRequestBody TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockSEPAPaymentRequestBody -> TrackingReference
mockSEPAPaymentRequestBodyTrackingRef
Codec
Object
MockSEPAPaymentRequestBody
(MoneyAmount -> MockSEPAPaymentRequestBody)
-> Codec Object MockSEPAPaymentRequestBody MoneyAmount
-> ObjectCodec
MockSEPAPaymentRequestBody MockSEPAPaymentRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (MockSEPAPaymentRequestBody -> MoneyAmount)
-> Codec Object MockSEPAPaymentRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockSEPAPaymentRequestBody -> MoneyAmount
mockSEPAPaymentRequestBodyAmount
newtype MockBeneficiaryBankDetails = MockBeneficiaryBankDetails {MockBeneficiaryBankDetails -> AccountNumber
mockBeneficiaryBankDetailsAccountNumber :: AccountNumber}
deriving (MockBeneficiaryBankDetails -> MockBeneficiaryBankDetails -> Bool
(MockBeneficiaryBankDetails -> MockBeneficiaryBankDetails -> Bool)
-> (MockBeneficiaryBankDetails
-> MockBeneficiaryBankDetails -> Bool)
-> Eq MockBeneficiaryBankDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MockBeneficiaryBankDetails -> MockBeneficiaryBankDetails -> Bool
$c/= :: MockBeneficiaryBankDetails -> MockBeneficiaryBankDetails -> Bool
== :: MockBeneficiaryBankDetails -> MockBeneficiaryBankDetails -> Bool
$c== :: MockBeneficiaryBankDetails -> MockBeneficiaryBankDetails -> Bool
Eq, Int -> MockBeneficiaryBankDetails -> ShowS
[MockBeneficiaryBankDetails] -> ShowS
MockBeneficiaryBankDetails -> String
(Int -> MockBeneficiaryBankDetails -> ShowS)
-> (MockBeneficiaryBankDetails -> String)
-> ([MockBeneficiaryBankDetails] -> ShowS)
-> Show MockBeneficiaryBankDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MockBeneficiaryBankDetails] -> ShowS
$cshowList :: [MockBeneficiaryBankDetails] -> ShowS
show :: MockBeneficiaryBankDetails -> String
$cshow :: MockBeneficiaryBankDetails -> String
showsPrec :: Int -> MockBeneficiaryBankDetails -> ShowS
$cshowsPrec :: Int -> MockBeneficiaryBankDetails -> ShowS
Show, [MockBeneficiaryBankDetails] -> Encoding
[MockBeneficiaryBankDetails] -> Value
MockBeneficiaryBankDetails -> Encoding
MockBeneficiaryBankDetails -> Value
(MockBeneficiaryBankDetails -> Value)
-> (MockBeneficiaryBankDetails -> Encoding)
-> ([MockBeneficiaryBankDetails] -> Value)
-> ([MockBeneficiaryBankDetails] -> Encoding)
-> ToJSON MockBeneficiaryBankDetails
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MockBeneficiaryBankDetails] -> Encoding
$ctoEncodingList :: [MockBeneficiaryBankDetails] -> Encoding
toJSONList :: [MockBeneficiaryBankDetails] -> Value
$ctoJSONList :: [MockBeneficiaryBankDetails] -> Value
toEncoding :: MockBeneficiaryBankDetails -> Encoding
$ctoEncoding :: MockBeneficiaryBankDetails -> Encoding
toJSON :: MockBeneficiaryBankDetails -> Value
$ctoJSON :: MockBeneficiaryBankDetails -> Value
ToJSON, Value -> Parser [MockBeneficiaryBankDetails]
Value -> Parser MockBeneficiaryBankDetails
(Value -> Parser MockBeneficiaryBankDetails)
-> (Value -> Parser [MockBeneficiaryBankDetails])
-> FromJSON MockBeneficiaryBankDetails
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MockBeneficiaryBankDetails]
$cparseJSONList :: Value -> Parser [MockBeneficiaryBankDetails]
parseJSON :: Value -> Parser MockBeneficiaryBankDetails
$cparseJSON :: Value -> Parser MockBeneficiaryBankDetails
FromJSON)
instance HasCodec MockBeneficiaryBankDetails where
codec :: JSONCodec MockBeneficiaryBankDetails
codec = (AccountNumber -> MockBeneficiaryBankDetails)
-> (MockBeneficiaryBankDetails -> AccountNumber)
-> Codec Value AccountNumber AccountNumber
-> JSONCodec MockBeneficiaryBankDetails
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec AccountNumber -> MockBeneficiaryBankDetails
MockBeneficiaryBankDetails MockBeneficiaryBankDetails -> AccountNumber
mockBeneficiaryBankDetailsAccountNumber Codec Value AccountNumber AccountNumber
forall value. HasCodec value => JSONCodec value
codec
data SENAccountRequest
type instance CircleRequest SENAccountRequest = CircleResponseBody SENAccountResponseBody
data SENAccountsRequest
type instance CircleRequest SENAccountsRequest = CircleResponseBody [SENAccountResponseBody]
data SENInstructionsRequest
type instance CircleRequest SENInstructionsRequest = CircleResponseBody SENInstructionsResponseData
data SENAccountRequestBody = SENAccountRequestBody
{ SENAccountRequestBody -> UUID
senAccountRequestBodyIdempotencyKey :: !UUID,
SENAccountRequestBody -> AccountNumber
senAccountRequestBodyAccountNumber :: !AccountNumber,
SENAccountRequestBody -> Maybe SupportedCurrencies
senAccountRequestBodyCurrency :: !(Maybe SupportedCurrencies)
}
deriving (SENAccountRequestBody -> SENAccountRequestBody -> Bool
(SENAccountRequestBody -> SENAccountRequestBody -> Bool)
-> (SENAccountRequestBody -> SENAccountRequestBody -> Bool)
-> Eq SENAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SENAccountRequestBody -> SENAccountRequestBody -> Bool
$c/= :: SENAccountRequestBody -> SENAccountRequestBody -> Bool
== :: SENAccountRequestBody -> SENAccountRequestBody -> Bool
$c== :: SENAccountRequestBody -> SENAccountRequestBody -> Bool
Eq, Int -> SENAccountRequestBody -> ShowS
[SENAccountRequestBody] -> ShowS
SENAccountRequestBody -> String
(Int -> SENAccountRequestBody -> ShowS)
-> (SENAccountRequestBody -> String)
-> ([SENAccountRequestBody] -> ShowS)
-> Show SENAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SENAccountRequestBody] -> ShowS
$cshowList :: [SENAccountRequestBody] -> ShowS
show :: SENAccountRequestBody -> String
$cshow :: SENAccountRequestBody -> String
showsPrec :: Int -> SENAccountRequestBody -> ShowS
$cshowsPrec :: Int -> SENAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [SENAccountRequestBody]
Value -> Parser SENAccountRequestBody
(Value -> Parser SENAccountRequestBody)
-> (Value -> Parser [SENAccountRequestBody])
-> FromJSON SENAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SENAccountRequestBody]
$cparseJSONList :: Value -> Parser [SENAccountRequestBody]
parseJSON :: Value -> Parser SENAccountRequestBody
$cparseJSON :: Value -> Parser SENAccountRequestBody
FromJSON,
[SENAccountRequestBody] -> Encoding
[SENAccountRequestBody] -> Value
SENAccountRequestBody -> Encoding
SENAccountRequestBody -> Value
(SENAccountRequestBody -> Value)
-> (SENAccountRequestBody -> Encoding)
-> ([SENAccountRequestBody] -> Value)
-> ([SENAccountRequestBody] -> Encoding)
-> ToJSON SENAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SENAccountRequestBody] -> Encoding
$ctoEncodingList :: [SENAccountRequestBody] -> Encoding
toJSONList :: [SENAccountRequestBody] -> Value
$ctoJSONList :: [SENAccountRequestBody] -> Value
toEncoding :: SENAccountRequestBody -> Encoding
$ctoEncoding :: SENAccountRequestBody -> Encoding
toJSON :: SENAccountRequestBody -> Value
$ctoJSON :: SENAccountRequestBody -> Value
ToJSON
)
via (Autodocodec SENAccountRequestBody)
instance HasCodec SENAccountRequestBody where
codec :: JSONCodec SENAccountRequestBody
codec =
Text
-> ObjectCodec SENAccountRequestBody SENAccountRequestBody
-> JSONCodec SENAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SENAccountRequestBody" (ObjectCodec SENAccountRequestBody SENAccountRequestBody
-> JSONCodec SENAccountRequestBody)
-> ObjectCodec SENAccountRequestBody SENAccountRequestBody
-> JSONCodec SENAccountRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> AccountNumber
-> Maybe SupportedCurrencies
-> SENAccountRequestBody
SENAccountRequestBody
(UUID
-> AccountNumber
-> Maybe SupportedCurrencies
-> SENAccountRequestBody)
-> Codec Object SENAccountRequestBody UUID
-> Codec
Object
SENAccountRequestBody
(AccountNumber
-> Maybe SupportedCurrencies -> SENAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (SENAccountRequestBody -> UUID)
-> Codec Object SENAccountRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountRequestBody -> UUID
senAccountRequestBodyIdempotencyKey
Codec
Object
SENAccountRequestBody
(AccountNumber
-> Maybe SupportedCurrencies -> SENAccountRequestBody)
-> Codec Object SENAccountRequestBody AccountNumber
-> Codec
Object
SENAccountRequestBody
(Maybe SupportedCurrencies -> SENAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AccountNumber AccountNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"accountNumber" ObjectCodec AccountNumber AccountNumber
-> (SENAccountRequestBody -> AccountNumber)
-> Codec Object SENAccountRequestBody AccountNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountRequestBody -> AccountNumber
senAccountRequestBodyAccountNumber
Codec
Object
SENAccountRequestBody
(Maybe SupportedCurrencies -> SENAccountRequestBody)
-> Codec Object SENAccountRequestBody (Maybe SupportedCurrencies)
-> ObjectCodec SENAccountRequestBody SENAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe SupportedCurrencies) (Maybe SupportedCurrencies)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"currency" ObjectCodec (Maybe SupportedCurrencies) (Maybe SupportedCurrencies)
-> (SENAccountRequestBody -> Maybe SupportedCurrencies)
-> Codec Object SENAccountRequestBody (Maybe SupportedCurrencies)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountRequestBody -> Maybe SupportedCurrencies
senAccountRequestBodyCurrency
data SENAccountResponseBody = SENAccountResponseBody
{ SENAccountResponseBody -> UUID
senAccountResponseBodyId :: !UUID,
SENAccountResponseBody -> Status
senAccountResponseBodyStatus :: !Status,
SENAccountResponseBody -> Text
senAccountResponseBodyDescription :: !Text,
SENAccountResponseBody -> TrackingReference
senAccountResponseBodyTrackingRef :: !TrackingReference,
SENAccountResponseBody -> UTCTime
senAccountResponseBodyCreateDate :: !UTCTime,
SENAccountResponseBody -> UTCTime
senAccountResponseBodyUpdateDate :: !UTCTime,
SENAccountResponseBody -> Maybe SupportedCurrencies
senAccountResponseBodyCurrency :: !(Maybe SupportedCurrencies)
}
deriving (SENAccountResponseBody -> SENAccountResponseBody -> Bool
(SENAccountResponseBody -> SENAccountResponseBody -> Bool)
-> (SENAccountResponseBody -> SENAccountResponseBody -> Bool)
-> Eq SENAccountResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SENAccountResponseBody -> SENAccountResponseBody -> Bool
$c/= :: SENAccountResponseBody -> SENAccountResponseBody -> Bool
== :: SENAccountResponseBody -> SENAccountResponseBody -> Bool
$c== :: SENAccountResponseBody -> SENAccountResponseBody -> Bool
Eq, Int -> SENAccountResponseBody -> ShowS
[SENAccountResponseBody] -> ShowS
SENAccountResponseBody -> String
(Int -> SENAccountResponseBody -> ShowS)
-> (SENAccountResponseBody -> String)
-> ([SENAccountResponseBody] -> ShowS)
-> Show SENAccountResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SENAccountResponseBody] -> ShowS
$cshowList :: [SENAccountResponseBody] -> ShowS
show :: SENAccountResponseBody -> String
$cshow :: SENAccountResponseBody -> String
showsPrec :: Int -> SENAccountResponseBody -> ShowS
$cshowsPrec :: Int -> SENAccountResponseBody -> ShowS
Show)
deriving
( Value -> Parser [SENAccountResponseBody]
Value -> Parser SENAccountResponseBody
(Value -> Parser SENAccountResponseBody)
-> (Value -> Parser [SENAccountResponseBody])
-> FromJSON SENAccountResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SENAccountResponseBody]
$cparseJSONList :: Value -> Parser [SENAccountResponseBody]
parseJSON :: Value -> Parser SENAccountResponseBody
$cparseJSON :: Value -> Parser SENAccountResponseBody
FromJSON,
[SENAccountResponseBody] -> Encoding
[SENAccountResponseBody] -> Value
SENAccountResponseBody -> Encoding
SENAccountResponseBody -> Value
(SENAccountResponseBody -> Value)
-> (SENAccountResponseBody -> Encoding)
-> ([SENAccountResponseBody] -> Value)
-> ([SENAccountResponseBody] -> Encoding)
-> ToJSON SENAccountResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SENAccountResponseBody] -> Encoding
$ctoEncodingList :: [SENAccountResponseBody] -> Encoding
toJSONList :: [SENAccountResponseBody] -> Value
$ctoJSONList :: [SENAccountResponseBody] -> Value
toEncoding :: SENAccountResponseBody -> Encoding
$ctoEncoding :: SENAccountResponseBody -> Encoding
toJSON :: SENAccountResponseBody -> Value
$ctoJSON :: SENAccountResponseBody -> Value
ToJSON
)
via (Autodocodec SENAccountResponseBody)
instance HasCodec SENAccountResponseBody where
codec :: JSONCodec SENAccountResponseBody
codec =
Text
-> ObjectCodec SENAccountResponseBody SENAccountResponseBody
-> JSONCodec SENAccountResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SENAccountResponseBody" (ObjectCodec SENAccountResponseBody SENAccountResponseBody
-> JSONCodec SENAccountResponseBody)
-> ObjectCodec SENAccountResponseBody SENAccountResponseBody
-> JSONCodec SENAccountResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Status
-> Text
-> TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody
SENAccountResponseBody
(UUID
-> Status
-> Text
-> TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody)
-> Codec Object SENAccountResponseBody UUID
-> Codec
Object
SENAccountResponseBody
(Status
-> Text
-> TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (SENAccountResponseBody -> UUID)
-> Codec Object SENAccountResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountResponseBody -> UUID
senAccountResponseBodyId
Codec
Object
SENAccountResponseBody
(Status
-> Text
-> TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody)
-> Codec Object SENAccountResponseBody Status
-> Codec
Object
SENAccountResponseBody
(Text
-> TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (SENAccountResponseBody -> Status)
-> Codec Object SENAccountResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountResponseBody -> Status
senAccountResponseBodyStatus
Codec
Object
SENAccountResponseBody
(Text
-> TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody)
-> Codec Object SENAccountResponseBody Text
-> Codec
Object
SENAccountResponseBody
(TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (SENAccountResponseBody -> Text)
-> Codec Object SENAccountResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountResponseBody -> Text
senAccountResponseBodyDescription
Codec
Object
SENAccountResponseBody
(TrackingReference
-> UTCTime
-> UTCTime
-> Maybe SupportedCurrencies
-> SENAccountResponseBody)
-> Codec Object SENAccountResponseBody TrackingReference
-> Codec
Object
SENAccountResponseBody
(UTCTime
-> UTCTime -> Maybe SupportedCurrencies -> SENAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (SENAccountResponseBody -> TrackingReference)
-> Codec Object SENAccountResponseBody TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountResponseBody -> TrackingReference
senAccountResponseBodyTrackingRef
Codec
Object
SENAccountResponseBody
(UTCTime
-> UTCTime -> Maybe SupportedCurrencies -> SENAccountResponseBody)
-> Codec Object SENAccountResponseBody UTCTime
-> Codec
Object
SENAccountResponseBody
(UTCTime -> Maybe SupportedCurrencies -> SENAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (SENAccountResponseBody -> UTCTime)
-> Codec Object SENAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountResponseBody -> UTCTime
senAccountResponseBodyCreateDate
Codec
Object
SENAccountResponseBody
(UTCTime -> Maybe SupportedCurrencies -> SENAccountResponseBody)
-> Codec Object SENAccountResponseBody UTCTime
-> Codec
Object
SENAccountResponseBody
(Maybe SupportedCurrencies -> SENAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (SENAccountResponseBody -> UTCTime)
-> Codec Object SENAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountResponseBody -> UTCTime
senAccountResponseBodyUpdateDate
Codec
Object
SENAccountResponseBody
(Maybe SupportedCurrencies -> SENAccountResponseBody)
-> Codec Object SENAccountResponseBody (Maybe SupportedCurrencies)
-> ObjectCodec SENAccountResponseBody SENAccountResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe SupportedCurrencies) (Maybe SupportedCurrencies)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"currency" ObjectCodec (Maybe SupportedCurrencies) (Maybe SupportedCurrencies)
-> (SENAccountResponseBody -> Maybe SupportedCurrencies)
-> Codec Object SENAccountResponseBody (Maybe SupportedCurrencies)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENAccountResponseBody -> Maybe SupportedCurrencies
senAccountResponseBodyCurrency
data SENInstructionsResponseData = SENInstructionsResponseData
{ SENInstructionsResponseData -> TrackingReference
senInstructionsResponseDataTrackingRef :: !TrackingReference,
SENInstructionsResponseData -> AccountNumber
senInstructionsResponseDataAccountNumber :: !AccountNumber,
SENInstructionsResponseData -> SupportedCurrencies
senInstructionsResponseDataCurrency :: !SupportedCurrencies
}
deriving stock (SENInstructionsResponseData -> SENInstructionsResponseData -> Bool
(SENInstructionsResponseData
-> SENInstructionsResponseData -> Bool)
-> (SENInstructionsResponseData
-> SENInstructionsResponseData -> Bool)
-> Eq SENInstructionsResponseData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SENInstructionsResponseData -> SENInstructionsResponseData -> Bool
$c/= :: SENInstructionsResponseData -> SENInstructionsResponseData -> Bool
== :: SENInstructionsResponseData -> SENInstructionsResponseData -> Bool
$c== :: SENInstructionsResponseData -> SENInstructionsResponseData -> Bool
Eq, Int -> SENInstructionsResponseData -> ShowS
[SENInstructionsResponseData] -> ShowS
SENInstructionsResponseData -> String
(Int -> SENInstructionsResponseData -> ShowS)
-> (SENInstructionsResponseData -> String)
-> ([SENInstructionsResponseData] -> ShowS)
-> Show SENInstructionsResponseData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SENInstructionsResponseData] -> ShowS
$cshowList :: [SENInstructionsResponseData] -> ShowS
show :: SENInstructionsResponseData -> String
$cshow :: SENInstructionsResponseData -> String
showsPrec :: Int -> SENInstructionsResponseData -> ShowS
$cshowsPrec :: Int -> SENInstructionsResponseData -> ShowS
Show, (forall x.
SENInstructionsResponseData -> Rep SENInstructionsResponseData x)
-> (forall x.
Rep SENInstructionsResponseData x -> SENInstructionsResponseData)
-> Generic SENInstructionsResponseData
forall x.
Rep SENInstructionsResponseData x -> SENInstructionsResponseData
forall x.
SENInstructionsResponseData -> Rep SENInstructionsResponseData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SENInstructionsResponseData x -> SENInstructionsResponseData
$cfrom :: forall x.
SENInstructionsResponseData -> Rep SENInstructionsResponseData x
Generic)
deriving
( Value -> Parser [SENInstructionsResponseData]
Value -> Parser SENInstructionsResponseData
(Value -> Parser SENInstructionsResponseData)
-> (Value -> Parser [SENInstructionsResponseData])
-> FromJSON SENInstructionsResponseData
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SENInstructionsResponseData]
$cparseJSONList :: Value -> Parser [SENInstructionsResponseData]
parseJSON :: Value -> Parser SENInstructionsResponseData
$cparseJSON :: Value -> Parser SENInstructionsResponseData
FromJSON,
[SENInstructionsResponseData] -> Encoding
[SENInstructionsResponseData] -> Value
SENInstructionsResponseData -> Encoding
SENInstructionsResponseData -> Value
(SENInstructionsResponseData -> Value)
-> (SENInstructionsResponseData -> Encoding)
-> ([SENInstructionsResponseData] -> Value)
-> ([SENInstructionsResponseData] -> Encoding)
-> ToJSON SENInstructionsResponseData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SENInstructionsResponseData] -> Encoding
$ctoEncodingList :: [SENInstructionsResponseData] -> Encoding
toJSONList :: [SENInstructionsResponseData] -> Value
$ctoJSONList :: [SENInstructionsResponseData] -> Value
toEncoding :: SENInstructionsResponseData -> Encoding
$ctoEncoding :: SENInstructionsResponseData -> Encoding
toJSON :: SENInstructionsResponseData -> Value
$ctoJSON :: SENInstructionsResponseData -> Value
ToJSON
)
via (Autodocodec SENInstructionsResponseData)
instance HasCodec SENInstructionsResponseData where
codec :: JSONCodec SENInstructionsResponseData
codec =
Text
-> ObjectCodec
SENInstructionsResponseData SENInstructionsResponseData
-> JSONCodec SENInstructionsResponseData
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SENInstructionsResponseData" (ObjectCodec
SENInstructionsResponseData SENInstructionsResponseData
-> JSONCodec SENInstructionsResponseData)
-> ObjectCodec
SENInstructionsResponseData SENInstructionsResponseData
-> JSONCodec SENInstructionsResponseData
forall a b. (a -> b) -> a -> b
$
TrackingReference
-> AccountNumber
-> SupportedCurrencies
-> SENInstructionsResponseData
SENInstructionsResponseData
(TrackingReference
-> AccountNumber
-> SupportedCurrencies
-> SENInstructionsResponseData)
-> Codec Object SENInstructionsResponseData TrackingReference
-> Codec
Object
SENInstructionsResponseData
(AccountNumber
-> SupportedCurrencies -> SENInstructionsResponseData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (SENInstructionsResponseData -> TrackingReference)
-> Codec Object SENInstructionsResponseData TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENInstructionsResponseData -> TrackingReference
senInstructionsResponseDataTrackingRef
Codec
Object
SENInstructionsResponseData
(AccountNumber
-> SupportedCurrencies -> SENInstructionsResponseData)
-> Codec Object SENInstructionsResponseData AccountNumber
-> Codec
Object
SENInstructionsResponseData
(SupportedCurrencies -> SENInstructionsResponseData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AccountNumber AccountNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"accountNumber" ObjectCodec AccountNumber AccountNumber
-> (SENInstructionsResponseData -> AccountNumber)
-> Codec Object SENInstructionsResponseData AccountNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENInstructionsResponseData -> AccountNumber
senInstructionsResponseDataAccountNumber
Codec
Object
SENInstructionsResponseData
(SupportedCurrencies -> SENInstructionsResponseData)
-> Codec Object SENInstructionsResponseData SupportedCurrencies
-> ObjectCodec
SENInstructionsResponseData SENInstructionsResponseData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (SENInstructionsResponseData -> SupportedCurrencies)
-> Codec Object SENInstructionsResponseData SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SENInstructionsResponseData -> SupportedCurrencies
senInstructionsResponseDataCurrency
data SignetBankAccountRequest
type instance CircleRequest SignetBankAccountRequest = CircleResponseBody SignetBankAccountResponseData
data SignetBankAccountsRequest
type instance CircleRequest SignetBankAccountsRequest = CircleResponseBody [SignetBankAccountResponseData]
data SignetBankInstructionsRequest
type instance CircleRequest SignetBankInstructionsRequest = CircleResponseBody SignetBankInstructionsResponseData
data SignetBankAccountRequestBody = SignetBankAccountRequestBody
{ SignetBankAccountRequestBody -> UUID
signetBankAccountRequestBodyIdempotencyKey :: !UUID,
SignetBankAccountRequestBody -> HexString
signetBankAccountRequestBodyWalletAddress :: !HexString
}
deriving (SignetBankAccountRequestBody
-> SignetBankAccountRequestBody -> Bool
(SignetBankAccountRequestBody
-> SignetBankAccountRequestBody -> Bool)
-> (SignetBankAccountRequestBody
-> SignetBankAccountRequestBody -> Bool)
-> Eq SignetBankAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignetBankAccountRequestBody
-> SignetBankAccountRequestBody -> Bool
$c/= :: SignetBankAccountRequestBody
-> SignetBankAccountRequestBody -> Bool
== :: SignetBankAccountRequestBody
-> SignetBankAccountRequestBody -> Bool
$c== :: SignetBankAccountRequestBody
-> SignetBankAccountRequestBody -> Bool
Eq, Int -> SignetBankAccountRequestBody -> ShowS
[SignetBankAccountRequestBody] -> ShowS
SignetBankAccountRequestBody -> String
(Int -> SignetBankAccountRequestBody -> ShowS)
-> (SignetBankAccountRequestBody -> String)
-> ([SignetBankAccountRequestBody] -> ShowS)
-> Show SignetBankAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignetBankAccountRequestBody] -> ShowS
$cshowList :: [SignetBankAccountRequestBody] -> ShowS
show :: SignetBankAccountRequestBody -> String
$cshow :: SignetBankAccountRequestBody -> String
showsPrec :: Int -> SignetBankAccountRequestBody -> ShowS
$cshowsPrec :: Int -> SignetBankAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [SignetBankAccountRequestBody]
Value -> Parser SignetBankAccountRequestBody
(Value -> Parser SignetBankAccountRequestBody)
-> (Value -> Parser [SignetBankAccountRequestBody])
-> FromJSON SignetBankAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SignetBankAccountRequestBody]
$cparseJSONList :: Value -> Parser [SignetBankAccountRequestBody]
parseJSON :: Value -> Parser SignetBankAccountRequestBody
$cparseJSON :: Value -> Parser SignetBankAccountRequestBody
FromJSON,
[SignetBankAccountRequestBody] -> Encoding
[SignetBankAccountRequestBody] -> Value
SignetBankAccountRequestBody -> Encoding
SignetBankAccountRequestBody -> Value
(SignetBankAccountRequestBody -> Value)
-> (SignetBankAccountRequestBody -> Encoding)
-> ([SignetBankAccountRequestBody] -> Value)
-> ([SignetBankAccountRequestBody] -> Encoding)
-> ToJSON SignetBankAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SignetBankAccountRequestBody] -> Encoding
$ctoEncodingList :: [SignetBankAccountRequestBody] -> Encoding
toJSONList :: [SignetBankAccountRequestBody] -> Value
$ctoJSONList :: [SignetBankAccountRequestBody] -> Value
toEncoding :: SignetBankAccountRequestBody -> Encoding
$ctoEncoding :: SignetBankAccountRequestBody -> Encoding
toJSON :: SignetBankAccountRequestBody -> Value
$ctoJSON :: SignetBankAccountRequestBody -> Value
ToJSON
)
via (Autodocodec SignetBankAccountRequestBody)
instance HasCodec SignetBankAccountRequestBody where
codec :: JSONCodec SignetBankAccountRequestBody
codec =
Text
-> ObjectCodec
SignetBankAccountRequestBody SignetBankAccountRequestBody
-> JSONCodec SignetBankAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SignetBankAccountRequestBody" (ObjectCodec
SignetBankAccountRequestBody SignetBankAccountRequestBody
-> JSONCodec SignetBankAccountRequestBody)
-> ObjectCodec
SignetBankAccountRequestBody SignetBankAccountRequestBody
-> JSONCodec SignetBankAccountRequestBody
forall a b. (a -> b) -> a -> b
$
UUID -> HexString -> SignetBankAccountRequestBody
SignetBankAccountRequestBody
(UUID -> HexString -> SignetBankAccountRequestBody)
-> Codec Object SignetBankAccountRequestBody UUID
-> Codec
Object
SignetBankAccountRequestBody
(HexString -> SignetBankAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (SignetBankAccountRequestBody -> UUID)
-> Codec Object SignetBankAccountRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountRequestBody -> UUID
signetBankAccountRequestBodyIdempotencyKey
Codec
Object
SignetBankAccountRequestBody
(HexString -> SignetBankAccountRequestBody)
-> Codec Object SignetBankAccountRequestBody HexString
-> ObjectCodec
SignetBankAccountRequestBody SignetBankAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec HexString HexString
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"walletAddress" ObjectCodec HexString HexString
-> (SignetBankAccountRequestBody -> HexString)
-> Codec Object SignetBankAccountRequestBody HexString
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountRequestBody -> HexString
signetBankAccountRequestBodyWalletAddress
data SignetBankAccountResponseData = SignetBankAccountResponseData
{ SignetBankAccountResponseData -> UUID
signetBankAccountId :: !UUID,
SignetBankAccountResponseData -> Status
signetBankAccountStatus :: !Status,
SignetBankAccountResponseData -> TrackingReference
signetBankAccountTrackingRef :: !TrackingReference,
SignetBankAccountResponseData -> HexString
signetBankAccountWalletAddress :: !HexString,
SignetBankAccountResponseData -> UTCTime
signetBankAccountCreateDate :: !UTCTime,
SignetBankAccountResponseData -> UTCTime
signetBankAccountUpdateDate :: !UTCTime
}
deriving (SignetBankAccountResponseData
-> SignetBankAccountResponseData -> Bool
(SignetBankAccountResponseData
-> SignetBankAccountResponseData -> Bool)
-> (SignetBankAccountResponseData
-> SignetBankAccountResponseData -> Bool)
-> Eq SignetBankAccountResponseData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignetBankAccountResponseData
-> SignetBankAccountResponseData -> Bool
$c/= :: SignetBankAccountResponseData
-> SignetBankAccountResponseData -> Bool
== :: SignetBankAccountResponseData
-> SignetBankAccountResponseData -> Bool
$c== :: SignetBankAccountResponseData
-> SignetBankAccountResponseData -> Bool
Eq, Int -> SignetBankAccountResponseData -> ShowS
[SignetBankAccountResponseData] -> ShowS
SignetBankAccountResponseData -> String
(Int -> SignetBankAccountResponseData -> ShowS)
-> (SignetBankAccountResponseData -> String)
-> ([SignetBankAccountResponseData] -> ShowS)
-> Show SignetBankAccountResponseData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignetBankAccountResponseData] -> ShowS
$cshowList :: [SignetBankAccountResponseData] -> ShowS
show :: SignetBankAccountResponseData -> String
$cshow :: SignetBankAccountResponseData -> String
showsPrec :: Int -> SignetBankAccountResponseData -> ShowS
$cshowsPrec :: Int -> SignetBankAccountResponseData -> ShowS
Show)
deriving
( Value -> Parser [SignetBankAccountResponseData]
Value -> Parser SignetBankAccountResponseData
(Value -> Parser SignetBankAccountResponseData)
-> (Value -> Parser [SignetBankAccountResponseData])
-> FromJSON SignetBankAccountResponseData
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SignetBankAccountResponseData]
$cparseJSONList :: Value -> Parser [SignetBankAccountResponseData]
parseJSON :: Value -> Parser SignetBankAccountResponseData
$cparseJSON :: Value -> Parser SignetBankAccountResponseData
FromJSON,
[SignetBankAccountResponseData] -> Encoding
[SignetBankAccountResponseData] -> Value
SignetBankAccountResponseData -> Encoding
SignetBankAccountResponseData -> Value
(SignetBankAccountResponseData -> Value)
-> (SignetBankAccountResponseData -> Encoding)
-> ([SignetBankAccountResponseData] -> Value)
-> ([SignetBankAccountResponseData] -> Encoding)
-> ToJSON SignetBankAccountResponseData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SignetBankAccountResponseData] -> Encoding
$ctoEncodingList :: [SignetBankAccountResponseData] -> Encoding
toJSONList :: [SignetBankAccountResponseData] -> Value
$ctoJSONList :: [SignetBankAccountResponseData] -> Value
toEncoding :: SignetBankAccountResponseData -> Encoding
$ctoEncoding :: SignetBankAccountResponseData -> Encoding
toJSON :: SignetBankAccountResponseData -> Value
$ctoJSON :: SignetBankAccountResponseData -> Value
ToJSON
)
via (Autodocodec SignetBankAccountResponseData)
instance HasCodec SignetBankAccountResponseData where
codec :: JSONCodec SignetBankAccountResponseData
codec =
Text
-> ObjectCodec
SignetBankAccountResponseData SignetBankAccountResponseData
-> JSONCodec SignetBankAccountResponseData
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SignetBankAccountResponseData" (ObjectCodec
SignetBankAccountResponseData SignetBankAccountResponseData
-> JSONCodec SignetBankAccountResponseData)
-> ObjectCodec
SignetBankAccountResponseData SignetBankAccountResponseData
-> JSONCodec SignetBankAccountResponseData
forall a b. (a -> b) -> a -> b
$
UUID
-> Status
-> TrackingReference
-> HexString
-> UTCTime
-> UTCTime
-> SignetBankAccountResponseData
SignetBankAccountResponseData
(UUID
-> Status
-> TrackingReference
-> HexString
-> UTCTime
-> UTCTime
-> SignetBankAccountResponseData)
-> Codec Object SignetBankAccountResponseData UUID
-> Codec
Object
SignetBankAccountResponseData
(Status
-> TrackingReference
-> HexString
-> UTCTime
-> UTCTime
-> SignetBankAccountResponseData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (SignetBankAccountResponseData -> UUID)
-> Codec Object SignetBankAccountResponseData UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountResponseData -> UUID
signetBankAccountId
Codec
Object
SignetBankAccountResponseData
(Status
-> TrackingReference
-> HexString
-> UTCTime
-> UTCTime
-> SignetBankAccountResponseData)
-> Codec Object SignetBankAccountResponseData Status
-> Codec
Object
SignetBankAccountResponseData
(TrackingReference
-> HexString
-> UTCTime
-> UTCTime
-> SignetBankAccountResponseData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (SignetBankAccountResponseData -> Status)
-> Codec Object SignetBankAccountResponseData Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountResponseData -> Status
signetBankAccountStatus
Codec
Object
SignetBankAccountResponseData
(TrackingReference
-> HexString
-> UTCTime
-> UTCTime
-> SignetBankAccountResponseData)
-> Codec Object SignetBankAccountResponseData TrackingReference
-> Codec
Object
SignetBankAccountResponseData
(HexString -> UTCTime -> UTCTime -> SignetBankAccountResponseData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (SignetBankAccountResponseData -> TrackingReference)
-> Codec Object SignetBankAccountResponseData TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountResponseData -> TrackingReference
signetBankAccountTrackingRef
Codec
Object
SignetBankAccountResponseData
(HexString -> UTCTime -> UTCTime -> SignetBankAccountResponseData)
-> Codec Object SignetBankAccountResponseData HexString
-> Codec
Object
SignetBankAccountResponseData
(UTCTime -> UTCTime -> SignetBankAccountResponseData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec HexString HexString
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"walletAddress" ObjectCodec HexString HexString
-> (SignetBankAccountResponseData -> HexString)
-> Codec Object SignetBankAccountResponseData HexString
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountResponseData -> HexString
signetBankAccountWalletAddress
Codec
Object
SignetBankAccountResponseData
(UTCTime -> UTCTime -> SignetBankAccountResponseData)
-> Codec Object SignetBankAccountResponseData UTCTime
-> Codec
Object
SignetBankAccountResponseData
(UTCTime -> SignetBankAccountResponseData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (SignetBankAccountResponseData -> UTCTime)
-> Codec Object SignetBankAccountResponseData UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountResponseData -> UTCTime
signetBankAccountCreateDate
Codec
Object
SignetBankAccountResponseData
(UTCTime -> SignetBankAccountResponseData)
-> Codec Object SignetBankAccountResponseData UTCTime
-> ObjectCodec
SignetBankAccountResponseData SignetBankAccountResponseData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (SignetBankAccountResponseData -> UTCTime)
-> Codec Object SignetBankAccountResponseData UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankAccountResponseData -> UTCTime
signetBankAccountUpdateDate
data SignetBankInstructionsResponseData = SignetBankInstructionsResponseData
{ SignetBankInstructionsResponseData -> Maybe TrackingReference
signetBankInstructionsTrackingRef :: !(Maybe TrackingReference),
SignetBankInstructionsResponseData -> Maybe HexString
signetBankInstructionsWalletAddress :: !(Maybe HexString)
}
deriving (SignetBankInstructionsResponseData
-> SignetBankInstructionsResponseData -> Bool
(SignetBankInstructionsResponseData
-> SignetBankInstructionsResponseData -> Bool)
-> (SignetBankInstructionsResponseData
-> SignetBankInstructionsResponseData -> Bool)
-> Eq SignetBankInstructionsResponseData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignetBankInstructionsResponseData
-> SignetBankInstructionsResponseData -> Bool
$c/= :: SignetBankInstructionsResponseData
-> SignetBankInstructionsResponseData -> Bool
== :: SignetBankInstructionsResponseData
-> SignetBankInstructionsResponseData -> Bool
$c== :: SignetBankInstructionsResponseData
-> SignetBankInstructionsResponseData -> Bool
Eq, Int -> SignetBankInstructionsResponseData -> ShowS
[SignetBankInstructionsResponseData] -> ShowS
SignetBankInstructionsResponseData -> String
(Int -> SignetBankInstructionsResponseData -> ShowS)
-> (SignetBankInstructionsResponseData -> String)
-> ([SignetBankInstructionsResponseData] -> ShowS)
-> Show SignetBankInstructionsResponseData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignetBankInstructionsResponseData] -> ShowS
$cshowList :: [SignetBankInstructionsResponseData] -> ShowS
show :: SignetBankInstructionsResponseData -> String
$cshow :: SignetBankInstructionsResponseData -> String
showsPrec :: Int -> SignetBankInstructionsResponseData -> ShowS
$cshowsPrec :: Int -> SignetBankInstructionsResponseData -> ShowS
Show)
deriving
( Value -> Parser [SignetBankInstructionsResponseData]
Value -> Parser SignetBankInstructionsResponseData
(Value -> Parser SignetBankInstructionsResponseData)
-> (Value -> Parser [SignetBankInstructionsResponseData])
-> FromJSON SignetBankInstructionsResponseData
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SignetBankInstructionsResponseData]
$cparseJSONList :: Value -> Parser [SignetBankInstructionsResponseData]
parseJSON :: Value -> Parser SignetBankInstructionsResponseData
$cparseJSON :: Value -> Parser SignetBankInstructionsResponseData
FromJSON,
[SignetBankInstructionsResponseData] -> Encoding
[SignetBankInstructionsResponseData] -> Value
SignetBankInstructionsResponseData -> Encoding
SignetBankInstructionsResponseData -> Value
(SignetBankInstructionsResponseData -> Value)
-> (SignetBankInstructionsResponseData -> Encoding)
-> ([SignetBankInstructionsResponseData] -> Value)
-> ([SignetBankInstructionsResponseData] -> Encoding)
-> ToJSON SignetBankInstructionsResponseData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SignetBankInstructionsResponseData] -> Encoding
$ctoEncodingList :: [SignetBankInstructionsResponseData] -> Encoding
toJSONList :: [SignetBankInstructionsResponseData] -> Value
$ctoJSONList :: [SignetBankInstructionsResponseData] -> Value
toEncoding :: SignetBankInstructionsResponseData -> Encoding
$ctoEncoding :: SignetBankInstructionsResponseData -> Encoding
toJSON :: SignetBankInstructionsResponseData -> Value
$ctoJSON :: SignetBankInstructionsResponseData -> Value
ToJSON
)
via (Autodocodec SignetBankInstructionsResponseData)
instance HasCodec SignetBankInstructionsResponseData where
codec :: JSONCodec SignetBankInstructionsResponseData
codec =
Text
-> ObjectCodec
SignetBankInstructionsResponseData
SignetBankInstructionsResponseData
-> JSONCodec SignetBankInstructionsResponseData
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SignetBankInstructionsResponseData" (ObjectCodec
SignetBankInstructionsResponseData
SignetBankInstructionsResponseData
-> JSONCodec SignetBankInstructionsResponseData)
-> ObjectCodec
SignetBankInstructionsResponseData
SignetBankInstructionsResponseData
-> JSONCodec SignetBankInstructionsResponseData
forall a b. (a -> b) -> a -> b
$
Maybe TrackingReference
-> Maybe HexString -> SignetBankInstructionsResponseData
SignetBankInstructionsResponseData
(Maybe TrackingReference
-> Maybe HexString -> SignetBankInstructionsResponseData)
-> Codec
Object SignetBankInstructionsResponseData (Maybe TrackingReference)
-> Codec
Object
SignetBankInstructionsResponseData
(Maybe HexString -> SignetBankInstructionsResponseData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"trackingRef" ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
-> (SignetBankInstructionsResponseData -> Maybe TrackingReference)
-> Codec
Object SignetBankInstructionsResponseData (Maybe TrackingReference)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankInstructionsResponseData -> Maybe TrackingReference
signetBankInstructionsTrackingRef
Codec
Object
SignetBankInstructionsResponseData
(Maybe HexString -> SignetBankInstructionsResponseData)
-> Codec
Object SignetBankInstructionsResponseData (Maybe HexString)
-> ObjectCodec
SignetBankInstructionsResponseData
SignetBankInstructionsResponseData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe HexString) (Maybe HexString)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"walletAddress" ObjectCodec (Maybe HexString) (Maybe HexString)
-> (SignetBankInstructionsResponseData -> Maybe HexString)
-> Codec
Object SignetBankInstructionsResponseData (Maybe HexString)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SignetBankInstructionsResponseData -> Maybe HexString
signetBankInstructionsWalletAddress
data WireAccountRequest
type instance CircleRequest WireAccountRequest = CircleResponseBody WireAccountResponseBody
data WireAccountsRequest
type instance CircleRequest WireAccountsRequest = CircleResponseBody [WireAccountResponseBody]
data WireInstructionsRequest
type instance CircleRequest WireInstructionsRequest = CircleResponseBody WireInstructionsResponseData
instance CircleHasParam WireInstructionsRequest PaginationQueryParams
data WireAccountRequestBody
= USBankAccount !USBankAccountRequestBody
| IBANBankAccount !IBANBankAccountRequestBody
| NonIBANBankAccount !NonIBANBankAccountRequestBody
deriving (WireAccountRequestBody -> WireAccountRequestBody -> Bool
(WireAccountRequestBody -> WireAccountRequestBody -> Bool)
-> (WireAccountRequestBody -> WireAccountRequestBody -> Bool)
-> Eq WireAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WireAccountRequestBody -> WireAccountRequestBody -> Bool
$c/= :: WireAccountRequestBody -> WireAccountRequestBody -> Bool
== :: WireAccountRequestBody -> WireAccountRequestBody -> Bool
$c== :: WireAccountRequestBody -> WireAccountRequestBody -> Bool
Eq, Int -> WireAccountRequestBody -> ShowS
[WireAccountRequestBody] -> ShowS
WireAccountRequestBody -> String
(Int -> WireAccountRequestBody -> ShowS)
-> (WireAccountRequestBody -> String)
-> ([WireAccountRequestBody] -> ShowS)
-> Show WireAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WireAccountRequestBody] -> ShowS
$cshowList :: [WireAccountRequestBody] -> ShowS
show :: WireAccountRequestBody -> String
$cshow :: WireAccountRequestBody -> String
showsPrec :: Int -> WireAccountRequestBody -> ShowS
$cshowsPrec :: Int -> WireAccountRequestBody -> ShowS
Show)
data USBankAccountRequestBody = USBankAccountRequestBody
{ USBankAccountRequestBody -> UUID
usBankAccountIdempotencyKey :: !UUID,
USBankAccountRequestBody -> AccountNumber
usBankAccountAccountNumber :: !AccountNumber,
USBankAccountRequestBody -> RoutingNumber
usBankAccountRoutingNumber :: !RoutingNumber,
USBankAccountRequestBody -> BillingDetails
usBankAccountBillingDetails :: !BillingDetails,
USBankAccountRequestBody -> BankAddress
usBankAccountBankAddress :: !BankAddress
}
deriving (USBankAccountRequestBody -> USBankAccountRequestBody -> Bool
(USBankAccountRequestBody -> USBankAccountRequestBody -> Bool)
-> (USBankAccountRequestBody -> USBankAccountRequestBody -> Bool)
-> Eq USBankAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: USBankAccountRequestBody -> USBankAccountRequestBody -> Bool
$c/= :: USBankAccountRequestBody -> USBankAccountRequestBody -> Bool
== :: USBankAccountRequestBody -> USBankAccountRequestBody -> Bool
$c== :: USBankAccountRequestBody -> USBankAccountRequestBody -> Bool
Eq, Int -> USBankAccountRequestBody -> ShowS
[USBankAccountRequestBody] -> ShowS
USBankAccountRequestBody -> String
(Int -> USBankAccountRequestBody -> ShowS)
-> (USBankAccountRequestBody -> String)
-> ([USBankAccountRequestBody] -> ShowS)
-> Show USBankAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [USBankAccountRequestBody] -> ShowS
$cshowList :: [USBankAccountRequestBody] -> ShowS
show :: USBankAccountRequestBody -> String
$cshow :: USBankAccountRequestBody -> String
showsPrec :: Int -> USBankAccountRequestBody -> ShowS
$cshowsPrec :: Int -> USBankAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [USBankAccountRequestBody]
Value -> Parser USBankAccountRequestBody
(Value -> Parser USBankAccountRequestBody)
-> (Value -> Parser [USBankAccountRequestBody])
-> FromJSON USBankAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [USBankAccountRequestBody]
$cparseJSONList :: Value -> Parser [USBankAccountRequestBody]
parseJSON :: Value -> Parser USBankAccountRequestBody
$cparseJSON :: Value -> Parser USBankAccountRequestBody
FromJSON,
[USBankAccountRequestBody] -> Encoding
[USBankAccountRequestBody] -> Value
USBankAccountRequestBody -> Encoding
USBankAccountRequestBody -> Value
(USBankAccountRequestBody -> Value)
-> (USBankAccountRequestBody -> Encoding)
-> ([USBankAccountRequestBody] -> Value)
-> ([USBankAccountRequestBody] -> Encoding)
-> ToJSON USBankAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [USBankAccountRequestBody] -> Encoding
$ctoEncodingList :: [USBankAccountRequestBody] -> Encoding
toJSONList :: [USBankAccountRequestBody] -> Value
$ctoJSONList :: [USBankAccountRequestBody] -> Value
toEncoding :: USBankAccountRequestBody -> Encoding
$ctoEncoding :: USBankAccountRequestBody -> Encoding
toJSON :: USBankAccountRequestBody -> Value
$ctoJSON :: USBankAccountRequestBody -> Value
ToJSON
)
via (Autodocodec USBankAccountRequestBody)
instance HasCodec USBankAccountRequestBody where
codec :: JSONCodec USBankAccountRequestBody
codec =
Text
-> ObjectCodec USBankAccountRequestBody USBankAccountRequestBody
-> JSONCodec USBankAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"USBankAccountRequestBody" (ObjectCodec USBankAccountRequestBody USBankAccountRequestBody
-> JSONCodec USBankAccountRequestBody)
-> ObjectCodec USBankAccountRequestBody USBankAccountRequestBody
-> JSONCodec USBankAccountRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> USBankAccountRequestBody
USBankAccountRequestBody
(UUID
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> USBankAccountRequestBody)
-> Codec Object USBankAccountRequestBody UUID
-> Codec
Object
USBankAccountRequestBody
(AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> USBankAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (USBankAccountRequestBody -> UUID)
-> Codec Object USBankAccountRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= USBankAccountRequestBody -> UUID
usBankAccountIdempotencyKey
Codec
Object
USBankAccountRequestBody
(AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> USBankAccountRequestBody)
-> Codec Object USBankAccountRequestBody AccountNumber
-> Codec
Object
USBankAccountRequestBody
(RoutingNumber
-> BillingDetails -> BankAddress -> USBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AccountNumber AccountNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"accountNumber" ObjectCodec AccountNumber AccountNumber
-> (USBankAccountRequestBody -> AccountNumber)
-> Codec Object USBankAccountRequestBody AccountNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= USBankAccountRequestBody -> AccountNumber
usBankAccountAccountNumber
Codec
Object
USBankAccountRequestBody
(RoutingNumber
-> BillingDetails -> BankAddress -> USBankAccountRequestBody)
-> Codec Object USBankAccountRequestBody RoutingNumber
-> Codec
Object
USBankAccountRequestBody
(BillingDetails -> BankAddress -> USBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RoutingNumber RoutingNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"routingNumber" ObjectCodec RoutingNumber RoutingNumber
-> (USBankAccountRequestBody -> RoutingNumber)
-> Codec Object USBankAccountRequestBody RoutingNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= USBankAccountRequestBody -> RoutingNumber
usBankAccountRoutingNumber
Codec
Object
USBankAccountRequestBody
(BillingDetails -> BankAddress -> USBankAccountRequestBody)
-> Codec Object USBankAccountRequestBody BillingDetails
-> Codec
Object
USBankAccountRequestBody
(BankAddress -> USBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (USBankAccountRequestBody -> BillingDetails)
-> Codec Object USBankAccountRequestBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= USBankAccountRequestBody -> BillingDetails
usBankAccountBillingDetails
Codec
Object
USBankAccountRequestBody
(BankAddress -> USBankAccountRequestBody)
-> Codec Object USBankAccountRequestBody BankAddress
-> ObjectCodec USBankAccountRequestBody USBankAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BankAddress BankAddress
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"bankAddress" ObjectCodec BankAddress BankAddress
-> (USBankAccountRequestBody -> BankAddress)
-> Codec Object USBankAccountRequestBody BankAddress
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= USBankAccountRequestBody -> BankAddress
usBankAccountBankAddress
data IBANBankAccountRequestBody = IBANBankAccountRequestBody
{ IBANBankAccountRequestBody -> UUID
ibanBankAccountIdempotencyKey :: !UUID,
IBANBankAccountRequestBody -> Iban
ibanBankAccountIBAN :: !Iban,
IBANBankAccountRequestBody -> BillingDetails
ibanBankAccountBillingDetails :: !BillingDetails,
IBANBankAccountRequestBody -> BankAddress
ibanBankAccountBankAddress :: !BankAddress
}
deriving (IBANBankAccountRequestBody -> IBANBankAccountRequestBody -> Bool
(IBANBankAccountRequestBody -> IBANBankAccountRequestBody -> Bool)
-> (IBANBankAccountRequestBody
-> IBANBankAccountRequestBody -> Bool)
-> Eq IBANBankAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IBANBankAccountRequestBody -> IBANBankAccountRequestBody -> Bool
$c/= :: IBANBankAccountRequestBody -> IBANBankAccountRequestBody -> Bool
== :: IBANBankAccountRequestBody -> IBANBankAccountRequestBody -> Bool
$c== :: IBANBankAccountRequestBody -> IBANBankAccountRequestBody -> Bool
Eq, Int -> IBANBankAccountRequestBody -> ShowS
[IBANBankAccountRequestBody] -> ShowS
IBANBankAccountRequestBody -> String
(Int -> IBANBankAccountRequestBody -> ShowS)
-> (IBANBankAccountRequestBody -> String)
-> ([IBANBankAccountRequestBody] -> ShowS)
-> Show IBANBankAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IBANBankAccountRequestBody] -> ShowS
$cshowList :: [IBANBankAccountRequestBody] -> ShowS
show :: IBANBankAccountRequestBody -> String
$cshow :: IBANBankAccountRequestBody -> String
showsPrec :: Int -> IBANBankAccountRequestBody -> ShowS
$cshowsPrec :: Int -> IBANBankAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [IBANBankAccountRequestBody]
Value -> Parser IBANBankAccountRequestBody
(Value -> Parser IBANBankAccountRequestBody)
-> (Value -> Parser [IBANBankAccountRequestBody])
-> FromJSON IBANBankAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [IBANBankAccountRequestBody]
$cparseJSONList :: Value -> Parser [IBANBankAccountRequestBody]
parseJSON :: Value -> Parser IBANBankAccountRequestBody
$cparseJSON :: Value -> Parser IBANBankAccountRequestBody
FromJSON,
[IBANBankAccountRequestBody] -> Encoding
[IBANBankAccountRequestBody] -> Value
IBANBankAccountRequestBody -> Encoding
IBANBankAccountRequestBody -> Value
(IBANBankAccountRequestBody -> Value)
-> (IBANBankAccountRequestBody -> Encoding)
-> ([IBANBankAccountRequestBody] -> Value)
-> ([IBANBankAccountRequestBody] -> Encoding)
-> ToJSON IBANBankAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [IBANBankAccountRequestBody] -> Encoding
$ctoEncodingList :: [IBANBankAccountRequestBody] -> Encoding
toJSONList :: [IBANBankAccountRequestBody] -> Value
$ctoJSONList :: [IBANBankAccountRequestBody] -> Value
toEncoding :: IBANBankAccountRequestBody -> Encoding
$ctoEncoding :: IBANBankAccountRequestBody -> Encoding
toJSON :: IBANBankAccountRequestBody -> Value
$ctoJSON :: IBANBankAccountRequestBody -> Value
ToJSON
)
via (Autodocodec IBANBankAccountRequestBody)
instance HasCodec IBANBankAccountRequestBody where
codec :: JSONCodec IBANBankAccountRequestBody
codec =
Text
-> ObjectCodec
IBANBankAccountRequestBody IBANBankAccountRequestBody
-> JSONCodec IBANBankAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"IBANBankAccountRequestBody" (ObjectCodec IBANBankAccountRequestBody IBANBankAccountRequestBody
-> JSONCodec IBANBankAccountRequestBody)
-> ObjectCodec
IBANBankAccountRequestBody IBANBankAccountRequestBody
-> JSONCodec IBANBankAccountRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Iban
-> BillingDetails
-> BankAddress
-> IBANBankAccountRequestBody
IBANBankAccountRequestBody
(UUID
-> Iban
-> BillingDetails
-> BankAddress
-> IBANBankAccountRequestBody)
-> Codec Object IBANBankAccountRequestBody UUID
-> Codec
Object
IBANBankAccountRequestBody
(Iban
-> BillingDetails -> BankAddress -> IBANBankAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (IBANBankAccountRequestBody -> UUID)
-> Codec Object IBANBankAccountRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= IBANBankAccountRequestBody -> UUID
ibanBankAccountIdempotencyKey
Codec
Object
IBANBankAccountRequestBody
(Iban
-> BillingDetails -> BankAddress -> IBANBankAccountRequestBody)
-> Codec Object IBANBankAccountRequestBody Iban
-> Codec
Object
IBANBankAccountRequestBody
(BillingDetails -> BankAddress -> IBANBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Iban Iban
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"iban" ObjectCodec Iban Iban
-> (IBANBankAccountRequestBody -> Iban)
-> Codec Object IBANBankAccountRequestBody Iban
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= IBANBankAccountRequestBody -> Iban
ibanBankAccountIBAN
Codec
Object
IBANBankAccountRequestBody
(BillingDetails -> BankAddress -> IBANBankAccountRequestBody)
-> Codec Object IBANBankAccountRequestBody BillingDetails
-> Codec
Object
IBANBankAccountRequestBody
(BankAddress -> IBANBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (IBANBankAccountRequestBody -> BillingDetails)
-> Codec Object IBANBankAccountRequestBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= IBANBankAccountRequestBody -> BillingDetails
ibanBankAccountBillingDetails
Codec
Object
IBANBankAccountRequestBody
(BankAddress -> IBANBankAccountRequestBody)
-> Codec Object IBANBankAccountRequestBody BankAddress
-> ObjectCodec
IBANBankAccountRequestBody IBANBankAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BankAddress BankAddress
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"bankAddress" ObjectCodec BankAddress BankAddress
-> (IBANBankAccountRequestBody -> BankAddress)
-> Codec Object IBANBankAccountRequestBody BankAddress
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= IBANBankAccountRequestBody -> BankAddress
ibanBankAccountBankAddress
data NonIBANBankAccountRequestBody = NonIBANBankAccountRequestBody
{ NonIBANBankAccountRequestBody -> UUID
nonIBANBankAccountIdempotencyKey :: !UUID,
NonIBANBankAccountRequestBody -> AccountNumber
nonIBANBankAccountAccountNumber :: !AccountNumber,
NonIBANBankAccountRequestBody -> RoutingNumber
nonIBANBankAccountRoutingNumber :: !RoutingNumber,
NonIBANBankAccountRequestBody -> BillingDetails
nonIBANBankAccountBillingDetails :: !BillingDetails,
NonIBANBankAccountRequestBody -> BankAddress
nonIBANBankAccountBankAddress :: !BankAddress
}
deriving (NonIBANBankAccountRequestBody
-> NonIBANBankAccountRequestBody -> Bool
(NonIBANBankAccountRequestBody
-> NonIBANBankAccountRequestBody -> Bool)
-> (NonIBANBankAccountRequestBody
-> NonIBANBankAccountRequestBody -> Bool)
-> Eq NonIBANBankAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonIBANBankAccountRequestBody
-> NonIBANBankAccountRequestBody -> Bool
$c/= :: NonIBANBankAccountRequestBody
-> NonIBANBankAccountRequestBody -> Bool
== :: NonIBANBankAccountRequestBody
-> NonIBANBankAccountRequestBody -> Bool
$c== :: NonIBANBankAccountRequestBody
-> NonIBANBankAccountRequestBody -> Bool
Eq, Int -> NonIBANBankAccountRequestBody -> ShowS
[NonIBANBankAccountRequestBody] -> ShowS
NonIBANBankAccountRequestBody -> String
(Int -> NonIBANBankAccountRequestBody -> ShowS)
-> (NonIBANBankAccountRequestBody -> String)
-> ([NonIBANBankAccountRequestBody] -> ShowS)
-> Show NonIBANBankAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonIBANBankAccountRequestBody] -> ShowS
$cshowList :: [NonIBANBankAccountRequestBody] -> ShowS
show :: NonIBANBankAccountRequestBody -> String
$cshow :: NonIBANBankAccountRequestBody -> String
showsPrec :: Int -> NonIBANBankAccountRequestBody -> ShowS
$cshowsPrec :: Int -> NonIBANBankAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [NonIBANBankAccountRequestBody]
Value -> Parser NonIBANBankAccountRequestBody
(Value -> Parser NonIBANBankAccountRequestBody)
-> (Value -> Parser [NonIBANBankAccountRequestBody])
-> FromJSON NonIBANBankAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [NonIBANBankAccountRequestBody]
$cparseJSONList :: Value -> Parser [NonIBANBankAccountRequestBody]
parseJSON :: Value -> Parser NonIBANBankAccountRequestBody
$cparseJSON :: Value -> Parser NonIBANBankAccountRequestBody
FromJSON,
[NonIBANBankAccountRequestBody] -> Encoding
[NonIBANBankAccountRequestBody] -> Value
NonIBANBankAccountRequestBody -> Encoding
NonIBANBankAccountRequestBody -> Value
(NonIBANBankAccountRequestBody -> Value)
-> (NonIBANBankAccountRequestBody -> Encoding)
-> ([NonIBANBankAccountRequestBody] -> Value)
-> ([NonIBANBankAccountRequestBody] -> Encoding)
-> ToJSON NonIBANBankAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [NonIBANBankAccountRequestBody] -> Encoding
$ctoEncodingList :: [NonIBANBankAccountRequestBody] -> Encoding
toJSONList :: [NonIBANBankAccountRequestBody] -> Value
$ctoJSONList :: [NonIBANBankAccountRequestBody] -> Value
toEncoding :: NonIBANBankAccountRequestBody -> Encoding
$ctoEncoding :: NonIBANBankAccountRequestBody -> Encoding
toJSON :: NonIBANBankAccountRequestBody -> Value
$ctoJSON :: NonIBANBankAccountRequestBody -> Value
ToJSON
)
via (Autodocodec NonIBANBankAccountRequestBody)
instance HasCodec NonIBANBankAccountRequestBody where
codec :: JSONCodec NonIBANBankAccountRequestBody
codec =
Text
-> ObjectCodec
NonIBANBankAccountRequestBody NonIBANBankAccountRequestBody
-> JSONCodec NonIBANBankAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"NonIBANBankAccountRequestBody" (ObjectCodec
NonIBANBankAccountRequestBody NonIBANBankAccountRequestBody
-> JSONCodec NonIBANBankAccountRequestBody)
-> ObjectCodec
NonIBANBankAccountRequestBody NonIBANBankAccountRequestBody
-> JSONCodec NonIBANBankAccountRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> NonIBANBankAccountRequestBody
NonIBANBankAccountRequestBody
(UUID
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> NonIBANBankAccountRequestBody)
-> Codec Object NonIBANBankAccountRequestBody UUID
-> Codec
Object
NonIBANBankAccountRequestBody
(AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> NonIBANBankAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (NonIBANBankAccountRequestBody -> UUID)
-> Codec Object NonIBANBankAccountRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= NonIBANBankAccountRequestBody -> UUID
nonIBANBankAccountIdempotencyKey
Codec
Object
NonIBANBankAccountRequestBody
(AccountNumber
-> RoutingNumber
-> BillingDetails
-> BankAddress
-> NonIBANBankAccountRequestBody)
-> Codec Object NonIBANBankAccountRequestBody AccountNumber
-> Codec
Object
NonIBANBankAccountRequestBody
(RoutingNumber
-> BillingDetails -> BankAddress -> NonIBANBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AccountNumber AccountNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"accountNumber" ObjectCodec AccountNumber AccountNumber
-> (NonIBANBankAccountRequestBody -> AccountNumber)
-> Codec Object NonIBANBankAccountRequestBody AccountNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= NonIBANBankAccountRequestBody -> AccountNumber
nonIBANBankAccountAccountNumber
Codec
Object
NonIBANBankAccountRequestBody
(RoutingNumber
-> BillingDetails -> BankAddress -> NonIBANBankAccountRequestBody)
-> Codec Object NonIBANBankAccountRequestBody RoutingNumber
-> Codec
Object
NonIBANBankAccountRequestBody
(BillingDetails -> BankAddress -> NonIBANBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RoutingNumber RoutingNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"routingNumber" ObjectCodec RoutingNumber RoutingNumber
-> (NonIBANBankAccountRequestBody -> RoutingNumber)
-> Codec Object NonIBANBankAccountRequestBody RoutingNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= NonIBANBankAccountRequestBody -> RoutingNumber
nonIBANBankAccountRoutingNumber
Codec
Object
NonIBANBankAccountRequestBody
(BillingDetails -> BankAddress -> NonIBANBankAccountRequestBody)
-> Codec Object NonIBANBankAccountRequestBody BillingDetails
-> Codec
Object
NonIBANBankAccountRequestBody
(BankAddress -> NonIBANBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (NonIBANBankAccountRequestBody -> BillingDetails)
-> Codec Object NonIBANBankAccountRequestBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= NonIBANBankAccountRequestBody -> BillingDetails
nonIBANBankAccountBillingDetails
Codec
Object
NonIBANBankAccountRequestBody
(BankAddress -> NonIBANBankAccountRequestBody)
-> Codec Object NonIBANBankAccountRequestBody BankAddress
-> ObjectCodec
NonIBANBankAccountRequestBody NonIBANBankAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BankAddress BankAddress
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"bankAddress" ObjectCodec BankAddress BankAddress
-> (NonIBANBankAccountRequestBody -> BankAddress)
-> Codec Object NonIBANBankAccountRequestBody BankAddress
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= NonIBANBankAccountRequestBody -> BankAddress
nonIBANBankAccountBankAddress
data WireInstructionsResponseData = WireInstructionsResponseData
{ WireInstructionsResponseData -> TrackingReference
wireInstructionsResponseDataTrackingRef :: !TrackingReference,
WireInstructionsResponseData -> BeneficiaryDetails
wireInstructionsResponseDataBeneficiaryDetails :: !BeneficiaryDetails,
WireInstructionsResponseData -> BeneficiaryBankDetails
wireInstructionsResponseDataBeneficiaryBankDetails :: !BeneficiaryBankDetails
}
deriving (WireInstructionsResponseData
-> WireInstructionsResponseData -> Bool
(WireInstructionsResponseData
-> WireInstructionsResponseData -> Bool)
-> (WireInstructionsResponseData
-> WireInstructionsResponseData -> Bool)
-> Eq WireInstructionsResponseData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WireInstructionsResponseData
-> WireInstructionsResponseData -> Bool
$c/= :: WireInstructionsResponseData
-> WireInstructionsResponseData -> Bool
== :: WireInstructionsResponseData
-> WireInstructionsResponseData -> Bool
$c== :: WireInstructionsResponseData
-> WireInstructionsResponseData -> Bool
Eq, Int -> WireInstructionsResponseData -> ShowS
[WireInstructionsResponseData] -> ShowS
WireInstructionsResponseData -> String
(Int -> WireInstructionsResponseData -> ShowS)
-> (WireInstructionsResponseData -> String)
-> ([WireInstructionsResponseData] -> ShowS)
-> Show WireInstructionsResponseData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WireInstructionsResponseData] -> ShowS
$cshowList :: [WireInstructionsResponseData] -> ShowS
show :: WireInstructionsResponseData -> String
$cshow :: WireInstructionsResponseData -> String
showsPrec :: Int -> WireInstructionsResponseData -> ShowS
$cshowsPrec :: Int -> WireInstructionsResponseData -> ShowS
Show)
deriving
( Value -> Parser [WireInstructionsResponseData]
Value -> Parser WireInstructionsResponseData
(Value -> Parser WireInstructionsResponseData)
-> (Value -> Parser [WireInstructionsResponseData])
-> FromJSON WireInstructionsResponseData
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WireInstructionsResponseData]
$cparseJSONList :: Value -> Parser [WireInstructionsResponseData]
parseJSON :: Value -> Parser WireInstructionsResponseData
$cparseJSON :: Value -> Parser WireInstructionsResponseData
FromJSON,
[WireInstructionsResponseData] -> Encoding
[WireInstructionsResponseData] -> Value
WireInstructionsResponseData -> Encoding
WireInstructionsResponseData -> Value
(WireInstructionsResponseData -> Value)
-> (WireInstructionsResponseData -> Encoding)
-> ([WireInstructionsResponseData] -> Value)
-> ([WireInstructionsResponseData] -> Encoding)
-> ToJSON WireInstructionsResponseData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WireInstructionsResponseData] -> Encoding
$ctoEncodingList :: [WireInstructionsResponseData] -> Encoding
toJSONList :: [WireInstructionsResponseData] -> Value
$ctoJSONList :: [WireInstructionsResponseData] -> Value
toEncoding :: WireInstructionsResponseData -> Encoding
$ctoEncoding :: WireInstructionsResponseData -> Encoding
toJSON :: WireInstructionsResponseData -> Value
$ctoJSON :: WireInstructionsResponseData -> Value
ToJSON
)
via (Autodocodec WireInstructionsResponseData)
instance HasCodec WireInstructionsResponseData where
codec :: JSONCodec WireInstructionsResponseData
codec =
Text
-> ObjectCodec
WireInstructionsResponseData WireInstructionsResponseData
-> JSONCodec WireInstructionsResponseData
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"WireInstructionsResponseData" (ObjectCodec
WireInstructionsResponseData WireInstructionsResponseData
-> JSONCodec WireInstructionsResponseData)
-> ObjectCodec
WireInstructionsResponseData WireInstructionsResponseData
-> JSONCodec WireInstructionsResponseData
forall a b. (a -> b) -> a -> b
$
TrackingReference
-> BeneficiaryDetails
-> BeneficiaryBankDetails
-> WireInstructionsResponseData
WireInstructionsResponseData
(TrackingReference
-> BeneficiaryDetails
-> BeneficiaryBankDetails
-> WireInstructionsResponseData)
-> Codec Object WireInstructionsResponseData TrackingReference
-> Codec
Object
WireInstructionsResponseData
(BeneficiaryDetails
-> BeneficiaryBankDetails -> WireInstructionsResponseData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (WireInstructionsResponseData -> TrackingReference)
-> Codec Object WireInstructionsResponseData TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireInstructionsResponseData -> TrackingReference
wireInstructionsResponseDataTrackingRef
Codec
Object
WireInstructionsResponseData
(BeneficiaryDetails
-> BeneficiaryBankDetails -> WireInstructionsResponseData)
-> Codec Object WireInstructionsResponseData BeneficiaryDetails
-> Codec
Object
WireInstructionsResponseData
(BeneficiaryBankDetails -> WireInstructionsResponseData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BeneficiaryDetails BeneficiaryDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"beneficiary" ObjectCodec BeneficiaryDetails BeneficiaryDetails
-> (WireInstructionsResponseData -> BeneficiaryDetails)
-> Codec Object WireInstructionsResponseData BeneficiaryDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireInstructionsResponseData -> BeneficiaryDetails
wireInstructionsResponseDataBeneficiaryDetails
Codec
Object
WireInstructionsResponseData
(BeneficiaryBankDetails -> WireInstructionsResponseData)
-> Codec Object WireInstructionsResponseData BeneficiaryBankDetails
-> ObjectCodec
WireInstructionsResponseData WireInstructionsResponseData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BeneficiaryBankDetails BeneficiaryBankDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"beneficiaryBank" ObjectCodec BeneficiaryBankDetails BeneficiaryBankDetails
-> (WireInstructionsResponseData -> BeneficiaryBankDetails)
-> Codec Object WireInstructionsResponseData BeneficiaryBankDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireInstructionsResponseData -> BeneficiaryBankDetails
wireInstructionsResponseDataBeneficiaryBankDetails
data WireAccountResponseBody = WireAccountResponseBody
{ WireAccountResponseBody -> UUID
wireAccountResponseBodyId :: !UUID,
WireAccountResponseBody -> Status
wireAccountResponseBodyStatus :: !Status,
WireAccountResponseBody -> Text
wireAccountResponseBodyDescription :: !Text,
WireAccountResponseBody -> TrackingReference
wireAccountResponseBodyTrackingRef :: !TrackingReference,
WireAccountResponseBody -> UUID
wireAccountResponseBodyFingerprint :: !UUID,
WireAccountResponseBody -> BillingDetails
wireAccountResponseBodyBillingDetails :: !BillingDetails,
WireAccountResponseBody -> BankAddress
wireAccountResponseBodyBankAddress :: !BankAddress,
WireAccountResponseBody -> UTCTime
wireAccountResponseBodyCreateDate :: !UTCTime,
WireAccountResponseBody -> UTCTime
wireAccountResponseBodyUpdateDate :: !UTCTime
}
deriving (WireAccountResponseBody -> WireAccountResponseBody -> Bool
(WireAccountResponseBody -> WireAccountResponseBody -> Bool)
-> (WireAccountResponseBody -> WireAccountResponseBody -> Bool)
-> Eq WireAccountResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WireAccountResponseBody -> WireAccountResponseBody -> Bool
$c/= :: WireAccountResponseBody -> WireAccountResponseBody -> Bool
== :: WireAccountResponseBody -> WireAccountResponseBody -> Bool
$c== :: WireAccountResponseBody -> WireAccountResponseBody -> Bool
Eq, Int -> WireAccountResponseBody -> ShowS
[WireAccountResponseBody] -> ShowS
WireAccountResponseBody -> String
(Int -> WireAccountResponseBody -> ShowS)
-> (WireAccountResponseBody -> String)
-> ([WireAccountResponseBody] -> ShowS)
-> Show WireAccountResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WireAccountResponseBody] -> ShowS
$cshowList :: [WireAccountResponseBody] -> ShowS
show :: WireAccountResponseBody -> String
$cshow :: WireAccountResponseBody -> String
showsPrec :: Int -> WireAccountResponseBody -> ShowS
$cshowsPrec :: Int -> WireAccountResponseBody -> ShowS
Show)
deriving
( Value -> Parser [WireAccountResponseBody]
Value -> Parser WireAccountResponseBody
(Value -> Parser WireAccountResponseBody)
-> (Value -> Parser [WireAccountResponseBody])
-> FromJSON WireAccountResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WireAccountResponseBody]
$cparseJSONList :: Value -> Parser [WireAccountResponseBody]
parseJSON :: Value -> Parser WireAccountResponseBody
$cparseJSON :: Value -> Parser WireAccountResponseBody
FromJSON,
[WireAccountResponseBody] -> Encoding
[WireAccountResponseBody] -> Value
WireAccountResponseBody -> Encoding
WireAccountResponseBody -> Value
(WireAccountResponseBody -> Value)
-> (WireAccountResponseBody -> Encoding)
-> ([WireAccountResponseBody] -> Value)
-> ([WireAccountResponseBody] -> Encoding)
-> ToJSON WireAccountResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WireAccountResponseBody] -> Encoding
$ctoEncodingList :: [WireAccountResponseBody] -> Encoding
toJSONList :: [WireAccountResponseBody] -> Value
$ctoJSONList :: [WireAccountResponseBody] -> Value
toEncoding :: WireAccountResponseBody -> Encoding
$ctoEncoding :: WireAccountResponseBody -> Encoding
toJSON :: WireAccountResponseBody -> Value
$ctoJSON :: WireAccountResponseBody -> Value
ToJSON
)
via (Autodocodec WireAccountResponseBody)
instance HasCodec WireAccountResponseBody where
codec :: JSONCodec WireAccountResponseBody
codec =
Text
-> ObjectCodec WireAccountResponseBody WireAccountResponseBody
-> JSONCodec WireAccountResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"WireAccountResponseBody" (ObjectCodec WireAccountResponseBody WireAccountResponseBody
-> JSONCodec WireAccountResponseBody)
-> ObjectCodec WireAccountResponseBody WireAccountResponseBody
-> JSONCodec WireAccountResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Status
-> Text
-> TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody
WireAccountResponseBody
(UUID
-> Status
-> Text
-> TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody UUID
-> Codec
Object
WireAccountResponseBody
(Status
-> Text
-> TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (WireAccountResponseBody -> UUID)
-> Codec Object WireAccountResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> UUID
wireAccountResponseBodyId
Codec
Object
WireAccountResponseBody
(Status
-> Text
-> TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody Status
-> Codec
Object
WireAccountResponseBody
(Text
-> TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (WireAccountResponseBody -> Status)
-> Codec Object WireAccountResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> Status
wireAccountResponseBodyStatus
Codec
Object
WireAccountResponseBody
(Text
-> TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody Text
-> Codec
Object
WireAccountResponseBody
(TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (WireAccountResponseBody -> Text)
-> Codec Object WireAccountResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> Text
wireAccountResponseBodyDescription
Codec
Object
WireAccountResponseBody
(TrackingReference
-> UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody TrackingReference
-> Codec
Object
WireAccountResponseBody
(UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (WireAccountResponseBody -> TrackingReference)
-> Codec Object WireAccountResponseBody TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> TrackingReference
wireAccountResponseBodyTrackingRef
Codec
Object
WireAccountResponseBody
(UUID
-> BillingDetails
-> BankAddress
-> UTCTime
-> UTCTime
-> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody UUID
-> Codec
Object
WireAccountResponseBody
(BillingDetails
-> BankAddress -> UTCTime -> UTCTime -> WireAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fingerprint" ObjectCodec UUID UUID
-> (WireAccountResponseBody -> UUID)
-> Codec Object WireAccountResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> UUID
wireAccountResponseBodyFingerprint
Codec
Object
WireAccountResponseBody
(BillingDetails
-> BankAddress -> UTCTime -> UTCTime -> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody BillingDetails
-> Codec
Object
WireAccountResponseBody
(BankAddress -> UTCTime -> UTCTime -> WireAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (WireAccountResponseBody -> BillingDetails)
-> Codec Object WireAccountResponseBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> BillingDetails
wireAccountResponseBodyBillingDetails
Codec
Object
WireAccountResponseBody
(BankAddress -> UTCTime -> UTCTime -> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody BankAddress
-> Codec
Object
WireAccountResponseBody
(UTCTime -> UTCTime -> WireAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BankAddress BankAddress
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"bankAddress" ObjectCodec BankAddress BankAddress
-> (WireAccountResponseBody -> BankAddress)
-> Codec Object WireAccountResponseBody BankAddress
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> BankAddress
wireAccountResponseBodyBankAddress
Codec
Object
WireAccountResponseBody
(UTCTime -> UTCTime -> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody UTCTime
-> Codec
Object WireAccountResponseBody (UTCTime -> WireAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (WireAccountResponseBody -> UTCTime)
-> Codec Object WireAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> UTCTime
wireAccountResponseBodyCreateDate
Codec
Object WireAccountResponseBody (UTCTime -> WireAccountResponseBody)
-> Codec Object WireAccountResponseBody UTCTime
-> ObjectCodec WireAccountResponseBody WireAccountResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (WireAccountResponseBody -> UTCTime)
-> Codec Object WireAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WireAccountResponseBody -> UTCTime
wireAccountResponseBodyUpdateDate
data PaymentRequest
type instance CircleRequest PaymentRequest = CircleResponseBody (ThisOrThat FiatOrCryptoPaymentResponseBody FiatCancelOrRefundResponseBody)
data PaymentsRequest
type instance CircleRequest PaymentsRequest = CircleResponseBody [ThisOrThat FiatOrCryptoPaymentResponseBody FiatCancelOrRefundResponseBody]
instance CircleHasParam PaymentsRequest PaginationQueryParams
instance CircleHasParam PaymentsRequest FromQueryParam
instance CircleHasParam PaymentsRequest ToQueryParam
instance CircleHasParam PaymentsRequest PageSizeQueryParam
instance CircleHasParam PaymentsRequest PaymentStatusQueryParams
instance CircleHasParam PaymentsRequest TypeQueryParam
instance CircleHasParam PaymentsRequest DestinationQueryParam
instance CircleHasParam PaymentsRequest SourceQueryParam
instance CircleHasParam PaymentsRequest SettlementIdQueryParam
instance CircleHasParam PaymentsRequest PaymentIntentIdQueryParam
data CreatePaymentRequestBody = CreatePaymentRequestBody
{ CreatePaymentRequestBody -> UUID
createPaymentIdempotencyKey :: !UUID,
CreatePaymentRequestBody -> Text
createPaymentKeyId :: !Text,
CreatePaymentRequestBody -> RequestMetadata
requestMetadata :: !RequestMetadata,
CreatePaymentRequestBody -> MoneyAmount
createPaymentAmount :: !MoneyAmount,
CreatePaymentRequestBody -> Maybe Bool
createPaymentAutoCapture :: !(Maybe Bool),
CreatePaymentRequestBody -> VerificationType
createPaymentVerification :: !VerificationType,
CreatePaymentRequestBody -> Maybe URL
createPaymentVerificationSuccessUrl :: !(Maybe URL),
CreatePaymentRequestBody -> Maybe URL
createPaymentVerificationFailureUrl :: !(Maybe URL),
CreatePaymentRequestBody -> PaymentSource
createPaymentSource :: !PaymentSource,
CreatePaymentRequestBody -> Maybe Text
createPaymentDescription :: !(Maybe Text),
CreatePaymentRequestBody -> Maybe Text
createPaymentEncryptedData :: !(Maybe Text),
CreatePaymentRequestBody -> Maybe UUID
createPaymentChannel :: !(Maybe UUID)
}
deriving (CreatePaymentRequestBody -> CreatePaymentRequestBody -> Bool
(CreatePaymentRequestBody -> CreatePaymentRequestBody -> Bool)
-> (CreatePaymentRequestBody -> CreatePaymentRequestBody -> Bool)
-> Eq CreatePaymentRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePaymentRequestBody -> CreatePaymentRequestBody -> Bool
$c/= :: CreatePaymentRequestBody -> CreatePaymentRequestBody -> Bool
== :: CreatePaymentRequestBody -> CreatePaymentRequestBody -> Bool
$c== :: CreatePaymentRequestBody -> CreatePaymentRequestBody -> Bool
Eq, Int -> CreatePaymentRequestBody -> ShowS
[CreatePaymentRequestBody] -> ShowS
CreatePaymentRequestBody -> String
(Int -> CreatePaymentRequestBody -> ShowS)
-> (CreatePaymentRequestBody -> String)
-> ([CreatePaymentRequestBody] -> ShowS)
-> Show CreatePaymentRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePaymentRequestBody] -> ShowS
$cshowList :: [CreatePaymentRequestBody] -> ShowS
show :: CreatePaymentRequestBody -> String
$cshow :: CreatePaymentRequestBody -> String
showsPrec :: Int -> CreatePaymentRequestBody -> ShowS
$cshowsPrec :: Int -> CreatePaymentRequestBody -> ShowS
Show)
deriving
( Value -> Parser [CreatePaymentRequestBody]
Value -> Parser CreatePaymentRequestBody
(Value -> Parser CreatePaymentRequestBody)
-> (Value -> Parser [CreatePaymentRequestBody])
-> FromJSON CreatePaymentRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CreatePaymentRequestBody]
$cparseJSONList :: Value -> Parser [CreatePaymentRequestBody]
parseJSON :: Value -> Parser CreatePaymentRequestBody
$cparseJSON :: Value -> Parser CreatePaymentRequestBody
FromJSON,
[CreatePaymentRequestBody] -> Encoding
[CreatePaymentRequestBody] -> Value
CreatePaymentRequestBody -> Encoding
CreatePaymentRequestBody -> Value
(CreatePaymentRequestBody -> Value)
-> (CreatePaymentRequestBody -> Encoding)
-> ([CreatePaymentRequestBody] -> Value)
-> ([CreatePaymentRequestBody] -> Encoding)
-> ToJSON CreatePaymentRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreatePaymentRequestBody] -> Encoding
$ctoEncodingList :: [CreatePaymentRequestBody] -> Encoding
toJSONList :: [CreatePaymentRequestBody] -> Value
$ctoJSONList :: [CreatePaymentRequestBody] -> Value
toEncoding :: CreatePaymentRequestBody -> Encoding
$ctoEncoding :: CreatePaymentRequestBody -> Encoding
toJSON :: CreatePaymentRequestBody -> Value
$ctoJSON :: CreatePaymentRequestBody -> Value
ToJSON
)
via (Autodocodec CreatePaymentRequestBody)
instance HasCodec CreatePaymentRequestBody where
codec :: JSONCodec CreatePaymentRequestBody
codec =
Text
-> ObjectCodec CreatePaymentRequestBody CreatePaymentRequestBody
-> JSONCodec CreatePaymentRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CreatePaymentRequestBody" (ObjectCodec CreatePaymentRequestBody CreatePaymentRequestBody
-> JSONCodec CreatePaymentRequestBody)
-> ObjectCodec CreatePaymentRequestBody CreatePaymentRequestBody
-> JSONCodec CreatePaymentRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Text
-> RequestMetadata
-> MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody
CreatePaymentRequestBody
(UUID
-> Text
-> RequestMetadata
-> MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody UUID
-> Codec
Object
CreatePaymentRequestBody
(Text
-> RequestMetadata
-> MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (CreatePaymentRequestBody -> UUID)
-> Codec Object CreatePaymentRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> UUID
createPaymentIdempotencyKey
Codec
Object
CreatePaymentRequestBody
(Text
-> RequestMetadata
-> MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody Text
-> Codec
Object
CreatePaymentRequestBody
(RequestMetadata
-> MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"keyId" ObjectCodec Text Text
-> (CreatePaymentRequestBody -> Text)
-> Codec Object CreatePaymentRequestBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> Text
createPaymentKeyId
Codec
Object
CreatePaymentRequestBody
(RequestMetadata
-> MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody RequestMetadata
-> Codec
Object
CreatePaymentRequestBody
(MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RequestMetadata RequestMetadata
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"metadata" ObjectCodec RequestMetadata RequestMetadata
-> (CreatePaymentRequestBody -> RequestMetadata)
-> Codec Object CreatePaymentRequestBody RequestMetadata
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> RequestMetadata
requestMetadata
Codec
Object
CreatePaymentRequestBody
(MoneyAmount
-> Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody MoneyAmount
-> Codec
Object
CreatePaymentRequestBody
(Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (CreatePaymentRequestBody -> MoneyAmount)
-> Codec Object CreatePaymentRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> MoneyAmount
createPaymentAmount
Codec
Object
CreatePaymentRequestBody
(Maybe Bool
-> VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody (Maybe Bool)
-> Codec
Object
CreatePaymentRequestBody
(VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"autoCapture" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (CreatePaymentRequestBody -> Maybe Bool)
-> Codec Object CreatePaymentRequestBody (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> Maybe Bool
createPaymentAutoCapture
Codec
Object
CreatePaymentRequestBody
(VerificationType
-> Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody VerificationType
-> Codec
Object
CreatePaymentRequestBody
(Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec VerificationType VerificationType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"verification" ObjectCodec VerificationType VerificationType
-> (CreatePaymentRequestBody -> VerificationType)
-> Codec Object CreatePaymentRequestBody VerificationType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> VerificationType
createPaymentVerification
Codec
Object
CreatePaymentRequestBody
(Maybe URL
-> Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody (Maybe URL)
-> Codec
Object
CreatePaymentRequestBody
(Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe URL) (Maybe URL)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"verificationSuccessfulUrl" ObjectCodec (Maybe URL) (Maybe URL)
-> (CreatePaymentRequestBody -> Maybe URL)
-> Codec Object CreatePaymentRequestBody (Maybe URL)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> Maybe URL
createPaymentVerificationSuccessUrl
Codec
Object
CreatePaymentRequestBody
(Maybe URL
-> PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody (Maybe URL)
-> Codec
Object
CreatePaymentRequestBody
(PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe URL) (Maybe URL)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"verificationFailureUrl" ObjectCodec (Maybe URL) (Maybe URL)
-> (CreatePaymentRequestBody -> Maybe URL)
-> Codec Object CreatePaymentRequestBody (Maybe URL)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> Maybe URL
createPaymentVerificationFailureUrl
Codec
Object
CreatePaymentRequestBody
(PaymentSource
-> Maybe Text
-> Maybe Text
-> Maybe UUID
-> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody PaymentSource
-> Codec
Object
CreatePaymentRequestBody
(Maybe Text
-> Maybe Text -> Maybe UUID -> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentSource PaymentSource
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"source" ObjectCodec PaymentSource PaymentSource
-> (CreatePaymentRequestBody -> PaymentSource)
-> Codec Object CreatePaymentRequestBody PaymentSource
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> PaymentSource
createPaymentSource
Codec
Object
CreatePaymentRequestBody
(Maybe Text
-> Maybe Text -> Maybe UUID -> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody (Maybe Text)
-> Codec
Object
CreatePaymentRequestBody
(Maybe Text -> Maybe UUID -> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"description" ObjectCodec (Maybe Text) (Maybe Text)
-> (CreatePaymentRequestBody -> Maybe Text)
-> Codec Object CreatePaymentRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> Maybe Text
createPaymentDescription
Codec
Object
CreatePaymentRequestBody
(Maybe Text -> Maybe UUID -> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody (Maybe Text)
-> Codec
Object
CreatePaymentRequestBody
(Maybe UUID -> CreatePaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"encryptedData" ObjectCodec (Maybe Text) (Maybe Text)
-> (CreatePaymentRequestBody -> Maybe Text)
-> Codec Object CreatePaymentRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> Maybe Text
createPaymentEncryptedData
Codec
Object
CreatePaymentRequestBody
(Maybe UUID -> CreatePaymentRequestBody)
-> Codec Object CreatePaymentRequestBody (Maybe UUID)
-> ObjectCodec CreatePaymentRequestBody CreatePaymentRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UUID) (Maybe UUID)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"channel" ObjectCodec (Maybe UUID) (Maybe UUID)
-> (CreatePaymentRequestBody -> Maybe UUID)
-> Codec Object CreatePaymentRequestBody (Maybe UUID)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentRequestBody -> Maybe UUID
createPaymentChannel
data RequestMetadata = RequestMetadata
{ RequestMetadata -> Email
requestMetadataEmail :: !Email,
RequestMetadata -> Maybe PhoneNumber
requestMetadataPhoneNumber :: !(Maybe PhoneNumber),
RequestMetadata -> SessionId
requestMetadataSessionId :: !SessionId,
RequestMetadata -> IPAddress
requestMetadataIpAddress :: !IPAddress
}
deriving (RequestMetadata -> RequestMetadata -> Bool
(RequestMetadata -> RequestMetadata -> Bool)
-> (RequestMetadata -> RequestMetadata -> Bool)
-> Eq RequestMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestMetadata -> RequestMetadata -> Bool
$c/= :: RequestMetadata -> RequestMetadata -> Bool
== :: RequestMetadata -> RequestMetadata -> Bool
$c== :: RequestMetadata -> RequestMetadata -> Bool
Eq, Int -> RequestMetadata -> ShowS
[RequestMetadata] -> ShowS
RequestMetadata -> String
(Int -> RequestMetadata -> ShowS)
-> (RequestMetadata -> String)
-> ([RequestMetadata] -> ShowS)
-> Show RequestMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestMetadata] -> ShowS
$cshowList :: [RequestMetadata] -> ShowS
show :: RequestMetadata -> String
$cshow :: RequestMetadata -> String
showsPrec :: Int -> RequestMetadata -> ShowS
$cshowsPrec :: Int -> RequestMetadata -> ShowS
Show)
deriving
( Value -> Parser [RequestMetadata]
Value -> Parser RequestMetadata
(Value -> Parser RequestMetadata)
-> (Value -> Parser [RequestMetadata]) -> FromJSON RequestMetadata
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RequestMetadata]
$cparseJSONList :: Value -> Parser [RequestMetadata]
parseJSON :: Value -> Parser RequestMetadata
$cparseJSON :: Value -> Parser RequestMetadata
FromJSON,
[RequestMetadata] -> Encoding
[RequestMetadata] -> Value
RequestMetadata -> Encoding
RequestMetadata -> Value
(RequestMetadata -> Value)
-> (RequestMetadata -> Encoding)
-> ([RequestMetadata] -> Value)
-> ([RequestMetadata] -> Encoding)
-> ToJSON RequestMetadata
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RequestMetadata] -> Encoding
$ctoEncodingList :: [RequestMetadata] -> Encoding
toJSONList :: [RequestMetadata] -> Value
$ctoJSONList :: [RequestMetadata] -> Value
toEncoding :: RequestMetadata -> Encoding
$ctoEncoding :: RequestMetadata -> Encoding
toJSON :: RequestMetadata -> Value
$ctoJSON :: RequestMetadata -> Value
ToJSON
)
via (Autodocodec RequestMetadata)
newtype SessionId = SessionId
{ SessionId -> Text
unSessionId :: Text
}
deriving (SessionId -> SessionId -> Bool
(SessionId -> SessionId -> Bool)
-> (SessionId -> SessionId -> Bool) -> Eq SessionId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SessionId -> SessionId -> Bool
$c/= :: SessionId -> SessionId -> Bool
== :: SessionId -> SessionId -> Bool
$c== :: SessionId -> SessionId -> Bool
Eq, Int -> SessionId -> ShowS
[SessionId] -> ShowS
SessionId -> String
(Int -> SessionId -> ShowS)
-> (SessionId -> String)
-> ([SessionId] -> ShowS)
-> Show SessionId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SessionId] -> ShowS
$cshowList :: [SessionId] -> ShowS
show :: SessionId -> String
$cshow :: SessionId -> String
showsPrec :: Int -> SessionId -> ShowS
$cshowsPrec :: Int -> SessionId -> ShowS
Show, [SessionId] -> Encoding
[SessionId] -> Value
SessionId -> Encoding
SessionId -> Value
(SessionId -> Value)
-> (SessionId -> Encoding)
-> ([SessionId] -> Value)
-> ([SessionId] -> Encoding)
-> ToJSON SessionId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SessionId] -> Encoding
$ctoEncodingList :: [SessionId] -> Encoding
toJSONList :: [SessionId] -> Value
$ctoJSONList :: [SessionId] -> Value
toEncoding :: SessionId -> Encoding
$ctoEncoding :: SessionId -> Encoding
toJSON :: SessionId -> Value
$ctoJSON :: SessionId -> Value
ToJSON, Value -> Parser [SessionId]
Value -> Parser SessionId
(Value -> Parser SessionId)
-> (Value -> Parser [SessionId]) -> FromJSON SessionId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SessionId]
$cparseJSONList :: Value -> Parser [SessionId]
parseJSON :: Value -> Parser SessionId
$cparseJSON :: Value -> Parser SessionId
FromJSON)
instance HasCodec SessionId where
codec :: JSONCodec SessionId
codec = (Text -> SessionId)
-> (SessionId -> Text)
-> Codec Value Text Text
-> JSONCodec SessionId
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> SessionId
SessionId SessionId -> Text
unSessionId Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype IPAddress = IPAddress
{ IPAddress -> Text
unIPAddress :: Text
}
deriving (IPAddress -> IPAddress -> Bool
(IPAddress -> IPAddress -> Bool)
-> (IPAddress -> IPAddress -> Bool) -> Eq IPAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IPAddress -> IPAddress -> Bool
$c/= :: IPAddress -> IPAddress -> Bool
== :: IPAddress -> IPAddress -> Bool
$c== :: IPAddress -> IPAddress -> Bool
Eq, Int -> IPAddress -> ShowS
[IPAddress] -> ShowS
IPAddress -> String
(Int -> IPAddress -> ShowS)
-> (IPAddress -> String)
-> ([IPAddress] -> ShowS)
-> Show IPAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IPAddress] -> ShowS
$cshowList :: [IPAddress] -> ShowS
show :: IPAddress -> String
$cshow :: IPAddress -> String
showsPrec :: Int -> IPAddress -> ShowS
$cshowsPrec :: Int -> IPAddress -> ShowS
Show, [IPAddress] -> Encoding
[IPAddress] -> Value
IPAddress -> Encoding
IPAddress -> Value
(IPAddress -> Value)
-> (IPAddress -> Encoding)
-> ([IPAddress] -> Value)
-> ([IPAddress] -> Encoding)
-> ToJSON IPAddress
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [IPAddress] -> Encoding
$ctoEncodingList :: [IPAddress] -> Encoding
toJSONList :: [IPAddress] -> Value
$ctoJSONList :: [IPAddress] -> Value
toEncoding :: IPAddress -> Encoding
$ctoEncoding :: IPAddress -> Encoding
toJSON :: IPAddress -> Value
$ctoJSON :: IPAddress -> Value
ToJSON, Value -> Parser [IPAddress]
Value -> Parser IPAddress
(Value -> Parser IPAddress)
-> (Value -> Parser [IPAddress]) -> FromJSON IPAddress
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [IPAddress]
$cparseJSONList :: Value -> Parser [IPAddress]
parseJSON :: Value -> Parser IPAddress
$cparseJSON :: Value -> Parser IPAddress
FromJSON)
instance HasCodec IPAddress where
codec :: JSONCodec IPAddress
codec = (Text -> IPAddress)
-> (IPAddress -> Text)
-> Codec Value Text Text
-> JSONCodec IPAddress
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> IPAddress
IPAddress IPAddress -> Text
unIPAddress Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype PhoneNumber = PhoneNumber
{ PhoneNumber -> Text
unPhoneNumber :: Text
}
deriving (PhoneNumber -> PhoneNumber -> Bool
(PhoneNumber -> PhoneNumber -> Bool)
-> (PhoneNumber -> PhoneNumber -> Bool) -> Eq PhoneNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhoneNumber -> PhoneNumber -> Bool
$c/= :: PhoneNumber -> PhoneNumber -> Bool
== :: PhoneNumber -> PhoneNumber -> Bool
$c== :: PhoneNumber -> PhoneNumber -> Bool
Eq, Int -> PhoneNumber -> ShowS
[PhoneNumber] -> ShowS
PhoneNumber -> String
(Int -> PhoneNumber -> ShowS)
-> (PhoneNumber -> String)
-> ([PhoneNumber] -> ShowS)
-> Show PhoneNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PhoneNumber] -> ShowS
$cshowList :: [PhoneNumber] -> ShowS
show :: PhoneNumber -> String
$cshow :: PhoneNumber -> String
showsPrec :: Int -> PhoneNumber -> ShowS
$cshowsPrec :: Int -> PhoneNumber -> ShowS
Show, [PhoneNumber] -> Encoding
[PhoneNumber] -> Value
PhoneNumber -> Encoding
PhoneNumber -> Value
(PhoneNumber -> Value)
-> (PhoneNumber -> Encoding)
-> ([PhoneNumber] -> Value)
-> ([PhoneNumber] -> Encoding)
-> ToJSON PhoneNumber
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PhoneNumber] -> Encoding
$ctoEncodingList :: [PhoneNumber] -> Encoding
toJSONList :: [PhoneNumber] -> Value
$ctoJSONList :: [PhoneNumber] -> Value
toEncoding :: PhoneNumber -> Encoding
$ctoEncoding :: PhoneNumber -> Encoding
toJSON :: PhoneNumber -> Value
$ctoJSON :: PhoneNumber -> Value
ToJSON, Value -> Parser [PhoneNumber]
Value -> Parser PhoneNumber
(Value -> Parser PhoneNumber)
-> (Value -> Parser [PhoneNumber]) -> FromJSON PhoneNumber
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PhoneNumber]
$cparseJSONList :: Value -> Parser [PhoneNumber]
parseJSON :: Value -> Parser PhoneNumber
$cparseJSON :: Value -> Parser PhoneNumber
FromJSON)
instance HasCodec PhoneNumber where
codec :: JSONCodec PhoneNumber
codec = (Text -> PhoneNumber)
-> (PhoneNumber -> Text)
-> Codec Value Text Text
-> JSONCodec PhoneNumber
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> PhoneNumber
PhoneNumber PhoneNumber -> Text
unPhoneNumber Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
instance HasCodec RequestMetadata where
codec :: JSONCodec RequestMetadata
codec =
Text
-> ObjectCodec RequestMetadata RequestMetadata
-> JSONCodec RequestMetadata
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"RequestMetadata" (ObjectCodec RequestMetadata RequestMetadata
-> JSONCodec RequestMetadata)
-> ObjectCodec RequestMetadata RequestMetadata
-> JSONCodec RequestMetadata
forall a b. (a -> b) -> a -> b
$
Email
-> Maybe PhoneNumber -> SessionId -> IPAddress -> RequestMetadata
RequestMetadata
(Email
-> Maybe PhoneNumber -> SessionId -> IPAddress -> RequestMetadata)
-> Codec Object RequestMetadata Email
-> Codec
Object
RequestMetadata
(Maybe PhoneNumber -> SessionId -> IPAddress -> RequestMetadata)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Email Email
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"email" ObjectCodec Email Email
-> (RequestMetadata -> Email) -> Codec Object RequestMetadata Email
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RequestMetadata -> Email
requestMetadataEmail
Codec
Object
RequestMetadata
(Maybe PhoneNumber -> SessionId -> IPAddress -> RequestMetadata)
-> Codec Object RequestMetadata (Maybe PhoneNumber)
-> Codec
Object RequestMetadata (SessionId -> IPAddress -> RequestMetadata)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe PhoneNumber) (Maybe PhoneNumber)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"phoneNumber" ObjectCodec (Maybe PhoneNumber) (Maybe PhoneNumber)
-> (RequestMetadata -> Maybe PhoneNumber)
-> Codec Object RequestMetadata (Maybe PhoneNumber)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RequestMetadata -> Maybe PhoneNumber
requestMetadataPhoneNumber
Codec
Object RequestMetadata (SessionId -> IPAddress -> RequestMetadata)
-> Codec Object RequestMetadata SessionId
-> Codec Object RequestMetadata (IPAddress -> RequestMetadata)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SessionId SessionId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"sessionId" ObjectCodec SessionId SessionId
-> (RequestMetadata -> SessionId)
-> Codec Object RequestMetadata SessionId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RequestMetadata -> SessionId
requestMetadataSessionId
Codec Object RequestMetadata (IPAddress -> RequestMetadata)
-> Codec Object RequestMetadata IPAddress
-> ObjectCodec RequestMetadata RequestMetadata
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec IPAddress IPAddress
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"ipAddress" ObjectCodec IPAddress IPAddress
-> (RequestMetadata -> IPAddress)
-> Codec Object RequestMetadata IPAddress
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RequestMetadata -> IPAddress
requestMetadataIpAddress
data PaymentErrorCode
= PaymentFailedErrorCode
| PaymentFraudDetected
| PaymentDenied
| PaymentNotSupportedByIssuer
| PaymentNotFunded
| PaymentUnprocessable
| PaymentStoppedByIssuer
| PaymentCanceled
| PaymentReturned
| PaymentFailedBalanceCheck
| CardFailed
| CardInvalid
| CardAddressMismatch
| CardZipMismatch
| CardCvvInvalid
| CardExpired
| CardLimitViolated
| CardNotHonored
| CardCvvRequired
| CardRestricted
| CardAccountIneligible
| CardNetworkUnsupported
| ChannelInvalid
| UnauthorizedTransaction
| BankAccountIneligible
| PaymentBankTransactionError
| InvalidAccountNumber
| InvalidWireRtn
| InvalidAchRtn
| RefIdInvalid
| AccountNameMismatch
| AccountNumberMismatch
| AccountIneligible
| WalletAddressMismatch
| CustomerNameMismatch
| InstitutionNameMismatch
| PaymentVendorInactive
deriving (PaymentErrorCode -> PaymentErrorCode -> Bool
(PaymentErrorCode -> PaymentErrorCode -> Bool)
-> (PaymentErrorCode -> PaymentErrorCode -> Bool)
-> Eq PaymentErrorCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentErrorCode -> PaymentErrorCode -> Bool
$c/= :: PaymentErrorCode -> PaymentErrorCode -> Bool
== :: PaymentErrorCode -> PaymentErrorCode -> Bool
$c== :: PaymentErrorCode -> PaymentErrorCode -> Bool
Eq, Int -> PaymentErrorCode -> ShowS
[PaymentErrorCode] -> ShowS
PaymentErrorCode -> String
(Int -> PaymentErrorCode -> ShowS)
-> (PaymentErrorCode -> String)
-> ([PaymentErrorCode] -> ShowS)
-> Show PaymentErrorCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentErrorCode] -> ShowS
$cshowList :: [PaymentErrorCode] -> ShowS
show :: PaymentErrorCode -> String
$cshow :: PaymentErrorCode -> String
showsPrec :: Int -> PaymentErrorCode -> ShowS
$cshowsPrec :: Int -> PaymentErrorCode -> ShowS
Show)
deriving
( Value -> Parser [PaymentErrorCode]
Value -> Parser PaymentErrorCode
(Value -> Parser PaymentErrorCode)
-> (Value -> Parser [PaymentErrorCode])
-> FromJSON PaymentErrorCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentErrorCode]
$cparseJSONList :: Value -> Parser [PaymentErrorCode]
parseJSON :: Value -> Parser PaymentErrorCode
$cparseJSON :: Value -> Parser PaymentErrorCode
FromJSON,
[PaymentErrorCode] -> Encoding
[PaymentErrorCode] -> Value
PaymentErrorCode -> Encoding
PaymentErrorCode -> Value
(PaymentErrorCode -> Value)
-> (PaymentErrorCode -> Encoding)
-> ([PaymentErrorCode] -> Value)
-> ([PaymentErrorCode] -> Encoding)
-> ToJSON PaymentErrorCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentErrorCode] -> Encoding
$ctoEncodingList :: [PaymentErrorCode] -> Encoding
toJSONList :: [PaymentErrorCode] -> Value
$ctoJSONList :: [PaymentErrorCode] -> Value
toEncoding :: PaymentErrorCode -> Encoding
$ctoEncoding :: PaymentErrorCode -> Encoding
toJSON :: PaymentErrorCode -> Value
$ctoJSON :: PaymentErrorCode -> Value
ToJSON
)
via (Autodocodec PaymentErrorCode)
instance HasCodec PaymentErrorCode where
codec :: JSONCodec PaymentErrorCode
codec =
NonEmpty (PaymentErrorCode, Text) -> JSONCodec PaymentErrorCode
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (PaymentErrorCode, Text) -> JSONCodec PaymentErrorCode)
-> NonEmpty (PaymentErrorCode, Text) -> JSONCodec PaymentErrorCode
forall a b. (a -> b) -> a -> b
$
[(PaymentErrorCode, Text)] -> NonEmpty (PaymentErrorCode, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (PaymentErrorCode
PaymentFailedErrorCode, Text
"payment_failed"),
(PaymentErrorCode
PaymentFraudDetected, Text
"payment_fraud_detected"),
(PaymentErrorCode
PaymentDenied, Text
"payment_denied"),
(PaymentErrorCode
PaymentNotSupportedByIssuer, Text
"payment_not_supported_by_issuer"),
(PaymentErrorCode
PaymentNotFunded, Text
"payment_not_funded"),
(PaymentErrorCode
PaymentUnprocessable, Text
"payment_unprocessable"),
(PaymentErrorCode
PaymentStoppedByIssuer, Text
"payment_stopped_by_issuer"),
(PaymentErrorCode
PaymentCanceled, Text
"payment_canceled"),
(PaymentErrorCode
PaymentReturned, Text
"payment_returned"),
(PaymentErrorCode
PaymentFailedBalanceCheck, Text
"payment_failed_balance_check"),
(PaymentErrorCode
CardFailed, Text
"card_failed"),
(PaymentErrorCode
CardInvalid, Text
"card_invalid"),
(PaymentErrorCode
CardAddressMismatch, Text
"card_address_mismatch"),
(PaymentErrorCode
CardZipMismatch, Text
"card_zip_mismatch"),
(PaymentErrorCode
CardCvvInvalid, Text
"card_cvv_invalid"),
(PaymentErrorCode
CardExpired, Text
"card_expired"),
(PaymentErrorCode
CardLimitViolated, Text
"card_limit_violated"),
(PaymentErrorCode
CardNotHonored, Text
"card_not_honored"),
(PaymentErrorCode
CardCvvRequired, Text
"card_cvv_required"),
(PaymentErrorCode
CardRestricted, Text
"card_restricted"),
(PaymentErrorCode
CardAccountIneligible, Text
"card_account_ineligible"),
(PaymentErrorCode
CardNetworkUnsupported, Text
"card_network_unsupported"),
(PaymentErrorCode
ChannelInvalid, Text
"channel_invalid"),
(PaymentErrorCode
UnauthorizedTransaction, Text
"unauthorized_transaction"),
(PaymentErrorCode
BankAccountIneligible, Text
"bank_account_ineligible"),
(PaymentErrorCode
PaymentBankTransactionError, Text
"bank_transaction_error"),
(PaymentErrorCode
InvalidAccountNumber, Text
"invalid_account_number"),
(PaymentErrorCode
InvalidWireRtn, Text
"invalid_wire_rtn"),
(PaymentErrorCode
InvalidAchRtn, Text
"invalid_ach_rtn"),
(PaymentErrorCode
RefIdInvalid, Text
"ref_id_invalid"),
(PaymentErrorCode
AccountNameMismatch, Text
"account_name_mismatch"),
(PaymentErrorCode
AccountNumberMismatch, Text
"account_number_mismatch"),
(PaymentErrorCode
AccountIneligible, Text
"account_ineligible"),
(PaymentErrorCode
WalletAddressMismatch, Text
"wallet_address_mismatch"),
(PaymentErrorCode
CustomerNameMismatch, Text
"customer_name_mismatch"),
(PaymentErrorCode
InstitutionNameMismatch, Text
"institution_name_mismatch"),
(PaymentErrorCode
PaymentVendorInactive, Text
"vendor_inactive")
]
data FiatOrCryptoPaymentResponseBody = FiatOrCryptoPaymentResponseBody
{
FiatOrCryptoPaymentResponseBody -> UUID
fiatOrCryptoPaymentId :: !UUID,
FiatOrCryptoPaymentResponseBody -> PaymentType
fiatOrCryptoPaymentType :: !PaymentType,
FiatOrCryptoPaymentResponseBody -> UUID
fiatOrCryptoPaymentMerchantId :: !UUID,
FiatOrCryptoPaymentResponseBody -> WalletId
fiatOrCryptoPaymentMerchantWalletId :: !WalletId,
FiatOrCryptoPaymentResponseBody -> MoneyAmount
fiatOrCryptoPaymentAmount :: !MoneyAmount,
FiatOrCryptoPaymentResponseBody -> PaymentSource
fiatOrCryptoPaymentSource :: !PaymentSource,
FiatOrCryptoPaymentResponseBody -> Text
fiatOrCryptoPaymentDescription :: !Text,
FiatOrCryptoPaymentResponseBody -> PaymentStatus
fiatOrCryptoPaymentStatus :: !PaymentStatus,
FiatOrCryptoPaymentResponseBody -> Maybe UUID
fiatOrCryptoPaymentPaymentIntentId :: !(Maybe UUID),
FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount
fiatOrCryptoPaymentSettlementAmount :: !(Maybe MoneyAmount),
FiatOrCryptoPaymentResponseBody -> Maybe PaymentDepositAddress
fiatOrCryptoPaymentDepositAddress :: !(Maybe PaymentDepositAddress),
FiatOrCryptoPaymentResponseBody -> Maybe HexString
fiatOrCryptoPaymentTransactionHash :: !(Maybe HexString),
FiatOrCryptoPaymentResponseBody -> Maybe VerificationData
fiatOrCryptoPaymentVerification :: !(Maybe VerificationData),
FiatOrCryptoPaymentResponseBody -> Maybe Bool
fiatOrCryptoPaymentCaptured :: !(Maybe Bool),
FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount
fiatOrCryptoPaymentCaptureAmount :: !(Maybe MoneyAmount),
FiatOrCryptoPaymentResponseBody -> Maybe UTCTime
fiatOrCryptoPaymentCaptureDate :: !(Maybe UTCTime),
FiatOrCryptoPaymentResponseBody -> Maybe PaymentActionRequired
fiatOrCryptoPaymentRequiredAction :: !(Maybe PaymentActionRequired),
FiatOrCryptoPaymentResponseBody
-> Maybe FiatCancelOrRefundResponseBody
fiatOrCryptoPaymentCancel :: !(Maybe FiatCancelOrRefundResponseBody),
FiatOrCryptoPaymentResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
fiatOrCryptoPaymentRefunds :: !(Maybe [FiatCancelOrRefundResponseBody]),
FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount
fiatOrCryptoPaymentFees :: !(Maybe MoneyAmount),
FiatOrCryptoPaymentResponseBody -> Maybe UUID
fiatOrCryptoPaymentChannel :: !(Maybe UUID),
FiatOrCryptoPaymentResponseBody -> Maybe UTCTime
fiatOrCryptoPaymentCreateDate :: !(Maybe UTCTime),
FiatOrCryptoPaymentResponseBody -> Maybe UTCTime
fiatOrCryptoPaymentUpdateDate :: !(Maybe UTCTime),
FiatOrCryptoPaymentResponseBody -> Maybe TrackingReference
fiatOrCryptoPaymentTrackingRef :: !(Maybe TrackingReference),
FiatOrCryptoPaymentResponseBody -> Maybe PaymentErrorCode
fiatOrCryptoPaymentErrorCode :: !(Maybe PaymentErrorCode),
FiatOrCryptoPaymentResponseBody -> Maybe ResponseMetadata
fiatOrCryptoMetadata :: !(Maybe ResponseMetadata),
FiatOrCryptoPaymentResponseBody -> Maybe RiskEvaluation
fiatOrCryptoPaymentRiskEvaluation :: !(Maybe RiskEvaluation)
}
deriving (FiatOrCryptoPaymentResponseBody
-> FiatOrCryptoPaymentResponseBody -> Bool
(FiatOrCryptoPaymentResponseBody
-> FiatOrCryptoPaymentResponseBody -> Bool)
-> (FiatOrCryptoPaymentResponseBody
-> FiatOrCryptoPaymentResponseBody -> Bool)
-> Eq FiatOrCryptoPaymentResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FiatOrCryptoPaymentResponseBody
-> FiatOrCryptoPaymentResponseBody -> Bool
$c/= :: FiatOrCryptoPaymentResponseBody
-> FiatOrCryptoPaymentResponseBody -> Bool
== :: FiatOrCryptoPaymentResponseBody
-> FiatOrCryptoPaymentResponseBody -> Bool
$c== :: FiatOrCryptoPaymentResponseBody
-> FiatOrCryptoPaymentResponseBody -> Bool
Eq, Int -> FiatOrCryptoPaymentResponseBody -> ShowS
[FiatOrCryptoPaymentResponseBody] -> ShowS
FiatOrCryptoPaymentResponseBody -> String
(Int -> FiatOrCryptoPaymentResponseBody -> ShowS)
-> (FiatOrCryptoPaymentResponseBody -> String)
-> ([FiatOrCryptoPaymentResponseBody] -> ShowS)
-> Show FiatOrCryptoPaymentResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FiatOrCryptoPaymentResponseBody] -> ShowS
$cshowList :: [FiatOrCryptoPaymentResponseBody] -> ShowS
show :: FiatOrCryptoPaymentResponseBody -> String
$cshow :: FiatOrCryptoPaymentResponseBody -> String
showsPrec :: Int -> FiatOrCryptoPaymentResponseBody -> ShowS
$cshowsPrec :: Int -> FiatOrCryptoPaymentResponseBody -> ShowS
Show)
deriving
( Value -> Parser [FiatOrCryptoPaymentResponseBody]
Value -> Parser FiatOrCryptoPaymentResponseBody
(Value -> Parser FiatOrCryptoPaymentResponseBody)
-> (Value -> Parser [FiatOrCryptoPaymentResponseBody])
-> FromJSON FiatOrCryptoPaymentResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [FiatOrCryptoPaymentResponseBody]
$cparseJSONList :: Value -> Parser [FiatOrCryptoPaymentResponseBody]
parseJSON :: Value -> Parser FiatOrCryptoPaymentResponseBody
$cparseJSON :: Value -> Parser FiatOrCryptoPaymentResponseBody
FromJSON,
[FiatOrCryptoPaymentResponseBody] -> Encoding
[FiatOrCryptoPaymentResponseBody] -> Value
FiatOrCryptoPaymentResponseBody -> Encoding
FiatOrCryptoPaymentResponseBody -> Value
(FiatOrCryptoPaymentResponseBody -> Value)
-> (FiatOrCryptoPaymentResponseBody -> Encoding)
-> ([FiatOrCryptoPaymentResponseBody] -> Value)
-> ([FiatOrCryptoPaymentResponseBody] -> Encoding)
-> ToJSON FiatOrCryptoPaymentResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FiatOrCryptoPaymentResponseBody] -> Encoding
$ctoEncodingList :: [FiatOrCryptoPaymentResponseBody] -> Encoding
toJSONList :: [FiatOrCryptoPaymentResponseBody] -> Value
$ctoJSONList :: [FiatOrCryptoPaymentResponseBody] -> Value
toEncoding :: FiatOrCryptoPaymentResponseBody -> Encoding
$ctoEncoding :: FiatOrCryptoPaymentResponseBody -> Encoding
toJSON :: FiatOrCryptoPaymentResponseBody -> Value
$ctoJSON :: FiatOrCryptoPaymentResponseBody -> Value
ToJSON
)
via (Autodocodec FiatOrCryptoPaymentResponseBody)
instance HasCodec FiatOrCryptoPaymentResponseBody where
codec :: JSONCodec FiatOrCryptoPaymentResponseBody
codec =
Text
-> ObjectCodec
FiatOrCryptoPaymentResponseBody FiatOrCryptoPaymentResponseBody
-> JSONCodec FiatOrCryptoPaymentResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"FiatOrCryptoPaymentResponseBody" (ObjectCodec
FiatOrCryptoPaymentResponseBody FiatOrCryptoPaymentResponseBody
-> JSONCodec FiatOrCryptoPaymentResponseBody)
-> ObjectCodec
FiatOrCryptoPaymentResponseBody FiatOrCryptoPaymentResponseBody
-> JSONCodec FiatOrCryptoPaymentResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody
FiatOrCryptoPaymentResponseBody
(UUID
-> PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody UUID
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (FiatOrCryptoPaymentResponseBody -> UUID)
-> Codec Object FiatOrCryptoPaymentResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> UUID
fiatOrCryptoPaymentId
Codec
Object
FiatOrCryptoPaymentResponseBody
(PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody PaymentType
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentType PaymentType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec PaymentType PaymentType
-> (FiatOrCryptoPaymentResponseBody -> PaymentType)
-> Codec Object FiatOrCryptoPaymentResponseBody PaymentType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> PaymentType
fiatOrCryptoPaymentType
Codec
Object
FiatOrCryptoPaymentResponseBody
(UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody UUID
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"merchantId" ObjectCodec UUID UUID
-> (FiatOrCryptoPaymentResponseBody -> UUID)
-> Codec Object FiatOrCryptoPaymentResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> UUID
fiatOrCryptoPaymentMerchantId
Codec
Object
FiatOrCryptoPaymentResponseBody
(WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody WalletId
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec WalletId WalletId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"merchantWalletId" ObjectCodec WalletId WalletId
-> (FiatOrCryptoPaymentResponseBody -> WalletId)
-> Codec Object FiatOrCryptoPaymentResponseBody WalletId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> WalletId
fiatOrCryptoPaymentMerchantWalletId
Codec
Object
FiatOrCryptoPaymentResponseBody
(MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody MoneyAmount
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (FiatOrCryptoPaymentResponseBody -> MoneyAmount)
-> Codec Object FiatOrCryptoPaymentResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> MoneyAmount
fiatOrCryptoPaymentAmount
Codec
Object
FiatOrCryptoPaymentResponseBody
(PaymentSource
-> Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody PaymentSource
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentSource PaymentSource
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"source" ObjectCodec PaymentSource PaymentSource
-> (FiatOrCryptoPaymentResponseBody -> PaymentSource)
-> Codec Object FiatOrCryptoPaymentResponseBody PaymentSource
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> PaymentSource
fiatOrCryptoPaymentSource
Codec
Object
FiatOrCryptoPaymentResponseBody
(Text
-> PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody Text
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (FiatOrCryptoPaymentResponseBody -> Text)
-> Codec Object FiatOrCryptoPaymentResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Text
fiatOrCryptoPaymentDescription
Codec
Object
FiatOrCryptoPaymentResponseBody
(PaymentStatus
-> Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody PaymentStatus
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentStatus PaymentStatus
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec PaymentStatus PaymentStatus
-> (FiatOrCryptoPaymentResponseBody -> PaymentStatus)
-> Codec Object FiatOrCryptoPaymentResponseBody PaymentStatus
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> PaymentStatus
fiatOrCryptoPaymentStatus
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UUID
-> Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UUID)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UUID) (Maybe UUID)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"paymentIntentId" ObjectCodec (Maybe UUID) (Maybe UUID)
-> (FiatOrCryptoPaymentResponseBody -> Maybe UUID)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UUID)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe UUID
fiatOrCryptoPaymentPaymentIntentId
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe MoneyAmount
-> Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe MoneyAmount)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"settlementAmount" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount
fiatOrCryptoPaymentSettlementAmount
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentDepositAddress
-> Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentDepositAddress)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe PaymentDepositAddress) (Maybe PaymentDepositAddress)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"depositAddress" ObjectCodec
(Maybe PaymentDepositAddress) (Maybe PaymentDepositAddress)
-> (FiatOrCryptoPaymentResponseBody -> Maybe PaymentDepositAddress)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentDepositAddress)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe PaymentDepositAddress
fiatOrCryptoPaymentDepositAddress
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe HexString
-> Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe HexString)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe HexString) (Maybe HexString)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"transactionHash" ObjectCodec (Maybe HexString) (Maybe HexString)
-> (FiatOrCryptoPaymentResponseBody -> Maybe HexString)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe HexString)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe HexString
fiatOrCryptoPaymentTransactionHash
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe VerificationData
-> Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe VerificationData)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec (Maybe VerificationData) (Maybe VerificationData)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"verification" ObjectCodec (Maybe VerificationData) (Maybe VerificationData)
-> (FiatOrCryptoPaymentResponseBody -> Maybe VerificationData)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe VerificationData)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe VerificationData
fiatOrCryptoPaymentVerification
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe Bool
-> Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe Bool)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Bool) (Maybe Bool)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"captured" ObjectCodec (Maybe Bool) (Maybe Bool)
-> (FiatOrCryptoPaymentResponseBody -> Maybe Bool)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe Bool)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe Bool
fiatOrCryptoPaymentCaptured
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe MoneyAmount
-> Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe MoneyAmount)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"captureAmount" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount
fiatOrCryptoPaymentCaptureAmount
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UTCTime
-> Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UTCTime)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"captureDate" ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
-> (FiatOrCryptoPaymentResponseBody -> Maybe UTCTime)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UTCTime)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe UTCTime
fiatOrCryptoPaymentCaptureDate
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentActionRequired
-> Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentActionRequired)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe PaymentActionRequired) (Maybe PaymentActionRequired)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"requiredAction" ObjectCodec
(Maybe PaymentActionRequired) (Maybe PaymentActionRequired)
-> (FiatOrCryptoPaymentResponseBody -> Maybe PaymentActionRequired)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentActionRequired)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe PaymentActionRequired
fiatOrCryptoPaymentRequiredAction
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe FiatCancelOrRefundResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe FiatCancelOrRefundResponseBody)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe FiatCancelOrRefundResponseBody)
(Maybe FiatCancelOrRefundResponseBody)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"cancel" ObjectCodec
(Maybe FiatCancelOrRefundResponseBody)
(Maybe FiatCancelOrRefundResponseBody)
-> (FiatOrCryptoPaymentResponseBody
-> Maybe FiatCancelOrRefundResponseBody)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe FiatCancelOrRefundResponseBody)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody
-> Maybe FiatCancelOrRefundResponseBody
fiatOrCryptoPaymentCancel
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe [FiatCancelOrRefundResponseBody]
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe [FiatCancelOrRefundResponseBody])
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe [FiatCancelOrRefundResponseBody])
(Maybe [FiatCancelOrRefundResponseBody])
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"refunds" ObjectCodec
(Maybe [FiatCancelOrRefundResponseBody])
(Maybe [FiatCancelOrRefundResponseBody])
-> (FiatOrCryptoPaymentResponseBody
-> Maybe [FiatCancelOrRefundResponseBody])
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe [FiatCancelOrRefundResponseBody])
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody
-> Maybe [FiatCancelOrRefundResponseBody]
fiatOrCryptoPaymentRefunds
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe MoneyAmount
-> Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe MoneyAmount)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"fees" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe MoneyAmount
fiatOrCryptoPaymentFees
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UUID
-> Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UUID)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UUID) (Maybe UUID)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"channel" ObjectCodec (Maybe UUID) (Maybe UUID)
-> (FiatOrCryptoPaymentResponseBody -> Maybe UUID)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UUID)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe UUID
fiatOrCryptoPaymentChannel
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UTCTime
-> Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UTCTime)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"createDate" ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
-> (FiatOrCryptoPaymentResponseBody -> Maybe UTCTime)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UTCTime)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe UTCTime
fiatOrCryptoPaymentCreateDate
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe UTCTime
-> Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UTCTime)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"updateDate" ObjectCodec (Maybe UTCTime) (Maybe UTCTime)
-> (FiatOrCryptoPaymentResponseBody -> Maybe UTCTime)
-> Codec Object FiatOrCryptoPaymentResponseBody (Maybe UTCTime)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe UTCTime
fiatOrCryptoPaymentUpdateDate
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe TrackingReference
-> Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe TrackingReference)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"trackingRef" ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
-> (FiatOrCryptoPaymentResponseBody -> Maybe TrackingReference)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe TrackingReference)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe TrackingReference
fiatOrCryptoPaymentTrackingRef
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe PaymentErrorCode
-> Maybe ResponseMetadata
-> Maybe RiskEvaluation
-> FiatOrCryptoPaymentResponseBody)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe PaymentErrorCode)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe ResponseMetadata
-> Maybe RiskEvaluation -> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec (Maybe PaymentErrorCode) (Maybe PaymentErrorCode)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"errorCode" ObjectCodec (Maybe PaymentErrorCode) (Maybe PaymentErrorCode)
-> (FiatOrCryptoPaymentResponseBody -> Maybe PaymentErrorCode)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe PaymentErrorCode)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe PaymentErrorCode
fiatOrCryptoPaymentErrorCode
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe ResponseMetadata
-> Maybe RiskEvaluation -> FiatOrCryptoPaymentResponseBody)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe ResponseMetadata)
-> Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe RiskEvaluation -> FiatOrCryptoPaymentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec (Maybe ResponseMetadata) (Maybe ResponseMetadata)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"metadata" ObjectCodec (Maybe ResponseMetadata) (Maybe ResponseMetadata)
-> (FiatOrCryptoPaymentResponseBody -> Maybe ResponseMetadata)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe ResponseMetadata)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe ResponseMetadata
fiatOrCryptoMetadata
Codec
Object
FiatOrCryptoPaymentResponseBody
(Maybe RiskEvaluation -> FiatOrCryptoPaymentResponseBody)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe RiskEvaluation)
-> ObjectCodec
FiatOrCryptoPaymentResponseBody FiatOrCryptoPaymentResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"channel" ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
-> (FiatOrCryptoPaymentResponseBody -> Maybe RiskEvaluation)
-> Codec
Object FiatOrCryptoPaymentResponseBody (Maybe RiskEvaluation)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatOrCryptoPaymentResponseBody -> Maybe RiskEvaluation
fiatOrCryptoPaymentRiskEvaluation
data ResponseMetadata = ResponseMetadata
{ ResponseMetadata -> Email
responseMetadataEmail :: !Email,
ResponseMetadata -> Maybe PhoneNumber
responseMetadataPhoneNumber :: !(Maybe PhoneNumber)
}
deriving (ResponseMetadata -> ResponseMetadata -> Bool
(ResponseMetadata -> ResponseMetadata -> Bool)
-> (ResponseMetadata -> ResponseMetadata -> Bool)
-> Eq ResponseMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResponseMetadata -> ResponseMetadata -> Bool
$c/= :: ResponseMetadata -> ResponseMetadata -> Bool
== :: ResponseMetadata -> ResponseMetadata -> Bool
$c== :: ResponseMetadata -> ResponseMetadata -> Bool
Eq, Int -> ResponseMetadata -> ShowS
[ResponseMetadata] -> ShowS
ResponseMetadata -> String
(Int -> ResponseMetadata -> ShowS)
-> (ResponseMetadata -> String)
-> ([ResponseMetadata] -> ShowS)
-> Show ResponseMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResponseMetadata] -> ShowS
$cshowList :: [ResponseMetadata] -> ShowS
show :: ResponseMetadata -> String
$cshow :: ResponseMetadata -> String
showsPrec :: Int -> ResponseMetadata -> ShowS
$cshowsPrec :: Int -> ResponseMetadata -> ShowS
Show)
deriving
( Value -> Parser [ResponseMetadata]
Value -> Parser ResponseMetadata
(Value -> Parser ResponseMetadata)
-> (Value -> Parser [ResponseMetadata])
-> FromJSON ResponseMetadata
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ResponseMetadata]
$cparseJSONList :: Value -> Parser [ResponseMetadata]
parseJSON :: Value -> Parser ResponseMetadata
$cparseJSON :: Value -> Parser ResponseMetadata
FromJSON,
[ResponseMetadata] -> Encoding
[ResponseMetadata] -> Value
ResponseMetadata -> Encoding
ResponseMetadata -> Value
(ResponseMetadata -> Value)
-> (ResponseMetadata -> Encoding)
-> ([ResponseMetadata] -> Value)
-> ([ResponseMetadata] -> Encoding)
-> ToJSON ResponseMetadata
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ResponseMetadata] -> Encoding
$ctoEncodingList :: [ResponseMetadata] -> Encoding
toJSONList :: [ResponseMetadata] -> Value
$ctoJSONList :: [ResponseMetadata] -> Value
toEncoding :: ResponseMetadata -> Encoding
$ctoEncoding :: ResponseMetadata -> Encoding
toJSON :: ResponseMetadata -> Value
$ctoJSON :: ResponseMetadata -> Value
ToJSON
)
via (Autodocodec ResponseMetadata)
instance HasCodec ResponseMetadata where
codec :: JSONCodec ResponseMetadata
codec =
Text
-> ObjectCodec ResponseMetadata ResponseMetadata
-> JSONCodec ResponseMetadata
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ResponseMetadata" (ObjectCodec ResponseMetadata ResponseMetadata
-> JSONCodec ResponseMetadata)
-> ObjectCodec ResponseMetadata ResponseMetadata
-> JSONCodec ResponseMetadata
forall a b. (a -> b) -> a -> b
$
Email -> Maybe PhoneNumber -> ResponseMetadata
ResponseMetadata
(Email -> Maybe PhoneNumber -> ResponseMetadata)
-> Codec Object ResponseMetadata Email
-> Codec
Object ResponseMetadata (Maybe PhoneNumber -> ResponseMetadata)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Email Email
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"email" ObjectCodec Email Email
-> (ResponseMetadata -> Email)
-> Codec Object ResponseMetadata Email
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ResponseMetadata -> Email
responseMetadataEmail
Codec
Object ResponseMetadata (Maybe PhoneNumber -> ResponseMetadata)
-> Codec Object ResponseMetadata (Maybe PhoneNumber)
-> ObjectCodec ResponseMetadata ResponseMetadata
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe PhoneNumber) (Maybe PhoneNumber)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"phoneNumber" ObjectCodec (Maybe PhoneNumber) (Maybe PhoneNumber)
-> (ResponseMetadata -> Maybe PhoneNumber)
-> Codec Object ResponseMetadata (Maybe PhoneNumber)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ResponseMetadata -> Maybe PhoneNumber
responseMetadataPhoneNumber
data VerificationData = VerificationData
{ VerificationData -> AVS
verificationAVS :: !AVS,
VerificationData -> CVV
verificationCVV :: !CVV
}
deriving (VerificationData -> VerificationData -> Bool
(VerificationData -> VerificationData -> Bool)
-> (VerificationData -> VerificationData -> Bool)
-> Eq VerificationData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationData -> VerificationData -> Bool
$c/= :: VerificationData -> VerificationData -> Bool
== :: VerificationData -> VerificationData -> Bool
$c== :: VerificationData -> VerificationData -> Bool
Eq, Int -> VerificationData -> ShowS
[VerificationData] -> ShowS
VerificationData -> String
(Int -> VerificationData -> ShowS)
-> (VerificationData -> String)
-> ([VerificationData] -> ShowS)
-> Show VerificationData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationData] -> ShowS
$cshowList :: [VerificationData] -> ShowS
show :: VerificationData -> String
$cshow :: VerificationData -> String
showsPrec :: Int -> VerificationData -> ShowS
$cshowsPrec :: Int -> VerificationData -> ShowS
Show, (forall x. VerificationData -> Rep VerificationData x)
-> (forall x. Rep VerificationData x -> VerificationData)
-> Generic VerificationData
forall x. Rep VerificationData x -> VerificationData
forall x. VerificationData -> Rep VerificationData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerificationData x -> VerificationData
$cfrom :: forall x. VerificationData -> Rep VerificationData x
Generic)
deriving
( Value -> Parser [VerificationData]
Value -> Parser VerificationData
(Value -> Parser VerificationData)
-> (Value -> Parser [VerificationData])
-> FromJSON VerificationData
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [VerificationData]
$cparseJSONList :: Value -> Parser [VerificationData]
parseJSON :: Value -> Parser VerificationData
$cparseJSON :: Value -> Parser VerificationData
FromJSON,
[VerificationData] -> Encoding
[VerificationData] -> Value
VerificationData -> Encoding
VerificationData -> Value
(VerificationData -> Value)
-> (VerificationData -> Encoding)
-> ([VerificationData] -> Value)
-> ([VerificationData] -> Encoding)
-> ToJSON VerificationData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [VerificationData] -> Encoding
$ctoEncodingList :: [VerificationData] -> Encoding
toJSONList :: [VerificationData] -> Value
$ctoJSONList :: [VerificationData] -> Value
toEncoding :: VerificationData -> Encoding
$ctoEncoding :: VerificationData -> Encoding
toJSON :: VerificationData -> Value
$ctoJSON :: VerificationData -> Value
ToJSON
)
via (Autodocodec VerificationData)
instance HasCodec VerificationData where
codec :: JSONCodec VerificationData
codec =
Text
-> ObjectCodec VerificationData VerificationData
-> JSONCodec VerificationData
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"VerificationData" (ObjectCodec VerificationData VerificationData
-> JSONCodec VerificationData)
-> ObjectCodec VerificationData VerificationData
-> JSONCodec VerificationData
forall a b. (a -> b) -> a -> b
$
AVS -> CVV -> VerificationData
VerificationData
(AVS -> CVV -> VerificationData)
-> Codec Object VerificationData AVS
-> Codec Object VerificationData (CVV -> VerificationData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ObjectCodec AVS AVS
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
requiredField Text
"avs" Text
"Represents the raw AVS response, expressed as an upper-case letter." ObjectCodec AVS AVS
-> (VerificationData -> AVS) -> Codec Object VerificationData AVS
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= VerificationData -> AVS
verificationAVS
Codec Object VerificationData (CVV -> VerificationData)
-> Codec Object VerificationData CVV
-> ObjectCodec VerificationData VerificationData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec CVV CVV
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
requiredField Text
"cvv" Text
"Represents the CVV response" ObjectCodec CVV CVV
-> (VerificationData -> CVV) -> Codec Object VerificationData CVV
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= VerificationData -> CVV
verificationCVV
data AVS = AVSNotRequested | AVSPending | Y | N
deriving (AVS -> AVS -> Bool
(AVS -> AVS -> Bool) -> (AVS -> AVS -> Bool) -> Eq AVS
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AVS -> AVS -> Bool
$c/= :: AVS -> AVS -> Bool
== :: AVS -> AVS -> Bool
$c== :: AVS -> AVS -> Bool
Eq, Int -> AVS -> ShowS
[AVS] -> ShowS
AVS -> String
(Int -> AVS -> ShowS)
-> (AVS -> String) -> ([AVS] -> ShowS) -> Show AVS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AVS] -> ShowS
$cshowList :: [AVS] -> ShowS
show :: AVS -> String
$cshow :: AVS -> String
showsPrec :: Int -> AVS -> ShowS
$cshowsPrec :: Int -> AVS -> ShowS
Show)
deriving
( Value -> Parser [AVS]
Value -> Parser AVS
(Value -> Parser AVS) -> (Value -> Parser [AVS]) -> FromJSON AVS
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AVS]
$cparseJSONList :: Value -> Parser [AVS]
parseJSON :: Value -> Parser AVS
$cparseJSON :: Value -> Parser AVS
FromJSON,
[AVS] -> Encoding
[AVS] -> Value
AVS -> Encoding
AVS -> Value
(AVS -> Value)
-> (AVS -> Encoding)
-> ([AVS] -> Value)
-> ([AVS] -> Encoding)
-> ToJSON AVS
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AVS] -> Encoding
$ctoEncodingList :: [AVS] -> Encoding
toJSONList :: [AVS] -> Value
$ctoJSONList :: [AVS] -> Value
toEncoding :: AVS -> Encoding
$ctoEncoding :: AVS -> Encoding
toJSON :: AVS -> Value
$ctoJSON :: AVS -> Value
ToJSON
)
via (Autodocodec AVS)
instance HasCodec AVS where
codec :: JSONCodec AVS
codec = NonEmpty (AVS, Text) -> JSONCodec AVS
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (AVS, Text) -> JSONCodec AVS)
-> NonEmpty (AVS, Text) -> JSONCodec AVS
forall a b. (a -> b) -> a -> b
$ [(AVS, Text)] -> NonEmpty (AVS, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(AVS
AVSNotRequested, Text
"not_requested"), (AVS
AVSPending, Text
"pending"), (AVS
Y, Text
"Y"), (AVS
N, Text
"N")]
data CVV = CVVNotRequested | CVVPass | CVVFail | CVVUnavailable | CVVPending
deriving (CVV -> CVV -> Bool
(CVV -> CVV -> Bool) -> (CVV -> CVV -> Bool) -> Eq CVV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CVV -> CVV -> Bool
$c/= :: CVV -> CVV -> Bool
== :: CVV -> CVV -> Bool
$c== :: CVV -> CVV -> Bool
Eq, Int -> CVV -> ShowS
[CVV] -> ShowS
CVV -> String
(Int -> CVV -> ShowS)
-> (CVV -> String) -> ([CVV] -> ShowS) -> Show CVV
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CVV] -> ShowS
$cshowList :: [CVV] -> ShowS
show :: CVV -> String
$cshow :: CVV -> String
showsPrec :: Int -> CVV -> ShowS
$cshowsPrec :: Int -> CVV -> ShowS
Show)
deriving
( Value -> Parser [CVV]
Value -> Parser CVV
(Value -> Parser CVV) -> (Value -> Parser [CVV]) -> FromJSON CVV
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CVV]
$cparseJSONList :: Value -> Parser [CVV]
parseJSON :: Value -> Parser CVV
$cparseJSON :: Value -> Parser CVV
FromJSON,
[CVV] -> Encoding
[CVV] -> Value
CVV -> Encoding
CVV -> Value
(CVV -> Value)
-> (CVV -> Encoding)
-> ([CVV] -> Value)
-> ([CVV] -> Encoding)
-> ToJSON CVV
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CVV] -> Encoding
$ctoEncodingList :: [CVV] -> Encoding
toJSONList :: [CVV] -> Value
$ctoJSONList :: [CVV] -> Value
toEncoding :: CVV -> Encoding
$ctoEncoding :: CVV -> Encoding
toJSON :: CVV -> Value
$ctoJSON :: CVV -> Value
ToJSON
)
via (Autodocodec CVV)
instance HasCodec CVV where
codec :: JSONCodec CVV
codec = NonEmpty (CVV, Text) -> JSONCodec CVV
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (CVV, Text) -> JSONCodec CVV)
-> NonEmpty (CVV, Text) -> JSONCodec CVV
forall a b. (a -> b) -> a -> b
$ [(CVV, Text)] -> NonEmpty (CVV, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(CVV
CVVNotRequested, Text
"not_requested"), (CVV
CVVPending, Text
"pending"), (CVV
CVVPass, Text
"pass"), (CVV
CVVFail, Text
"fail"), (CVV
CVVUnavailable, Text
"unavailable")]
data PaymentDepositAddress = PaymentDepositAddress
{ PaymentDepositAddress -> Chain
paymentDepositAddressChain :: !Chain,
PaymentDepositAddress -> HexString
paymentDepositAddressAddress :: !HexString
}
deriving (PaymentDepositAddress -> PaymentDepositAddress -> Bool
(PaymentDepositAddress -> PaymentDepositAddress -> Bool)
-> (PaymentDepositAddress -> PaymentDepositAddress -> Bool)
-> Eq PaymentDepositAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentDepositAddress -> PaymentDepositAddress -> Bool
$c/= :: PaymentDepositAddress -> PaymentDepositAddress -> Bool
== :: PaymentDepositAddress -> PaymentDepositAddress -> Bool
$c== :: PaymentDepositAddress -> PaymentDepositAddress -> Bool
Eq, Int -> PaymentDepositAddress -> ShowS
[PaymentDepositAddress] -> ShowS
PaymentDepositAddress -> String
(Int -> PaymentDepositAddress -> ShowS)
-> (PaymentDepositAddress -> String)
-> ([PaymentDepositAddress] -> ShowS)
-> Show PaymentDepositAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentDepositAddress] -> ShowS
$cshowList :: [PaymentDepositAddress] -> ShowS
show :: PaymentDepositAddress -> String
$cshow :: PaymentDepositAddress -> String
showsPrec :: Int -> PaymentDepositAddress -> ShowS
$cshowsPrec :: Int -> PaymentDepositAddress -> ShowS
Show)
deriving
( Value -> Parser [PaymentDepositAddress]
Value -> Parser PaymentDepositAddress
(Value -> Parser PaymentDepositAddress)
-> (Value -> Parser [PaymentDepositAddress])
-> FromJSON PaymentDepositAddress
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentDepositAddress]
$cparseJSONList :: Value -> Parser [PaymentDepositAddress]
parseJSON :: Value -> Parser PaymentDepositAddress
$cparseJSON :: Value -> Parser PaymentDepositAddress
FromJSON,
[PaymentDepositAddress] -> Encoding
[PaymentDepositAddress] -> Value
PaymentDepositAddress -> Encoding
PaymentDepositAddress -> Value
(PaymentDepositAddress -> Value)
-> (PaymentDepositAddress -> Encoding)
-> ([PaymentDepositAddress] -> Value)
-> ([PaymentDepositAddress] -> Encoding)
-> ToJSON PaymentDepositAddress
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentDepositAddress] -> Encoding
$ctoEncodingList :: [PaymentDepositAddress] -> Encoding
toJSONList :: [PaymentDepositAddress] -> Value
$ctoJSONList :: [PaymentDepositAddress] -> Value
toEncoding :: PaymentDepositAddress -> Encoding
$ctoEncoding :: PaymentDepositAddress -> Encoding
toJSON :: PaymentDepositAddress -> Value
$ctoJSON :: PaymentDepositAddress -> Value
ToJSON
)
via (Autodocodec PaymentDepositAddress)
instance HasCodec PaymentDepositAddress where
codec :: JSONCodec PaymentDepositAddress
codec =
Text
-> ObjectCodec PaymentDepositAddress PaymentDepositAddress
-> JSONCodec PaymentDepositAddress
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PaymentDepositAddress" (ObjectCodec PaymentDepositAddress PaymentDepositAddress
-> JSONCodec PaymentDepositAddress)
-> ObjectCodec PaymentDepositAddress PaymentDepositAddress
-> JSONCodec PaymentDepositAddress
forall a b. (a -> b) -> a -> b
$
Chain -> HexString -> PaymentDepositAddress
PaymentDepositAddress
(Chain -> HexString -> PaymentDepositAddress)
-> Codec Object PaymentDepositAddress Chain
-> Codec
Object PaymentDepositAddress (HexString -> PaymentDepositAddress)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (PaymentDepositAddress -> Chain)
-> Codec Object PaymentDepositAddress Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentDepositAddress -> Chain
paymentDepositAddressChain
Codec
Object PaymentDepositAddress (HexString -> PaymentDepositAddress)
-> Codec Object PaymentDepositAddress HexString
-> ObjectCodec PaymentDepositAddress PaymentDepositAddress
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec HexString HexString
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"address" ObjectCodec HexString HexString
-> (PaymentDepositAddress -> HexString)
-> Codec Object PaymentDepositAddress HexString
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentDepositAddress -> HexString
paymentDepositAddressAddress
data FiatCancelOrRefundResponseBody = FiatCancelOrRefundResponseBody
{
FiatCancelOrRefundResponseBody -> UUID
fiatCancelOrRefundResponseBodyId :: !UUID,
FiatCancelOrRefundResponseBody -> PaymentType
fiatCancelOrRefundResponseBodyType :: !PaymentType,
FiatCancelOrRefundResponseBody -> UUID
fiatCancelOrRefundResponseBodyMerchantId :: !UUID,
FiatCancelOrRefundResponseBody -> WalletId
fiatCancelOrRefundResponseBodyMerchantWalletId :: !WalletId,
FiatCancelOrRefundResponseBody -> MoneyAmount
fiatCancelOrRefundResponseBodyAmount :: !MoneyAmount,
FiatCancelOrRefundResponseBody -> PaymentSource
fiatCancelOrRefundResponseBodySource :: !PaymentSource,
FiatCancelOrRefundResponseBody -> Text
fiatCancelOrRefundResponseBodyDescription :: !Text,
FiatCancelOrRefundResponseBody -> PaymentStatus
fiatCancelOrRefundResponseBodyStatus :: !PaymentStatus,
FiatCancelOrRefundResponseBody -> OriginalFiatPayment
fiatCancelOrRefundResponseBodyOriginalPayment :: !OriginalFiatPayment,
FiatCancelOrRefundResponseBody -> Maybe MoneyAmount
fiatCancelOrRefundResponseBodyFees :: !(Maybe MoneyAmount),
FiatCancelOrRefundResponseBody -> Maybe Text
fiatCancelOrRefundResponseBodyChannel :: !(Maybe Text),
FiatCancelOrRefundResponseBody -> Maybe CancelPaymentReason
fiatCancelOrRefundResponseBodyReason :: !(Maybe CancelPaymentReason),
FiatCancelOrRefundResponseBody -> UTCTime
fiatCancelOrRefundResponseBodyCreateDate :: !UTCTime,
FiatCancelOrRefundResponseBody -> UTCTime
fiatCancelOrRefundResponseBodyUpdateDate :: !UTCTime
}
deriving (FiatCancelOrRefundResponseBody
-> FiatCancelOrRefundResponseBody -> Bool
(FiatCancelOrRefundResponseBody
-> FiatCancelOrRefundResponseBody -> Bool)
-> (FiatCancelOrRefundResponseBody
-> FiatCancelOrRefundResponseBody -> Bool)
-> Eq FiatCancelOrRefundResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FiatCancelOrRefundResponseBody
-> FiatCancelOrRefundResponseBody -> Bool
$c/= :: FiatCancelOrRefundResponseBody
-> FiatCancelOrRefundResponseBody -> Bool
== :: FiatCancelOrRefundResponseBody
-> FiatCancelOrRefundResponseBody -> Bool
$c== :: FiatCancelOrRefundResponseBody
-> FiatCancelOrRefundResponseBody -> Bool
Eq, Int -> FiatCancelOrRefundResponseBody -> ShowS
[FiatCancelOrRefundResponseBody] -> ShowS
FiatCancelOrRefundResponseBody -> String
(Int -> FiatCancelOrRefundResponseBody -> ShowS)
-> (FiatCancelOrRefundResponseBody -> String)
-> ([FiatCancelOrRefundResponseBody] -> ShowS)
-> Show FiatCancelOrRefundResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FiatCancelOrRefundResponseBody] -> ShowS
$cshowList :: [FiatCancelOrRefundResponseBody] -> ShowS
show :: FiatCancelOrRefundResponseBody -> String
$cshow :: FiatCancelOrRefundResponseBody -> String
showsPrec :: Int -> FiatCancelOrRefundResponseBody -> ShowS
$cshowsPrec :: Int -> FiatCancelOrRefundResponseBody -> ShowS
Show)
deriving
( Value -> Parser [FiatCancelOrRefundResponseBody]
Value -> Parser FiatCancelOrRefundResponseBody
(Value -> Parser FiatCancelOrRefundResponseBody)
-> (Value -> Parser [FiatCancelOrRefundResponseBody])
-> FromJSON FiatCancelOrRefundResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [FiatCancelOrRefundResponseBody]
$cparseJSONList :: Value -> Parser [FiatCancelOrRefundResponseBody]
parseJSON :: Value -> Parser FiatCancelOrRefundResponseBody
$cparseJSON :: Value -> Parser FiatCancelOrRefundResponseBody
FromJSON,
[FiatCancelOrRefundResponseBody] -> Encoding
[FiatCancelOrRefundResponseBody] -> Value
FiatCancelOrRefundResponseBody -> Encoding
FiatCancelOrRefundResponseBody -> Value
(FiatCancelOrRefundResponseBody -> Value)
-> (FiatCancelOrRefundResponseBody -> Encoding)
-> ([FiatCancelOrRefundResponseBody] -> Value)
-> ([FiatCancelOrRefundResponseBody] -> Encoding)
-> ToJSON FiatCancelOrRefundResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FiatCancelOrRefundResponseBody] -> Encoding
$ctoEncodingList :: [FiatCancelOrRefundResponseBody] -> Encoding
toJSONList :: [FiatCancelOrRefundResponseBody] -> Value
$ctoJSONList :: [FiatCancelOrRefundResponseBody] -> Value
toEncoding :: FiatCancelOrRefundResponseBody -> Encoding
$ctoEncoding :: FiatCancelOrRefundResponseBody -> Encoding
toJSON :: FiatCancelOrRefundResponseBody -> Value
$ctoJSON :: FiatCancelOrRefundResponseBody -> Value
ToJSON
)
via (Autodocodec FiatCancelOrRefundResponseBody)
instance HasCodec FiatCancelOrRefundResponseBody where
codec :: JSONCodec FiatCancelOrRefundResponseBody
codec =
Text
-> ObjectCodec
FiatCancelOrRefundResponseBody FiatCancelOrRefundResponseBody
-> JSONCodec FiatCancelOrRefundResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"FiatCancelOrRefundResponseBody" (ObjectCodec
FiatCancelOrRefundResponseBody FiatCancelOrRefundResponseBody
-> JSONCodec FiatCancelOrRefundResponseBody)
-> ObjectCodec
FiatCancelOrRefundResponseBody FiatCancelOrRefundResponseBody
-> JSONCodec FiatCancelOrRefundResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody
FiatCancelOrRefundResponseBody
(UUID
-> PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody UUID
-> Codec
Object
FiatCancelOrRefundResponseBody
(PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (FiatCancelOrRefundResponseBody -> UUID)
-> Codec Object FiatCancelOrRefundResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> UUID
fiatCancelOrRefundResponseBodyId
Codec
Object
FiatCancelOrRefundResponseBody
(PaymentType
-> UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody PaymentType
-> Codec
Object
FiatCancelOrRefundResponseBody
(UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentType PaymentType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec PaymentType PaymentType
-> (FiatCancelOrRefundResponseBody -> PaymentType)
-> Codec Object FiatCancelOrRefundResponseBody PaymentType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> PaymentType
fiatCancelOrRefundResponseBodyType
Codec
Object
FiatCancelOrRefundResponseBody
(UUID
-> WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody UUID
-> Codec
Object
FiatCancelOrRefundResponseBody
(WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"merchantId" ObjectCodec UUID UUID
-> (FiatCancelOrRefundResponseBody -> UUID)
-> Codec Object FiatCancelOrRefundResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> UUID
fiatCancelOrRefundResponseBodyMerchantId
Codec
Object
FiatCancelOrRefundResponseBody
(WalletId
-> MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody WalletId
-> Codec
Object
FiatCancelOrRefundResponseBody
(MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec WalletId WalletId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"merchantWalletId" ObjectCodec WalletId WalletId
-> (FiatCancelOrRefundResponseBody -> WalletId)
-> Codec Object FiatCancelOrRefundResponseBody WalletId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> WalletId
fiatCancelOrRefundResponseBodyMerchantWalletId
Codec
Object
FiatCancelOrRefundResponseBody
(MoneyAmount
-> PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody MoneyAmount
-> Codec
Object
FiatCancelOrRefundResponseBody
(PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (FiatCancelOrRefundResponseBody -> MoneyAmount)
-> Codec Object FiatCancelOrRefundResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> MoneyAmount
fiatCancelOrRefundResponseBodyAmount
Codec
Object
FiatCancelOrRefundResponseBody
(PaymentSource
-> Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody PaymentSource
-> Codec
Object
FiatCancelOrRefundResponseBody
(Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentSource PaymentSource
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"source" ObjectCodec PaymentSource PaymentSource
-> (FiatCancelOrRefundResponseBody -> PaymentSource)
-> Codec Object FiatCancelOrRefundResponseBody PaymentSource
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> PaymentSource
fiatCancelOrRefundResponseBodySource
Codec
Object
FiatCancelOrRefundResponseBody
(Text
-> PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody Text
-> Codec
Object
FiatCancelOrRefundResponseBody
(PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (FiatCancelOrRefundResponseBody -> Text)
-> Codec Object FiatCancelOrRefundResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> Text
fiatCancelOrRefundResponseBodyDescription
Codec
Object
FiatCancelOrRefundResponseBody
(PaymentStatus
-> OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody PaymentStatus
-> Codec
Object
FiatCancelOrRefundResponseBody
(OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentStatus PaymentStatus
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec PaymentStatus PaymentStatus
-> (FiatCancelOrRefundResponseBody -> PaymentStatus)
-> Codec Object FiatCancelOrRefundResponseBody PaymentStatus
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> PaymentStatus
fiatCancelOrRefundResponseBodyStatus
Codec
Object
FiatCancelOrRefundResponseBody
(OriginalFiatPayment
-> Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody OriginalFiatPayment
-> Codec
Object
FiatCancelOrRefundResponseBody
(Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec OriginalFiatPayment OriginalFiatPayment
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"originalPayment" ObjectCodec OriginalFiatPayment OriginalFiatPayment
-> (FiatCancelOrRefundResponseBody -> OriginalFiatPayment)
-> Codec Object FiatCancelOrRefundResponseBody OriginalFiatPayment
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> OriginalFiatPayment
fiatCancelOrRefundResponseBodyOriginalPayment
Codec
Object
FiatCancelOrRefundResponseBody
(Maybe MoneyAmount
-> Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody (Maybe MoneyAmount)
-> Codec
Object
FiatCancelOrRefundResponseBody
(Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"fees" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (FiatCancelOrRefundResponseBody -> Maybe MoneyAmount)
-> Codec Object FiatCancelOrRefundResponseBody (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> Maybe MoneyAmount
fiatCancelOrRefundResponseBodyFees
Codec
Object
FiatCancelOrRefundResponseBody
(Maybe Text
-> Maybe CancelPaymentReason
-> UTCTime
-> UTCTime
-> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody (Maybe Text)
-> Codec
Object
FiatCancelOrRefundResponseBody
(Maybe CancelPaymentReason
-> UTCTime -> UTCTime -> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"channel" ObjectCodec (Maybe Text) (Maybe Text)
-> (FiatCancelOrRefundResponseBody -> Maybe Text)
-> Codec Object FiatCancelOrRefundResponseBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> Maybe Text
fiatCancelOrRefundResponseBodyChannel
Codec
Object
FiatCancelOrRefundResponseBody
(Maybe CancelPaymentReason
-> UTCTime -> UTCTime -> FiatCancelOrRefundResponseBody)
-> Codec
Object FiatCancelOrRefundResponseBody (Maybe CancelPaymentReason)
-> Codec
Object
FiatCancelOrRefundResponseBody
(UTCTime -> UTCTime -> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe CancelPaymentReason) (Maybe CancelPaymentReason)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"reason" ObjectCodec (Maybe CancelPaymentReason) (Maybe CancelPaymentReason)
-> (FiatCancelOrRefundResponseBody -> Maybe CancelPaymentReason)
-> Codec
Object FiatCancelOrRefundResponseBody (Maybe CancelPaymentReason)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> Maybe CancelPaymentReason
fiatCancelOrRefundResponseBodyReason
Codec
Object
FiatCancelOrRefundResponseBody
(UTCTime -> UTCTime -> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody UTCTime
-> Codec
Object
FiatCancelOrRefundResponseBody
(UTCTime -> FiatCancelOrRefundResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (FiatCancelOrRefundResponseBody -> UTCTime)
-> Codec Object FiatCancelOrRefundResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> UTCTime
fiatCancelOrRefundResponseBodyCreateDate
Codec
Object
FiatCancelOrRefundResponseBody
(UTCTime -> FiatCancelOrRefundResponseBody)
-> Codec Object FiatCancelOrRefundResponseBody UTCTime
-> ObjectCodec
FiatCancelOrRefundResponseBody FiatCancelOrRefundResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (FiatCancelOrRefundResponseBody -> UTCTime)
-> Codec Object FiatCancelOrRefundResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= FiatCancelOrRefundResponseBody -> UTCTime
fiatCancelOrRefundResponseBodyUpdateDate
data OriginalFiatPayment = OriginalFiatPayment
{ OriginalFiatPayment -> UUID
originalFiatPaymentId :: !UUID,
OriginalFiatPayment -> PaymentType
originalFiatPaymentType :: !PaymentType,
OriginalFiatPayment -> PaymentStatus
originalFiatPaymentStatus :: !PaymentStatus,
OriginalFiatPayment -> UTCTime
originalFiatPaymentCreateDate :: !UTCTime,
OriginalFiatPayment -> UTCTime
originalFiatPaymentUpdateDate :: !UTCTime,
OriginalFiatPayment -> Maybe Text
originalFiatPaymentDescription :: !(Maybe Text),
OriginalFiatPayment -> Maybe MoneyAmount
originalFiatPaymentAmount :: !(Maybe MoneyAmount),
OriginalFiatPayment -> Maybe MoneyAmount
originalFiatPaymentFees :: !(Maybe MoneyAmount),
OriginalFiatPayment -> Maybe UUID
originalFiatPaymentMerchantId :: !(Maybe UUID),
OriginalFiatPayment -> Maybe WalletId
originalFiatPaymentMerchantWalletId :: !(Maybe WalletId),
OriginalFiatPayment -> Maybe PaymentSource
originalFiatPaymentSource :: !(Maybe PaymentSource),
OriginalFiatPayment -> Maybe TrackingReference
originalFiatPaymentTrackingRef :: !(Maybe TrackingReference)
}
deriving (OriginalFiatPayment -> OriginalFiatPayment -> Bool
(OriginalFiatPayment -> OriginalFiatPayment -> Bool)
-> (OriginalFiatPayment -> OriginalFiatPayment -> Bool)
-> Eq OriginalFiatPayment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OriginalFiatPayment -> OriginalFiatPayment -> Bool
$c/= :: OriginalFiatPayment -> OriginalFiatPayment -> Bool
== :: OriginalFiatPayment -> OriginalFiatPayment -> Bool
$c== :: OriginalFiatPayment -> OriginalFiatPayment -> Bool
Eq, Int -> OriginalFiatPayment -> ShowS
[OriginalFiatPayment] -> ShowS
OriginalFiatPayment -> String
(Int -> OriginalFiatPayment -> ShowS)
-> (OriginalFiatPayment -> String)
-> ([OriginalFiatPayment] -> ShowS)
-> Show OriginalFiatPayment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OriginalFiatPayment] -> ShowS
$cshowList :: [OriginalFiatPayment] -> ShowS
show :: OriginalFiatPayment -> String
$cshow :: OriginalFiatPayment -> String
showsPrec :: Int -> OriginalFiatPayment -> ShowS
$cshowsPrec :: Int -> OriginalFiatPayment -> ShowS
Show, (forall x. OriginalFiatPayment -> Rep OriginalFiatPayment x)
-> (forall x. Rep OriginalFiatPayment x -> OriginalFiatPayment)
-> Generic OriginalFiatPayment
forall x. Rep OriginalFiatPayment x -> OriginalFiatPayment
forall x. OriginalFiatPayment -> Rep OriginalFiatPayment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OriginalFiatPayment x -> OriginalFiatPayment
$cfrom :: forall x. OriginalFiatPayment -> Rep OriginalFiatPayment x
Generic)
deriving
( Value -> Parser [OriginalFiatPayment]
Value -> Parser OriginalFiatPayment
(Value -> Parser OriginalFiatPayment)
-> (Value -> Parser [OriginalFiatPayment])
-> FromJSON OriginalFiatPayment
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [OriginalFiatPayment]
$cparseJSONList :: Value -> Parser [OriginalFiatPayment]
parseJSON :: Value -> Parser OriginalFiatPayment
$cparseJSON :: Value -> Parser OriginalFiatPayment
FromJSON,
[OriginalFiatPayment] -> Encoding
[OriginalFiatPayment] -> Value
OriginalFiatPayment -> Encoding
OriginalFiatPayment -> Value
(OriginalFiatPayment -> Value)
-> (OriginalFiatPayment -> Encoding)
-> ([OriginalFiatPayment] -> Value)
-> ([OriginalFiatPayment] -> Encoding)
-> ToJSON OriginalFiatPayment
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [OriginalFiatPayment] -> Encoding
$ctoEncodingList :: [OriginalFiatPayment] -> Encoding
toJSONList :: [OriginalFiatPayment] -> Value
$ctoJSONList :: [OriginalFiatPayment] -> Value
toEncoding :: OriginalFiatPayment -> Encoding
$ctoEncoding :: OriginalFiatPayment -> Encoding
toJSON :: OriginalFiatPayment -> Value
$ctoJSON :: OriginalFiatPayment -> Value
ToJSON
)
via (Autodocodec OriginalFiatPayment)
instance HasCodec OriginalFiatPayment where
codec :: JSONCodec OriginalFiatPayment
codec =
Text
-> ObjectCodec OriginalFiatPayment OriginalFiatPayment
-> JSONCodec OriginalFiatPayment
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"OriginalFiatPayment" (ObjectCodec OriginalFiatPayment OriginalFiatPayment
-> JSONCodec OriginalFiatPayment)
-> ObjectCodec OriginalFiatPayment OriginalFiatPayment
-> JSONCodec OriginalFiatPayment
forall a b. (a -> b) -> a -> b
$
UUID
-> PaymentType
-> PaymentStatus
-> UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment
OriginalFiatPayment
(UUID
-> PaymentType
-> PaymentStatus
-> UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment UUID
-> Codec
Object
OriginalFiatPayment
(PaymentType
-> PaymentStatus
-> UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (OriginalFiatPayment -> UUID)
-> Codec Object OriginalFiatPayment UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> UUID
originalFiatPaymentId
Codec
Object
OriginalFiatPayment
(PaymentType
-> PaymentStatus
-> UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment PaymentType
-> Codec
Object
OriginalFiatPayment
(PaymentStatus
-> UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentType PaymentType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec PaymentType PaymentType
-> (OriginalFiatPayment -> PaymentType)
-> Codec Object OriginalFiatPayment PaymentType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> PaymentType
originalFiatPaymentType
Codec
Object
OriginalFiatPayment
(PaymentStatus
-> UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment PaymentStatus
-> Codec
Object
OriginalFiatPayment
(UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentStatus PaymentStatus
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec PaymentStatus PaymentStatus
-> (OriginalFiatPayment -> PaymentStatus)
-> Codec Object OriginalFiatPayment PaymentStatus
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> PaymentStatus
originalFiatPaymentStatus
Codec
Object
OriginalFiatPayment
(UTCTime
-> UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment UTCTime
-> Codec
Object
OriginalFiatPayment
(UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (OriginalFiatPayment -> UTCTime)
-> Codec Object OriginalFiatPayment UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> UTCTime
originalFiatPaymentCreateDate
Codec
Object
OriginalFiatPayment
(UTCTime
-> Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment UTCTime
-> Codec
Object
OriginalFiatPayment
(Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (OriginalFiatPayment -> UTCTime)
-> Codec Object OriginalFiatPayment UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> UTCTime
originalFiatPaymentUpdateDate
Codec
Object
OriginalFiatPayment
(Maybe Text
-> Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment (Maybe Text)
-> Codec
Object
OriginalFiatPayment
(Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"description" ObjectCodec (Maybe Text) (Maybe Text)
-> (OriginalFiatPayment -> Maybe Text)
-> Codec Object OriginalFiatPayment (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> Maybe Text
originalFiatPaymentDescription
Codec
Object
OriginalFiatPayment
(Maybe MoneyAmount
-> Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment (Maybe MoneyAmount)
-> Codec
Object
OriginalFiatPayment
(Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"amount" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (OriginalFiatPayment -> Maybe MoneyAmount)
-> Codec Object OriginalFiatPayment (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> Maybe MoneyAmount
originalFiatPaymentAmount
Codec
Object
OriginalFiatPayment
(Maybe MoneyAmount
-> Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment (Maybe MoneyAmount)
-> Codec
Object
OriginalFiatPayment
(Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"fees" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (OriginalFiatPayment -> Maybe MoneyAmount)
-> Codec Object OriginalFiatPayment (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> Maybe MoneyAmount
originalFiatPaymentFees
Codec
Object
OriginalFiatPayment
(Maybe UUID
-> Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment (Maybe UUID)
-> Codec
Object
OriginalFiatPayment
(Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UUID) (Maybe UUID)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"merchantId" ObjectCodec (Maybe UUID) (Maybe UUID)
-> (OriginalFiatPayment -> Maybe UUID)
-> Codec Object OriginalFiatPayment (Maybe UUID)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> Maybe UUID
originalFiatPaymentMerchantId
Codec
Object
OriginalFiatPayment
(Maybe WalletId
-> Maybe PaymentSource
-> Maybe TrackingReference
-> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment (Maybe WalletId)
-> Codec
Object
OriginalFiatPayment
(Maybe PaymentSource
-> Maybe TrackingReference -> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe WalletId) (Maybe WalletId)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"merchantWalletId" ObjectCodec (Maybe WalletId) (Maybe WalletId)
-> (OriginalFiatPayment -> Maybe WalletId)
-> Codec Object OriginalFiatPayment (Maybe WalletId)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> Maybe WalletId
originalFiatPaymentMerchantWalletId
Codec
Object
OriginalFiatPayment
(Maybe PaymentSource
-> Maybe TrackingReference -> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment (Maybe PaymentSource)
-> Codec
Object
OriginalFiatPayment
(Maybe TrackingReference -> OriginalFiatPayment)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe PaymentSource) (Maybe PaymentSource)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"source" ObjectCodec (Maybe PaymentSource) (Maybe PaymentSource)
-> (OriginalFiatPayment -> Maybe PaymentSource)
-> Codec Object OriginalFiatPayment (Maybe PaymentSource)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> Maybe PaymentSource
originalFiatPaymentSource
Codec
Object
OriginalFiatPayment
(Maybe TrackingReference -> OriginalFiatPayment)
-> Codec Object OriginalFiatPayment (Maybe TrackingReference)
-> ObjectCodec OriginalFiatPayment OriginalFiatPayment
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"trackingRef" ObjectCodec (Maybe TrackingReference) (Maybe TrackingReference)
-> (OriginalFiatPayment -> Maybe TrackingReference)
-> Codec Object OriginalFiatPayment (Maybe TrackingReference)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= OriginalFiatPayment -> Maybe TrackingReference
originalFiatPaymentTrackingRef
data PaymentSource = PaymentSource
{ PaymentSource -> UUID
paymentSourceId :: !UUID,
PaymentSource -> PaymentSourceType
paymentSourceType :: !PaymentSourceType
}
deriving (PaymentSource -> PaymentSource -> Bool
(PaymentSource -> PaymentSource -> Bool)
-> (PaymentSource -> PaymentSource -> Bool) -> Eq PaymentSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentSource -> PaymentSource -> Bool
$c/= :: PaymentSource -> PaymentSource -> Bool
== :: PaymentSource -> PaymentSource -> Bool
$c== :: PaymentSource -> PaymentSource -> Bool
Eq, Int -> PaymentSource -> ShowS
[PaymentSource] -> ShowS
PaymentSource -> String
(Int -> PaymentSource -> ShowS)
-> (PaymentSource -> String)
-> ([PaymentSource] -> ShowS)
-> Show PaymentSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentSource] -> ShowS
$cshowList :: [PaymentSource] -> ShowS
show :: PaymentSource -> String
$cshow :: PaymentSource -> String
showsPrec :: Int -> PaymentSource -> ShowS
$cshowsPrec :: Int -> PaymentSource -> ShowS
Show)
deriving
( Value -> Parser [PaymentSource]
Value -> Parser PaymentSource
(Value -> Parser PaymentSource)
-> (Value -> Parser [PaymentSource]) -> FromJSON PaymentSource
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentSource]
$cparseJSONList :: Value -> Parser [PaymentSource]
parseJSON :: Value -> Parser PaymentSource
$cparseJSON :: Value -> Parser PaymentSource
FromJSON,
[PaymentSource] -> Encoding
[PaymentSource] -> Value
PaymentSource -> Encoding
PaymentSource -> Value
(PaymentSource -> Value)
-> (PaymentSource -> Encoding)
-> ([PaymentSource] -> Value)
-> ([PaymentSource] -> Encoding)
-> ToJSON PaymentSource
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentSource] -> Encoding
$ctoEncodingList :: [PaymentSource] -> Encoding
toJSONList :: [PaymentSource] -> Value
$ctoJSONList :: [PaymentSource] -> Value
toEncoding :: PaymentSource -> Encoding
$ctoEncoding :: PaymentSource -> Encoding
toJSON :: PaymentSource -> Value
$ctoJSON :: PaymentSource -> Value
ToJSON
)
via (Autodocodec PaymentSource)
instance HasCodec PaymentSource where
codec :: JSONCodec PaymentSource
codec =
Text
-> ObjectCodec PaymentSource PaymentSource
-> JSONCodec PaymentSource
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PaymentSource" (ObjectCodec PaymentSource PaymentSource
-> JSONCodec PaymentSource)
-> ObjectCodec PaymentSource PaymentSource
-> JSONCodec PaymentSource
forall a b. (a -> b) -> a -> b
$
UUID -> PaymentSourceType -> PaymentSource
PaymentSource
(UUID -> PaymentSourceType -> PaymentSource)
-> Codec Object PaymentSource UUID
-> Codec Object PaymentSource (PaymentSourceType -> PaymentSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (PaymentSource -> UUID) -> Codec Object PaymentSource UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentSource -> UUID
paymentSourceId
Codec Object PaymentSource (PaymentSourceType -> PaymentSource)
-> Codec Object PaymentSource PaymentSourceType
-> ObjectCodec PaymentSource PaymentSource
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentSourceType PaymentSourceType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec PaymentSourceType PaymentSourceType
-> (PaymentSource -> PaymentSourceType)
-> Codec Object PaymentSource PaymentSourceType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentSource -> PaymentSourceType
paymentSourceType
data PaymentActionRequired = PaymentActionRequired
{ PaymentActionRequired -> ActionRequiredType
paymentActionRequiredType :: !ActionRequiredType,
PaymentActionRequired -> URL
paymentActionRequiredRedirectUrl :: !URL
}
deriving (PaymentActionRequired -> PaymentActionRequired -> Bool
(PaymentActionRequired -> PaymentActionRequired -> Bool)
-> (PaymentActionRequired -> PaymentActionRequired -> Bool)
-> Eq PaymentActionRequired
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentActionRequired -> PaymentActionRequired -> Bool
$c/= :: PaymentActionRequired -> PaymentActionRequired -> Bool
== :: PaymentActionRequired -> PaymentActionRequired -> Bool
$c== :: PaymentActionRequired -> PaymentActionRequired -> Bool
Eq, Int -> PaymentActionRequired -> ShowS
[PaymentActionRequired] -> ShowS
PaymentActionRequired -> String
(Int -> PaymentActionRequired -> ShowS)
-> (PaymentActionRequired -> String)
-> ([PaymentActionRequired] -> ShowS)
-> Show PaymentActionRequired
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentActionRequired] -> ShowS
$cshowList :: [PaymentActionRequired] -> ShowS
show :: PaymentActionRequired -> String
$cshow :: PaymentActionRequired -> String
showsPrec :: Int -> PaymentActionRequired -> ShowS
$cshowsPrec :: Int -> PaymentActionRequired -> ShowS
Show)
deriving
( Value -> Parser [PaymentActionRequired]
Value -> Parser PaymentActionRequired
(Value -> Parser PaymentActionRequired)
-> (Value -> Parser [PaymentActionRequired])
-> FromJSON PaymentActionRequired
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentActionRequired]
$cparseJSONList :: Value -> Parser [PaymentActionRequired]
parseJSON :: Value -> Parser PaymentActionRequired
$cparseJSON :: Value -> Parser PaymentActionRequired
FromJSON,
[PaymentActionRequired] -> Encoding
[PaymentActionRequired] -> Value
PaymentActionRequired -> Encoding
PaymentActionRequired -> Value
(PaymentActionRequired -> Value)
-> (PaymentActionRequired -> Encoding)
-> ([PaymentActionRequired] -> Value)
-> ([PaymentActionRequired] -> Encoding)
-> ToJSON PaymentActionRequired
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentActionRequired] -> Encoding
$ctoEncodingList :: [PaymentActionRequired] -> Encoding
toJSONList :: [PaymentActionRequired] -> Value
$ctoJSONList :: [PaymentActionRequired] -> Value
toEncoding :: PaymentActionRequired -> Encoding
$ctoEncoding :: PaymentActionRequired -> Encoding
toJSON :: PaymentActionRequired -> Value
$ctoJSON :: PaymentActionRequired -> Value
ToJSON
)
via (Autodocodec PaymentActionRequired)
instance HasCodec PaymentActionRequired where
codec :: JSONCodec PaymentActionRequired
codec =
Text
-> ObjectCodec PaymentActionRequired PaymentActionRequired
-> JSONCodec PaymentActionRequired
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PaymentActionRequired" (ObjectCodec PaymentActionRequired PaymentActionRequired
-> JSONCodec PaymentActionRequired)
-> ObjectCodec PaymentActionRequired PaymentActionRequired
-> JSONCodec PaymentActionRequired
forall a b. (a -> b) -> a -> b
$
ActionRequiredType -> URL -> PaymentActionRequired
PaymentActionRequired
(ActionRequiredType -> URL -> PaymentActionRequired)
-> Codec Object PaymentActionRequired ActionRequiredType
-> Codec
Object PaymentActionRequired (URL -> PaymentActionRequired)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec ActionRequiredType ActionRequiredType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec ActionRequiredType ActionRequiredType
-> (PaymentActionRequired -> ActionRequiredType)
-> Codec Object PaymentActionRequired ActionRequiredType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentActionRequired -> ActionRequiredType
paymentActionRequiredType
Codec Object PaymentActionRequired (URL -> PaymentActionRequired)
-> Codec Object PaymentActionRequired URL
-> ObjectCodec PaymentActionRequired PaymentActionRequired
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec URL URL
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"redirectUrl" ObjectCodec URL URL
-> (PaymentActionRequired -> URL)
-> Codec Object PaymentActionRequired URL
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentActionRequired -> URL
paymentActionRequiredRedirectUrl
data ActionRequiredType = ThreeDSecureRequired
deriving (ActionRequiredType -> ActionRequiredType -> Bool
(ActionRequiredType -> ActionRequiredType -> Bool)
-> (ActionRequiredType -> ActionRequiredType -> Bool)
-> Eq ActionRequiredType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionRequiredType -> ActionRequiredType -> Bool
$c/= :: ActionRequiredType -> ActionRequiredType -> Bool
== :: ActionRequiredType -> ActionRequiredType -> Bool
$c== :: ActionRequiredType -> ActionRequiredType -> Bool
Eq, Int -> ActionRequiredType -> ShowS
[ActionRequiredType] -> ShowS
ActionRequiredType -> String
(Int -> ActionRequiredType -> ShowS)
-> (ActionRequiredType -> String)
-> ([ActionRequiredType] -> ShowS)
-> Show ActionRequiredType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionRequiredType] -> ShowS
$cshowList :: [ActionRequiredType] -> ShowS
show :: ActionRequiredType -> String
$cshow :: ActionRequiredType -> String
showsPrec :: Int -> ActionRequiredType -> ShowS
$cshowsPrec :: Int -> ActionRequiredType -> ShowS
Show)
deriving
( Value -> Parser [ActionRequiredType]
Value -> Parser ActionRequiredType
(Value -> Parser ActionRequiredType)
-> (Value -> Parser [ActionRequiredType])
-> FromJSON ActionRequiredType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ActionRequiredType]
$cparseJSONList :: Value -> Parser [ActionRequiredType]
parseJSON :: Value -> Parser ActionRequiredType
$cparseJSON :: Value -> Parser ActionRequiredType
FromJSON,
[ActionRequiredType] -> Encoding
[ActionRequiredType] -> Value
ActionRequiredType -> Encoding
ActionRequiredType -> Value
(ActionRequiredType -> Value)
-> (ActionRequiredType -> Encoding)
-> ([ActionRequiredType] -> Value)
-> ([ActionRequiredType] -> Encoding)
-> ToJSON ActionRequiredType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ActionRequiredType] -> Encoding
$ctoEncodingList :: [ActionRequiredType] -> Encoding
toJSONList :: [ActionRequiredType] -> Value
$ctoJSONList :: [ActionRequiredType] -> Value
toEncoding :: ActionRequiredType -> Encoding
$ctoEncoding :: ActionRequiredType -> Encoding
toJSON :: ActionRequiredType -> Value
$ctoJSON :: ActionRequiredType -> Value
ToJSON
)
via (Autodocodec ActionRequiredType)
instance HasCodec ActionRequiredType where
codec :: JSONCodec ActionRequiredType
codec = NonEmpty (ActionRequiredType, Text) -> JSONCodec ActionRequiredType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (ActionRequiredType, Text)
-> JSONCodec ActionRequiredType)
-> NonEmpty (ActionRequiredType, Text)
-> JSONCodec ActionRequiredType
forall a b. (a -> b) -> a -> b
$ [(ActionRequiredType, Text)] -> NonEmpty (ActionRequiredType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(ActionRequiredType
ThreeDSecureRequired, Text
"three_d_secure_required")]
data VerificationType = VerificationThreeDSecure | VerificationCVV
deriving (VerificationType -> VerificationType -> Bool
(VerificationType -> VerificationType -> Bool)
-> (VerificationType -> VerificationType -> Bool)
-> Eq VerificationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationType -> VerificationType -> Bool
$c/= :: VerificationType -> VerificationType -> Bool
== :: VerificationType -> VerificationType -> Bool
$c== :: VerificationType -> VerificationType -> Bool
Eq, Int -> VerificationType -> ShowS
[VerificationType] -> ShowS
VerificationType -> String
(Int -> VerificationType -> ShowS)
-> (VerificationType -> String)
-> ([VerificationType] -> ShowS)
-> Show VerificationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationType] -> ShowS
$cshowList :: [VerificationType] -> ShowS
show :: VerificationType -> String
$cshow :: VerificationType -> String
showsPrec :: Int -> VerificationType -> ShowS
$cshowsPrec :: Int -> VerificationType -> ShowS
Show)
deriving
( Value -> Parser [VerificationType]
Value -> Parser VerificationType
(Value -> Parser VerificationType)
-> (Value -> Parser [VerificationType])
-> FromJSON VerificationType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [VerificationType]
$cparseJSONList :: Value -> Parser [VerificationType]
parseJSON :: Value -> Parser VerificationType
$cparseJSON :: Value -> Parser VerificationType
FromJSON,
[VerificationType] -> Encoding
[VerificationType] -> Value
VerificationType -> Encoding
VerificationType -> Value
(VerificationType -> Value)
-> (VerificationType -> Encoding)
-> ([VerificationType] -> Value)
-> ([VerificationType] -> Encoding)
-> ToJSON VerificationType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [VerificationType] -> Encoding
$ctoEncodingList :: [VerificationType] -> Encoding
toJSONList :: [VerificationType] -> Value
$ctoJSONList :: [VerificationType] -> Value
toEncoding :: VerificationType -> Encoding
$ctoEncoding :: VerificationType -> Encoding
toJSON :: VerificationType -> Value
$ctoJSON :: VerificationType -> Value
ToJSON
)
via (Autodocodec VerificationType)
instance HasCodec VerificationType where
codec :: JSONCodec VerificationType
codec = NonEmpty (VerificationType, Text) -> JSONCodec VerificationType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (VerificationType, Text) -> JSONCodec VerificationType)
-> NonEmpty (VerificationType, Text) -> JSONCodec VerificationType
forall a b. (a -> b) -> a -> b
$ [(VerificationType, Text)] -> NonEmpty (VerificationType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(VerificationType
VerificationThreeDSecure, Text
"three_d_secure"), (VerificationType
VerificationCVV, Text
"cvv")]
data PaymentType = Payment | Cancel | Refund
deriving (PaymentType -> PaymentType -> Bool
(PaymentType -> PaymentType -> Bool)
-> (PaymentType -> PaymentType -> Bool) -> Eq PaymentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentType -> PaymentType -> Bool
$c/= :: PaymentType -> PaymentType -> Bool
== :: PaymentType -> PaymentType -> Bool
$c== :: PaymentType -> PaymentType -> Bool
Eq, Int -> PaymentType -> ShowS
[PaymentType] -> ShowS
PaymentType -> String
(Int -> PaymentType -> ShowS)
-> (PaymentType -> String)
-> ([PaymentType] -> ShowS)
-> Show PaymentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentType] -> ShowS
$cshowList :: [PaymentType] -> ShowS
show :: PaymentType -> String
$cshow :: PaymentType -> String
showsPrec :: Int -> PaymentType -> ShowS
$cshowsPrec :: Int -> PaymentType -> ShowS
Show)
deriving
( Value -> Parser [PaymentType]
Value -> Parser PaymentType
(Value -> Parser PaymentType)
-> (Value -> Parser [PaymentType]) -> FromJSON PaymentType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentType]
$cparseJSONList :: Value -> Parser [PaymentType]
parseJSON :: Value -> Parser PaymentType
$cparseJSON :: Value -> Parser PaymentType
FromJSON,
[PaymentType] -> Encoding
[PaymentType] -> Value
PaymentType -> Encoding
PaymentType -> Value
(PaymentType -> Value)
-> (PaymentType -> Encoding)
-> ([PaymentType] -> Value)
-> ([PaymentType] -> Encoding)
-> ToJSON PaymentType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentType] -> Encoding
$ctoEncodingList :: [PaymentType] -> Encoding
toJSONList :: [PaymentType] -> Value
$ctoJSONList :: [PaymentType] -> Value
toEncoding :: PaymentType -> Encoding
$ctoEncoding :: PaymentType -> Encoding
toJSON :: PaymentType -> Value
$ctoJSON :: PaymentType -> Value
ToJSON
)
via (Autodocodec PaymentType)
instance HasCodec PaymentType where
codec :: JSONCodec PaymentType
codec = NonEmpty (PaymentType, Text) -> JSONCodec PaymentType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (PaymentType, Text) -> JSONCodec PaymentType)
-> NonEmpty (PaymentType, Text) -> JSONCodec PaymentType
forall a b. (a -> b) -> a -> b
$ [(PaymentType, Text)] -> NonEmpty (PaymentType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(PaymentType
Payment, Text
"payment"), (PaymentType
Cancel, Text
"cancel"), (PaymentType
Refund, Text
"refund")]
data PaymentSourceType = Card | ACH | WireSource | SEPA
deriving (PaymentSourceType -> PaymentSourceType -> Bool
(PaymentSourceType -> PaymentSourceType -> Bool)
-> (PaymentSourceType -> PaymentSourceType -> Bool)
-> Eq PaymentSourceType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentSourceType -> PaymentSourceType -> Bool
$c/= :: PaymentSourceType -> PaymentSourceType -> Bool
== :: PaymentSourceType -> PaymentSourceType -> Bool
$c== :: PaymentSourceType -> PaymentSourceType -> Bool
Eq, Int -> PaymentSourceType -> ShowS
[PaymentSourceType] -> ShowS
PaymentSourceType -> String
(Int -> PaymentSourceType -> ShowS)
-> (PaymentSourceType -> String)
-> ([PaymentSourceType] -> ShowS)
-> Show PaymentSourceType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentSourceType] -> ShowS
$cshowList :: [PaymentSourceType] -> ShowS
show :: PaymentSourceType -> String
$cshow :: PaymentSourceType -> String
showsPrec :: Int -> PaymentSourceType -> ShowS
$cshowsPrec :: Int -> PaymentSourceType -> ShowS
Show)
deriving
( Value -> Parser [PaymentSourceType]
Value -> Parser PaymentSourceType
(Value -> Parser PaymentSourceType)
-> (Value -> Parser [PaymentSourceType])
-> FromJSON PaymentSourceType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentSourceType]
$cparseJSONList :: Value -> Parser [PaymentSourceType]
parseJSON :: Value -> Parser PaymentSourceType
$cparseJSON :: Value -> Parser PaymentSourceType
FromJSON,
[PaymentSourceType] -> Encoding
[PaymentSourceType] -> Value
PaymentSourceType -> Encoding
PaymentSourceType -> Value
(PaymentSourceType -> Value)
-> (PaymentSourceType -> Encoding)
-> ([PaymentSourceType] -> Value)
-> ([PaymentSourceType] -> Encoding)
-> ToJSON PaymentSourceType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentSourceType] -> Encoding
$ctoEncodingList :: [PaymentSourceType] -> Encoding
toJSONList :: [PaymentSourceType] -> Value
$ctoJSONList :: [PaymentSourceType] -> Value
toEncoding :: PaymentSourceType -> Encoding
$ctoEncoding :: PaymentSourceType -> Encoding
toJSON :: PaymentSourceType -> Value
$ctoJSON :: PaymentSourceType -> Value
ToJSON
)
via (Autodocodec PaymentSourceType)
instance HasCodec PaymentSourceType where
codec :: JSONCodec PaymentSourceType
codec = NonEmpty (PaymentSourceType, Text) -> JSONCodec PaymentSourceType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (PaymentSourceType, Text) -> JSONCodec PaymentSourceType)
-> NonEmpty (PaymentSourceType, Text)
-> JSONCodec PaymentSourceType
forall a b. (a -> b) -> a -> b
$ [(PaymentSourceType, Text)] -> NonEmpty (PaymentSourceType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(PaymentSourceType
Card, Text
"card"), (PaymentSourceType
ACH, Text
"ach"), (PaymentSourceType
WireSource, Text
"wire"), (PaymentSourceType
SEPA, Text
"sepa")]
data CancelPaymentRequestBody = CancelPaymentRequestBody
{ CancelPaymentRequestBody -> UUID
cancelPaymentIdempotencyKey :: !UUID,
CancelPaymentRequestBody -> Maybe CancelPaymentReason
cancelPaymentReason :: !(Maybe CancelPaymentReason)
}
deriving (CancelPaymentRequestBody -> CancelPaymentRequestBody -> Bool
(CancelPaymentRequestBody -> CancelPaymentRequestBody -> Bool)
-> (CancelPaymentRequestBody -> CancelPaymentRequestBody -> Bool)
-> Eq CancelPaymentRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelPaymentRequestBody -> CancelPaymentRequestBody -> Bool
$c/= :: CancelPaymentRequestBody -> CancelPaymentRequestBody -> Bool
== :: CancelPaymentRequestBody -> CancelPaymentRequestBody -> Bool
$c== :: CancelPaymentRequestBody -> CancelPaymentRequestBody -> Bool
Eq, Int -> CancelPaymentRequestBody -> ShowS
[CancelPaymentRequestBody] -> ShowS
CancelPaymentRequestBody -> String
(Int -> CancelPaymentRequestBody -> ShowS)
-> (CancelPaymentRequestBody -> String)
-> ([CancelPaymentRequestBody] -> ShowS)
-> Show CancelPaymentRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelPaymentRequestBody] -> ShowS
$cshowList :: [CancelPaymentRequestBody] -> ShowS
show :: CancelPaymentRequestBody -> String
$cshow :: CancelPaymentRequestBody -> String
showsPrec :: Int -> CancelPaymentRequestBody -> ShowS
$cshowsPrec :: Int -> CancelPaymentRequestBody -> ShowS
Show)
deriving
( [CancelPaymentRequestBody] -> Encoding
[CancelPaymentRequestBody] -> Value
CancelPaymentRequestBody -> Encoding
CancelPaymentRequestBody -> Value
(CancelPaymentRequestBody -> Value)
-> (CancelPaymentRequestBody -> Encoding)
-> ([CancelPaymentRequestBody] -> Value)
-> ([CancelPaymentRequestBody] -> Encoding)
-> ToJSON CancelPaymentRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CancelPaymentRequestBody] -> Encoding
$ctoEncodingList :: [CancelPaymentRequestBody] -> Encoding
toJSONList :: [CancelPaymentRequestBody] -> Value
$ctoJSONList :: [CancelPaymentRequestBody] -> Value
toEncoding :: CancelPaymentRequestBody -> Encoding
$ctoEncoding :: CancelPaymentRequestBody -> Encoding
toJSON :: CancelPaymentRequestBody -> Value
$ctoJSON :: CancelPaymentRequestBody -> Value
ToJSON,
Value -> Parser [CancelPaymentRequestBody]
Value -> Parser CancelPaymentRequestBody
(Value -> Parser CancelPaymentRequestBody)
-> (Value -> Parser [CancelPaymentRequestBody])
-> FromJSON CancelPaymentRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CancelPaymentRequestBody]
$cparseJSONList :: Value -> Parser [CancelPaymentRequestBody]
parseJSON :: Value -> Parser CancelPaymentRequestBody
$cparseJSON :: Value -> Parser CancelPaymentRequestBody
FromJSON
)
via (Autodocodec CancelPaymentRequestBody)
instance HasCodec CancelPaymentRequestBody where
codec :: JSONCodec CancelPaymentRequestBody
codec =
Text
-> ObjectCodec CancelPaymentRequestBody CancelPaymentRequestBody
-> JSONCodec CancelPaymentRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CancelPaymentRequestBody" (ObjectCodec CancelPaymentRequestBody CancelPaymentRequestBody
-> JSONCodec CancelPaymentRequestBody)
-> ObjectCodec CancelPaymentRequestBody CancelPaymentRequestBody
-> JSONCodec CancelPaymentRequestBody
forall a b. (a -> b) -> a -> b
$
UUID -> Maybe CancelPaymentReason -> CancelPaymentRequestBody
CancelPaymentRequestBody
(UUID -> Maybe CancelPaymentReason -> CancelPaymentRequestBody)
-> Codec Object CancelPaymentRequestBody UUID
-> Codec
Object
CancelPaymentRequestBody
(Maybe CancelPaymentReason -> CancelPaymentRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (CancelPaymentRequestBody -> UUID)
-> Codec Object CancelPaymentRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CancelPaymentRequestBody -> UUID
cancelPaymentIdempotencyKey
Codec
Object
CancelPaymentRequestBody
(Maybe CancelPaymentReason -> CancelPaymentRequestBody)
-> Codec
Object CancelPaymentRequestBody (Maybe CancelPaymentReason)
-> ObjectCodec CancelPaymentRequestBody CancelPaymentRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe CancelPaymentReason) (Maybe CancelPaymentReason)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"reason" ObjectCodec (Maybe CancelPaymentReason) (Maybe CancelPaymentReason)
-> (CancelPaymentRequestBody -> Maybe CancelPaymentReason)
-> Codec
Object CancelPaymentRequestBody (Maybe CancelPaymentReason)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CancelPaymentRequestBody -> Maybe CancelPaymentReason
cancelPaymentReason
data CancelPaymentReason
= CancelPaymentReasonDuplicate
| CancelPaymentReasonFraudulent
| CancelPaymentReasonRequestedByCustomer
| CancelPaymentReasonBankTransactionError
| CancelPaymentReasonInvalidAccountNumber
| CancelPaymentReasonInsufficientFunds
| CancelPaymentReasonPaymentStoppedByIssuer
deriving (CancelPaymentReason -> CancelPaymentReason -> Bool
(CancelPaymentReason -> CancelPaymentReason -> Bool)
-> (CancelPaymentReason -> CancelPaymentReason -> Bool)
-> Eq CancelPaymentReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelPaymentReason -> CancelPaymentReason -> Bool
$c/= :: CancelPaymentReason -> CancelPaymentReason -> Bool
== :: CancelPaymentReason -> CancelPaymentReason -> Bool
$c== :: CancelPaymentReason -> CancelPaymentReason -> Bool
Eq, Int -> CancelPaymentReason -> ShowS
[CancelPaymentReason] -> ShowS
CancelPaymentReason -> String
(Int -> CancelPaymentReason -> ShowS)
-> (CancelPaymentReason -> String)
-> ([CancelPaymentReason] -> ShowS)
-> Show CancelPaymentReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelPaymentReason] -> ShowS
$cshowList :: [CancelPaymentReason] -> ShowS
show :: CancelPaymentReason -> String
$cshow :: CancelPaymentReason -> String
showsPrec :: Int -> CancelPaymentReason -> ShowS
$cshowsPrec :: Int -> CancelPaymentReason -> ShowS
Show)
deriving
( Value -> Parser [CancelPaymentReason]
Value -> Parser CancelPaymentReason
(Value -> Parser CancelPaymentReason)
-> (Value -> Parser [CancelPaymentReason])
-> FromJSON CancelPaymentReason
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CancelPaymentReason]
$cparseJSONList :: Value -> Parser [CancelPaymentReason]
parseJSON :: Value -> Parser CancelPaymentReason
$cparseJSON :: Value -> Parser CancelPaymentReason
FromJSON,
[CancelPaymentReason] -> Encoding
[CancelPaymentReason] -> Value
CancelPaymentReason -> Encoding
CancelPaymentReason -> Value
(CancelPaymentReason -> Value)
-> (CancelPaymentReason -> Encoding)
-> ([CancelPaymentReason] -> Value)
-> ([CancelPaymentReason] -> Encoding)
-> ToJSON CancelPaymentReason
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CancelPaymentReason] -> Encoding
$ctoEncodingList :: [CancelPaymentReason] -> Encoding
toJSONList :: [CancelPaymentReason] -> Value
$ctoJSONList :: [CancelPaymentReason] -> Value
toEncoding :: CancelPaymentReason -> Encoding
$ctoEncoding :: CancelPaymentReason -> Encoding
toJSON :: CancelPaymentReason -> Value
$ctoJSON :: CancelPaymentReason -> Value
ToJSON
)
via (Autodocodec CancelPaymentReason)
instance HasCodec CancelPaymentReason where
codec :: JSONCodec CancelPaymentReason
codec =
NonEmpty (CancelPaymentReason, Text)
-> JSONCodec CancelPaymentReason
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (CancelPaymentReason, Text)
-> JSONCodec CancelPaymentReason)
-> NonEmpty (CancelPaymentReason, Text)
-> JSONCodec CancelPaymentReason
forall a b. (a -> b) -> a -> b
$
[(CancelPaymentReason, Text)]
-> NonEmpty (CancelPaymentReason, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (CancelPaymentReason
CancelPaymentReasonDuplicate, Text
"duplicate"),
(CancelPaymentReason
CancelPaymentReasonFraudulent, Text
"fraudulent"),
(CancelPaymentReason
CancelPaymentReasonRequestedByCustomer, Text
"requested_by_customer"),
(CancelPaymentReason
CancelPaymentReasonBankTransactionError, Text
"bank_transaction_error"),
(CancelPaymentReason
CancelPaymentReasonInvalidAccountNumber, Text
"invalid_account_number"),
(CancelPaymentReason
CancelPaymentReasonInsufficientFunds, Text
"insufficient_funds"),
(CancelPaymentReason
CancelPaymentReasonPaymentStoppedByIssuer, Text
"payment_stopped_by_issuer")
]
data RefundPaymentRequestBody = RefundPaymentRequestBody
{ RefundPaymentRequestBody -> UUID
refundPaymentIdempotencyKey :: !UUID,
RefundPaymentRequestBody -> MoneyAmount
refundPaymentAmount :: !MoneyAmount,
RefundPaymentRequestBody -> Maybe CancelPaymentReason
refundPaymentReason :: !(Maybe CancelPaymentReason)
}
deriving (RefundPaymentRequestBody -> RefundPaymentRequestBody -> Bool
(RefundPaymentRequestBody -> RefundPaymentRequestBody -> Bool)
-> (RefundPaymentRequestBody -> RefundPaymentRequestBody -> Bool)
-> Eq RefundPaymentRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RefundPaymentRequestBody -> RefundPaymentRequestBody -> Bool
$c/= :: RefundPaymentRequestBody -> RefundPaymentRequestBody -> Bool
== :: RefundPaymentRequestBody -> RefundPaymentRequestBody -> Bool
$c== :: RefundPaymentRequestBody -> RefundPaymentRequestBody -> Bool
Eq, Int -> RefundPaymentRequestBody -> ShowS
[RefundPaymentRequestBody] -> ShowS
RefundPaymentRequestBody -> String
(Int -> RefundPaymentRequestBody -> ShowS)
-> (RefundPaymentRequestBody -> String)
-> ([RefundPaymentRequestBody] -> ShowS)
-> Show RefundPaymentRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RefundPaymentRequestBody] -> ShowS
$cshowList :: [RefundPaymentRequestBody] -> ShowS
show :: RefundPaymentRequestBody -> String
$cshow :: RefundPaymentRequestBody -> String
showsPrec :: Int -> RefundPaymentRequestBody -> ShowS
$cshowsPrec :: Int -> RefundPaymentRequestBody -> ShowS
Show)
deriving
( [RefundPaymentRequestBody] -> Encoding
[RefundPaymentRequestBody] -> Value
RefundPaymentRequestBody -> Encoding
RefundPaymentRequestBody -> Value
(RefundPaymentRequestBody -> Value)
-> (RefundPaymentRequestBody -> Encoding)
-> ([RefundPaymentRequestBody] -> Value)
-> ([RefundPaymentRequestBody] -> Encoding)
-> ToJSON RefundPaymentRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RefundPaymentRequestBody] -> Encoding
$ctoEncodingList :: [RefundPaymentRequestBody] -> Encoding
toJSONList :: [RefundPaymentRequestBody] -> Value
$ctoJSONList :: [RefundPaymentRequestBody] -> Value
toEncoding :: RefundPaymentRequestBody -> Encoding
$ctoEncoding :: RefundPaymentRequestBody -> Encoding
toJSON :: RefundPaymentRequestBody -> Value
$ctoJSON :: RefundPaymentRequestBody -> Value
ToJSON,
Value -> Parser [RefundPaymentRequestBody]
Value -> Parser RefundPaymentRequestBody
(Value -> Parser RefundPaymentRequestBody)
-> (Value -> Parser [RefundPaymentRequestBody])
-> FromJSON RefundPaymentRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RefundPaymentRequestBody]
$cparseJSONList :: Value -> Parser [RefundPaymentRequestBody]
parseJSON :: Value -> Parser RefundPaymentRequestBody
$cparseJSON :: Value -> Parser RefundPaymentRequestBody
FromJSON
)
via (Autodocodec RefundPaymentRequestBody)
instance HasCodec RefundPaymentRequestBody where
codec :: JSONCodec RefundPaymentRequestBody
codec =
Text
-> ObjectCodec RefundPaymentRequestBody RefundPaymentRequestBody
-> JSONCodec RefundPaymentRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"RefundPaymentRequestBody" (ObjectCodec RefundPaymentRequestBody RefundPaymentRequestBody
-> JSONCodec RefundPaymentRequestBody)
-> ObjectCodec RefundPaymentRequestBody RefundPaymentRequestBody
-> JSONCodec RefundPaymentRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> MoneyAmount
-> Maybe CancelPaymentReason
-> RefundPaymentRequestBody
RefundPaymentRequestBody
(UUID
-> MoneyAmount
-> Maybe CancelPaymentReason
-> RefundPaymentRequestBody)
-> Codec Object RefundPaymentRequestBody UUID
-> Codec
Object
RefundPaymentRequestBody
(MoneyAmount
-> Maybe CancelPaymentReason -> RefundPaymentRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (RefundPaymentRequestBody -> UUID)
-> Codec Object RefundPaymentRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RefundPaymentRequestBody -> UUID
refundPaymentIdempotencyKey
Codec
Object
RefundPaymentRequestBody
(MoneyAmount
-> Maybe CancelPaymentReason -> RefundPaymentRequestBody)
-> Codec Object RefundPaymentRequestBody MoneyAmount
-> Codec
Object
RefundPaymentRequestBody
(Maybe CancelPaymentReason -> RefundPaymentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (RefundPaymentRequestBody -> MoneyAmount)
-> Codec Object RefundPaymentRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RefundPaymentRequestBody -> MoneyAmount
refundPaymentAmount
Codec
Object
RefundPaymentRequestBody
(Maybe CancelPaymentReason -> RefundPaymentRequestBody)
-> Codec
Object RefundPaymentRequestBody (Maybe CancelPaymentReason)
-> ObjectCodec RefundPaymentRequestBody RefundPaymentRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe CancelPaymentReason) (Maybe CancelPaymentReason)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"reason" ObjectCodec (Maybe CancelPaymentReason) (Maybe CancelPaymentReason)
-> (RefundPaymentRequestBody -> Maybe CancelPaymentReason)
-> Codec
Object RefundPaymentRequestBody (Maybe CancelPaymentReason)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RefundPaymentRequestBody -> Maybe CancelPaymentReason
refundPaymentReason
data OnChainTransferRequest
type instance CircleRequest OnChainTransferRequest = CircleResponseBody TransferResponseBody
instance CircleHasParam OnChainTransferRequest ReturnIdentitiesQueryParam
data OnChainTransfersRequest
type instance CircleRequest OnChainTransfersRequest = CircleResponseBody [TransferResponseBody]
instance CircleHasParam OnChainTransfersRequest PaginationQueryParams
instance CircleHasParam OnChainTransfersRequest FromQueryParam
instance CircleHasParam OnChainTransfersRequest ToQueryParam
instance CircleHasParam OnChainTransfersRequest PageSizeQueryParam
instance CircleHasParam OnChainTransfersRequest WalletIdQueryParam
instance CircleHasParam OnChainTransfersRequest SourceWalletIdQueryParam
instance CircleHasParam OnChainTransfersRequest DestinationWalletIdQueryParam
instance CircleHasParam OnChainTransfersRequest ReturnIdentitiesQueryParam
data OnChainAddressRequest
type instance CircleRequest OnChainAddressRequest = CircleResponseBody DepositAddressResponseBody
data OnChainTransferRequestBody = OnChainTransferRequestBody
{ OnChainTransferRequestBody -> UUID
onChainTransferRequestBodyIdempotencyKey :: !UUID,
OnChainTransferRequestBody -> SourceWallet
onChainTransferRequestBodySource :: !SourceWallet,
OnChainTransferRequestBody
-> ThisOrThat DestinationWallet DestinationBlockchain
onChainTransferRequestBodyDestination :: !(ThisOrThat DestinationWallet DestinationBlockchain),
OnChainTransferRequestBody -> MoneyAmount
onChainTransferRequestBodyAmount :: !MoneyAmount
}
deriving (OnChainTransferRequestBody -> OnChainTransferRequestBody -> Bool
(OnChainTransferRequestBody -> OnChainTransferRequestBody -> Bool)
-> (OnChainTransferRequestBody
-> OnChainTransferRequestBody -> Bool)
-> Eq OnChainTransferRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OnChainTransferRequestBody -> OnChainTransferRequestBody -> Bool
$c/= :: OnChainTransferRequestBody -> OnChainTransferRequestBody -> Bool
== :: OnChainTransferRequestBody -> OnChainTransferRequestBody -> Bool
$c== :: OnChainTransferRequestBody -> OnChainTransferRequestBody -> Bool
Eq, Int -> OnChainTransferRequestBody -> ShowS
[OnChainTransferRequestBody] -> ShowS
OnChainTransferRequestBody -> String
(Int -> OnChainTransferRequestBody -> ShowS)
-> (OnChainTransferRequestBody -> String)
-> ([OnChainTransferRequestBody] -> ShowS)
-> Show OnChainTransferRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OnChainTransferRequestBody] -> ShowS
$cshowList :: [OnChainTransferRequestBody] -> ShowS
show :: OnChainTransferRequestBody -> String
$cshow :: OnChainTransferRequestBody -> String
showsPrec :: Int -> OnChainTransferRequestBody -> ShowS
$cshowsPrec :: Int -> OnChainTransferRequestBody -> ShowS
Show)
instance ToJSON OnChainTransferRequestBody where
toJSON :: OnChainTransferRequestBody -> Aeson.Value
toJSON :: OnChainTransferRequestBody -> Value
toJSON OnChainTransferRequestBody {UUID
MoneyAmount
ThisOrThat DestinationWallet DestinationBlockchain
SourceWallet
onChainTransferRequestBodyAmount :: MoneyAmount
onChainTransferRequestBodyDestination :: ThisOrThat DestinationWallet DestinationBlockchain
onChainTransferRequestBodySource :: SourceWallet
onChainTransferRequestBodyIdempotencyKey :: UUID
onChainTransferRequestBodyAmount :: OnChainTransferRequestBody -> MoneyAmount
onChainTransferRequestBodyDestination :: OnChainTransferRequestBody
-> ThisOrThat DestinationWallet DestinationBlockchain
onChainTransferRequestBodySource :: OnChainTransferRequestBody -> SourceWallet
onChainTransferRequestBodyIdempotencyKey :: OnChainTransferRequestBody -> UUID
..} =
[Pair] -> Value
Aeson.object
[ Text
"idempotencyKey" Text -> UUID -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Aeson..= UUID
onChainTransferRequestBodyIdempotencyKey,
Text
"source" Text -> SourceWallet -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Aeson..= SourceWallet
onChainTransferRequestBodySource,
Text
"destination" Text -> ThisOrThat DestinationWallet DestinationBlockchain -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Aeson..= ThisOrThat DestinationWallet DestinationBlockchain
onChainTransferRequestBodyDestination,
Text
"amount" Text -> MoneyAmount -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Aeson..= MoneyAmount
onChainTransferRequestBodyAmount
]
data CardsRequest
type instance CircleRequest CardsRequest = CircleResponseBody [ListCardResponseBody]
instance CircleHasParam CardsRequest PaginationQueryParams
instance CircleHasParam CardsRequest PageSizeQueryParam
data CardRequest
type instance CircleRequest CardRequest = CircleResponseBody CardResponseBody
data ListCardResponseBody = ListCardResponseBody
{ ListCardResponseBody -> UUID
listCardId :: !UUID,
ListCardResponseBody -> Status
listCardStatus :: !Status,
ListCardResponseBody -> ListCardBillingDetails
listCardBillingDetails :: !ListCardBillingDetails,
ListCardResponseBody -> Int
listCardExpiryMonth :: !Int,
ListCardResponseBody -> Int
listCardExpiryYear :: !Int,
ListCardResponseBody -> CardNetwork
listCardNetwork :: !CardNetwork,
ListCardResponseBody -> Maybe Text
listCardBin :: !(Maybe Text),
ListCardResponseBody -> Maybe ISO3166Alpha2
listCardIssuerCountry :: !(Maybe ISO3166Alpha2),
ListCardResponseBody -> UUID
listCardFingerprint :: !UUID,
ListCardResponseBody -> VerificationData
listCardVerification :: !VerificationData,
ListCardResponseBody -> Maybe RiskEvaluation
listCardRiskEvaluation :: !(Maybe RiskEvaluation),
ListCardResponseBody -> UTCTime
listCardCreateDate :: !UTCTime,
ListCardResponseBody -> UTCTime
listCardUpdateDate :: !UTCTime
}
deriving (ListCardResponseBody -> ListCardResponseBody -> Bool
(ListCardResponseBody -> ListCardResponseBody -> Bool)
-> (ListCardResponseBody -> ListCardResponseBody -> Bool)
-> Eq ListCardResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCardResponseBody -> ListCardResponseBody -> Bool
$c/= :: ListCardResponseBody -> ListCardResponseBody -> Bool
== :: ListCardResponseBody -> ListCardResponseBody -> Bool
$c== :: ListCardResponseBody -> ListCardResponseBody -> Bool
Eq, Int -> ListCardResponseBody -> ShowS
[ListCardResponseBody] -> ShowS
ListCardResponseBody -> String
(Int -> ListCardResponseBody -> ShowS)
-> (ListCardResponseBody -> String)
-> ([ListCardResponseBody] -> ShowS)
-> Show ListCardResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCardResponseBody] -> ShowS
$cshowList :: [ListCardResponseBody] -> ShowS
show :: ListCardResponseBody -> String
$cshow :: ListCardResponseBody -> String
showsPrec :: Int -> ListCardResponseBody -> ShowS
$cshowsPrec :: Int -> ListCardResponseBody -> ShowS
Show)
deriving
( Value -> Parser [ListCardResponseBody]
Value -> Parser ListCardResponseBody
(Value -> Parser ListCardResponseBody)
-> (Value -> Parser [ListCardResponseBody])
-> FromJSON ListCardResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ListCardResponseBody]
$cparseJSONList :: Value -> Parser [ListCardResponseBody]
parseJSON :: Value -> Parser ListCardResponseBody
$cparseJSON :: Value -> Parser ListCardResponseBody
FromJSON,
[ListCardResponseBody] -> Encoding
[ListCardResponseBody] -> Value
ListCardResponseBody -> Encoding
ListCardResponseBody -> Value
(ListCardResponseBody -> Value)
-> (ListCardResponseBody -> Encoding)
-> ([ListCardResponseBody] -> Value)
-> ([ListCardResponseBody] -> Encoding)
-> ToJSON ListCardResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ListCardResponseBody] -> Encoding
$ctoEncodingList :: [ListCardResponseBody] -> Encoding
toJSONList :: [ListCardResponseBody] -> Value
$ctoJSONList :: [ListCardResponseBody] -> Value
toEncoding :: ListCardResponseBody -> Encoding
$ctoEncoding :: ListCardResponseBody -> Encoding
toJSON :: ListCardResponseBody -> Value
$ctoJSON :: ListCardResponseBody -> Value
ToJSON
)
via (Autodocodec ListCardResponseBody)
instance HasCodec ListCardResponseBody where
codec :: JSONCodec ListCardResponseBody
codec =
Text
-> ObjectCodec ListCardResponseBody ListCardResponseBody
-> JSONCodec ListCardResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ListCardResponseBody" (ObjectCodec ListCardResponseBody ListCardResponseBody
-> JSONCodec ListCardResponseBody)
-> ObjectCodec ListCardResponseBody ListCardResponseBody
-> JSONCodec ListCardResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Status
-> ListCardBillingDetails
-> Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody
ListCardResponseBody
(UUID
-> Status
-> ListCardBillingDetails
-> Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody UUID
-> Codec
Object
ListCardResponseBody
(Status
-> ListCardBillingDetails
-> Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (ListCardResponseBody -> UUID)
-> Codec Object ListCardResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> UUID
listCardId
Codec
Object
ListCardResponseBody
(Status
-> ListCardBillingDetails
-> Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody Status
-> Codec
Object
ListCardResponseBody
(ListCardBillingDetails
-> Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (ListCardResponseBody -> Status)
-> Codec Object ListCardResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> Status
listCardStatus
Codec
Object
ListCardResponseBody
(ListCardBillingDetails
-> Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody ListCardBillingDetails
-> Codec
Object
ListCardResponseBody
(Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ListCardBillingDetails ListCardBillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec ListCardBillingDetails ListCardBillingDetails
-> (ListCardResponseBody -> ListCardBillingDetails)
-> Codec Object ListCardResponseBody ListCardBillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> ListCardBillingDetails
listCardBillingDetails
Codec
Object
ListCardResponseBody
(Int
-> Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody Int
-> Codec
Object
ListCardResponseBody
(Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expMonth" ObjectCodec Int Int
-> (ListCardResponseBody -> Int)
-> Codec Object ListCardResponseBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> Int
listCardExpiryMonth
Codec
Object
ListCardResponseBody
(Int
-> CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody Int
-> Codec
Object
ListCardResponseBody
(CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expYear" ObjectCodec Int Int
-> (ListCardResponseBody -> Int)
-> Codec Object ListCardResponseBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> Int
listCardExpiryYear
Codec
Object
ListCardResponseBody
(CardNetwork
-> Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody CardNetwork
-> Codec
Object
ListCardResponseBody
(Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec CardNetwork CardNetwork
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"network" ObjectCodec CardNetwork CardNetwork
-> (ListCardResponseBody -> CardNetwork)
-> Codec Object ListCardResponseBody CardNetwork
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> CardNetwork
listCardNetwork
Codec
Object
ListCardResponseBody
(Maybe Text
-> Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody (Maybe Text)
-> Codec
Object
ListCardResponseBody
(Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"bin" ObjectCodec (Maybe Text) (Maybe Text)
-> (ListCardResponseBody -> Maybe Text)
-> Codec Object ListCardResponseBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> Maybe Text
listCardBin
Codec
Object
ListCardResponseBody
(Maybe ISO3166Alpha2
-> UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody (Maybe ISO3166Alpha2)
-> Codec
Object
ListCardResponseBody
(UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"issuerCountry" ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
-> (ListCardResponseBody -> Maybe ISO3166Alpha2)
-> Codec Object ListCardResponseBody (Maybe ISO3166Alpha2)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> Maybe ISO3166Alpha2
listCardIssuerCountry
Codec
Object
ListCardResponseBody
(UUID
-> VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody UUID
-> Codec
Object
ListCardResponseBody
(VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fingerprint" ObjectCodec UUID UUID
-> (ListCardResponseBody -> UUID)
-> Codec Object ListCardResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> UUID
listCardFingerprint
Codec
Object
ListCardResponseBody
(VerificationData
-> Maybe RiskEvaluation
-> UTCTime
-> UTCTime
-> ListCardResponseBody)
-> Codec Object ListCardResponseBody VerificationData
-> Codec
Object
ListCardResponseBody
(Maybe RiskEvaluation
-> UTCTime -> UTCTime -> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec VerificationData VerificationData
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"verification" ObjectCodec VerificationData VerificationData
-> (ListCardResponseBody -> VerificationData)
-> Codec Object ListCardResponseBody VerificationData
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> VerificationData
listCardVerification
Codec
Object
ListCardResponseBody
(Maybe RiskEvaluation
-> UTCTime -> UTCTime -> ListCardResponseBody)
-> Codec Object ListCardResponseBody (Maybe RiskEvaluation)
-> Codec
Object
ListCardResponseBody
(UTCTime -> UTCTime -> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"riskEvaluation" ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
-> (ListCardResponseBody -> Maybe RiskEvaluation)
-> Codec Object ListCardResponseBody (Maybe RiskEvaluation)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> Maybe RiskEvaluation
listCardRiskEvaluation
Codec
Object
ListCardResponseBody
(UTCTime -> UTCTime -> ListCardResponseBody)
-> Codec Object ListCardResponseBody UTCTime
-> Codec
Object ListCardResponseBody (UTCTime -> ListCardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (ListCardResponseBody -> UTCTime)
-> Codec Object ListCardResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> UTCTime
listCardCreateDate
Codec Object ListCardResponseBody (UTCTime -> ListCardResponseBody)
-> Codec Object ListCardResponseBody UTCTime
-> ObjectCodec ListCardResponseBody ListCardResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (ListCardResponseBody -> UTCTime)
-> Codec Object ListCardResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardResponseBody -> UTCTime
listCardUpdateDate
data CardResponseBody = CardResponseBody
{ CardResponseBody -> UUID
cardId :: !UUID,
CardResponseBody -> Status
cardStatus :: !Status,
CardResponseBody -> BillingDetails
cardBillingDetails :: !BillingDetails,
CardResponseBody -> Int
cardExpiryMonth :: !Int,
CardResponseBody -> Int
cardExpiryYear :: !Int,
CardResponseBody -> CardNetwork
cardNetwork :: !CardNetwork,
CardResponseBody -> Text
cardLast4 :: !Text,
CardResponseBody -> Maybe Text
cardBin :: !(Maybe Text),
CardResponseBody -> Maybe ISO3166Alpha2
cardIssuerCountry :: !(Maybe ISO3166Alpha2),
CardResponseBody -> Maybe CardFundingType
cardFundingType :: !(Maybe CardFundingType),
CardResponseBody -> UUID
cardFingerprint :: !UUID,
CardResponseBody -> Maybe VerificationErrorCode
cardErrorCode :: !(Maybe VerificationErrorCode),
CardResponseBody -> VerificationData
cardVerification :: !VerificationData,
CardResponseBody -> Maybe RiskEvaluation
cardRiskEvaluation :: !(Maybe RiskEvaluation),
CardResponseBody -> ResponseMetadata
cardMetadata :: !ResponseMetadata,
CardResponseBody -> UTCTime
cardCreateDate :: !UTCTime,
CardResponseBody -> UTCTime
cardUpdateDate :: !UTCTime
}
deriving (CardResponseBody -> CardResponseBody -> Bool
(CardResponseBody -> CardResponseBody -> Bool)
-> (CardResponseBody -> CardResponseBody -> Bool)
-> Eq CardResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardResponseBody -> CardResponseBody -> Bool
$c/= :: CardResponseBody -> CardResponseBody -> Bool
== :: CardResponseBody -> CardResponseBody -> Bool
$c== :: CardResponseBody -> CardResponseBody -> Bool
Eq, Int -> CardResponseBody -> ShowS
[CardResponseBody] -> ShowS
CardResponseBody -> String
(Int -> CardResponseBody -> ShowS)
-> (CardResponseBody -> String)
-> ([CardResponseBody] -> ShowS)
-> Show CardResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardResponseBody] -> ShowS
$cshowList :: [CardResponseBody] -> ShowS
show :: CardResponseBody -> String
$cshow :: CardResponseBody -> String
showsPrec :: Int -> CardResponseBody -> ShowS
$cshowsPrec :: Int -> CardResponseBody -> ShowS
Show)
deriving
( Value -> Parser [CardResponseBody]
Value -> Parser CardResponseBody
(Value -> Parser CardResponseBody)
-> (Value -> Parser [CardResponseBody])
-> FromJSON CardResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CardResponseBody]
$cparseJSONList :: Value -> Parser [CardResponseBody]
parseJSON :: Value -> Parser CardResponseBody
$cparseJSON :: Value -> Parser CardResponseBody
FromJSON,
[CardResponseBody] -> Encoding
[CardResponseBody] -> Value
CardResponseBody -> Encoding
CardResponseBody -> Value
(CardResponseBody -> Value)
-> (CardResponseBody -> Encoding)
-> ([CardResponseBody] -> Value)
-> ([CardResponseBody] -> Encoding)
-> ToJSON CardResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CardResponseBody] -> Encoding
$ctoEncodingList :: [CardResponseBody] -> Encoding
toJSONList :: [CardResponseBody] -> Value
$ctoJSONList :: [CardResponseBody] -> Value
toEncoding :: CardResponseBody -> Encoding
$ctoEncoding :: CardResponseBody -> Encoding
toJSON :: CardResponseBody -> Value
$ctoJSON :: CardResponseBody -> Value
ToJSON
)
via (Autodocodec CardResponseBody)
instance HasCodec CardResponseBody where
codec :: JSONCodec CardResponseBody
codec =
Text
-> ObjectCodec CardResponseBody CardResponseBody
-> JSONCodec CardResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CardResponseBody" (ObjectCodec CardResponseBody CardResponseBody
-> JSONCodec CardResponseBody)
-> ObjectCodec CardResponseBody CardResponseBody
-> JSONCodec CardResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Status
-> BillingDetails
-> Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody
CardResponseBody
(UUID
-> Status
-> BillingDetails
-> Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody UUID
-> Codec
Object
CardResponseBody
(Status
-> BillingDetails
-> Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (CardResponseBody -> UUID) -> Codec Object CardResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> UUID
cardId
Codec
Object
CardResponseBody
(Status
-> BillingDetails
-> Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody Status
-> Codec
Object
CardResponseBody
(BillingDetails
-> Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (CardResponseBody -> Status)
-> Codec Object CardResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Status
cardStatus
Codec
Object
CardResponseBody
(BillingDetails
-> Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody BillingDetails
-> Codec
Object
CardResponseBody
(Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (CardResponseBody -> BillingDetails)
-> Codec Object CardResponseBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> BillingDetails
cardBillingDetails
Codec
Object
CardResponseBody
(Int
-> Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody Int
-> Codec
Object
CardResponseBody
(Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expMonth" ObjectCodec Int Int
-> (CardResponseBody -> Int) -> Codec Object CardResponseBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Int
cardExpiryMonth
Codec
Object
CardResponseBody
(Int
-> CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody Int
-> Codec
Object
CardResponseBody
(CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expYear" ObjectCodec Int Int
-> (CardResponseBody -> Int) -> Codec Object CardResponseBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Int
cardExpiryYear
Codec
Object
CardResponseBody
(CardNetwork
-> Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody CardNetwork
-> Codec
Object
CardResponseBody
(Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec CardNetwork CardNetwork
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"network" ObjectCodec CardNetwork CardNetwork
-> (CardResponseBody -> CardNetwork)
-> Codec Object CardResponseBody CardNetwork
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> CardNetwork
cardNetwork
Codec
Object
CardResponseBody
(Text
-> Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody Text
-> Codec
Object
CardResponseBody
(Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"last4" ObjectCodec Text Text
-> (CardResponseBody -> Text) -> Codec Object CardResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Text
cardLast4
Codec
Object
CardResponseBody
(Maybe Text
-> Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody (Maybe Text)
-> Codec
Object
CardResponseBody
(Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"bin" ObjectCodec (Maybe Text) (Maybe Text)
-> (CardResponseBody -> Maybe Text)
-> Codec Object CardResponseBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Maybe Text
cardBin
Codec
Object
CardResponseBody
(Maybe ISO3166Alpha2
-> Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody (Maybe ISO3166Alpha2)
-> Codec
Object
CardResponseBody
(Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"issuerCountry" ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
-> (CardResponseBody -> Maybe ISO3166Alpha2)
-> Codec Object CardResponseBody (Maybe ISO3166Alpha2)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Maybe ISO3166Alpha2
cardIssuerCountry
Codec
Object
CardResponseBody
(Maybe CardFundingType
-> UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody (Maybe CardFundingType)
-> Codec
Object
CardResponseBody
(UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe CardFundingType) (Maybe CardFundingType)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"fundingType" ObjectCodec (Maybe CardFundingType) (Maybe CardFundingType)
-> (CardResponseBody -> Maybe CardFundingType)
-> Codec Object CardResponseBody (Maybe CardFundingType)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Maybe CardFundingType
cardFundingType
Codec
Object
CardResponseBody
(UUID
-> Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody UUID
-> Codec
Object
CardResponseBody
(Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fingerprint" ObjectCodec UUID UUID
-> (CardResponseBody -> UUID) -> Codec Object CardResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> UUID
cardFingerprint
Codec
Object
CardResponseBody
(Maybe VerificationErrorCode
-> VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody (Maybe VerificationErrorCode)
-> Codec
Object
CardResponseBody
(VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe VerificationErrorCode) (Maybe VerificationErrorCode)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"errorCode" ObjectCodec
(Maybe VerificationErrorCode) (Maybe VerificationErrorCode)
-> (CardResponseBody -> Maybe VerificationErrorCode)
-> Codec Object CardResponseBody (Maybe VerificationErrorCode)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Maybe VerificationErrorCode
cardErrorCode
Codec
Object
CardResponseBody
(VerificationData
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> CardResponseBody)
-> Codec Object CardResponseBody VerificationData
-> Codec
Object
CardResponseBody
(Maybe RiskEvaluation
-> ResponseMetadata -> UTCTime -> UTCTime -> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec VerificationData VerificationData
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"verification" ObjectCodec VerificationData VerificationData
-> (CardResponseBody -> VerificationData)
-> Codec Object CardResponseBody VerificationData
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> VerificationData
cardVerification
Codec
Object
CardResponseBody
(Maybe RiskEvaluation
-> ResponseMetadata -> UTCTime -> UTCTime -> CardResponseBody)
-> Codec Object CardResponseBody (Maybe RiskEvaluation)
-> Codec
Object
CardResponseBody
(ResponseMetadata -> UTCTime -> UTCTime -> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"riskEvaluation" ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
-> (CardResponseBody -> Maybe RiskEvaluation)
-> Codec Object CardResponseBody (Maybe RiskEvaluation)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> Maybe RiskEvaluation
cardRiskEvaluation
Codec
Object
CardResponseBody
(ResponseMetadata -> UTCTime -> UTCTime -> CardResponseBody)
-> Codec Object CardResponseBody ResponseMetadata
-> Codec
Object CardResponseBody (UTCTime -> UTCTime -> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ResponseMetadata ResponseMetadata
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"metadata" ObjectCodec ResponseMetadata ResponseMetadata
-> (CardResponseBody -> ResponseMetadata)
-> Codec Object CardResponseBody ResponseMetadata
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> ResponseMetadata
cardMetadata
Codec
Object CardResponseBody (UTCTime -> UTCTime -> CardResponseBody)
-> Codec Object CardResponseBody UTCTime
-> Codec Object CardResponseBody (UTCTime -> CardResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (CardResponseBody -> UTCTime)
-> Codec Object CardResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> UTCTime
cardCreateDate
Codec Object CardResponseBody (UTCTime -> CardResponseBody)
-> Codec Object CardResponseBody UTCTime
-> ObjectCodec CardResponseBody CardResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (CardResponseBody -> UTCTime)
-> Codec Object CardResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CardResponseBody -> UTCTime
cardUpdateDate
data CreateCardRequestBody = CreateCardRequestBody
{ CreateCardRequestBody -> UUID
createCardIdempotencyKey :: !UUID,
CreateCardRequestBody -> Maybe Text
createCardKeyId :: !(Maybe Text),
CreateCardRequestBody -> Maybe Text
createCardEncryptedData :: !(Maybe Text),
CreateCardRequestBody -> BillingDetails
createCardBillingDetails :: !BillingDetails,
CreateCardRequestBody -> Int
createCardExpiryMonth :: !Int,
CreateCardRequestBody -> Int
createCardExpiryYear :: !Int,
CreateCardRequestBody -> RequestMetadata
createCardMetadata :: !RequestMetadata
}
deriving (CreateCardRequestBody -> CreateCardRequestBody -> Bool
(CreateCardRequestBody -> CreateCardRequestBody -> Bool)
-> (CreateCardRequestBody -> CreateCardRequestBody -> Bool)
-> Eq CreateCardRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCardRequestBody -> CreateCardRequestBody -> Bool
$c/= :: CreateCardRequestBody -> CreateCardRequestBody -> Bool
== :: CreateCardRequestBody -> CreateCardRequestBody -> Bool
$c== :: CreateCardRequestBody -> CreateCardRequestBody -> Bool
Eq, Int -> CreateCardRequestBody -> ShowS
[CreateCardRequestBody] -> ShowS
CreateCardRequestBody -> String
(Int -> CreateCardRequestBody -> ShowS)
-> (CreateCardRequestBody -> String)
-> ([CreateCardRequestBody] -> ShowS)
-> Show CreateCardRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCardRequestBody] -> ShowS
$cshowList :: [CreateCardRequestBody] -> ShowS
show :: CreateCardRequestBody -> String
$cshow :: CreateCardRequestBody -> String
showsPrec :: Int -> CreateCardRequestBody -> ShowS
$cshowsPrec :: Int -> CreateCardRequestBody -> ShowS
Show)
deriving
( Value -> Parser [CreateCardRequestBody]
Value -> Parser CreateCardRequestBody
(Value -> Parser CreateCardRequestBody)
-> (Value -> Parser [CreateCardRequestBody])
-> FromJSON CreateCardRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CreateCardRequestBody]
$cparseJSONList :: Value -> Parser [CreateCardRequestBody]
parseJSON :: Value -> Parser CreateCardRequestBody
$cparseJSON :: Value -> Parser CreateCardRequestBody
FromJSON,
[CreateCardRequestBody] -> Encoding
[CreateCardRequestBody] -> Value
CreateCardRequestBody -> Encoding
CreateCardRequestBody -> Value
(CreateCardRequestBody -> Value)
-> (CreateCardRequestBody -> Encoding)
-> ([CreateCardRequestBody] -> Value)
-> ([CreateCardRequestBody] -> Encoding)
-> ToJSON CreateCardRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreateCardRequestBody] -> Encoding
$ctoEncodingList :: [CreateCardRequestBody] -> Encoding
toJSONList :: [CreateCardRequestBody] -> Value
$ctoJSONList :: [CreateCardRequestBody] -> Value
toEncoding :: CreateCardRequestBody -> Encoding
$ctoEncoding :: CreateCardRequestBody -> Encoding
toJSON :: CreateCardRequestBody -> Value
$ctoJSON :: CreateCardRequestBody -> Value
ToJSON
)
via (Autodocodec CreateCardRequestBody)
instance HasCodec CreateCardRequestBody where
codec :: JSONCodec CreateCardRequestBody
codec =
Text
-> ObjectCodec CreateCardRequestBody CreateCardRequestBody
-> JSONCodec CreateCardRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CreateCardRequestBody" (ObjectCodec CreateCardRequestBody CreateCardRequestBody
-> JSONCodec CreateCardRequestBody)
-> ObjectCodec CreateCardRequestBody CreateCardRequestBody
-> JSONCodec CreateCardRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Maybe Text
-> Maybe Text
-> BillingDetails
-> Int
-> Int
-> RequestMetadata
-> CreateCardRequestBody
CreateCardRequestBody
(UUID
-> Maybe Text
-> Maybe Text
-> BillingDetails
-> Int
-> Int
-> RequestMetadata
-> CreateCardRequestBody)
-> Codec Object CreateCardRequestBody UUID
-> Codec
Object
CreateCardRequestBody
(Maybe Text
-> Maybe Text
-> BillingDetails
-> Int
-> Int
-> RequestMetadata
-> CreateCardRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (CreateCardRequestBody -> UUID)
-> Codec Object CreateCardRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateCardRequestBody -> UUID
createCardIdempotencyKey
Codec
Object
CreateCardRequestBody
(Maybe Text
-> Maybe Text
-> BillingDetails
-> Int
-> Int
-> RequestMetadata
-> CreateCardRequestBody)
-> Codec Object CreateCardRequestBody (Maybe Text)
-> Codec
Object
CreateCardRequestBody
(Maybe Text
-> BillingDetails
-> Int
-> Int
-> RequestMetadata
-> CreateCardRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"keyId" ObjectCodec (Maybe Text) (Maybe Text)
-> (CreateCardRequestBody -> Maybe Text)
-> Codec Object CreateCardRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateCardRequestBody -> Maybe Text
createCardKeyId
Codec
Object
CreateCardRequestBody
(Maybe Text
-> BillingDetails
-> Int
-> Int
-> RequestMetadata
-> CreateCardRequestBody)
-> Codec Object CreateCardRequestBody (Maybe Text)
-> Codec
Object
CreateCardRequestBody
(BillingDetails
-> Int -> Int -> RequestMetadata -> CreateCardRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"encryptedData" ObjectCodec (Maybe Text) (Maybe Text)
-> (CreateCardRequestBody -> Maybe Text)
-> Codec Object CreateCardRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateCardRequestBody -> Maybe Text
createCardEncryptedData
Codec
Object
CreateCardRequestBody
(BillingDetails
-> Int -> Int -> RequestMetadata -> CreateCardRequestBody)
-> Codec Object CreateCardRequestBody BillingDetails
-> Codec
Object
CreateCardRequestBody
(Int -> Int -> RequestMetadata -> CreateCardRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (CreateCardRequestBody -> BillingDetails)
-> Codec Object CreateCardRequestBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateCardRequestBody -> BillingDetails
createCardBillingDetails
Codec
Object
CreateCardRequestBody
(Int -> Int -> RequestMetadata -> CreateCardRequestBody)
-> Codec Object CreateCardRequestBody Int
-> Codec
Object
CreateCardRequestBody
(Int -> RequestMetadata -> CreateCardRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expMonth" ObjectCodec Int Int
-> (CreateCardRequestBody -> Int)
-> Codec Object CreateCardRequestBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateCardRequestBody -> Int
createCardExpiryMonth
Codec
Object
CreateCardRequestBody
(Int -> RequestMetadata -> CreateCardRequestBody)
-> Codec Object CreateCardRequestBody Int
-> Codec
Object
CreateCardRequestBody
(RequestMetadata -> CreateCardRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expYear" ObjectCodec Int Int
-> (CreateCardRequestBody -> Int)
-> Codec Object CreateCardRequestBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateCardRequestBody -> Int
createCardExpiryYear
Codec
Object
CreateCardRequestBody
(RequestMetadata -> CreateCardRequestBody)
-> Codec Object CreateCardRequestBody RequestMetadata
-> ObjectCodec CreateCardRequestBody CreateCardRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RequestMetadata RequestMetadata
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"metadata" ObjectCodec RequestMetadata RequestMetadata
-> (CreateCardRequestBody -> RequestMetadata)
-> Codec Object CreateCardRequestBody RequestMetadata
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateCardRequestBody -> RequestMetadata
createCardMetadata
data UpdateCardRequestBody = UpdateCardRequestBody
{ UpdateCardRequestBody -> Maybe Text
updateCardKeyId :: !(Maybe Text),
UpdateCardRequestBody -> Maybe Text
updateCardEncryptedData :: !(Maybe Text),
UpdateCardRequestBody -> Int
updateCardExpiryMonth :: !Int,
UpdateCardRequestBody -> Int
updateCardExpiryYear :: !Int
}
deriving (UpdateCardRequestBody -> UpdateCardRequestBody -> Bool
(UpdateCardRequestBody -> UpdateCardRequestBody -> Bool)
-> (UpdateCardRequestBody -> UpdateCardRequestBody -> Bool)
-> Eq UpdateCardRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCardRequestBody -> UpdateCardRequestBody -> Bool
$c/= :: UpdateCardRequestBody -> UpdateCardRequestBody -> Bool
== :: UpdateCardRequestBody -> UpdateCardRequestBody -> Bool
$c== :: UpdateCardRequestBody -> UpdateCardRequestBody -> Bool
Eq, Int -> UpdateCardRequestBody -> ShowS
[UpdateCardRequestBody] -> ShowS
UpdateCardRequestBody -> String
(Int -> UpdateCardRequestBody -> ShowS)
-> (UpdateCardRequestBody -> String)
-> ([UpdateCardRequestBody] -> ShowS)
-> Show UpdateCardRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCardRequestBody] -> ShowS
$cshowList :: [UpdateCardRequestBody] -> ShowS
show :: UpdateCardRequestBody -> String
$cshow :: UpdateCardRequestBody -> String
showsPrec :: Int -> UpdateCardRequestBody -> ShowS
$cshowsPrec :: Int -> UpdateCardRequestBody -> ShowS
Show)
deriving
( Value -> Parser [UpdateCardRequestBody]
Value -> Parser UpdateCardRequestBody
(Value -> Parser UpdateCardRequestBody)
-> (Value -> Parser [UpdateCardRequestBody])
-> FromJSON UpdateCardRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [UpdateCardRequestBody]
$cparseJSONList :: Value -> Parser [UpdateCardRequestBody]
parseJSON :: Value -> Parser UpdateCardRequestBody
$cparseJSON :: Value -> Parser UpdateCardRequestBody
FromJSON,
[UpdateCardRequestBody] -> Encoding
[UpdateCardRequestBody] -> Value
UpdateCardRequestBody -> Encoding
UpdateCardRequestBody -> Value
(UpdateCardRequestBody -> Value)
-> (UpdateCardRequestBody -> Encoding)
-> ([UpdateCardRequestBody] -> Value)
-> ([UpdateCardRequestBody] -> Encoding)
-> ToJSON UpdateCardRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [UpdateCardRequestBody] -> Encoding
$ctoEncodingList :: [UpdateCardRequestBody] -> Encoding
toJSONList :: [UpdateCardRequestBody] -> Value
$ctoJSONList :: [UpdateCardRequestBody] -> Value
toEncoding :: UpdateCardRequestBody -> Encoding
$ctoEncoding :: UpdateCardRequestBody -> Encoding
toJSON :: UpdateCardRequestBody -> Value
$ctoJSON :: UpdateCardRequestBody -> Value
ToJSON
)
via (Autodocodec UpdateCardRequestBody)
instance HasCodec UpdateCardRequestBody where
codec :: JSONCodec UpdateCardRequestBody
codec =
Text
-> ObjectCodec UpdateCardRequestBody UpdateCardRequestBody
-> JSONCodec UpdateCardRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"UpdateCardRequestBody" (ObjectCodec UpdateCardRequestBody UpdateCardRequestBody
-> JSONCodec UpdateCardRequestBody)
-> ObjectCodec UpdateCardRequestBody UpdateCardRequestBody
-> JSONCodec UpdateCardRequestBody
forall a b. (a -> b) -> a -> b
$
Maybe Text -> Maybe Text -> Int -> Int -> UpdateCardRequestBody
UpdateCardRequestBody
(Maybe Text -> Maybe Text -> Int -> Int -> UpdateCardRequestBody)
-> Codec Object UpdateCardRequestBody (Maybe Text)
-> Codec
Object
UpdateCardRequestBody
(Maybe Text -> Int -> Int -> UpdateCardRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"keyId" ObjectCodec (Maybe Text) (Maybe Text)
-> (UpdateCardRequestBody -> Maybe Text)
-> Codec Object UpdateCardRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= UpdateCardRequestBody -> Maybe Text
updateCardKeyId
Codec
Object
UpdateCardRequestBody
(Maybe Text -> Int -> Int -> UpdateCardRequestBody)
-> Codec Object UpdateCardRequestBody (Maybe Text)
-> Codec
Object UpdateCardRequestBody (Int -> Int -> UpdateCardRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"encryptedData" ObjectCodec (Maybe Text) (Maybe Text)
-> (UpdateCardRequestBody -> Maybe Text)
-> Codec Object UpdateCardRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= UpdateCardRequestBody -> Maybe Text
updateCardEncryptedData
Codec
Object UpdateCardRequestBody (Int -> Int -> UpdateCardRequestBody)
-> Codec Object UpdateCardRequestBody Int
-> Codec
Object UpdateCardRequestBody (Int -> UpdateCardRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expMonth" ObjectCodec Int Int
-> (UpdateCardRequestBody -> Int)
-> Codec Object UpdateCardRequestBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= UpdateCardRequestBody -> Int
updateCardExpiryMonth
Codec Object UpdateCardRequestBody (Int -> UpdateCardRequestBody)
-> Codec Object UpdateCardRequestBody Int
-> ObjectCodec UpdateCardRequestBody UpdateCardRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Int Int
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expYear" ObjectCodec Int Int
-> (UpdateCardRequestBody -> Int)
-> Codec Object UpdateCardRequestBody Int
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= UpdateCardRequestBody -> Int
updateCardExpiryYear
data ListCardBillingDetails = ListCardBillingDetails
{ ListCardBillingDetails -> ISO3166Alpha2
listCardBillingDetailsCountry :: !ISO3166Alpha2,
ListCardBillingDetails -> District
listCardBillingDetailsDistrict :: !District
}
deriving (ListCardBillingDetails -> ListCardBillingDetails -> Bool
(ListCardBillingDetails -> ListCardBillingDetails -> Bool)
-> (ListCardBillingDetails -> ListCardBillingDetails -> Bool)
-> Eq ListCardBillingDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCardBillingDetails -> ListCardBillingDetails -> Bool
$c/= :: ListCardBillingDetails -> ListCardBillingDetails -> Bool
== :: ListCardBillingDetails -> ListCardBillingDetails -> Bool
$c== :: ListCardBillingDetails -> ListCardBillingDetails -> Bool
Eq, Int -> ListCardBillingDetails -> ShowS
[ListCardBillingDetails] -> ShowS
ListCardBillingDetails -> String
(Int -> ListCardBillingDetails -> ShowS)
-> (ListCardBillingDetails -> String)
-> ([ListCardBillingDetails] -> ShowS)
-> Show ListCardBillingDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCardBillingDetails] -> ShowS
$cshowList :: [ListCardBillingDetails] -> ShowS
show :: ListCardBillingDetails -> String
$cshow :: ListCardBillingDetails -> String
showsPrec :: Int -> ListCardBillingDetails -> ShowS
$cshowsPrec :: Int -> ListCardBillingDetails -> ShowS
Show, (forall x. ListCardBillingDetails -> Rep ListCardBillingDetails x)
-> (forall x.
Rep ListCardBillingDetails x -> ListCardBillingDetails)
-> Generic ListCardBillingDetails
forall x. Rep ListCardBillingDetails x -> ListCardBillingDetails
forall x. ListCardBillingDetails -> Rep ListCardBillingDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCardBillingDetails x -> ListCardBillingDetails
$cfrom :: forall x. ListCardBillingDetails -> Rep ListCardBillingDetails x
Generic)
deriving
( [ListCardBillingDetails] -> Encoding
[ListCardBillingDetails] -> Value
ListCardBillingDetails -> Encoding
ListCardBillingDetails -> Value
(ListCardBillingDetails -> Value)
-> (ListCardBillingDetails -> Encoding)
-> ([ListCardBillingDetails] -> Value)
-> ([ListCardBillingDetails] -> Encoding)
-> ToJSON ListCardBillingDetails
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ListCardBillingDetails] -> Encoding
$ctoEncodingList :: [ListCardBillingDetails] -> Encoding
toJSONList :: [ListCardBillingDetails] -> Value
$ctoJSONList :: [ListCardBillingDetails] -> Value
toEncoding :: ListCardBillingDetails -> Encoding
$ctoEncoding :: ListCardBillingDetails -> Encoding
toJSON :: ListCardBillingDetails -> Value
$ctoJSON :: ListCardBillingDetails -> Value
ToJSON,
Value -> Parser [ListCardBillingDetails]
Value -> Parser ListCardBillingDetails
(Value -> Parser ListCardBillingDetails)
-> (Value -> Parser [ListCardBillingDetails])
-> FromJSON ListCardBillingDetails
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ListCardBillingDetails]
$cparseJSONList :: Value -> Parser [ListCardBillingDetails]
parseJSON :: Value -> Parser ListCardBillingDetails
$cparseJSON :: Value -> Parser ListCardBillingDetails
FromJSON
)
via (Autodocodec ListCardBillingDetails)
instance HasCodec ListCardBillingDetails where
codec :: JSONCodec ListCardBillingDetails
codec =
Text
-> ObjectCodec ListCardBillingDetails ListCardBillingDetails
-> JSONCodec ListCardBillingDetails
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ListCardBillingDetails" (ObjectCodec ListCardBillingDetails ListCardBillingDetails
-> JSONCodec ListCardBillingDetails)
-> ObjectCodec ListCardBillingDetails ListCardBillingDetails
-> JSONCodec ListCardBillingDetails
forall a b. (a -> b) -> a -> b
$
ISO3166Alpha2 -> District -> ListCardBillingDetails
ListCardBillingDetails
(ISO3166Alpha2 -> District -> ListCardBillingDetails)
-> Codec Object ListCardBillingDetails ISO3166Alpha2
-> Codec
Object ListCardBillingDetails (District -> ListCardBillingDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec ISO3166Alpha2 ISO3166Alpha2
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"country" ObjectCodec ISO3166Alpha2 ISO3166Alpha2
-> (ListCardBillingDetails -> ISO3166Alpha2)
-> Codec Object ListCardBillingDetails ISO3166Alpha2
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardBillingDetails -> ISO3166Alpha2
listCardBillingDetailsCountry
Codec
Object ListCardBillingDetails (District -> ListCardBillingDetails)
-> Codec Object ListCardBillingDetails District
-> ObjectCodec ListCardBillingDetails ListCardBillingDetails
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec District District
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"district" ObjectCodec District District
-> (ListCardBillingDetails -> District)
-> Codec Object ListCardBillingDetails District
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ListCardBillingDetails -> District
listCardBillingDetailsDistrict
data CardNetwork
= VISA
| MASTERCARD
| AMEX
| UNKNOWN
deriving (CardNetwork -> CardNetwork -> Bool
(CardNetwork -> CardNetwork -> Bool)
-> (CardNetwork -> CardNetwork -> Bool) -> Eq CardNetwork
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardNetwork -> CardNetwork -> Bool
$c/= :: CardNetwork -> CardNetwork -> Bool
== :: CardNetwork -> CardNetwork -> Bool
$c== :: CardNetwork -> CardNetwork -> Bool
Eq, Int -> CardNetwork -> ShowS
[CardNetwork] -> ShowS
CardNetwork -> String
(Int -> CardNetwork -> ShowS)
-> (CardNetwork -> String)
-> ([CardNetwork] -> ShowS)
-> Show CardNetwork
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardNetwork] -> ShowS
$cshowList :: [CardNetwork] -> ShowS
show :: CardNetwork -> String
$cshow :: CardNetwork -> String
showsPrec :: Int -> CardNetwork -> ShowS
$cshowsPrec :: Int -> CardNetwork -> ShowS
Show, Int -> CardNetwork
CardNetwork -> Int
CardNetwork -> [CardNetwork]
CardNetwork -> CardNetwork
CardNetwork -> CardNetwork -> [CardNetwork]
CardNetwork -> CardNetwork -> CardNetwork -> [CardNetwork]
(CardNetwork -> CardNetwork)
-> (CardNetwork -> CardNetwork)
-> (Int -> CardNetwork)
-> (CardNetwork -> Int)
-> (CardNetwork -> [CardNetwork])
-> (CardNetwork -> CardNetwork -> [CardNetwork])
-> (CardNetwork -> CardNetwork -> [CardNetwork])
-> (CardNetwork -> CardNetwork -> CardNetwork -> [CardNetwork])
-> Enum CardNetwork
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CardNetwork -> CardNetwork -> CardNetwork -> [CardNetwork]
$cenumFromThenTo :: CardNetwork -> CardNetwork -> CardNetwork -> [CardNetwork]
enumFromTo :: CardNetwork -> CardNetwork -> [CardNetwork]
$cenumFromTo :: CardNetwork -> CardNetwork -> [CardNetwork]
enumFromThen :: CardNetwork -> CardNetwork -> [CardNetwork]
$cenumFromThen :: CardNetwork -> CardNetwork -> [CardNetwork]
enumFrom :: CardNetwork -> [CardNetwork]
$cenumFrom :: CardNetwork -> [CardNetwork]
fromEnum :: CardNetwork -> Int
$cfromEnum :: CardNetwork -> Int
toEnum :: Int -> CardNetwork
$ctoEnum :: Int -> CardNetwork
pred :: CardNetwork -> CardNetwork
$cpred :: CardNetwork -> CardNetwork
succ :: CardNetwork -> CardNetwork
$csucc :: CardNetwork -> CardNetwork
Enum, CardNetwork
CardNetwork -> CardNetwork -> Bounded CardNetwork
forall a. a -> a -> Bounded a
maxBound :: CardNetwork
$cmaxBound :: CardNetwork
minBound :: CardNetwork
$cminBound :: CardNetwork
Bounded)
deriving
( Value -> Parser [CardNetwork]
Value -> Parser CardNetwork
(Value -> Parser CardNetwork)
-> (Value -> Parser [CardNetwork]) -> FromJSON CardNetwork
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CardNetwork]
$cparseJSONList :: Value -> Parser [CardNetwork]
parseJSON :: Value -> Parser CardNetwork
$cparseJSON :: Value -> Parser CardNetwork
FromJSON,
[CardNetwork] -> Encoding
[CardNetwork] -> Value
CardNetwork -> Encoding
CardNetwork -> Value
(CardNetwork -> Value)
-> (CardNetwork -> Encoding)
-> ([CardNetwork] -> Value)
-> ([CardNetwork] -> Encoding)
-> ToJSON CardNetwork
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CardNetwork] -> Encoding
$ctoEncodingList :: [CardNetwork] -> Encoding
toJSONList :: [CardNetwork] -> Value
$ctoJSONList :: [CardNetwork] -> Value
toEncoding :: CardNetwork -> Encoding
$ctoEncoding :: CardNetwork -> Encoding
toJSON :: CardNetwork -> Value
$ctoJSON :: CardNetwork -> Value
ToJSON
)
via (Autodocodec CardNetwork)
instance HasCodec CardNetwork where
codec :: JSONCodec CardNetwork
codec = JSONCodec CardNetwork
forall enum.
(Show enum, Eq enum, Enum enum, Bounded enum) =>
JSONCodec enum
shownBoundedEnumCodec
data CardFundingType
= Credit
| Debit
| Prepaid
| Unknown
deriving (CardFundingType -> CardFundingType -> Bool
(CardFundingType -> CardFundingType -> Bool)
-> (CardFundingType -> CardFundingType -> Bool)
-> Eq CardFundingType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardFundingType -> CardFundingType -> Bool
$c/= :: CardFundingType -> CardFundingType -> Bool
== :: CardFundingType -> CardFundingType -> Bool
$c== :: CardFundingType -> CardFundingType -> Bool
Eq, Int -> CardFundingType -> ShowS
[CardFundingType] -> ShowS
CardFundingType -> String
(Int -> CardFundingType -> ShowS)
-> (CardFundingType -> String)
-> ([CardFundingType] -> ShowS)
-> Show CardFundingType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardFundingType] -> ShowS
$cshowList :: [CardFundingType] -> ShowS
show :: CardFundingType -> String
$cshow :: CardFundingType -> String
showsPrec :: Int -> CardFundingType -> ShowS
$cshowsPrec :: Int -> CardFundingType -> ShowS
Show, Int -> CardFundingType
CardFundingType -> Int
CardFundingType -> [CardFundingType]
CardFundingType -> CardFundingType
CardFundingType -> CardFundingType -> [CardFundingType]
CardFundingType
-> CardFundingType -> CardFundingType -> [CardFundingType]
(CardFundingType -> CardFundingType)
-> (CardFundingType -> CardFundingType)
-> (Int -> CardFundingType)
-> (CardFundingType -> Int)
-> (CardFundingType -> [CardFundingType])
-> (CardFundingType -> CardFundingType -> [CardFundingType])
-> (CardFundingType -> CardFundingType -> [CardFundingType])
-> (CardFundingType
-> CardFundingType -> CardFundingType -> [CardFundingType])
-> Enum CardFundingType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: CardFundingType
-> CardFundingType -> CardFundingType -> [CardFundingType]
$cenumFromThenTo :: CardFundingType
-> CardFundingType -> CardFundingType -> [CardFundingType]
enumFromTo :: CardFundingType -> CardFundingType -> [CardFundingType]
$cenumFromTo :: CardFundingType -> CardFundingType -> [CardFundingType]
enumFromThen :: CardFundingType -> CardFundingType -> [CardFundingType]
$cenumFromThen :: CardFundingType -> CardFundingType -> [CardFundingType]
enumFrom :: CardFundingType -> [CardFundingType]
$cenumFrom :: CardFundingType -> [CardFundingType]
fromEnum :: CardFundingType -> Int
$cfromEnum :: CardFundingType -> Int
toEnum :: Int -> CardFundingType
$ctoEnum :: Int -> CardFundingType
pred :: CardFundingType -> CardFundingType
$cpred :: CardFundingType -> CardFundingType
succ :: CardFundingType -> CardFundingType
$csucc :: CardFundingType -> CardFundingType
Enum, CardFundingType
CardFundingType -> CardFundingType -> Bounded CardFundingType
forall a. a -> a -> Bounded a
maxBound :: CardFundingType
$cmaxBound :: CardFundingType
minBound :: CardFundingType
$cminBound :: CardFundingType
Bounded)
deriving
( Value -> Parser [CardFundingType]
Value -> Parser CardFundingType
(Value -> Parser CardFundingType)
-> (Value -> Parser [CardFundingType]) -> FromJSON CardFundingType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CardFundingType]
$cparseJSONList :: Value -> Parser [CardFundingType]
parseJSON :: Value -> Parser CardFundingType
$cparseJSON :: Value -> Parser CardFundingType
FromJSON,
[CardFundingType] -> Encoding
[CardFundingType] -> Value
CardFundingType -> Encoding
CardFundingType -> Value
(CardFundingType -> Value)
-> (CardFundingType -> Encoding)
-> ([CardFundingType] -> Value)
-> ([CardFundingType] -> Encoding)
-> ToJSON CardFundingType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CardFundingType] -> Encoding
$ctoEncodingList :: [CardFundingType] -> Encoding
toJSONList :: [CardFundingType] -> Value
$ctoJSONList :: [CardFundingType] -> Value
toEncoding :: CardFundingType -> Encoding
$ctoEncoding :: CardFundingType -> Encoding
toJSON :: CardFundingType -> Value
$ctoJSON :: CardFundingType -> Value
ToJSON
)
via (Autodocodec CardFundingType)
instance HasCodec CardFundingType where
codec :: JSONCodec CardFundingType
codec =
NonEmpty (CardFundingType, Text) -> JSONCodec CardFundingType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (CardFundingType, Text) -> JSONCodec CardFundingType)
-> NonEmpty (CardFundingType, Text) -> JSONCodec CardFundingType
forall a b. (a -> b) -> a -> b
$
[(CardFundingType, Text)] -> NonEmpty (CardFundingType, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (CardFundingType
Credit, Text
"credit"),
(CardFundingType
Debit, Text
"debit"),
(CardFundingType
Prepaid, Text
"prepaid"),
(CardFundingType
Unknown, Text
"unknown")
]
data VerificationErrorCode
= VerificationFailed
| VerificationFraudDetected
| VerificationDenied
| VerificationNotSupportedByIssuer
| VerificationStoppedByIssuer
| VerificationCardFailed
| VerificationCardInvalid
| VerificationCardAddressMismatch
| VerificationCardZipMismatch
| VerificationCardCvvInvalid
| VerificationCardExpired
| VerificationCardLimitViolated
| VerificationCardNotHonored
| VerificationCardCvvRequired
| VerificationCreditCardNotAllowed
| VerificationCardAccountIneligible
| VerificationCardNetworkUnsupported
deriving (VerificationErrorCode -> VerificationErrorCode -> Bool
(VerificationErrorCode -> VerificationErrorCode -> Bool)
-> (VerificationErrorCode -> VerificationErrorCode -> Bool)
-> Eq VerificationErrorCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationErrorCode -> VerificationErrorCode -> Bool
$c/= :: VerificationErrorCode -> VerificationErrorCode -> Bool
== :: VerificationErrorCode -> VerificationErrorCode -> Bool
$c== :: VerificationErrorCode -> VerificationErrorCode -> Bool
Eq, Int -> VerificationErrorCode -> ShowS
[VerificationErrorCode] -> ShowS
VerificationErrorCode -> String
(Int -> VerificationErrorCode -> ShowS)
-> (VerificationErrorCode -> String)
-> ([VerificationErrorCode] -> ShowS)
-> Show VerificationErrorCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationErrorCode] -> ShowS
$cshowList :: [VerificationErrorCode] -> ShowS
show :: VerificationErrorCode -> String
$cshow :: VerificationErrorCode -> String
showsPrec :: Int -> VerificationErrorCode -> ShowS
$cshowsPrec :: Int -> VerificationErrorCode -> ShowS
Show)
deriving
( Value -> Parser [VerificationErrorCode]
Value -> Parser VerificationErrorCode
(Value -> Parser VerificationErrorCode)
-> (Value -> Parser [VerificationErrorCode])
-> FromJSON VerificationErrorCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [VerificationErrorCode]
$cparseJSONList :: Value -> Parser [VerificationErrorCode]
parseJSON :: Value -> Parser VerificationErrorCode
$cparseJSON :: Value -> Parser VerificationErrorCode
FromJSON,
[VerificationErrorCode] -> Encoding
[VerificationErrorCode] -> Value
VerificationErrorCode -> Encoding
VerificationErrorCode -> Value
(VerificationErrorCode -> Value)
-> (VerificationErrorCode -> Encoding)
-> ([VerificationErrorCode] -> Value)
-> ([VerificationErrorCode] -> Encoding)
-> ToJSON VerificationErrorCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [VerificationErrorCode] -> Encoding
$ctoEncodingList :: [VerificationErrorCode] -> Encoding
toJSONList :: [VerificationErrorCode] -> Value
$ctoJSONList :: [VerificationErrorCode] -> Value
toEncoding :: VerificationErrorCode -> Encoding
$ctoEncoding :: VerificationErrorCode -> Encoding
toJSON :: VerificationErrorCode -> Value
$ctoJSON :: VerificationErrorCode -> Value
ToJSON
)
via (Autodocodec VerificationErrorCode)
instance HasCodec VerificationErrorCode where
codec :: JSONCodec VerificationErrorCode
codec =
NonEmpty (VerificationErrorCode, Text)
-> JSONCodec VerificationErrorCode
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (VerificationErrorCode, Text)
-> JSONCodec VerificationErrorCode)
-> NonEmpty (VerificationErrorCode, Text)
-> JSONCodec VerificationErrorCode
forall a b. (a -> b) -> a -> b
$
[(VerificationErrorCode, Text)]
-> NonEmpty (VerificationErrorCode, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (VerificationErrorCode
VerificationFailed, Text
"verification_failed"),
(VerificationErrorCode
VerificationFraudDetected, Text
"verification_fraud_detected"),
(VerificationErrorCode
VerificationDenied, Text
"verification_denied"),
(VerificationErrorCode
VerificationNotSupportedByIssuer, Text
"verification_not_supported_by_issuer"),
(VerificationErrorCode
VerificationStoppedByIssuer, Text
"verification_stopped_by_issuer"),
(VerificationErrorCode
VerificationCardFailed, Text
"card_failed"),
(VerificationErrorCode
VerificationCardInvalid, Text
"card_invalid"),
(VerificationErrorCode
VerificationCardAddressMismatch, Text
"card_address_mismatch"),
(VerificationErrorCode
VerificationCardZipMismatch, Text
"card_zip_mismatch"),
(VerificationErrorCode
VerificationCardCvvInvalid, Text
"card_cvv_invalid"),
(VerificationErrorCode
VerificationCardExpired, Text
"card_expired"),
(VerificationErrorCode
VerificationCardLimitViolated, Text
"card_limit_violated"),
(VerificationErrorCode
VerificationCardNotHonored, Text
"card_not_honored"),
(VerificationErrorCode
VerificationCardCvvRequired, Text
"card_cvv_required"),
(VerificationErrorCode
VerificationCreditCardNotAllowed, Text
"credit_card_not_allowed"),
(VerificationErrorCode
VerificationCardAccountIneligible, Text
"card_account_ineligible"),
(VerificationErrorCode
VerificationCardNetworkUnsupported, Text
"card_network_unsupported")
]
data ACHBankAccountRequest
type instance CircleRequest ACHBankAccountRequest = CircleResponseBody ACHBankAccountResponseBody
data ACHBankAccountResponseBody = ACHBankAccountResponseBody
{ ACHBankAccountResponseBody -> UUID
achBankAccountId :: !UUID,
ACHBankAccountResponseBody -> Status
achBankAccountStatus :: !Status,
ACHBankAccountResponseBody -> AccountNumber
achBankAccountAccountNumber :: !AccountNumber,
ACHBankAccountResponseBody -> RoutingNumber
achBankAccountRoutingNumber :: !RoutingNumber,
ACHBankAccountResponseBody -> BillingDetails
achBankAccountBillingDetails :: !BillingDetails,
ACHBankAccountResponseBody -> Maybe ACHBankAccountType
achBankAccountType :: !(Maybe ACHBankAccountType),
ACHBankAccountResponseBody -> BankAddress
achBankAccountBankAddress :: !BankAddress,
ACHBankAccountResponseBody -> UUID
achBankAccountFingerprint :: !UUID,
ACHBankAccountResponseBody -> Maybe ACHBankAccountErrorCode
achBankAccountErrorCode :: !(Maybe ACHBankAccountErrorCode),
ACHBankAccountResponseBody -> Maybe RiskEvaluation
achBankAccountRiskEvaluation :: !(Maybe RiskEvaluation),
ACHBankAccountResponseBody -> ResponseMetadata
achBankAccountMetadata :: !ResponseMetadata,
ACHBankAccountResponseBody -> UTCTime
achBankAccountCreateDate :: !UTCTime,
ACHBankAccountResponseBody -> UTCTime
achBankAccountUpdateDate :: !UTCTime
}
deriving (ACHBankAccountResponseBody -> ACHBankAccountResponseBody -> Bool
(ACHBankAccountResponseBody -> ACHBankAccountResponseBody -> Bool)
-> (ACHBankAccountResponseBody
-> ACHBankAccountResponseBody -> Bool)
-> Eq ACHBankAccountResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ACHBankAccountResponseBody -> ACHBankAccountResponseBody -> Bool
$c/= :: ACHBankAccountResponseBody -> ACHBankAccountResponseBody -> Bool
== :: ACHBankAccountResponseBody -> ACHBankAccountResponseBody -> Bool
$c== :: ACHBankAccountResponseBody -> ACHBankAccountResponseBody -> Bool
Eq, Int -> ACHBankAccountResponseBody -> ShowS
[ACHBankAccountResponseBody] -> ShowS
ACHBankAccountResponseBody -> String
(Int -> ACHBankAccountResponseBody -> ShowS)
-> (ACHBankAccountResponseBody -> String)
-> ([ACHBankAccountResponseBody] -> ShowS)
-> Show ACHBankAccountResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ACHBankAccountResponseBody] -> ShowS
$cshowList :: [ACHBankAccountResponseBody] -> ShowS
show :: ACHBankAccountResponseBody -> String
$cshow :: ACHBankAccountResponseBody -> String
showsPrec :: Int -> ACHBankAccountResponseBody -> ShowS
$cshowsPrec :: Int -> ACHBankAccountResponseBody -> ShowS
Show)
deriving
( Value -> Parser [ACHBankAccountResponseBody]
Value -> Parser ACHBankAccountResponseBody
(Value -> Parser ACHBankAccountResponseBody)
-> (Value -> Parser [ACHBankAccountResponseBody])
-> FromJSON ACHBankAccountResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ACHBankAccountResponseBody]
$cparseJSONList :: Value -> Parser [ACHBankAccountResponseBody]
parseJSON :: Value -> Parser ACHBankAccountResponseBody
$cparseJSON :: Value -> Parser ACHBankAccountResponseBody
FromJSON,
[ACHBankAccountResponseBody] -> Encoding
[ACHBankAccountResponseBody] -> Value
ACHBankAccountResponseBody -> Encoding
ACHBankAccountResponseBody -> Value
(ACHBankAccountResponseBody -> Value)
-> (ACHBankAccountResponseBody -> Encoding)
-> ([ACHBankAccountResponseBody] -> Value)
-> ([ACHBankAccountResponseBody] -> Encoding)
-> ToJSON ACHBankAccountResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ACHBankAccountResponseBody] -> Encoding
$ctoEncodingList :: [ACHBankAccountResponseBody] -> Encoding
toJSONList :: [ACHBankAccountResponseBody] -> Value
$ctoJSONList :: [ACHBankAccountResponseBody] -> Value
toEncoding :: ACHBankAccountResponseBody -> Encoding
$ctoEncoding :: ACHBankAccountResponseBody -> Encoding
toJSON :: ACHBankAccountResponseBody -> Value
$ctoJSON :: ACHBankAccountResponseBody -> Value
ToJSON
)
via (Autodocodec ACHBankAccountResponseBody)
instance HasCodec ACHBankAccountResponseBody where
codec :: JSONCodec ACHBankAccountResponseBody
codec =
Text
-> ObjectCodec
ACHBankAccountResponseBody ACHBankAccountResponseBody
-> JSONCodec ACHBankAccountResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ACHBankAccountResponseBody" (ObjectCodec ACHBankAccountResponseBody ACHBankAccountResponseBody
-> JSONCodec ACHBankAccountResponseBody)
-> ObjectCodec
ACHBankAccountResponseBody ACHBankAccountResponseBody
-> JSONCodec ACHBankAccountResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Status
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody
ACHBankAccountResponseBody
(UUID
-> Status
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody UUID
-> Codec
Object
ACHBankAccountResponseBody
(Status
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (ACHBankAccountResponseBody -> UUID)
-> Codec Object ACHBankAccountResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> UUID
achBankAccountId
Codec
Object
ACHBankAccountResponseBody
(Status
-> AccountNumber
-> RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody Status
-> Codec
Object
ACHBankAccountResponseBody
(AccountNumber
-> RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (ACHBankAccountResponseBody -> Status)
-> Codec Object ACHBankAccountResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> Status
achBankAccountStatus
Codec
Object
ACHBankAccountResponseBody
(AccountNumber
-> RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody AccountNumber
-> Codec
Object
ACHBankAccountResponseBody
(RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AccountNumber AccountNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"accountNumber" ObjectCodec AccountNumber AccountNumber
-> (ACHBankAccountResponseBody -> AccountNumber)
-> Codec Object ACHBankAccountResponseBody AccountNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> AccountNumber
achBankAccountAccountNumber
Codec
Object
ACHBankAccountResponseBody
(RoutingNumber
-> BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody RoutingNumber
-> Codec
Object
ACHBankAccountResponseBody
(BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RoutingNumber RoutingNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"routingNumber" ObjectCodec RoutingNumber RoutingNumber
-> (ACHBankAccountResponseBody -> RoutingNumber)
-> Codec Object ACHBankAccountResponseBody RoutingNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> RoutingNumber
achBankAccountRoutingNumber
Codec
Object
ACHBankAccountResponseBody
(BillingDetails
-> Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody BillingDetails
-> Codec
Object
ACHBankAccountResponseBody
(Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (ACHBankAccountResponseBody -> BillingDetails)
-> Codec Object ACHBankAccountResponseBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> BillingDetails
achBankAccountBillingDetails
Codec
Object
ACHBankAccountResponseBody
(Maybe ACHBankAccountType
-> BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec
Object ACHBankAccountResponseBody (Maybe ACHBankAccountType)
-> Codec
Object
ACHBankAccountResponseBody
(BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe ACHBankAccountType) (Maybe ACHBankAccountType)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"bankAccountType" ObjectCodec (Maybe ACHBankAccountType) (Maybe ACHBankAccountType)
-> (ACHBankAccountResponseBody -> Maybe ACHBankAccountType)
-> Codec
Object ACHBankAccountResponseBody (Maybe ACHBankAccountType)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> Maybe ACHBankAccountType
achBankAccountType
Codec
Object
ACHBankAccountResponseBody
(BankAddress
-> UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody BankAddress
-> Codec
Object
ACHBankAccountResponseBody
(UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BankAddress BankAddress
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"bankAddress" ObjectCodec BankAddress BankAddress
-> (ACHBankAccountResponseBody -> BankAddress)
-> Codec Object ACHBankAccountResponseBody BankAddress
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> BankAddress
achBankAccountBankAddress
Codec
Object
ACHBankAccountResponseBody
(UUID
-> Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody UUID
-> Codec
Object
ACHBankAccountResponseBody
(Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fingerprint" ObjectCodec UUID UUID
-> (ACHBankAccountResponseBody -> UUID)
-> Codec Object ACHBankAccountResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> UUID
achBankAccountFingerprint
Codec
Object
ACHBankAccountResponseBody
(Maybe ACHBankAccountErrorCode
-> Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec
Object ACHBankAccountResponseBody (Maybe ACHBankAccountErrorCode)
-> Codec
Object
ACHBankAccountResponseBody
(Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe ACHBankAccountErrorCode) (Maybe ACHBankAccountErrorCode)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"errorCode" ObjectCodec
(Maybe ACHBankAccountErrorCode) (Maybe ACHBankAccountErrorCode)
-> (ACHBankAccountResponseBody -> Maybe ACHBankAccountErrorCode)
-> Codec
Object ACHBankAccountResponseBody (Maybe ACHBankAccountErrorCode)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> Maybe ACHBankAccountErrorCode
achBankAccountErrorCode
Codec
Object
ACHBankAccountResponseBody
(Maybe RiskEvaluation
-> ResponseMetadata
-> UTCTime
-> UTCTime
-> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody (Maybe RiskEvaluation)
-> Codec
Object
ACHBankAccountResponseBody
(ResponseMetadata
-> UTCTime -> UTCTime -> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"riskEvaluation" ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
-> (ACHBankAccountResponseBody -> Maybe RiskEvaluation)
-> Codec Object ACHBankAccountResponseBody (Maybe RiskEvaluation)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> Maybe RiskEvaluation
achBankAccountRiskEvaluation
Codec
Object
ACHBankAccountResponseBody
(ResponseMetadata
-> UTCTime -> UTCTime -> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody ResponseMetadata
-> Codec
Object
ACHBankAccountResponseBody
(UTCTime -> UTCTime -> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ResponseMetadata ResponseMetadata
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"metadata" ObjectCodec ResponseMetadata ResponseMetadata
-> (ACHBankAccountResponseBody -> ResponseMetadata)
-> Codec Object ACHBankAccountResponseBody ResponseMetadata
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> ResponseMetadata
achBankAccountMetadata
Codec
Object
ACHBankAccountResponseBody
(UTCTime -> UTCTime -> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody UTCTime
-> Codec
Object
ACHBankAccountResponseBody
(UTCTime -> ACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (ACHBankAccountResponseBody -> UTCTime)
-> Codec Object ACHBankAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> UTCTime
achBankAccountCreateDate
Codec
Object
ACHBankAccountResponseBody
(UTCTime -> ACHBankAccountResponseBody)
-> Codec Object ACHBankAccountResponseBody UTCTime
-> ObjectCodec
ACHBankAccountResponseBody ACHBankAccountResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (ACHBankAccountResponseBody -> UTCTime)
-> Codec Object ACHBankAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ACHBankAccountResponseBody -> UTCTime
achBankAccountUpdateDate
data ACHBankAccountErrorCode
= ACHBankAccountAuthorizationExpired
| ACHBankAccountError
| ACHBankAccountIneligible
| ACHBankAccountNotFound
| ACHBankAccountUnauthorized
| ACHBankAccountUnsupportedRoutingNumber
| ACHBankAccountVerificationFailed
deriving (ACHBankAccountErrorCode -> ACHBankAccountErrorCode -> Bool
(ACHBankAccountErrorCode -> ACHBankAccountErrorCode -> Bool)
-> (ACHBankAccountErrorCode -> ACHBankAccountErrorCode -> Bool)
-> Eq ACHBankAccountErrorCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ACHBankAccountErrorCode -> ACHBankAccountErrorCode -> Bool
$c/= :: ACHBankAccountErrorCode -> ACHBankAccountErrorCode -> Bool
== :: ACHBankAccountErrorCode -> ACHBankAccountErrorCode -> Bool
$c== :: ACHBankAccountErrorCode -> ACHBankAccountErrorCode -> Bool
Eq, Int -> ACHBankAccountErrorCode -> ShowS
[ACHBankAccountErrorCode] -> ShowS
ACHBankAccountErrorCode -> String
(Int -> ACHBankAccountErrorCode -> ShowS)
-> (ACHBankAccountErrorCode -> String)
-> ([ACHBankAccountErrorCode] -> ShowS)
-> Show ACHBankAccountErrorCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ACHBankAccountErrorCode] -> ShowS
$cshowList :: [ACHBankAccountErrorCode] -> ShowS
show :: ACHBankAccountErrorCode -> String
$cshow :: ACHBankAccountErrorCode -> String
showsPrec :: Int -> ACHBankAccountErrorCode -> ShowS
$cshowsPrec :: Int -> ACHBankAccountErrorCode -> ShowS
Show)
deriving
( Value -> Parser [ACHBankAccountErrorCode]
Value -> Parser ACHBankAccountErrorCode
(Value -> Parser ACHBankAccountErrorCode)
-> (Value -> Parser [ACHBankAccountErrorCode])
-> FromJSON ACHBankAccountErrorCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ACHBankAccountErrorCode]
$cparseJSONList :: Value -> Parser [ACHBankAccountErrorCode]
parseJSON :: Value -> Parser ACHBankAccountErrorCode
$cparseJSON :: Value -> Parser ACHBankAccountErrorCode
FromJSON,
[ACHBankAccountErrorCode] -> Encoding
[ACHBankAccountErrorCode] -> Value
ACHBankAccountErrorCode -> Encoding
ACHBankAccountErrorCode -> Value
(ACHBankAccountErrorCode -> Value)
-> (ACHBankAccountErrorCode -> Encoding)
-> ([ACHBankAccountErrorCode] -> Value)
-> ([ACHBankAccountErrorCode] -> Encoding)
-> ToJSON ACHBankAccountErrorCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ACHBankAccountErrorCode] -> Encoding
$ctoEncodingList :: [ACHBankAccountErrorCode] -> Encoding
toJSONList :: [ACHBankAccountErrorCode] -> Value
$ctoJSONList :: [ACHBankAccountErrorCode] -> Value
toEncoding :: ACHBankAccountErrorCode -> Encoding
$ctoEncoding :: ACHBankAccountErrorCode -> Encoding
toJSON :: ACHBankAccountErrorCode -> Value
$ctoJSON :: ACHBankAccountErrorCode -> Value
ToJSON
)
via (Autodocodec ACHBankAccountErrorCode)
instance HasCodec ACHBankAccountErrorCode where
codec :: JSONCodec ACHBankAccountErrorCode
codec =
NonEmpty (ACHBankAccountErrorCode, Text)
-> JSONCodec ACHBankAccountErrorCode
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (ACHBankAccountErrorCode, Text)
-> JSONCodec ACHBankAccountErrorCode)
-> NonEmpty (ACHBankAccountErrorCode, Text)
-> JSONCodec ACHBankAccountErrorCode
forall a b. (a -> b) -> a -> b
$
[(ACHBankAccountErrorCode, Text)]
-> NonEmpty (ACHBankAccountErrorCode, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (ACHBankAccountErrorCode
ACHBankAccountAuthorizationExpired, Text
"bank_account_authorization_expired"),
(ACHBankAccountErrorCode
ACHBankAccountError, Text
"bank_account_error"),
(ACHBankAccountErrorCode
ACHBankAccountIneligible, Text
"bank_account_ineligible"),
(ACHBankAccountErrorCode
ACHBankAccountNotFound, Text
"bank_account_not_found"),
(ACHBankAccountErrorCode
ACHBankAccountUnauthorized, Text
"bank_account_unauthorized"),
(ACHBankAccountErrorCode
ACHBankAccountUnsupportedRoutingNumber, Text
"unsupported_routing_number"),
(ACHBankAccountErrorCode
ACHBankAccountVerificationFailed, Text
"verification_failed")
]
data CreateACHBankAccountRequestBody = CreateACHBankAccountRequestBody
{ CreateACHBankAccountRequestBody -> UUID
achBankAccountBodyIdempotencyKey :: !UUID,
CreateACHBankAccountRequestBody -> ProcessorToken
achBankAccountBodyPlaidProcessorToken :: !ProcessorToken,
CreateACHBankAccountRequestBody -> BillingDetails
achBankAccountBodyBillingDetails :: !BillingDetails,
CreateACHBankAccountRequestBody -> Maybe ACHBankAccountType
achBankAccountBodyBankAccountType :: !(Maybe ACHBankAccountType),
CreateACHBankAccountRequestBody -> RequestMetadata
achBankAccountBodyMetadata :: !RequestMetadata
}
deriving (CreateACHBankAccountRequestBody
-> CreateACHBankAccountRequestBody -> Bool
(CreateACHBankAccountRequestBody
-> CreateACHBankAccountRequestBody -> Bool)
-> (CreateACHBankAccountRequestBody
-> CreateACHBankAccountRequestBody -> Bool)
-> Eq CreateACHBankAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateACHBankAccountRequestBody
-> CreateACHBankAccountRequestBody -> Bool
$c/= :: CreateACHBankAccountRequestBody
-> CreateACHBankAccountRequestBody -> Bool
== :: CreateACHBankAccountRequestBody
-> CreateACHBankAccountRequestBody -> Bool
$c== :: CreateACHBankAccountRequestBody
-> CreateACHBankAccountRequestBody -> Bool
Eq, Int -> CreateACHBankAccountRequestBody -> ShowS
[CreateACHBankAccountRequestBody] -> ShowS
CreateACHBankAccountRequestBody -> String
(Int -> CreateACHBankAccountRequestBody -> ShowS)
-> (CreateACHBankAccountRequestBody -> String)
-> ([CreateACHBankAccountRequestBody] -> ShowS)
-> Show CreateACHBankAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateACHBankAccountRequestBody] -> ShowS
$cshowList :: [CreateACHBankAccountRequestBody] -> ShowS
show :: CreateACHBankAccountRequestBody -> String
$cshow :: CreateACHBankAccountRequestBody -> String
showsPrec :: Int -> CreateACHBankAccountRequestBody -> ShowS
$cshowsPrec :: Int -> CreateACHBankAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [CreateACHBankAccountRequestBody]
Value -> Parser CreateACHBankAccountRequestBody
(Value -> Parser CreateACHBankAccountRequestBody)
-> (Value -> Parser [CreateACHBankAccountRequestBody])
-> FromJSON CreateACHBankAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CreateACHBankAccountRequestBody]
$cparseJSONList :: Value -> Parser [CreateACHBankAccountRequestBody]
parseJSON :: Value -> Parser CreateACHBankAccountRequestBody
$cparseJSON :: Value -> Parser CreateACHBankAccountRequestBody
FromJSON,
[CreateACHBankAccountRequestBody] -> Encoding
[CreateACHBankAccountRequestBody] -> Value
CreateACHBankAccountRequestBody -> Encoding
CreateACHBankAccountRequestBody -> Value
(CreateACHBankAccountRequestBody -> Value)
-> (CreateACHBankAccountRequestBody -> Encoding)
-> ([CreateACHBankAccountRequestBody] -> Value)
-> ([CreateACHBankAccountRequestBody] -> Encoding)
-> ToJSON CreateACHBankAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreateACHBankAccountRequestBody] -> Encoding
$ctoEncodingList :: [CreateACHBankAccountRequestBody] -> Encoding
toJSONList :: [CreateACHBankAccountRequestBody] -> Value
$ctoJSONList :: [CreateACHBankAccountRequestBody] -> Value
toEncoding :: CreateACHBankAccountRequestBody -> Encoding
$ctoEncoding :: CreateACHBankAccountRequestBody -> Encoding
toJSON :: CreateACHBankAccountRequestBody -> Value
$ctoJSON :: CreateACHBankAccountRequestBody -> Value
ToJSON
)
via (Autodocodec CreateACHBankAccountRequestBody)
instance HasCodec CreateACHBankAccountRequestBody where
codec :: JSONCodec CreateACHBankAccountRequestBody
codec =
Text
-> ObjectCodec
CreateACHBankAccountRequestBody CreateACHBankAccountRequestBody
-> JSONCodec CreateACHBankAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CreateACHBankAccountRequestBody" (ObjectCodec
CreateACHBankAccountRequestBody CreateACHBankAccountRequestBody
-> JSONCodec CreateACHBankAccountRequestBody)
-> ObjectCodec
CreateACHBankAccountRequestBody CreateACHBankAccountRequestBody
-> JSONCodec CreateACHBankAccountRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> ProcessorToken
-> BillingDetails
-> Maybe ACHBankAccountType
-> RequestMetadata
-> CreateACHBankAccountRequestBody
CreateACHBankAccountRequestBody
(UUID
-> ProcessorToken
-> BillingDetails
-> Maybe ACHBankAccountType
-> RequestMetadata
-> CreateACHBankAccountRequestBody)
-> Codec Object CreateACHBankAccountRequestBody UUID
-> Codec
Object
CreateACHBankAccountRequestBody
(ProcessorToken
-> BillingDetails
-> Maybe ACHBankAccountType
-> RequestMetadata
-> CreateACHBankAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (CreateACHBankAccountRequestBody -> UUID)
-> Codec Object CreateACHBankAccountRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateACHBankAccountRequestBody -> UUID
achBankAccountBodyIdempotencyKey
Codec
Object
CreateACHBankAccountRequestBody
(ProcessorToken
-> BillingDetails
-> Maybe ACHBankAccountType
-> RequestMetadata
-> CreateACHBankAccountRequestBody)
-> Codec Object CreateACHBankAccountRequestBody ProcessorToken
-> Codec
Object
CreateACHBankAccountRequestBody
(BillingDetails
-> Maybe ACHBankAccountType
-> RequestMetadata
-> CreateACHBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ProcessorToken ProcessorToken
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"plaidProcessorToken" ObjectCodec ProcessorToken ProcessorToken
-> (CreateACHBankAccountRequestBody -> ProcessorToken)
-> Codec Object CreateACHBankAccountRequestBody ProcessorToken
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateACHBankAccountRequestBody -> ProcessorToken
achBankAccountBodyPlaidProcessorToken
Codec
Object
CreateACHBankAccountRequestBody
(BillingDetails
-> Maybe ACHBankAccountType
-> RequestMetadata
-> CreateACHBankAccountRequestBody)
-> Codec Object CreateACHBankAccountRequestBody BillingDetails
-> Codec
Object
CreateACHBankAccountRequestBody
(Maybe ACHBankAccountType
-> RequestMetadata -> CreateACHBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (CreateACHBankAccountRequestBody -> BillingDetails)
-> Codec Object CreateACHBankAccountRequestBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateACHBankAccountRequestBody -> BillingDetails
achBankAccountBodyBillingDetails
Codec
Object
CreateACHBankAccountRequestBody
(Maybe ACHBankAccountType
-> RequestMetadata -> CreateACHBankAccountRequestBody)
-> Codec
Object CreateACHBankAccountRequestBody (Maybe ACHBankAccountType)
-> Codec
Object
CreateACHBankAccountRequestBody
(RequestMetadata -> CreateACHBankAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe ACHBankAccountType) (Maybe ACHBankAccountType)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"bankAccountType" ObjectCodec (Maybe ACHBankAccountType) (Maybe ACHBankAccountType)
-> (CreateACHBankAccountRequestBody -> Maybe ACHBankAccountType)
-> Codec
Object CreateACHBankAccountRequestBody (Maybe ACHBankAccountType)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateACHBankAccountRequestBody -> Maybe ACHBankAccountType
achBankAccountBodyBankAccountType
Codec
Object
CreateACHBankAccountRequestBody
(RequestMetadata -> CreateACHBankAccountRequestBody)
-> Codec Object CreateACHBankAccountRequestBody RequestMetadata
-> ObjectCodec
CreateACHBankAccountRequestBody CreateACHBankAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RequestMetadata RequestMetadata
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"metadata" ObjectCodec RequestMetadata RequestMetadata
-> (CreateACHBankAccountRequestBody -> RequestMetadata)
-> Codec Object CreateACHBankAccountRequestBody RequestMetadata
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateACHBankAccountRequestBody -> RequestMetadata
achBankAccountBodyMetadata
data MockAccountRequest
type instance CircleRequest MockAccountRequest = CircleResponseBody MockACHBankAccountResponseBody
data CreateMockACHBankAccountRequestBody = CreateMockACHBankAccountRequestBody
{ CreateMockACHBankAccountRequestBody -> MockACHBankAccount
mockACHBankAccountBodyAccount :: !MockACHBankAccount,
CreateMockACHBankAccountRequestBody -> MoneyAmount
mockACHBankAccountBodyBalance :: !MoneyAmount
}
deriving (CreateMockACHBankAccountRequestBody
-> CreateMockACHBankAccountRequestBody -> Bool
(CreateMockACHBankAccountRequestBody
-> CreateMockACHBankAccountRequestBody -> Bool)
-> (CreateMockACHBankAccountRequestBody
-> CreateMockACHBankAccountRequestBody -> Bool)
-> Eq CreateMockACHBankAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateMockACHBankAccountRequestBody
-> CreateMockACHBankAccountRequestBody -> Bool
$c/= :: CreateMockACHBankAccountRequestBody
-> CreateMockACHBankAccountRequestBody -> Bool
== :: CreateMockACHBankAccountRequestBody
-> CreateMockACHBankAccountRequestBody -> Bool
$c== :: CreateMockACHBankAccountRequestBody
-> CreateMockACHBankAccountRequestBody -> Bool
Eq, Int -> CreateMockACHBankAccountRequestBody -> ShowS
[CreateMockACHBankAccountRequestBody] -> ShowS
CreateMockACHBankAccountRequestBody -> String
(Int -> CreateMockACHBankAccountRequestBody -> ShowS)
-> (CreateMockACHBankAccountRequestBody -> String)
-> ([CreateMockACHBankAccountRequestBody] -> ShowS)
-> Show CreateMockACHBankAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateMockACHBankAccountRequestBody] -> ShowS
$cshowList :: [CreateMockACHBankAccountRequestBody] -> ShowS
show :: CreateMockACHBankAccountRequestBody -> String
$cshow :: CreateMockACHBankAccountRequestBody -> String
showsPrec :: Int -> CreateMockACHBankAccountRequestBody -> ShowS
$cshowsPrec :: Int -> CreateMockACHBankAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [CreateMockACHBankAccountRequestBody]
Value -> Parser CreateMockACHBankAccountRequestBody
(Value -> Parser CreateMockACHBankAccountRequestBody)
-> (Value -> Parser [CreateMockACHBankAccountRequestBody])
-> FromJSON CreateMockACHBankAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CreateMockACHBankAccountRequestBody]
$cparseJSONList :: Value -> Parser [CreateMockACHBankAccountRequestBody]
parseJSON :: Value -> Parser CreateMockACHBankAccountRequestBody
$cparseJSON :: Value -> Parser CreateMockACHBankAccountRequestBody
FromJSON,
[CreateMockACHBankAccountRequestBody] -> Encoding
[CreateMockACHBankAccountRequestBody] -> Value
CreateMockACHBankAccountRequestBody -> Encoding
CreateMockACHBankAccountRequestBody -> Value
(CreateMockACHBankAccountRequestBody -> Value)
-> (CreateMockACHBankAccountRequestBody -> Encoding)
-> ([CreateMockACHBankAccountRequestBody] -> Value)
-> ([CreateMockACHBankAccountRequestBody] -> Encoding)
-> ToJSON CreateMockACHBankAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreateMockACHBankAccountRequestBody] -> Encoding
$ctoEncodingList :: [CreateMockACHBankAccountRequestBody] -> Encoding
toJSONList :: [CreateMockACHBankAccountRequestBody] -> Value
$ctoJSONList :: [CreateMockACHBankAccountRequestBody] -> Value
toEncoding :: CreateMockACHBankAccountRequestBody -> Encoding
$ctoEncoding :: CreateMockACHBankAccountRequestBody -> Encoding
toJSON :: CreateMockACHBankAccountRequestBody -> Value
$ctoJSON :: CreateMockACHBankAccountRequestBody -> Value
ToJSON
)
via (Autodocodec CreateMockACHBankAccountRequestBody)
instance HasCodec CreateMockACHBankAccountRequestBody where
codec :: JSONCodec CreateMockACHBankAccountRequestBody
codec =
Text
-> ObjectCodec
CreateMockACHBankAccountRequestBody
CreateMockACHBankAccountRequestBody
-> JSONCodec CreateMockACHBankAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CreateMockACHBankAccountRequestBody" (ObjectCodec
CreateMockACHBankAccountRequestBody
CreateMockACHBankAccountRequestBody
-> JSONCodec CreateMockACHBankAccountRequestBody)
-> ObjectCodec
CreateMockACHBankAccountRequestBody
CreateMockACHBankAccountRequestBody
-> JSONCodec CreateMockACHBankAccountRequestBody
forall a b. (a -> b) -> a -> b
$
MockACHBankAccount
-> MoneyAmount -> CreateMockACHBankAccountRequestBody
CreateMockACHBankAccountRequestBody
(MockACHBankAccount
-> MoneyAmount -> CreateMockACHBankAccountRequestBody)
-> Codec
Object CreateMockACHBankAccountRequestBody MockACHBankAccount
-> Codec
Object
CreateMockACHBankAccountRequestBody
(MoneyAmount -> CreateMockACHBankAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec MockACHBankAccount MockACHBankAccount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"account" ObjectCodec MockACHBankAccount MockACHBankAccount
-> (CreateMockACHBankAccountRequestBody -> MockACHBankAccount)
-> Codec
Object CreateMockACHBankAccountRequestBody MockACHBankAccount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateMockACHBankAccountRequestBody -> MockACHBankAccount
mockACHBankAccountBodyAccount
Codec
Object
CreateMockACHBankAccountRequestBody
(MoneyAmount -> CreateMockACHBankAccountRequestBody)
-> Codec Object CreateMockACHBankAccountRequestBody MoneyAmount
-> ObjectCodec
CreateMockACHBankAccountRequestBody
CreateMockACHBankAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"balance" ObjectCodec MoneyAmount MoneyAmount
-> (CreateMockACHBankAccountRequestBody -> MoneyAmount)
-> Codec Object CreateMockACHBankAccountRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateMockACHBankAccountRequestBody -> MoneyAmount
mockACHBankAccountBodyBalance
data MockACHBankAccountResponseBody = MockACHBankAccountResponseBody
{ MockACHBankAccountResponseBody -> MockACHBankAccount
mockACHBankAccountResponseBodyAccount :: !MockACHBankAccount,
MockACHBankAccountResponseBody -> MoneyAmount
mockACHBankAccountResponseBodyBalance :: !MoneyAmount,
MockACHBankAccountResponseBody -> ProcessorToken
mockACHBankAccountResponseBodyProcessorToken :: !ProcessorToken
}
deriving (MockACHBankAccountResponseBody
-> MockACHBankAccountResponseBody -> Bool
(MockACHBankAccountResponseBody
-> MockACHBankAccountResponseBody -> Bool)
-> (MockACHBankAccountResponseBody
-> MockACHBankAccountResponseBody -> Bool)
-> Eq MockACHBankAccountResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MockACHBankAccountResponseBody
-> MockACHBankAccountResponseBody -> Bool
$c/= :: MockACHBankAccountResponseBody
-> MockACHBankAccountResponseBody -> Bool
== :: MockACHBankAccountResponseBody
-> MockACHBankAccountResponseBody -> Bool
$c== :: MockACHBankAccountResponseBody
-> MockACHBankAccountResponseBody -> Bool
Eq, Int -> MockACHBankAccountResponseBody -> ShowS
[MockACHBankAccountResponseBody] -> ShowS
MockACHBankAccountResponseBody -> String
(Int -> MockACHBankAccountResponseBody -> ShowS)
-> (MockACHBankAccountResponseBody -> String)
-> ([MockACHBankAccountResponseBody] -> ShowS)
-> Show MockACHBankAccountResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MockACHBankAccountResponseBody] -> ShowS
$cshowList :: [MockACHBankAccountResponseBody] -> ShowS
show :: MockACHBankAccountResponseBody -> String
$cshow :: MockACHBankAccountResponseBody -> String
showsPrec :: Int -> MockACHBankAccountResponseBody -> ShowS
$cshowsPrec :: Int -> MockACHBankAccountResponseBody -> ShowS
Show)
deriving
( Value -> Parser [MockACHBankAccountResponseBody]
Value -> Parser MockACHBankAccountResponseBody
(Value -> Parser MockACHBankAccountResponseBody)
-> (Value -> Parser [MockACHBankAccountResponseBody])
-> FromJSON MockACHBankAccountResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MockACHBankAccountResponseBody]
$cparseJSONList :: Value -> Parser [MockACHBankAccountResponseBody]
parseJSON :: Value -> Parser MockACHBankAccountResponseBody
$cparseJSON :: Value -> Parser MockACHBankAccountResponseBody
FromJSON,
[MockACHBankAccountResponseBody] -> Encoding
[MockACHBankAccountResponseBody] -> Value
MockACHBankAccountResponseBody -> Encoding
MockACHBankAccountResponseBody -> Value
(MockACHBankAccountResponseBody -> Value)
-> (MockACHBankAccountResponseBody -> Encoding)
-> ([MockACHBankAccountResponseBody] -> Value)
-> ([MockACHBankAccountResponseBody] -> Encoding)
-> ToJSON MockACHBankAccountResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MockACHBankAccountResponseBody] -> Encoding
$ctoEncodingList :: [MockACHBankAccountResponseBody] -> Encoding
toJSONList :: [MockACHBankAccountResponseBody] -> Value
$ctoJSONList :: [MockACHBankAccountResponseBody] -> Value
toEncoding :: MockACHBankAccountResponseBody -> Encoding
$ctoEncoding :: MockACHBankAccountResponseBody -> Encoding
toJSON :: MockACHBankAccountResponseBody -> Value
$ctoJSON :: MockACHBankAccountResponseBody -> Value
ToJSON
)
via (Autodocodec MockACHBankAccountResponseBody)
instance HasCodec MockACHBankAccountResponseBody where
codec :: JSONCodec MockACHBankAccountResponseBody
codec =
Text
-> ObjectCodec
MockACHBankAccountResponseBody MockACHBankAccountResponseBody
-> JSONCodec MockACHBankAccountResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"MockACHBankAccountResponseBody" (ObjectCodec
MockACHBankAccountResponseBody MockACHBankAccountResponseBody
-> JSONCodec MockACHBankAccountResponseBody)
-> ObjectCodec
MockACHBankAccountResponseBody MockACHBankAccountResponseBody
-> JSONCodec MockACHBankAccountResponseBody
forall a b. (a -> b) -> a -> b
$
MockACHBankAccount
-> MoneyAmount -> ProcessorToken -> MockACHBankAccountResponseBody
MockACHBankAccountResponseBody
(MockACHBankAccount
-> MoneyAmount -> ProcessorToken -> MockACHBankAccountResponseBody)
-> Codec Object MockACHBankAccountResponseBody MockACHBankAccount
-> Codec
Object
MockACHBankAccountResponseBody
(MoneyAmount -> ProcessorToken -> MockACHBankAccountResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec MockACHBankAccount MockACHBankAccount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"account" ObjectCodec MockACHBankAccount MockACHBankAccount
-> (MockACHBankAccountResponseBody -> MockACHBankAccount)
-> Codec Object MockACHBankAccountResponseBody MockACHBankAccount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockACHBankAccountResponseBody -> MockACHBankAccount
mockACHBankAccountResponseBodyAccount
Codec
Object
MockACHBankAccountResponseBody
(MoneyAmount -> ProcessorToken -> MockACHBankAccountResponseBody)
-> Codec Object MockACHBankAccountResponseBody MoneyAmount
-> Codec
Object
MockACHBankAccountResponseBody
(ProcessorToken -> MockACHBankAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"balance" ObjectCodec MoneyAmount MoneyAmount
-> (MockACHBankAccountResponseBody -> MoneyAmount)
-> Codec Object MockACHBankAccountResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockACHBankAccountResponseBody -> MoneyAmount
mockACHBankAccountResponseBodyBalance
Codec
Object
MockACHBankAccountResponseBody
(ProcessorToken -> MockACHBankAccountResponseBody)
-> Codec Object MockACHBankAccountResponseBody ProcessorToken
-> ObjectCodec
MockACHBankAccountResponseBody MockACHBankAccountResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ProcessorToken ProcessorToken
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"processorToken" ObjectCodec ProcessorToken ProcessorToken
-> (MockACHBankAccountResponseBody -> ProcessorToken)
-> Codec Object MockACHBankAccountResponseBody ProcessorToken
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockACHBankAccountResponseBody -> ProcessorToken
mockACHBankAccountResponseBodyProcessorToken
data MockACHBankAccount = MockACHBankAccount
{ MockACHBankAccount -> AccountNumber
mockACHBankAccountAccountNumber :: !AccountNumber,
MockACHBankAccount -> MockRoutingNumber
mockACHBankAccountRoutingNumber :: !MockRoutingNumber,
MockACHBankAccount -> Text
mockACHBankAccountDescription :: !Text
}
deriving (MockACHBankAccount -> MockACHBankAccount -> Bool
(MockACHBankAccount -> MockACHBankAccount -> Bool)
-> (MockACHBankAccount -> MockACHBankAccount -> Bool)
-> Eq MockACHBankAccount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MockACHBankAccount -> MockACHBankAccount -> Bool
$c/= :: MockACHBankAccount -> MockACHBankAccount -> Bool
== :: MockACHBankAccount -> MockACHBankAccount -> Bool
$c== :: MockACHBankAccount -> MockACHBankAccount -> Bool
Eq, Int -> MockACHBankAccount -> ShowS
[MockACHBankAccount] -> ShowS
MockACHBankAccount -> String
(Int -> MockACHBankAccount -> ShowS)
-> (MockACHBankAccount -> String)
-> ([MockACHBankAccount] -> ShowS)
-> Show MockACHBankAccount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MockACHBankAccount] -> ShowS
$cshowList :: [MockACHBankAccount] -> ShowS
show :: MockACHBankAccount -> String
$cshow :: MockACHBankAccount -> String
showsPrec :: Int -> MockACHBankAccount -> ShowS
$cshowsPrec :: Int -> MockACHBankAccount -> ShowS
Show)
deriving
( Value -> Parser [MockACHBankAccount]
Value -> Parser MockACHBankAccount
(Value -> Parser MockACHBankAccount)
-> (Value -> Parser [MockACHBankAccount])
-> FromJSON MockACHBankAccount
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MockACHBankAccount]
$cparseJSONList :: Value -> Parser [MockACHBankAccount]
parseJSON :: Value -> Parser MockACHBankAccount
$cparseJSON :: Value -> Parser MockACHBankAccount
FromJSON,
[MockACHBankAccount] -> Encoding
[MockACHBankAccount] -> Value
MockACHBankAccount -> Encoding
MockACHBankAccount -> Value
(MockACHBankAccount -> Value)
-> (MockACHBankAccount -> Encoding)
-> ([MockACHBankAccount] -> Value)
-> ([MockACHBankAccount] -> Encoding)
-> ToJSON MockACHBankAccount
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MockACHBankAccount] -> Encoding
$ctoEncodingList :: [MockACHBankAccount] -> Encoding
toJSONList :: [MockACHBankAccount] -> Value
$ctoJSONList :: [MockACHBankAccount] -> Value
toEncoding :: MockACHBankAccount -> Encoding
$ctoEncoding :: MockACHBankAccount -> Encoding
toJSON :: MockACHBankAccount -> Value
$ctoJSON :: MockACHBankAccount -> Value
ToJSON
)
via (Autodocodec MockACHBankAccount)
instance HasCodec MockACHBankAccount where
codec :: JSONCodec MockACHBankAccount
codec =
Text
-> ObjectCodec MockACHBankAccount MockACHBankAccount
-> JSONCodec MockACHBankAccount
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"MockACHBankAccount" (ObjectCodec MockACHBankAccount MockACHBankAccount
-> JSONCodec MockACHBankAccount)
-> ObjectCodec MockACHBankAccount MockACHBankAccount
-> JSONCodec MockACHBankAccount
forall a b. (a -> b) -> a -> b
$
AccountNumber -> MockRoutingNumber -> Text -> MockACHBankAccount
MockACHBankAccount
(AccountNumber -> MockRoutingNumber -> Text -> MockACHBankAccount)
-> Codec Object MockACHBankAccount AccountNumber
-> Codec
Object
MockACHBankAccount
(MockRoutingNumber -> Text -> MockACHBankAccount)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec AccountNumber AccountNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"accountNumber" ObjectCodec AccountNumber AccountNumber
-> (MockACHBankAccount -> AccountNumber)
-> Codec Object MockACHBankAccount AccountNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockACHBankAccount -> AccountNumber
mockACHBankAccountAccountNumber
Codec
Object
MockACHBankAccount
(MockRoutingNumber -> Text -> MockACHBankAccount)
-> Codec Object MockACHBankAccount MockRoutingNumber
-> Codec Object MockACHBankAccount (Text -> MockACHBankAccount)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MockRoutingNumber MockRoutingNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"routingNumber" ObjectCodec MockRoutingNumber MockRoutingNumber
-> (MockACHBankAccount -> MockRoutingNumber)
-> Codec Object MockACHBankAccount MockRoutingNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockACHBankAccount -> MockRoutingNumber
mockACHBankAccountRoutingNumber
Codec Object MockACHBankAccount (Text -> MockACHBankAccount)
-> Codec Object MockACHBankAccount Text
-> ObjectCodec MockACHBankAccount MockACHBankAccount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (MockACHBankAccount -> Text)
-> Codec Object MockACHBankAccount Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MockACHBankAccount -> Text
mockACHBankAccountDescription
data MockRoutingNumber
= MockRoutingNumber1
| MockRoutingNumber2
| MockRoutingNumber3
| MockRoutingNumber4
| MockRoutingNumber5
| MockRoutingNumber6
| MockRoutingNumber7
| MockRoutingNumber8
| MockRoutingNumber9
deriving (MockRoutingNumber -> MockRoutingNumber -> Bool
(MockRoutingNumber -> MockRoutingNumber -> Bool)
-> (MockRoutingNumber -> MockRoutingNumber -> Bool)
-> Eq MockRoutingNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MockRoutingNumber -> MockRoutingNumber -> Bool
$c/= :: MockRoutingNumber -> MockRoutingNumber -> Bool
== :: MockRoutingNumber -> MockRoutingNumber -> Bool
$c== :: MockRoutingNumber -> MockRoutingNumber -> Bool
Eq, Int -> MockRoutingNumber -> ShowS
[MockRoutingNumber] -> ShowS
MockRoutingNumber -> String
(Int -> MockRoutingNumber -> ShowS)
-> (MockRoutingNumber -> String)
-> ([MockRoutingNumber] -> ShowS)
-> Show MockRoutingNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MockRoutingNumber] -> ShowS
$cshowList :: [MockRoutingNumber] -> ShowS
show :: MockRoutingNumber -> String
$cshow :: MockRoutingNumber -> String
showsPrec :: Int -> MockRoutingNumber -> ShowS
$cshowsPrec :: Int -> MockRoutingNumber -> ShowS
Show, Int -> MockRoutingNumber
MockRoutingNumber -> Int
MockRoutingNumber -> [MockRoutingNumber]
MockRoutingNumber -> MockRoutingNumber
MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
MockRoutingNumber
-> MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
(MockRoutingNumber -> MockRoutingNumber)
-> (MockRoutingNumber -> MockRoutingNumber)
-> (Int -> MockRoutingNumber)
-> (MockRoutingNumber -> Int)
-> (MockRoutingNumber -> [MockRoutingNumber])
-> (MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber])
-> (MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber])
-> (MockRoutingNumber
-> MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber])
-> Enum MockRoutingNumber
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MockRoutingNumber
-> MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
$cenumFromThenTo :: MockRoutingNumber
-> MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
enumFromTo :: MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
$cenumFromTo :: MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
enumFromThen :: MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
$cenumFromThen :: MockRoutingNumber -> MockRoutingNumber -> [MockRoutingNumber]
enumFrom :: MockRoutingNumber -> [MockRoutingNumber]
$cenumFrom :: MockRoutingNumber -> [MockRoutingNumber]
fromEnum :: MockRoutingNumber -> Int
$cfromEnum :: MockRoutingNumber -> Int
toEnum :: Int -> MockRoutingNumber
$ctoEnum :: Int -> MockRoutingNumber
pred :: MockRoutingNumber -> MockRoutingNumber
$cpred :: MockRoutingNumber -> MockRoutingNumber
succ :: MockRoutingNumber -> MockRoutingNumber
$csucc :: MockRoutingNumber -> MockRoutingNumber
Enum, MockRoutingNumber
MockRoutingNumber -> MockRoutingNumber -> Bounded MockRoutingNumber
forall a. a -> a -> Bounded a
maxBound :: MockRoutingNumber
$cmaxBound :: MockRoutingNumber
minBound :: MockRoutingNumber
$cminBound :: MockRoutingNumber
Bounded)
deriving
( Value -> Parser [MockRoutingNumber]
Value -> Parser MockRoutingNumber
(Value -> Parser MockRoutingNumber)
-> (Value -> Parser [MockRoutingNumber])
-> FromJSON MockRoutingNumber
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MockRoutingNumber]
$cparseJSONList :: Value -> Parser [MockRoutingNumber]
parseJSON :: Value -> Parser MockRoutingNumber
$cparseJSON :: Value -> Parser MockRoutingNumber
FromJSON,
[MockRoutingNumber] -> Encoding
[MockRoutingNumber] -> Value
MockRoutingNumber -> Encoding
MockRoutingNumber -> Value
(MockRoutingNumber -> Value)
-> (MockRoutingNumber -> Encoding)
-> ([MockRoutingNumber] -> Value)
-> ([MockRoutingNumber] -> Encoding)
-> ToJSON MockRoutingNumber
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MockRoutingNumber] -> Encoding
$ctoEncodingList :: [MockRoutingNumber] -> Encoding
toJSONList :: [MockRoutingNumber] -> Value
$ctoJSONList :: [MockRoutingNumber] -> Value
toEncoding :: MockRoutingNumber -> Encoding
$ctoEncoding :: MockRoutingNumber -> Encoding
toJSON :: MockRoutingNumber -> Value
$ctoJSON :: MockRoutingNumber -> Value
ToJSON
)
via (Autodocodec MockRoutingNumber)
instance HasCodec MockRoutingNumber where
codec :: JSONCodec MockRoutingNumber
codec =
NonEmpty (MockRoutingNumber, Text) -> JSONCodec MockRoutingNumber
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (MockRoutingNumber, Text) -> JSONCodec MockRoutingNumber)
-> NonEmpty (MockRoutingNumber, Text)
-> JSONCodec MockRoutingNumber
forall a b. (a -> b) -> a -> b
$
[(MockRoutingNumber, Text)] -> NonEmpty (MockRoutingNumber, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (MockRoutingNumber
MockRoutingNumber1, Text
"011000028"),
(MockRoutingNumber
MockRoutingNumber2, Text
"011201762"),
(MockRoutingNumber
MockRoutingNumber3, Text
"011500120"),
(MockRoutingNumber
MockRoutingNumber4, Text
"021214862"),
(MockRoutingNumber
MockRoutingNumber5, Text
"121000248"),
(MockRoutingNumber
MockRoutingNumber6, Text
"121140399"),
(MockRoutingNumber
MockRoutingNumber7, Text
"211073473"),
(MockRoutingNumber
MockRoutingNumber8, Text
"221172610"),
(MockRoutingNumber
MockRoutingNumber9, Text
"011000138")
]
data SEPAAccountRequest
type instance CircleRequest SEPAAccountRequest = CircleResponseBody SEPAAccountResponseBody
data SEPAInstructionsRequest
type instance CircleRequest SEPAInstructionsRequest = CircleResponseBody WireInstructionsResponseData
data SEPAAccountRequestBody = SEPAAccountRequestBody
{ SEPAAccountRequestBody -> UUID
sepaAccountRequestBodyIdempotencyKey :: !UUID,
SEPAAccountRequestBody -> Iban
sepaAccountRequestBodyIBAN :: !Iban,
SEPAAccountRequestBody -> BillingDetails
sepaAccountRequestBodyBillingDetails :: !BillingDetails
}
deriving (SEPAAccountRequestBody -> SEPAAccountRequestBody -> Bool
(SEPAAccountRequestBody -> SEPAAccountRequestBody -> Bool)
-> (SEPAAccountRequestBody -> SEPAAccountRequestBody -> Bool)
-> Eq SEPAAccountRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SEPAAccountRequestBody -> SEPAAccountRequestBody -> Bool
$c/= :: SEPAAccountRequestBody -> SEPAAccountRequestBody -> Bool
== :: SEPAAccountRequestBody -> SEPAAccountRequestBody -> Bool
$c== :: SEPAAccountRequestBody -> SEPAAccountRequestBody -> Bool
Eq, Int -> SEPAAccountRequestBody -> ShowS
[SEPAAccountRequestBody] -> ShowS
SEPAAccountRequestBody -> String
(Int -> SEPAAccountRequestBody -> ShowS)
-> (SEPAAccountRequestBody -> String)
-> ([SEPAAccountRequestBody] -> ShowS)
-> Show SEPAAccountRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SEPAAccountRequestBody] -> ShowS
$cshowList :: [SEPAAccountRequestBody] -> ShowS
show :: SEPAAccountRequestBody -> String
$cshow :: SEPAAccountRequestBody -> String
showsPrec :: Int -> SEPAAccountRequestBody -> ShowS
$cshowsPrec :: Int -> SEPAAccountRequestBody -> ShowS
Show)
deriving
( Value -> Parser [SEPAAccountRequestBody]
Value -> Parser SEPAAccountRequestBody
(Value -> Parser SEPAAccountRequestBody)
-> (Value -> Parser [SEPAAccountRequestBody])
-> FromJSON SEPAAccountRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SEPAAccountRequestBody]
$cparseJSONList :: Value -> Parser [SEPAAccountRequestBody]
parseJSON :: Value -> Parser SEPAAccountRequestBody
$cparseJSON :: Value -> Parser SEPAAccountRequestBody
FromJSON,
[SEPAAccountRequestBody] -> Encoding
[SEPAAccountRequestBody] -> Value
SEPAAccountRequestBody -> Encoding
SEPAAccountRequestBody -> Value
(SEPAAccountRequestBody -> Value)
-> (SEPAAccountRequestBody -> Encoding)
-> ([SEPAAccountRequestBody] -> Value)
-> ([SEPAAccountRequestBody] -> Encoding)
-> ToJSON SEPAAccountRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SEPAAccountRequestBody] -> Encoding
$ctoEncodingList :: [SEPAAccountRequestBody] -> Encoding
toJSONList :: [SEPAAccountRequestBody] -> Value
$ctoJSONList :: [SEPAAccountRequestBody] -> Value
toEncoding :: SEPAAccountRequestBody -> Encoding
$ctoEncoding :: SEPAAccountRequestBody -> Encoding
toJSON :: SEPAAccountRequestBody -> Value
$ctoJSON :: SEPAAccountRequestBody -> Value
ToJSON
)
via (Autodocodec SEPAAccountRequestBody)
instance HasCodec SEPAAccountRequestBody where
codec :: JSONCodec SEPAAccountRequestBody
codec =
Text
-> ObjectCodec SEPAAccountRequestBody SEPAAccountRequestBody
-> JSONCodec SEPAAccountRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SEPAAccountRequestBody" (ObjectCodec SEPAAccountRequestBody SEPAAccountRequestBody
-> JSONCodec SEPAAccountRequestBody)
-> ObjectCodec SEPAAccountRequestBody SEPAAccountRequestBody
-> JSONCodec SEPAAccountRequestBody
forall a b. (a -> b) -> a -> b
$
UUID -> Iban -> BillingDetails -> SEPAAccountRequestBody
SEPAAccountRequestBody
(UUID -> Iban -> BillingDetails -> SEPAAccountRequestBody)
-> Codec Object SEPAAccountRequestBody UUID
-> Codec
Object
SEPAAccountRequestBody
(Iban -> BillingDetails -> SEPAAccountRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (SEPAAccountRequestBody -> UUID)
-> Codec Object SEPAAccountRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountRequestBody -> UUID
sepaAccountRequestBodyIdempotencyKey
Codec
Object
SEPAAccountRequestBody
(Iban -> BillingDetails -> SEPAAccountRequestBody)
-> Codec Object SEPAAccountRequestBody Iban
-> Codec
Object
SEPAAccountRequestBody
(BillingDetails -> SEPAAccountRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Iban Iban
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"iban" ObjectCodec Iban Iban
-> (SEPAAccountRequestBody -> Iban)
-> Codec Object SEPAAccountRequestBody Iban
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountRequestBody -> Iban
sepaAccountRequestBodyIBAN
Codec
Object
SEPAAccountRequestBody
(BillingDetails -> SEPAAccountRequestBody)
-> Codec Object SEPAAccountRequestBody BillingDetails
-> ObjectCodec SEPAAccountRequestBody SEPAAccountRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (SEPAAccountRequestBody -> BillingDetails)
-> Codec Object SEPAAccountRequestBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountRequestBody -> BillingDetails
sepaAccountRequestBodyBillingDetails
data SEPAAccountResponseBody = SEPAAccountResponseBody
{ SEPAAccountResponseBody -> UUID
sepaAccountResponseBodyId :: !UUID,
SEPAAccountResponseBody -> Status
sepaAccountResponseBodyStatus :: !Status,
SEPAAccountResponseBody -> Text
sepaAccountResponseBodyDescription :: !Text,
SEPAAccountResponseBody -> TrackingReference
sepaAccountResponseBodyTrackingRef :: !TrackingReference,
SEPAAccountResponseBody -> UUID
sepaAccountResponseBodyFingerprint :: !UUID,
SEPAAccountResponseBody -> Maybe RiskEvaluation
sepaAccountResponseBodyRiskEvaluation :: !(Maybe RiskEvaluation),
SEPAAccountResponseBody -> BillingDetails
sepaAccountResponseBodyBillingDetails :: !BillingDetails,
SEPAAccountResponseBody -> UTCTime
sepaAccountResponseBodyCreateDate :: !UTCTime,
SEPAAccountResponseBody -> UTCTime
sepaAccountResponseBodyUpdateDate :: !UTCTime
}
deriving (SEPAAccountResponseBody -> SEPAAccountResponseBody -> Bool
(SEPAAccountResponseBody -> SEPAAccountResponseBody -> Bool)
-> (SEPAAccountResponseBody -> SEPAAccountResponseBody -> Bool)
-> Eq SEPAAccountResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SEPAAccountResponseBody -> SEPAAccountResponseBody -> Bool
$c/= :: SEPAAccountResponseBody -> SEPAAccountResponseBody -> Bool
== :: SEPAAccountResponseBody -> SEPAAccountResponseBody -> Bool
$c== :: SEPAAccountResponseBody -> SEPAAccountResponseBody -> Bool
Eq, Int -> SEPAAccountResponseBody -> ShowS
[SEPAAccountResponseBody] -> ShowS
SEPAAccountResponseBody -> String
(Int -> SEPAAccountResponseBody -> ShowS)
-> (SEPAAccountResponseBody -> String)
-> ([SEPAAccountResponseBody] -> ShowS)
-> Show SEPAAccountResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SEPAAccountResponseBody] -> ShowS
$cshowList :: [SEPAAccountResponseBody] -> ShowS
show :: SEPAAccountResponseBody -> String
$cshow :: SEPAAccountResponseBody -> String
showsPrec :: Int -> SEPAAccountResponseBody -> ShowS
$cshowsPrec :: Int -> SEPAAccountResponseBody -> ShowS
Show)
deriving
( Value -> Parser [SEPAAccountResponseBody]
Value -> Parser SEPAAccountResponseBody
(Value -> Parser SEPAAccountResponseBody)
-> (Value -> Parser [SEPAAccountResponseBody])
-> FromJSON SEPAAccountResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SEPAAccountResponseBody]
$cparseJSONList :: Value -> Parser [SEPAAccountResponseBody]
parseJSON :: Value -> Parser SEPAAccountResponseBody
$cparseJSON :: Value -> Parser SEPAAccountResponseBody
FromJSON,
[SEPAAccountResponseBody] -> Encoding
[SEPAAccountResponseBody] -> Value
SEPAAccountResponseBody -> Encoding
SEPAAccountResponseBody -> Value
(SEPAAccountResponseBody -> Value)
-> (SEPAAccountResponseBody -> Encoding)
-> ([SEPAAccountResponseBody] -> Value)
-> ([SEPAAccountResponseBody] -> Encoding)
-> ToJSON SEPAAccountResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SEPAAccountResponseBody] -> Encoding
$ctoEncodingList :: [SEPAAccountResponseBody] -> Encoding
toJSONList :: [SEPAAccountResponseBody] -> Value
$ctoJSONList :: [SEPAAccountResponseBody] -> Value
toEncoding :: SEPAAccountResponseBody -> Encoding
$ctoEncoding :: SEPAAccountResponseBody -> Encoding
toJSON :: SEPAAccountResponseBody -> Value
$ctoJSON :: SEPAAccountResponseBody -> Value
ToJSON
)
via (Autodocodec SEPAAccountResponseBody)
instance HasCodec SEPAAccountResponseBody where
codec :: JSONCodec SEPAAccountResponseBody
codec =
Text
-> ObjectCodec SEPAAccountResponseBody SEPAAccountResponseBody
-> JSONCodec SEPAAccountResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SEPAAccountResponseBody" (ObjectCodec SEPAAccountResponseBody SEPAAccountResponseBody
-> JSONCodec SEPAAccountResponseBody)
-> ObjectCodec SEPAAccountResponseBody SEPAAccountResponseBody
-> JSONCodec SEPAAccountResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> Status
-> Text
-> TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody
SEPAAccountResponseBody
(UUID
-> Status
-> Text
-> TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody UUID
-> Codec
Object
SEPAAccountResponseBody
(Status
-> Text
-> TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (SEPAAccountResponseBody -> UUID)
-> Codec Object SEPAAccountResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> UUID
sepaAccountResponseBodyId
Codec
Object
SEPAAccountResponseBody
(Status
-> Text
-> TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody Status
-> Codec
Object
SEPAAccountResponseBody
(Text
-> TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (SEPAAccountResponseBody -> Status)
-> Codec Object SEPAAccountResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> Status
sepaAccountResponseBodyStatus
Codec
Object
SEPAAccountResponseBody
(Text
-> TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody Text
-> Codec
Object
SEPAAccountResponseBody
(TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (SEPAAccountResponseBody -> Text)
-> Codec Object SEPAAccountResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> Text
sepaAccountResponseBodyDescription
Codec
Object
SEPAAccountResponseBody
(TrackingReference
-> UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody TrackingReference
-> Codec
Object
SEPAAccountResponseBody
(UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec TrackingReference TrackingReference
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"trackingRef" ObjectCodec TrackingReference TrackingReference
-> (SEPAAccountResponseBody -> TrackingReference)
-> Codec Object SEPAAccountResponseBody TrackingReference
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> TrackingReference
sepaAccountResponseBodyTrackingRef
Codec
Object
SEPAAccountResponseBody
(UUID
-> Maybe RiskEvaluation
-> BillingDetails
-> UTCTime
-> UTCTime
-> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody UUID
-> Codec
Object
SEPAAccountResponseBody
(Maybe RiskEvaluation
-> BillingDetails -> UTCTime -> UTCTime -> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fingerprint" ObjectCodec UUID UUID
-> (SEPAAccountResponseBody -> UUID)
-> Codec Object SEPAAccountResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> UUID
sepaAccountResponseBodyFingerprint
Codec
Object
SEPAAccountResponseBody
(Maybe RiskEvaluation
-> BillingDetails -> UTCTime -> UTCTime -> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody (Maybe RiskEvaluation)
-> Codec
Object
SEPAAccountResponseBody
(BillingDetails -> UTCTime -> UTCTime -> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"riskEvaluation" ObjectCodec (Maybe RiskEvaluation) (Maybe RiskEvaluation)
-> (SEPAAccountResponseBody -> Maybe RiskEvaluation)
-> Codec Object SEPAAccountResponseBody (Maybe RiskEvaluation)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> Maybe RiskEvaluation
sepaAccountResponseBodyRiskEvaluation
Codec
Object
SEPAAccountResponseBody
(BillingDetails -> UTCTime -> UTCTime -> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody BillingDetails
-> Codec
Object
SEPAAccountResponseBody
(UTCTime -> UTCTime -> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec BillingDetails BillingDetails
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"billingDetails" ObjectCodec BillingDetails BillingDetails
-> (SEPAAccountResponseBody -> BillingDetails)
-> Codec Object SEPAAccountResponseBody BillingDetails
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> BillingDetails
sepaAccountResponseBodyBillingDetails
Codec
Object
SEPAAccountResponseBody
(UTCTime -> UTCTime -> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody UTCTime
-> Codec
Object SEPAAccountResponseBody (UTCTime -> SEPAAccountResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (SEPAAccountResponseBody -> UTCTime)
-> Codec Object SEPAAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> UTCTime
sepaAccountResponseBodyCreateDate
Codec
Object SEPAAccountResponseBody (UTCTime -> SEPAAccountResponseBody)
-> Codec Object SEPAAccountResponseBody UTCTime
-> ObjectCodec SEPAAccountResponseBody SEPAAccountResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (SEPAAccountResponseBody -> UTCTime)
-> Codec Object SEPAAccountResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SEPAAccountResponseBody -> UTCTime
sepaAccountResponseBodyUpdateDate
data SettlementRequest
type instance CircleRequest SettlementRequest = CircleResponseBody SettlementResponseBody
data SettlementsRequest
type instance CircleRequest SettlementsRequest = CircleResponseBody [SettlementResponseBody]
instance CircleHasParam SettlementsRequest PaginationQueryParams
instance CircleHasParam SettlementsRequest FromQueryParam
instance CircleHasParam SettlementsRequest ToQueryParam
instance CircleHasParam SettlementsRequest PageSizeQueryParam
data SettlementResponseBody = SettlementResponseBody
{ SettlementResponseBody -> UUID
settlementResponseBodyId :: !UUID,
SettlementResponseBody -> UUID
settlementResponseBodyMerchantWalletId :: !UUID,
SettlementResponseBody -> UUID
settlementResponseBodyWalletId :: !UUID,
SettlementResponseBody -> MoneyAmount
settlementResponseBodyTotalDebits :: !MoneyAmount,
SettlementResponseBody -> MoneyAmount
settlementResponseBodyTotalCredits :: !MoneyAmount,
SettlementResponseBody -> MoneyAmount
settlementResponseBodyPaymentFees :: !MoneyAmount,
SettlementResponseBody -> MoneyAmount
settlementResponseBodyChargebackFees :: !MoneyAmount,
SettlementResponseBody -> UTCTime
settlementResponseBodyCreateDate :: !UTCTime,
SettlementResponseBody -> UTCTime
settlementResponseBodyUpdateDate :: !UTCTime
}
deriving (SettlementResponseBody -> SettlementResponseBody -> Bool
(SettlementResponseBody -> SettlementResponseBody -> Bool)
-> (SettlementResponseBody -> SettlementResponseBody -> Bool)
-> Eq SettlementResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SettlementResponseBody -> SettlementResponseBody -> Bool
$c/= :: SettlementResponseBody -> SettlementResponseBody -> Bool
== :: SettlementResponseBody -> SettlementResponseBody -> Bool
$c== :: SettlementResponseBody -> SettlementResponseBody -> Bool
Eq, Int -> SettlementResponseBody -> ShowS
[SettlementResponseBody] -> ShowS
SettlementResponseBody -> String
(Int -> SettlementResponseBody -> ShowS)
-> (SettlementResponseBody -> String)
-> ([SettlementResponseBody] -> ShowS)
-> Show SettlementResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SettlementResponseBody] -> ShowS
$cshowList :: [SettlementResponseBody] -> ShowS
show :: SettlementResponseBody -> String
$cshow :: SettlementResponseBody -> String
showsPrec :: Int -> SettlementResponseBody -> ShowS
$cshowsPrec :: Int -> SettlementResponseBody -> ShowS
Show)
deriving
( Value -> Parser [SettlementResponseBody]
Value -> Parser SettlementResponseBody
(Value -> Parser SettlementResponseBody)
-> (Value -> Parser [SettlementResponseBody])
-> FromJSON SettlementResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SettlementResponseBody]
$cparseJSONList :: Value -> Parser [SettlementResponseBody]
parseJSON :: Value -> Parser SettlementResponseBody
$cparseJSON :: Value -> Parser SettlementResponseBody
FromJSON,
[SettlementResponseBody] -> Encoding
[SettlementResponseBody] -> Value
SettlementResponseBody -> Encoding
SettlementResponseBody -> Value
(SettlementResponseBody -> Value)
-> (SettlementResponseBody -> Encoding)
-> ([SettlementResponseBody] -> Value)
-> ([SettlementResponseBody] -> Encoding)
-> ToJSON SettlementResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SettlementResponseBody] -> Encoding
$ctoEncodingList :: [SettlementResponseBody] -> Encoding
toJSONList :: [SettlementResponseBody] -> Value
$ctoJSONList :: [SettlementResponseBody] -> Value
toEncoding :: SettlementResponseBody -> Encoding
$ctoEncoding :: SettlementResponseBody -> Encoding
toJSON :: SettlementResponseBody -> Value
$ctoJSON :: SettlementResponseBody -> Value
ToJSON
)
via (Autodocodec SettlementResponseBody)
instance HasCodec SettlementResponseBody where
codec :: JSONCodec SettlementResponseBody
codec =
Text
-> ObjectCodec SettlementResponseBody SettlementResponseBody
-> JSONCodec SettlementResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"SettlementResponseBody" (ObjectCodec SettlementResponseBody SettlementResponseBody
-> JSONCodec SettlementResponseBody)
-> ObjectCodec SettlementResponseBody SettlementResponseBody
-> JSONCodec SettlementResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody
SettlementResponseBody
(UUID
-> UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
-> Codec Object SettlementResponseBody UUID
-> Codec
Object
SettlementResponseBody
(UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (SettlementResponseBody -> UUID)
-> Codec Object SettlementResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> UUID
settlementResponseBodyId
Codec
Object
SettlementResponseBody
(UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
-> Codec Object SettlementResponseBody UUID
-> Codec
Object
SettlementResponseBody
(UUID
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"merchantWalletId" ObjectCodec UUID UUID
-> (SettlementResponseBody -> UUID)
-> Codec Object SettlementResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> UUID
settlementResponseBodyMerchantWalletId
Codec
Object
SettlementResponseBody
(UUID
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
-> Codec Object SettlementResponseBody UUID
-> Codec
Object
SettlementResponseBody
(MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"walletId" ObjectCodec UUID UUID
-> (SettlementResponseBody -> UUID)
-> Codec Object SettlementResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> UUID
settlementResponseBodyWalletId
Codec
Object
SettlementResponseBody
(MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
-> Codec Object SettlementResponseBody MoneyAmount
-> Codec
Object
SettlementResponseBody
(MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"totalDebits" ObjectCodec MoneyAmount MoneyAmount
-> (SettlementResponseBody -> MoneyAmount)
-> Codec Object SettlementResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> MoneyAmount
settlementResponseBodyTotalDebits
Codec
Object
SettlementResponseBody
(MoneyAmount
-> MoneyAmount
-> MoneyAmount
-> UTCTime
-> UTCTime
-> SettlementResponseBody)
-> Codec Object SettlementResponseBody MoneyAmount
-> Codec
Object
SettlementResponseBody
(MoneyAmount
-> MoneyAmount -> UTCTime -> UTCTime -> SettlementResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"totalCredits" ObjectCodec MoneyAmount MoneyAmount
-> (SettlementResponseBody -> MoneyAmount)
-> Codec Object SettlementResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> MoneyAmount
settlementResponseBodyTotalCredits
Codec
Object
SettlementResponseBody
(MoneyAmount
-> MoneyAmount -> UTCTime -> UTCTime -> SettlementResponseBody)
-> Codec Object SettlementResponseBody MoneyAmount
-> Codec
Object
SettlementResponseBody
(MoneyAmount -> UTCTime -> UTCTime -> SettlementResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"paymentFees" ObjectCodec MoneyAmount MoneyAmount
-> (SettlementResponseBody -> MoneyAmount)
-> Codec Object SettlementResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> MoneyAmount
settlementResponseBodyPaymentFees
Codec
Object
SettlementResponseBody
(MoneyAmount -> UTCTime -> UTCTime -> SettlementResponseBody)
-> Codec Object SettlementResponseBody MoneyAmount
-> Codec
Object
SettlementResponseBody
(UTCTime -> UTCTime -> SettlementResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chargebackFees" ObjectCodec MoneyAmount MoneyAmount
-> (SettlementResponseBody -> MoneyAmount)
-> Codec Object SettlementResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> MoneyAmount
settlementResponseBodyChargebackFees
Codec
Object
SettlementResponseBody
(UTCTime -> UTCTime -> SettlementResponseBody)
-> Codec Object SettlementResponseBody UTCTime
-> Codec
Object SettlementResponseBody (UTCTime -> SettlementResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (SettlementResponseBody -> UTCTime)
-> Codec Object SettlementResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> UTCTime
settlementResponseBodyCreateDate
Codec
Object SettlementResponseBody (UTCTime -> SettlementResponseBody)
-> Codec Object SettlementResponseBody UTCTime
-> ObjectCodec SettlementResponseBody SettlementResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (SettlementResponseBody -> UTCTime)
-> Codec Object SettlementResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= SettlementResponseBody -> UTCTime
settlementResponseBodyUpdateDate
data ChargebacksRequest
type instance CircleRequest ChargebacksRequest = CircleResponseBody [ChargebackResponseBody]
instance CircleHasParam ChargebacksRequest PaginationQueryParams
instance CircleHasParam ChargebacksRequest FromQueryParam
instance CircleHasParam ChargebacksRequest ToQueryParam
instance CircleHasParam ChargebacksRequest PageSizeQueryParam
instance CircleHasParam ChargebacksRequest PaymentIdQueryParam
data ChargebackRequest
type instance CircleRequest ChargebackRequest = CircleResponseBody ChargebackResponseBody
data MockChargebackRequest
type instance CircleRequest MockChargebackRequest = CircleResponseBody ChargebackResponseBody
data ChargebackResponseBody = ChargebackResponseBody
{ ChargebackResponseBody -> UUID
chargebackResponseBodyId :: !UUID,
ChargebackResponseBody -> UUID
chargebackResponseBodyPaymentId :: !UUID,
ChargebackResponseBody -> UUID
chargebackResponseBodyMerchantId :: !UUID,
ChargebackResponseBody -> Text
chargebackResponseBodyReasonCode :: !Text,
ChargebackResponseBody -> Maybe ChargebackCategory
chargebackResponseBodyCategory :: !(Maybe ChargebackCategory),
ChargebackResponseBody -> [ChargebackHistory]
chargebackResponseBodyHistory :: [ChargebackHistory]
}
deriving (ChargebackResponseBody -> ChargebackResponseBody -> Bool
(ChargebackResponseBody -> ChargebackResponseBody -> Bool)
-> (ChargebackResponseBody -> ChargebackResponseBody -> Bool)
-> Eq ChargebackResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChargebackResponseBody -> ChargebackResponseBody -> Bool
$c/= :: ChargebackResponseBody -> ChargebackResponseBody -> Bool
== :: ChargebackResponseBody -> ChargebackResponseBody -> Bool
$c== :: ChargebackResponseBody -> ChargebackResponseBody -> Bool
Eq, Int -> ChargebackResponseBody -> ShowS
[ChargebackResponseBody] -> ShowS
ChargebackResponseBody -> String
(Int -> ChargebackResponseBody -> ShowS)
-> (ChargebackResponseBody -> String)
-> ([ChargebackResponseBody] -> ShowS)
-> Show ChargebackResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChargebackResponseBody] -> ShowS
$cshowList :: [ChargebackResponseBody] -> ShowS
show :: ChargebackResponseBody -> String
$cshow :: ChargebackResponseBody -> String
showsPrec :: Int -> ChargebackResponseBody -> ShowS
$cshowsPrec :: Int -> ChargebackResponseBody -> ShowS
Show)
deriving
( Value -> Parser [ChargebackResponseBody]
Value -> Parser ChargebackResponseBody
(Value -> Parser ChargebackResponseBody)
-> (Value -> Parser [ChargebackResponseBody])
-> FromJSON ChargebackResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ChargebackResponseBody]
$cparseJSONList :: Value -> Parser [ChargebackResponseBody]
parseJSON :: Value -> Parser ChargebackResponseBody
$cparseJSON :: Value -> Parser ChargebackResponseBody
FromJSON,
[ChargebackResponseBody] -> Encoding
[ChargebackResponseBody] -> Value
ChargebackResponseBody -> Encoding
ChargebackResponseBody -> Value
(ChargebackResponseBody -> Value)
-> (ChargebackResponseBody -> Encoding)
-> ([ChargebackResponseBody] -> Value)
-> ([ChargebackResponseBody] -> Encoding)
-> ToJSON ChargebackResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ChargebackResponseBody] -> Encoding
$ctoEncodingList :: [ChargebackResponseBody] -> Encoding
toJSONList :: [ChargebackResponseBody] -> Value
$ctoJSONList :: [ChargebackResponseBody] -> Value
toEncoding :: ChargebackResponseBody -> Encoding
$ctoEncoding :: ChargebackResponseBody -> Encoding
toJSON :: ChargebackResponseBody -> Value
$ctoJSON :: ChargebackResponseBody -> Value
ToJSON
)
via (Autodocodec ChargebackResponseBody)
instance HasCodec ChargebackResponseBody where
codec :: JSONCodec ChargebackResponseBody
codec =
Text
-> ObjectCodec ChargebackResponseBody ChargebackResponseBody
-> JSONCodec ChargebackResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ChargebackResponseBody" (ObjectCodec ChargebackResponseBody ChargebackResponseBody
-> JSONCodec ChargebackResponseBody)
-> ObjectCodec ChargebackResponseBody ChargebackResponseBody
-> JSONCodec ChargebackResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> UUID
-> UUID
-> Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody
ChargebackResponseBody
(UUID
-> UUID
-> UUID
-> Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody)
-> Codec Object ChargebackResponseBody UUID
-> Codec
Object
ChargebackResponseBody
(UUID
-> UUID
-> Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (ChargebackResponseBody -> UUID)
-> Codec Object ChargebackResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackResponseBody -> UUID
chargebackResponseBodyId
Codec
Object
ChargebackResponseBody
(UUID
-> UUID
-> Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody)
-> Codec Object ChargebackResponseBody UUID
-> Codec
Object
ChargebackResponseBody
(UUID
-> Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"paymentId" ObjectCodec UUID UUID
-> (ChargebackResponseBody -> UUID)
-> Codec Object ChargebackResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackResponseBody -> UUID
chargebackResponseBodyPaymentId
Codec
Object
ChargebackResponseBody
(UUID
-> Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody)
-> Codec Object ChargebackResponseBody UUID
-> Codec
Object
ChargebackResponseBody
(Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"merchantId" ObjectCodec UUID UUID
-> (ChargebackResponseBody -> UUID)
-> Codec Object ChargebackResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackResponseBody -> UUID
chargebackResponseBodyMerchantId
Codec
Object
ChargebackResponseBody
(Text
-> Maybe ChargebackCategory
-> [ChargebackHistory]
-> ChargebackResponseBody)
-> Codec Object ChargebackResponseBody Text
-> Codec
Object
ChargebackResponseBody
(Maybe ChargebackCategory
-> [ChargebackHistory] -> ChargebackResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"reasonCode" ObjectCodec Text Text
-> (ChargebackResponseBody -> Text)
-> Codec Object ChargebackResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackResponseBody -> Text
chargebackResponseBodyReasonCode
Codec
Object
ChargebackResponseBody
(Maybe ChargebackCategory
-> [ChargebackHistory] -> ChargebackResponseBody)
-> Codec Object ChargebackResponseBody (Maybe ChargebackCategory)
-> Codec
Object
ChargebackResponseBody
([ChargebackHistory] -> ChargebackResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
(Maybe ChargebackCategory) (Maybe ChargebackCategory)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"category" ObjectCodec (Maybe ChargebackCategory) (Maybe ChargebackCategory)
-> (ChargebackResponseBody -> Maybe ChargebackCategory)
-> Codec Object ChargebackResponseBody (Maybe ChargebackCategory)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackResponseBody -> Maybe ChargebackCategory
chargebackResponseBodyCategory
Codec
Object
ChargebackResponseBody
([ChargebackHistory] -> ChargebackResponseBody)
-> Codec Object ChargebackResponseBody [ChargebackHistory]
-> ObjectCodec ChargebackResponseBody ChargebackResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [ChargebackHistory] [ChargebackHistory]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"history" ObjectCodec [ChargebackHistory] [ChargebackHistory]
-> (ChargebackResponseBody -> [ChargebackHistory])
-> Codec Object ChargebackResponseBody [ChargebackHistory]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackResponseBody -> [ChargebackHistory]
chargebackResponseBodyHistory
data ChargebackCategory
= CanceledRecurringPayment
| CustomerDispute
| Fraudulent
| General
| ProcessingError
| NotDefined
deriving (ChargebackCategory -> ChargebackCategory -> Bool
(ChargebackCategory -> ChargebackCategory -> Bool)
-> (ChargebackCategory -> ChargebackCategory -> Bool)
-> Eq ChargebackCategory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChargebackCategory -> ChargebackCategory -> Bool
$c/= :: ChargebackCategory -> ChargebackCategory -> Bool
== :: ChargebackCategory -> ChargebackCategory -> Bool
$c== :: ChargebackCategory -> ChargebackCategory -> Bool
Eq, Int -> ChargebackCategory -> ShowS
[ChargebackCategory] -> ShowS
ChargebackCategory -> String
(Int -> ChargebackCategory -> ShowS)
-> (ChargebackCategory -> String)
-> ([ChargebackCategory] -> ShowS)
-> Show ChargebackCategory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChargebackCategory] -> ShowS
$cshowList :: [ChargebackCategory] -> ShowS
show :: ChargebackCategory -> String
$cshow :: ChargebackCategory -> String
showsPrec :: Int -> ChargebackCategory -> ShowS
$cshowsPrec :: Int -> ChargebackCategory -> ShowS
Show, Int -> ChargebackCategory
ChargebackCategory -> Int
ChargebackCategory -> [ChargebackCategory]
ChargebackCategory -> ChargebackCategory
ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
ChargebackCategory
-> ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
(ChargebackCategory -> ChargebackCategory)
-> (ChargebackCategory -> ChargebackCategory)
-> (Int -> ChargebackCategory)
-> (ChargebackCategory -> Int)
-> (ChargebackCategory -> [ChargebackCategory])
-> (ChargebackCategory
-> ChargebackCategory -> [ChargebackCategory])
-> (ChargebackCategory
-> ChargebackCategory -> [ChargebackCategory])
-> (ChargebackCategory
-> ChargebackCategory
-> ChargebackCategory
-> [ChargebackCategory])
-> Enum ChargebackCategory
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ChargebackCategory
-> ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
$cenumFromThenTo :: ChargebackCategory
-> ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
enumFromTo :: ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
$cenumFromTo :: ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
enumFromThen :: ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
$cenumFromThen :: ChargebackCategory -> ChargebackCategory -> [ChargebackCategory]
enumFrom :: ChargebackCategory -> [ChargebackCategory]
$cenumFrom :: ChargebackCategory -> [ChargebackCategory]
fromEnum :: ChargebackCategory -> Int
$cfromEnum :: ChargebackCategory -> Int
toEnum :: Int -> ChargebackCategory
$ctoEnum :: Int -> ChargebackCategory
pred :: ChargebackCategory -> ChargebackCategory
$cpred :: ChargebackCategory -> ChargebackCategory
succ :: ChargebackCategory -> ChargebackCategory
$csucc :: ChargebackCategory -> ChargebackCategory
Enum, ChargebackCategory
ChargebackCategory
-> ChargebackCategory -> Bounded ChargebackCategory
forall a. a -> a -> Bounded a
maxBound :: ChargebackCategory
$cmaxBound :: ChargebackCategory
minBound :: ChargebackCategory
$cminBound :: ChargebackCategory
Bounded)
deriving
( Value -> Parser [ChargebackCategory]
Value -> Parser ChargebackCategory
(Value -> Parser ChargebackCategory)
-> (Value -> Parser [ChargebackCategory])
-> FromJSON ChargebackCategory
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ChargebackCategory]
$cparseJSONList :: Value -> Parser [ChargebackCategory]
parseJSON :: Value -> Parser ChargebackCategory
$cparseJSON :: Value -> Parser ChargebackCategory
FromJSON,
[ChargebackCategory] -> Encoding
[ChargebackCategory] -> Value
ChargebackCategory -> Encoding
ChargebackCategory -> Value
(ChargebackCategory -> Value)
-> (ChargebackCategory -> Encoding)
-> ([ChargebackCategory] -> Value)
-> ([ChargebackCategory] -> Encoding)
-> ToJSON ChargebackCategory
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ChargebackCategory] -> Encoding
$ctoEncodingList :: [ChargebackCategory] -> Encoding
toJSONList :: [ChargebackCategory] -> Value
$ctoJSONList :: [ChargebackCategory] -> Value
toEncoding :: ChargebackCategory -> Encoding
$ctoEncoding :: ChargebackCategory -> Encoding
toJSON :: ChargebackCategory -> Value
$ctoJSON :: ChargebackCategory -> Value
ToJSON
)
via (Autodocodec ChargebackCategory)
instance HasCodec ChargebackCategory where
codec :: JSONCodec ChargebackCategory
codec =
NonEmpty (ChargebackCategory, Text) -> JSONCodec ChargebackCategory
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (ChargebackCategory, Text)
-> JSONCodec ChargebackCategory)
-> NonEmpty (ChargebackCategory, Text)
-> JSONCodec ChargebackCategory
forall a b. (a -> b) -> a -> b
$
[(ChargebackCategory, Text)] -> NonEmpty (ChargebackCategory, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (ChargebackCategory
CanceledRecurringPayment, Text
"Canceled Recurring Payment"),
(ChargebackCategory
CustomerDispute, Text
"Customer Dispute"),
(ChargebackCategory
Fraudulent, Text
"Fraudulent"),
(ChargebackCategory
General, Text
"General"),
(ChargebackCategory
ProcessingError, Text
"Processing Error"),
(ChargebackCategory
NotDefined, Text
"Not Defined")
]
data ChargebackHistory = ChargebackHistory
{ ChargebackHistory -> ChargebackHistoryType
chargebackHistoryType :: !ChargebackHistoryType,
ChargebackHistory -> MoneyAmount
chargebackHistoryAmount :: !MoneyAmount,
ChargebackHistory -> Maybe MoneyAmount
chargebackHistoryFee :: !(Maybe MoneyAmount),
ChargebackHistory -> Text
chargebackHistoryDescription :: !Text,
ChargebackHistory -> Maybe UUID
chargebackHistorySettlementId :: !(Maybe UUID),
ChargebackHistory -> UTCTime
chargebackHistoryCreateDate :: !UTCTime
}
deriving (ChargebackHistory -> ChargebackHistory -> Bool
(ChargebackHistory -> ChargebackHistory -> Bool)
-> (ChargebackHistory -> ChargebackHistory -> Bool)
-> Eq ChargebackHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChargebackHistory -> ChargebackHistory -> Bool
$c/= :: ChargebackHistory -> ChargebackHistory -> Bool
== :: ChargebackHistory -> ChargebackHistory -> Bool
$c== :: ChargebackHistory -> ChargebackHistory -> Bool
Eq, Int -> ChargebackHistory -> ShowS
[ChargebackHistory] -> ShowS
ChargebackHistory -> String
(Int -> ChargebackHistory -> ShowS)
-> (ChargebackHistory -> String)
-> ([ChargebackHistory] -> ShowS)
-> Show ChargebackHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChargebackHistory] -> ShowS
$cshowList :: [ChargebackHistory] -> ShowS
show :: ChargebackHistory -> String
$cshow :: ChargebackHistory -> String
showsPrec :: Int -> ChargebackHistory -> ShowS
$cshowsPrec :: Int -> ChargebackHistory -> ShowS
Show)
deriving
( Value -> Parser [ChargebackHistory]
Value -> Parser ChargebackHistory
(Value -> Parser ChargebackHistory)
-> (Value -> Parser [ChargebackHistory])
-> FromJSON ChargebackHistory
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ChargebackHistory]
$cparseJSONList :: Value -> Parser [ChargebackHistory]
parseJSON :: Value -> Parser ChargebackHistory
$cparseJSON :: Value -> Parser ChargebackHistory
FromJSON,
[ChargebackHistory] -> Encoding
[ChargebackHistory] -> Value
ChargebackHistory -> Encoding
ChargebackHistory -> Value
(ChargebackHistory -> Value)
-> (ChargebackHistory -> Encoding)
-> ([ChargebackHistory] -> Value)
-> ([ChargebackHistory] -> Encoding)
-> ToJSON ChargebackHistory
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ChargebackHistory] -> Encoding
$ctoEncodingList :: [ChargebackHistory] -> Encoding
toJSONList :: [ChargebackHistory] -> Value
$ctoJSONList :: [ChargebackHistory] -> Value
toEncoding :: ChargebackHistory -> Encoding
$ctoEncoding :: ChargebackHistory -> Encoding
toJSON :: ChargebackHistory -> Value
$ctoJSON :: ChargebackHistory -> Value
ToJSON
)
via (Autodocodec ChargebackHistory)
instance HasCodec ChargebackHistory where
codec :: JSONCodec ChargebackHistory
codec =
Text
-> ObjectCodec ChargebackHistory ChargebackHistory
-> JSONCodec ChargebackHistory
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ChargebackHistory" (ObjectCodec ChargebackHistory ChargebackHistory
-> JSONCodec ChargebackHistory)
-> ObjectCodec ChargebackHistory ChargebackHistory
-> JSONCodec ChargebackHistory
forall a b. (a -> b) -> a -> b
$
ChargebackHistoryType
-> MoneyAmount
-> Maybe MoneyAmount
-> Text
-> Maybe UUID
-> UTCTime
-> ChargebackHistory
ChargebackHistory
(ChargebackHistoryType
-> MoneyAmount
-> Maybe MoneyAmount
-> Text
-> Maybe UUID
-> UTCTime
-> ChargebackHistory)
-> Codec Object ChargebackHistory ChargebackHistoryType
-> Codec
Object
ChargebackHistory
(MoneyAmount
-> Maybe MoneyAmount
-> Text
-> Maybe UUID
-> UTCTime
-> ChargebackHistory)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec ChargebackHistoryType ChargebackHistoryType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec ChargebackHistoryType ChargebackHistoryType
-> (ChargebackHistory -> ChargebackHistoryType)
-> Codec Object ChargebackHistory ChargebackHistoryType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackHistory -> ChargebackHistoryType
chargebackHistoryType
Codec
Object
ChargebackHistory
(MoneyAmount
-> Maybe MoneyAmount
-> Text
-> Maybe UUID
-> UTCTime
-> ChargebackHistory)
-> Codec Object ChargebackHistory MoneyAmount
-> Codec
Object
ChargebackHistory
(Maybe MoneyAmount
-> Text -> Maybe UUID -> UTCTime -> ChargebackHistory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (ChargebackHistory -> MoneyAmount)
-> Codec Object ChargebackHistory MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackHistory -> MoneyAmount
chargebackHistoryAmount
Codec
Object
ChargebackHistory
(Maybe MoneyAmount
-> Text -> Maybe UUID -> UTCTime -> ChargebackHistory)
-> Codec Object ChargebackHistory (Maybe MoneyAmount)
-> Codec
Object
ChargebackHistory
(Text -> Maybe UUID -> UTCTime -> ChargebackHistory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fee" ObjectCodec (Maybe MoneyAmount) (Maybe MoneyAmount)
-> (ChargebackHistory -> Maybe MoneyAmount)
-> Codec Object ChargebackHistory (Maybe MoneyAmount)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackHistory -> Maybe MoneyAmount
chargebackHistoryFee
Codec
Object
ChargebackHistory
(Text -> Maybe UUID -> UTCTime -> ChargebackHistory)
-> Codec Object ChargebackHistory Text
-> Codec
Object
ChargebackHistory
(Maybe UUID -> UTCTime -> ChargebackHistory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (ChargebackHistory -> Text)
-> Codec Object ChargebackHistory Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackHistory -> Text
chargebackHistoryDescription
Codec
Object
ChargebackHistory
(Maybe UUID -> UTCTime -> ChargebackHistory)
-> Codec Object ChargebackHistory (Maybe UUID)
-> Codec Object ChargebackHistory (UTCTime -> ChargebackHistory)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe UUID) (Maybe UUID)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"settlementId" ObjectCodec (Maybe UUID) (Maybe UUID)
-> (ChargebackHistory -> Maybe UUID)
-> Codec Object ChargebackHistory (Maybe UUID)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackHistory -> Maybe UUID
chargebackHistorySettlementId
Codec Object ChargebackHistory (UTCTime -> ChargebackHistory)
-> Codec Object ChargebackHistory UTCTime
-> ObjectCodec ChargebackHistory ChargebackHistory
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (ChargebackHistory -> UTCTime)
-> Codec Object ChargebackHistory UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ChargebackHistory -> UTCTime
chargebackHistoryCreateDate
data ChargebackHistoryType
= FirstChargeback
| SecondChargeback
| ChargebackReversal
| Representment
| ChargebackSettlement
deriving (ChargebackHistoryType -> ChargebackHistoryType -> Bool
(ChargebackHistoryType -> ChargebackHistoryType -> Bool)
-> (ChargebackHistoryType -> ChargebackHistoryType -> Bool)
-> Eq ChargebackHistoryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChargebackHistoryType -> ChargebackHistoryType -> Bool
$c/= :: ChargebackHistoryType -> ChargebackHistoryType -> Bool
== :: ChargebackHistoryType -> ChargebackHistoryType -> Bool
$c== :: ChargebackHistoryType -> ChargebackHistoryType -> Bool
Eq, Int -> ChargebackHistoryType -> ShowS
[ChargebackHistoryType] -> ShowS
ChargebackHistoryType -> String
(Int -> ChargebackHistoryType -> ShowS)
-> (ChargebackHistoryType -> String)
-> ([ChargebackHistoryType] -> ShowS)
-> Show ChargebackHistoryType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChargebackHistoryType] -> ShowS
$cshowList :: [ChargebackHistoryType] -> ShowS
show :: ChargebackHistoryType -> String
$cshow :: ChargebackHistoryType -> String
showsPrec :: Int -> ChargebackHistoryType -> ShowS
$cshowsPrec :: Int -> ChargebackHistoryType -> ShowS
Show, Int -> ChargebackHistoryType
ChargebackHistoryType -> Int
ChargebackHistoryType -> [ChargebackHistoryType]
ChargebackHistoryType -> ChargebackHistoryType
ChargebackHistoryType
-> ChargebackHistoryType -> [ChargebackHistoryType]
ChargebackHistoryType
-> ChargebackHistoryType
-> ChargebackHistoryType
-> [ChargebackHistoryType]
(ChargebackHistoryType -> ChargebackHistoryType)
-> (ChargebackHistoryType -> ChargebackHistoryType)
-> (Int -> ChargebackHistoryType)
-> (ChargebackHistoryType -> Int)
-> (ChargebackHistoryType -> [ChargebackHistoryType])
-> (ChargebackHistoryType
-> ChargebackHistoryType -> [ChargebackHistoryType])
-> (ChargebackHistoryType
-> ChargebackHistoryType -> [ChargebackHistoryType])
-> (ChargebackHistoryType
-> ChargebackHistoryType
-> ChargebackHistoryType
-> [ChargebackHistoryType])
-> Enum ChargebackHistoryType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ChargebackHistoryType
-> ChargebackHistoryType
-> ChargebackHistoryType
-> [ChargebackHistoryType]
$cenumFromThenTo :: ChargebackHistoryType
-> ChargebackHistoryType
-> ChargebackHistoryType
-> [ChargebackHistoryType]
enumFromTo :: ChargebackHistoryType
-> ChargebackHistoryType -> [ChargebackHistoryType]
$cenumFromTo :: ChargebackHistoryType
-> ChargebackHistoryType -> [ChargebackHistoryType]
enumFromThen :: ChargebackHistoryType
-> ChargebackHistoryType -> [ChargebackHistoryType]
$cenumFromThen :: ChargebackHistoryType
-> ChargebackHistoryType -> [ChargebackHistoryType]
enumFrom :: ChargebackHistoryType -> [ChargebackHistoryType]
$cenumFrom :: ChargebackHistoryType -> [ChargebackHistoryType]
fromEnum :: ChargebackHistoryType -> Int
$cfromEnum :: ChargebackHistoryType -> Int
toEnum :: Int -> ChargebackHistoryType
$ctoEnum :: Int -> ChargebackHistoryType
pred :: ChargebackHistoryType -> ChargebackHistoryType
$cpred :: ChargebackHistoryType -> ChargebackHistoryType
succ :: ChargebackHistoryType -> ChargebackHistoryType
$csucc :: ChargebackHistoryType -> ChargebackHistoryType
Enum, ChargebackHistoryType
ChargebackHistoryType
-> ChargebackHistoryType -> Bounded ChargebackHistoryType
forall a. a -> a -> Bounded a
maxBound :: ChargebackHistoryType
$cmaxBound :: ChargebackHistoryType
minBound :: ChargebackHistoryType
$cminBound :: ChargebackHistoryType
Bounded)
deriving
( Value -> Parser [ChargebackHistoryType]
Value -> Parser ChargebackHistoryType
(Value -> Parser ChargebackHistoryType)
-> (Value -> Parser [ChargebackHistoryType])
-> FromJSON ChargebackHistoryType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ChargebackHistoryType]
$cparseJSONList :: Value -> Parser [ChargebackHistoryType]
parseJSON :: Value -> Parser ChargebackHistoryType
$cparseJSON :: Value -> Parser ChargebackHistoryType
FromJSON,
[ChargebackHistoryType] -> Encoding
[ChargebackHistoryType] -> Value
ChargebackHistoryType -> Encoding
ChargebackHistoryType -> Value
(ChargebackHistoryType -> Value)
-> (ChargebackHistoryType -> Encoding)
-> ([ChargebackHistoryType] -> Value)
-> ([ChargebackHistoryType] -> Encoding)
-> ToJSON ChargebackHistoryType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ChargebackHistoryType] -> Encoding
$ctoEncodingList :: [ChargebackHistoryType] -> Encoding
toJSONList :: [ChargebackHistoryType] -> Value
$ctoJSONList :: [ChargebackHistoryType] -> Value
toEncoding :: ChargebackHistoryType -> Encoding
$ctoEncoding :: ChargebackHistoryType -> Encoding
toJSON :: ChargebackHistoryType -> Value
$ctoJSON :: ChargebackHistoryType -> Value
ToJSON
)
via (Autodocodec ChargebackHistoryType)
instance HasCodec ChargebackHistoryType where
codec :: JSONCodec ChargebackHistoryType
codec =
NonEmpty (ChargebackHistoryType, Text)
-> JSONCodec ChargebackHistoryType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (ChargebackHistoryType, Text)
-> JSONCodec ChargebackHistoryType)
-> NonEmpty (ChargebackHistoryType, Text)
-> JSONCodec ChargebackHistoryType
forall a b. (a -> b) -> a -> b
$
[(ChargebackHistoryType, Text)]
-> NonEmpty (ChargebackHistoryType, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (ChargebackHistoryType
FirstChargeback, Text
"First Chargeback"),
(ChargebackHistoryType
SecondChargeback, Text
"Second Chargeback"),
(ChargebackHistoryType
ChargebackReversal, Text
"Chargeback Reversal"),
(ChargebackHistoryType
Representment, Text
"Representment"),
(ChargebackHistoryType
ChargebackSettlement, Text
"Chargeback Settlement")
]
data ReversalsRequest
type instance CircleRequest ReversalsRequest = CircleResponseBody [ReversalResponseBody]
instance CircleHasParam ReversalsRequest PaginationQueryParams
instance CircleHasParam ReversalsRequest FromQueryParam
instance CircleHasParam ReversalsRequest ToQueryParam
instance CircleHasParam ReversalsRequest PageSizeQueryParam
instance CircleHasParam ReversalsRequest PaymentStatusQueryParams
data ReversalResponseBody = ReversalResponseBody
{ ReversalResponseBody -> UUID
reversalResponseBodyId :: !UUID,
ReversalResponseBody -> UUID
reversalResponseBodyPaymentId :: !UUID,
ReversalResponseBody -> MoneyAmount
reversalResponseBodyAmount :: !MoneyAmount,
ReversalResponseBody -> Text
reversalResponseBodyDescription :: !Text,
ReversalResponseBody -> Status
reversalResponseBodyStatus :: !Status,
ReversalResponseBody -> ReversalReason
reversalResponseBodyReason :: !ReversalReason,
ReversalResponseBody -> MoneyAmount
reversalResponseBodyFees :: !MoneyAmount,
ReversalResponseBody -> UTCTime
reversalResponseBodyCreateDate :: !UTCTime,
ReversalResponseBody -> UTCTime
reversalResponseBodyUpdateDate :: !UTCTime
}
deriving (ReversalResponseBody -> ReversalResponseBody -> Bool
(ReversalResponseBody -> ReversalResponseBody -> Bool)
-> (ReversalResponseBody -> ReversalResponseBody -> Bool)
-> Eq ReversalResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReversalResponseBody -> ReversalResponseBody -> Bool
$c/= :: ReversalResponseBody -> ReversalResponseBody -> Bool
== :: ReversalResponseBody -> ReversalResponseBody -> Bool
$c== :: ReversalResponseBody -> ReversalResponseBody -> Bool
Eq, Int -> ReversalResponseBody -> ShowS
[ReversalResponseBody] -> ShowS
ReversalResponseBody -> String
(Int -> ReversalResponseBody -> ShowS)
-> (ReversalResponseBody -> String)
-> ([ReversalResponseBody] -> ShowS)
-> Show ReversalResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReversalResponseBody] -> ShowS
$cshowList :: [ReversalResponseBody] -> ShowS
show :: ReversalResponseBody -> String
$cshow :: ReversalResponseBody -> String
showsPrec :: Int -> ReversalResponseBody -> ShowS
$cshowsPrec :: Int -> ReversalResponseBody -> ShowS
Show)
deriving
( Value -> Parser [ReversalResponseBody]
Value -> Parser ReversalResponseBody
(Value -> Parser ReversalResponseBody)
-> (Value -> Parser [ReversalResponseBody])
-> FromJSON ReversalResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ReversalResponseBody]
$cparseJSONList :: Value -> Parser [ReversalResponseBody]
parseJSON :: Value -> Parser ReversalResponseBody
$cparseJSON :: Value -> Parser ReversalResponseBody
FromJSON,
[ReversalResponseBody] -> Encoding
[ReversalResponseBody] -> Value
ReversalResponseBody -> Encoding
ReversalResponseBody -> Value
(ReversalResponseBody -> Value)
-> (ReversalResponseBody -> Encoding)
-> ([ReversalResponseBody] -> Value)
-> ([ReversalResponseBody] -> Encoding)
-> ToJSON ReversalResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ReversalResponseBody] -> Encoding
$ctoEncodingList :: [ReversalResponseBody] -> Encoding
toJSONList :: [ReversalResponseBody] -> Value
$ctoJSONList :: [ReversalResponseBody] -> Value
toEncoding :: ReversalResponseBody -> Encoding
$ctoEncoding :: ReversalResponseBody -> Encoding
toJSON :: ReversalResponseBody -> Value
$ctoJSON :: ReversalResponseBody -> Value
ToJSON
)
via (Autodocodec ReversalResponseBody)
instance HasCodec ReversalResponseBody where
codec :: JSONCodec ReversalResponseBody
codec =
Text
-> ObjectCodec ReversalResponseBody ReversalResponseBody
-> JSONCodec ReversalResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"ReversalResponseBody" (ObjectCodec ReversalResponseBody ReversalResponseBody
-> JSONCodec ReversalResponseBody)
-> ObjectCodec ReversalResponseBody ReversalResponseBody
-> JSONCodec ReversalResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> UUID
-> MoneyAmount
-> Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody
ReversalResponseBody
(UUID
-> UUID
-> MoneyAmount
-> Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
-> Codec Object ReversalResponseBody UUID
-> Codec
Object
ReversalResponseBody
(UUID
-> MoneyAmount
-> Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (ReversalResponseBody -> UUID)
-> Codec Object ReversalResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> UUID
reversalResponseBodyId
Codec
Object
ReversalResponseBody
(UUID
-> MoneyAmount
-> Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
-> Codec Object ReversalResponseBody UUID
-> Codec
Object
ReversalResponseBody
(MoneyAmount
-> Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"paymentId" ObjectCodec UUID UUID
-> (ReversalResponseBody -> UUID)
-> Codec Object ReversalResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> UUID
reversalResponseBodyPaymentId
Codec
Object
ReversalResponseBody
(MoneyAmount
-> Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
-> Codec Object ReversalResponseBody MoneyAmount
-> Codec
Object
ReversalResponseBody
(Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (ReversalResponseBody -> MoneyAmount)
-> Codec Object ReversalResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> MoneyAmount
reversalResponseBodyAmount
Codec
Object
ReversalResponseBody
(Text
-> Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
-> Codec Object ReversalResponseBody Text
-> Codec
Object
ReversalResponseBody
(Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"description" ObjectCodec Text Text
-> (ReversalResponseBody -> Text)
-> Codec Object ReversalResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> Text
reversalResponseBodyDescription
Codec
Object
ReversalResponseBody
(Status
-> ReversalReason
-> MoneyAmount
-> UTCTime
-> UTCTime
-> ReversalResponseBody)
-> Codec Object ReversalResponseBody Status
-> Codec
Object
ReversalResponseBody
(ReversalReason
-> MoneyAmount -> UTCTime -> UTCTime -> ReversalResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Status Status
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec Status Status
-> (ReversalResponseBody -> Status)
-> Codec Object ReversalResponseBody Status
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> Status
reversalResponseBodyStatus
Codec
Object
ReversalResponseBody
(ReversalReason
-> MoneyAmount -> UTCTime -> UTCTime -> ReversalResponseBody)
-> Codec Object ReversalResponseBody ReversalReason
-> Codec
Object
ReversalResponseBody
(MoneyAmount -> UTCTime -> UTCTime -> ReversalResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ReversalReason ReversalReason
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"reason" ObjectCodec ReversalReason ReversalReason
-> (ReversalResponseBody -> ReversalReason)
-> Codec Object ReversalResponseBody ReversalReason
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> ReversalReason
reversalResponseBodyReason
Codec
Object
ReversalResponseBody
(MoneyAmount -> UTCTime -> UTCTime -> ReversalResponseBody)
-> Codec Object ReversalResponseBody MoneyAmount
-> Codec
Object
ReversalResponseBody
(UTCTime -> UTCTime -> ReversalResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fees" ObjectCodec MoneyAmount MoneyAmount
-> (ReversalResponseBody -> MoneyAmount)
-> Codec Object ReversalResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> MoneyAmount
reversalResponseBodyFees
Codec
Object
ReversalResponseBody
(UTCTime -> UTCTime -> ReversalResponseBody)
-> Codec Object ReversalResponseBody UTCTime
-> Codec
Object ReversalResponseBody (UTCTime -> ReversalResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (ReversalResponseBody -> UTCTime)
-> Codec Object ReversalResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> UTCTime
reversalResponseBodyCreateDate
Codec Object ReversalResponseBody (UTCTime -> ReversalResponseBody)
-> Codec Object ReversalResponseBody UTCTime
-> ObjectCodec ReversalResponseBody ReversalResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (ReversalResponseBody -> UTCTime)
-> Codec Object ReversalResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= ReversalResponseBody -> UTCTime
reversalResponseBodyUpdateDate
data ReversalReason
= ReversalDuplicate
| ReversalFraudulent
| ReversalRequestedByCustomer
| ReversalBankTransactionError
| ReversalInvalidAccountNumber
| ReversalInsufficientFunds
| ReversalPaymentStoppedByIssuer
| ReversalPaymentReturned
| ReversalBankAccountIneligible
| ReversalInvalidACHRTN
| ReversalUnauthorizedTransaction
| ReversalPaymentFailed
deriving (ReversalReason -> ReversalReason -> Bool
(ReversalReason -> ReversalReason -> Bool)
-> (ReversalReason -> ReversalReason -> Bool) -> Eq ReversalReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReversalReason -> ReversalReason -> Bool
$c/= :: ReversalReason -> ReversalReason -> Bool
== :: ReversalReason -> ReversalReason -> Bool
$c== :: ReversalReason -> ReversalReason -> Bool
Eq, Int -> ReversalReason -> ShowS
[ReversalReason] -> ShowS
ReversalReason -> String
(Int -> ReversalReason -> ShowS)
-> (ReversalReason -> String)
-> ([ReversalReason] -> ShowS)
-> Show ReversalReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReversalReason] -> ShowS
$cshowList :: [ReversalReason] -> ShowS
show :: ReversalReason -> String
$cshow :: ReversalReason -> String
showsPrec :: Int -> ReversalReason -> ShowS
$cshowsPrec :: Int -> ReversalReason -> ShowS
Show, Int -> ReversalReason
ReversalReason -> Int
ReversalReason -> [ReversalReason]
ReversalReason -> ReversalReason
ReversalReason -> ReversalReason -> [ReversalReason]
ReversalReason
-> ReversalReason -> ReversalReason -> [ReversalReason]
(ReversalReason -> ReversalReason)
-> (ReversalReason -> ReversalReason)
-> (Int -> ReversalReason)
-> (ReversalReason -> Int)
-> (ReversalReason -> [ReversalReason])
-> (ReversalReason -> ReversalReason -> [ReversalReason])
-> (ReversalReason -> ReversalReason -> [ReversalReason])
-> (ReversalReason
-> ReversalReason -> ReversalReason -> [ReversalReason])
-> Enum ReversalReason
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ReversalReason
-> ReversalReason -> ReversalReason -> [ReversalReason]
$cenumFromThenTo :: ReversalReason
-> ReversalReason -> ReversalReason -> [ReversalReason]
enumFromTo :: ReversalReason -> ReversalReason -> [ReversalReason]
$cenumFromTo :: ReversalReason -> ReversalReason -> [ReversalReason]
enumFromThen :: ReversalReason -> ReversalReason -> [ReversalReason]
$cenumFromThen :: ReversalReason -> ReversalReason -> [ReversalReason]
enumFrom :: ReversalReason -> [ReversalReason]
$cenumFrom :: ReversalReason -> [ReversalReason]
fromEnum :: ReversalReason -> Int
$cfromEnum :: ReversalReason -> Int
toEnum :: Int -> ReversalReason
$ctoEnum :: Int -> ReversalReason
pred :: ReversalReason -> ReversalReason
$cpred :: ReversalReason -> ReversalReason
succ :: ReversalReason -> ReversalReason
$csucc :: ReversalReason -> ReversalReason
Enum, ReversalReason
ReversalReason -> ReversalReason -> Bounded ReversalReason
forall a. a -> a -> Bounded a
maxBound :: ReversalReason
$cmaxBound :: ReversalReason
minBound :: ReversalReason
$cminBound :: ReversalReason
Bounded)
deriving
( Value -> Parser [ReversalReason]
Value -> Parser ReversalReason
(Value -> Parser ReversalReason)
-> (Value -> Parser [ReversalReason]) -> FromJSON ReversalReason
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ReversalReason]
$cparseJSONList :: Value -> Parser [ReversalReason]
parseJSON :: Value -> Parser ReversalReason
$cparseJSON :: Value -> Parser ReversalReason
FromJSON,
[ReversalReason] -> Encoding
[ReversalReason] -> Value
ReversalReason -> Encoding
ReversalReason -> Value
(ReversalReason -> Value)
-> (ReversalReason -> Encoding)
-> ([ReversalReason] -> Value)
-> ([ReversalReason] -> Encoding)
-> ToJSON ReversalReason
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ReversalReason] -> Encoding
$ctoEncodingList :: [ReversalReason] -> Encoding
toJSONList :: [ReversalReason] -> Value
$ctoJSONList :: [ReversalReason] -> Value
toEncoding :: ReversalReason -> Encoding
$ctoEncoding :: ReversalReason -> Encoding
toJSON :: ReversalReason -> Value
$ctoJSON :: ReversalReason -> Value
ToJSON
)
via (Autodocodec ReversalReason)
instance HasCodec ReversalReason where
codec :: JSONCodec ReversalReason
codec =
NonEmpty (ReversalReason, Text) -> JSONCodec ReversalReason
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (ReversalReason, Text) -> JSONCodec ReversalReason)
-> NonEmpty (ReversalReason, Text) -> JSONCodec ReversalReason
forall a b. (a -> b) -> a -> b
$
[(ReversalReason, Text)] -> NonEmpty (ReversalReason, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (ReversalReason
ReversalDuplicate, Text
"duplicate"),
(ReversalReason
ReversalFraudulent, Text
"fraudulent"),
(ReversalReason
ReversalRequestedByCustomer, Text
"requested_by_customer"),
(ReversalReason
ReversalBankTransactionError, Text
"bank_transaction_error"),
(ReversalReason
ReversalInvalidAccountNumber, Text
"invalid_account_number"),
(ReversalReason
ReversalInsufficientFunds, Text
"insufficient_funds"),
(ReversalReason
ReversalPaymentStoppedByIssuer, Text
"payment_stopped_by_issuer"),
(ReversalReason
ReversalPaymentReturned, Text
"payment_returned"),
(ReversalReason
ReversalBankAccountIneligible, Text
"bank_account_ineligible"),
(ReversalReason
ReversalInvalidACHRTN, Text
"invalid_ach_rtn"),
(ReversalReason
ReversalUnauthorizedTransaction, Text
"unauthorized_transaction"),
(ReversalReason
ReversalPaymentFailed, Text
"payment_failed")
]
data PaymentIntentRequest
type instance CircleRequest PaymentIntentRequest = CircleResponseBody PaymentIntentResponseBody
data PaymentIntentsRequest
type instance CircleRequest PaymentIntentsRequest = CircleResponseBody [PaymentIntentResponseBody]
instance CircleHasParam PaymentIntentsRequest PaginationQueryParams
instance CircleHasParam PaymentIntentsRequest FromQueryParam
instance CircleHasParam PaymentIntentsRequest ToQueryParam
instance CircleHasParam PaymentIntentsRequest PageSizeQueryParam
instance CircleHasParam PaymentIntentsRequest PaymentStatusQueryParams
instance CircleHasParam PaymentIntentsRequest PaymentIntentContextQueryParams
data CreatePaymentIntentRequestBody = CreatePaymentIntentRequestBody
{ CreatePaymentIntentRequestBody -> UUID
createPaymentIntentIdempotencyKey :: !UUID,
CreatePaymentIntentRequestBody -> MoneyAmount
createPaymentIntentAmount :: !MoneyAmount,
CreatePaymentIntentRequestBody -> SupportedCurrencies
createPaymentIntentSettlementCurrency :: !SupportedCurrencies,
CreatePaymentIntentRequestBody -> [PaymentMethodData]
createPaymentIntentPaymentMethods :: [PaymentMethodData]
}
deriving (CreatePaymentIntentRequestBody
-> CreatePaymentIntentRequestBody -> Bool
(CreatePaymentIntentRequestBody
-> CreatePaymentIntentRequestBody -> Bool)
-> (CreatePaymentIntentRequestBody
-> CreatePaymentIntentRequestBody -> Bool)
-> Eq CreatePaymentIntentRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePaymentIntentRequestBody
-> CreatePaymentIntentRequestBody -> Bool
$c/= :: CreatePaymentIntentRequestBody
-> CreatePaymentIntentRequestBody -> Bool
== :: CreatePaymentIntentRequestBody
-> CreatePaymentIntentRequestBody -> Bool
$c== :: CreatePaymentIntentRequestBody
-> CreatePaymentIntentRequestBody -> Bool
Eq, Int -> CreatePaymentIntentRequestBody -> ShowS
[CreatePaymentIntentRequestBody] -> ShowS
CreatePaymentIntentRequestBody -> String
(Int -> CreatePaymentIntentRequestBody -> ShowS)
-> (CreatePaymentIntentRequestBody -> String)
-> ([CreatePaymentIntentRequestBody] -> ShowS)
-> Show CreatePaymentIntentRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePaymentIntentRequestBody] -> ShowS
$cshowList :: [CreatePaymentIntentRequestBody] -> ShowS
show :: CreatePaymentIntentRequestBody -> String
$cshow :: CreatePaymentIntentRequestBody -> String
showsPrec :: Int -> CreatePaymentIntentRequestBody -> ShowS
$cshowsPrec :: Int -> CreatePaymentIntentRequestBody -> ShowS
Show)
deriving
( Value -> Parser [CreatePaymentIntentRequestBody]
Value -> Parser CreatePaymentIntentRequestBody
(Value -> Parser CreatePaymentIntentRequestBody)
-> (Value -> Parser [CreatePaymentIntentRequestBody])
-> FromJSON CreatePaymentIntentRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CreatePaymentIntentRequestBody]
$cparseJSONList :: Value -> Parser [CreatePaymentIntentRequestBody]
parseJSON :: Value -> Parser CreatePaymentIntentRequestBody
$cparseJSON :: Value -> Parser CreatePaymentIntentRequestBody
FromJSON,
[CreatePaymentIntentRequestBody] -> Encoding
[CreatePaymentIntentRequestBody] -> Value
CreatePaymentIntentRequestBody -> Encoding
CreatePaymentIntentRequestBody -> Value
(CreatePaymentIntentRequestBody -> Value)
-> (CreatePaymentIntentRequestBody -> Encoding)
-> ([CreatePaymentIntentRequestBody] -> Value)
-> ([CreatePaymentIntentRequestBody] -> Encoding)
-> ToJSON CreatePaymentIntentRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreatePaymentIntentRequestBody] -> Encoding
$ctoEncodingList :: [CreatePaymentIntentRequestBody] -> Encoding
toJSONList :: [CreatePaymentIntentRequestBody] -> Value
$ctoJSONList :: [CreatePaymentIntentRequestBody] -> Value
toEncoding :: CreatePaymentIntentRequestBody -> Encoding
$ctoEncoding :: CreatePaymentIntentRequestBody -> Encoding
toJSON :: CreatePaymentIntentRequestBody -> Value
$ctoJSON :: CreatePaymentIntentRequestBody -> Value
ToJSON
)
via (Autodocodec CreatePaymentIntentRequestBody)
instance HasCodec CreatePaymentIntentRequestBody where
codec :: JSONCodec CreatePaymentIntentRequestBody
codec =
Text
-> ObjectCodec
CreatePaymentIntentRequestBody CreatePaymentIntentRequestBody
-> JSONCodec CreatePaymentIntentRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CreatePaymentIntentRequestBody" (ObjectCodec
CreatePaymentIntentRequestBody CreatePaymentIntentRequestBody
-> JSONCodec CreatePaymentIntentRequestBody)
-> ObjectCodec
CreatePaymentIntentRequestBody CreatePaymentIntentRequestBody
-> JSONCodec CreatePaymentIntentRequestBody
forall a b. (a -> b) -> a -> b
$
UUID
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> CreatePaymentIntentRequestBody
CreatePaymentIntentRequestBody
(UUID
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> CreatePaymentIntentRequestBody)
-> Codec Object CreatePaymentIntentRequestBody UUID
-> Codec
Object
CreatePaymentIntentRequestBody
(MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> CreatePaymentIntentRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (CreatePaymentIntentRequestBody -> UUID)
-> Codec Object CreatePaymentIntentRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentIntentRequestBody -> UUID
createPaymentIntentIdempotencyKey
Codec
Object
CreatePaymentIntentRequestBody
(MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> CreatePaymentIntentRequestBody)
-> Codec Object CreatePaymentIntentRequestBody MoneyAmount
-> Codec
Object
CreatePaymentIntentRequestBody
(SupportedCurrencies
-> [PaymentMethodData] -> CreatePaymentIntentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (CreatePaymentIntentRequestBody -> MoneyAmount)
-> Codec Object CreatePaymentIntentRequestBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentIntentRequestBody -> MoneyAmount
createPaymentIntentAmount
Codec
Object
CreatePaymentIntentRequestBody
(SupportedCurrencies
-> [PaymentMethodData] -> CreatePaymentIntentRequestBody)
-> Codec Object CreatePaymentIntentRequestBody SupportedCurrencies
-> Codec
Object
CreatePaymentIntentRequestBody
([PaymentMethodData] -> CreatePaymentIntentRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"settlementCurrency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (CreatePaymentIntentRequestBody -> SupportedCurrencies)
-> Codec Object CreatePaymentIntentRequestBody SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentIntentRequestBody -> SupportedCurrencies
createPaymentIntentSettlementCurrency
Codec
Object
CreatePaymentIntentRequestBody
([PaymentMethodData] -> CreatePaymentIntentRequestBody)
-> Codec Object CreatePaymentIntentRequestBody [PaymentMethodData]
-> ObjectCodec
CreatePaymentIntentRequestBody CreatePaymentIntentRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [PaymentMethodData] [PaymentMethodData]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"paymentMethods" ObjectCodec [PaymentMethodData] [PaymentMethodData]
-> (CreatePaymentIntentRequestBody -> [PaymentMethodData])
-> Codec Object CreatePaymentIntentRequestBody [PaymentMethodData]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreatePaymentIntentRequestBody -> [PaymentMethodData]
createPaymentIntentPaymentMethods
data PaymentIntentResponseBody = PaymentIntentResponseBody
{ PaymentIntentResponseBody -> UUID
paymentIntentResponseBodyIdempotencyKey :: !UUID,
PaymentIntentResponseBody -> UUID
paymentIntentResponseBodyId :: !UUID,
PaymentIntentResponseBody -> MoneyAmount
paymentIntentResponseBodyAmount :: !MoneyAmount,
PaymentIntentResponseBody -> MoneyAmount
paymentIntentResponseBodyAmountPaid :: !MoneyAmount,
PaymentIntentResponseBody -> SupportedCurrencies
paymentIntentResponseBodySettlementCurrency :: !SupportedCurrencies,
PaymentIntentResponseBody -> [PaymentMethodData]
paymentIntentResponseBodyPaymentMethods :: ![PaymentMethodData],
PaymentIntentResponseBody -> [BlockchainFeeMoneyAmount]
paymentIntentResponseBodyFees :: ![BlockchainFeeMoneyAmount],
PaymentIntentResponseBody -> [UUID]
paymentIntentResponseBodyPaymentIds :: ![UUID],
PaymentIntentResponseBody -> [TimelineData]
paymentIntentResponseBodyTimeline :: ![TimelineData],
PaymentIntentResponseBody -> UTCTime
paymentIntentResponseBodyExpiresOn :: !UTCTime,
PaymentIntentResponseBody -> UTCTime
paymentIntentResponseBodyUpdateDate :: !UTCTime,
PaymentIntentResponseBody -> UTCTime
paymentIntentResponseBodyCreateDate :: !UTCTime
}
deriving (PaymentIntentResponseBody -> PaymentIntentResponseBody -> Bool
(PaymentIntentResponseBody -> PaymentIntentResponseBody -> Bool)
-> (PaymentIntentResponseBody -> PaymentIntentResponseBody -> Bool)
-> Eq PaymentIntentResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentIntentResponseBody -> PaymentIntentResponseBody -> Bool
$c/= :: PaymentIntentResponseBody -> PaymentIntentResponseBody -> Bool
== :: PaymentIntentResponseBody -> PaymentIntentResponseBody -> Bool
$c== :: PaymentIntentResponseBody -> PaymentIntentResponseBody -> Bool
Eq, Int -> PaymentIntentResponseBody -> ShowS
[PaymentIntentResponseBody] -> ShowS
PaymentIntentResponseBody -> String
(Int -> PaymentIntentResponseBody -> ShowS)
-> (PaymentIntentResponseBody -> String)
-> ([PaymentIntentResponseBody] -> ShowS)
-> Show PaymentIntentResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentIntentResponseBody] -> ShowS
$cshowList :: [PaymentIntentResponseBody] -> ShowS
show :: PaymentIntentResponseBody -> String
$cshow :: PaymentIntentResponseBody -> String
showsPrec :: Int -> PaymentIntentResponseBody -> ShowS
$cshowsPrec :: Int -> PaymentIntentResponseBody -> ShowS
Show)
deriving
( Value -> Parser [PaymentIntentResponseBody]
Value -> Parser PaymentIntentResponseBody
(Value -> Parser PaymentIntentResponseBody)
-> (Value -> Parser [PaymentIntentResponseBody])
-> FromJSON PaymentIntentResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentIntentResponseBody]
$cparseJSONList :: Value -> Parser [PaymentIntentResponseBody]
parseJSON :: Value -> Parser PaymentIntentResponseBody
$cparseJSON :: Value -> Parser PaymentIntentResponseBody
FromJSON,
[PaymentIntentResponseBody] -> Encoding
[PaymentIntentResponseBody] -> Value
PaymentIntentResponseBody -> Encoding
PaymentIntentResponseBody -> Value
(PaymentIntentResponseBody -> Value)
-> (PaymentIntentResponseBody -> Encoding)
-> ([PaymentIntentResponseBody] -> Value)
-> ([PaymentIntentResponseBody] -> Encoding)
-> ToJSON PaymentIntentResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentIntentResponseBody] -> Encoding
$ctoEncodingList :: [PaymentIntentResponseBody] -> Encoding
toJSONList :: [PaymentIntentResponseBody] -> Value
$ctoJSONList :: [PaymentIntentResponseBody] -> Value
toEncoding :: PaymentIntentResponseBody -> Encoding
$ctoEncoding :: PaymentIntentResponseBody -> Encoding
toJSON :: PaymentIntentResponseBody -> Value
$ctoJSON :: PaymentIntentResponseBody -> Value
ToJSON
)
via (Autodocodec PaymentIntentResponseBody)
instance HasCodec PaymentIntentResponseBody where
codec :: JSONCodec PaymentIntentResponseBody
codec =
Text
-> ObjectCodec PaymentIntentResponseBody PaymentIntentResponseBody
-> JSONCodec PaymentIntentResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PaymentIntentResponseBody" (ObjectCodec PaymentIntentResponseBody PaymentIntentResponseBody
-> JSONCodec PaymentIntentResponseBody)
-> ObjectCodec PaymentIntentResponseBody PaymentIntentResponseBody
-> JSONCodec PaymentIntentResponseBody
forall a b. (a -> b) -> a -> b
$
UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody
PaymentIntentResponseBody
(UUID
-> UUID
-> MoneyAmount
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody UUID
-> Codec
Object
PaymentIntentResponseBody
(UUID
-> MoneyAmount
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (PaymentIntentResponseBody -> UUID)
-> Codec Object PaymentIntentResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> UUID
paymentIntentResponseBodyIdempotencyKey
Codec
Object
PaymentIntentResponseBody
(UUID
-> MoneyAmount
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody UUID
-> Codec
Object
PaymentIntentResponseBody
(MoneyAmount
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (PaymentIntentResponseBody -> UUID)
-> Codec Object PaymentIntentResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> UUID
paymentIntentResponseBodyId
Codec
Object
PaymentIntentResponseBody
(MoneyAmount
-> MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody MoneyAmount
-> Codec
Object
PaymentIntentResponseBody
(MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec MoneyAmount MoneyAmount
-> (PaymentIntentResponseBody -> MoneyAmount)
-> Codec Object PaymentIntentResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> MoneyAmount
paymentIntentResponseBodyAmount
Codec
Object
PaymentIntentResponseBody
(MoneyAmount
-> SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody MoneyAmount
-> Codec
Object
PaymentIntentResponseBody
(SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amountPaid" ObjectCodec MoneyAmount MoneyAmount
-> (PaymentIntentResponseBody -> MoneyAmount)
-> Codec Object PaymentIntentResponseBody MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> MoneyAmount
paymentIntentResponseBodyAmountPaid
Codec
Object
PaymentIntentResponseBody
(SupportedCurrencies
-> [PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody SupportedCurrencies
-> Codec
Object
PaymentIntentResponseBody
([PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"settlementCurrency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (PaymentIntentResponseBody -> SupportedCurrencies)
-> Codec Object PaymentIntentResponseBody SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> SupportedCurrencies
paymentIntentResponseBodySettlementCurrency
Codec
Object
PaymentIntentResponseBody
([PaymentMethodData]
-> [BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody [PaymentMethodData]
-> Codec
Object
PaymentIntentResponseBody
([BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [PaymentMethodData] [PaymentMethodData]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"paymentMethods" ObjectCodec [PaymentMethodData] [PaymentMethodData]
-> (PaymentIntentResponseBody -> [PaymentMethodData])
-> Codec Object PaymentIntentResponseBody [PaymentMethodData]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> [PaymentMethodData]
paymentIntentResponseBodyPaymentMethods
Codec
Object
PaymentIntentResponseBody
([BlockchainFeeMoneyAmount]
-> [UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec
Object PaymentIntentResponseBody [BlockchainFeeMoneyAmount]
-> Codec
Object
PaymentIntentResponseBody
([UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ObjectCodec
[BlockchainFeeMoneyAmount] [BlockchainFeeMoneyAmount]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fees" ObjectCodec [BlockchainFeeMoneyAmount] [BlockchainFeeMoneyAmount]
-> (PaymentIntentResponseBody -> [BlockchainFeeMoneyAmount])
-> Codec
Object PaymentIntentResponseBody [BlockchainFeeMoneyAmount]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> [BlockchainFeeMoneyAmount]
paymentIntentResponseBodyFees
Codec
Object
PaymentIntentResponseBody
([UUID]
-> [TimelineData]
-> UTCTime
-> UTCTime
-> UTCTime
-> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody [UUID]
-> Codec
Object
PaymentIntentResponseBody
([TimelineData]
-> UTCTime -> UTCTime -> UTCTime -> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [UUID] [UUID]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"paymentIds" ObjectCodec [UUID] [UUID]
-> (PaymentIntentResponseBody -> [UUID])
-> Codec Object PaymentIntentResponseBody [UUID]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> [UUID]
paymentIntentResponseBodyPaymentIds
Codec
Object
PaymentIntentResponseBody
([TimelineData]
-> UTCTime -> UTCTime -> UTCTime -> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody [TimelineData]
-> Codec
Object
PaymentIntentResponseBody
(UTCTime -> UTCTime -> UTCTime -> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [TimelineData] [TimelineData]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"timeline" ObjectCodec [TimelineData] [TimelineData]
-> (PaymentIntentResponseBody -> [TimelineData])
-> Codec Object PaymentIntentResponseBody [TimelineData]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> [TimelineData]
paymentIntentResponseBodyTimeline
Codec
Object
PaymentIntentResponseBody
(UTCTime -> UTCTime -> UTCTime -> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody UTCTime
-> Codec
Object
PaymentIntentResponseBody
(UTCTime -> UTCTime -> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"expiresOn" ObjectCodec UTCTime UTCTime
-> (PaymentIntentResponseBody -> UTCTime)
-> Codec Object PaymentIntentResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> UTCTime
paymentIntentResponseBodyExpiresOn
Codec
Object
PaymentIntentResponseBody
(UTCTime -> UTCTime -> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody UTCTime
-> Codec
Object
PaymentIntentResponseBody
(UTCTime -> PaymentIntentResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"updateDate" ObjectCodec UTCTime UTCTime
-> (PaymentIntentResponseBody -> UTCTime)
-> Codec Object PaymentIntentResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> UTCTime
paymentIntentResponseBodyUpdateDate
Codec
Object
PaymentIntentResponseBody
(UTCTime -> PaymentIntentResponseBody)
-> Codec Object PaymentIntentResponseBody UTCTime
-> ObjectCodec PaymentIntentResponseBody PaymentIntentResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"createDate" ObjectCodec UTCTime UTCTime
-> (PaymentIntentResponseBody -> UTCTime)
-> Codec Object PaymentIntentResponseBody UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentIntentResponseBody -> UTCTime
paymentIntentResponseBodyCreateDate
data PaymentMethodData = PaymentMethodData
{ PaymentMethodData -> Text
paymentMethodType :: !Text,
PaymentMethodData -> Chain
paymentMethodDataChain :: !Chain,
PaymentMethodData -> Maybe HexString
paymentMethodDataAddress :: !(Maybe HexString)
}
deriving (PaymentMethodData -> PaymentMethodData -> Bool
(PaymentMethodData -> PaymentMethodData -> Bool)
-> (PaymentMethodData -> PaymentMethodData -> Bool)
-> Eq PaymentMethodData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentMethodData -> PaymentMethodData -> Bool
$c/= :: PaymentMethodData -> PaymentMethodData -> Bool
== :: PaymentMethodData -> PaymentMethodData -> Bool
$c== :: PaymentMethodData -> PaymentMethodData -> Bool
Eq, Int -> PaymentMethodData -> ShowS
[PaymentMethodData] -> ShowS
PaymentMethodData -> String
(Int -> PaymentMethodData -> ShowS)
-> (PaymentMethodData -> String)
-> ([PaymentMethodData] -> ShowS)
-> Show PaymentMethodData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentMethodData] -> ShowS
$cshowList :: [PaymentMethodData] -> ShowS
show :: PaymentMethodData -> String
$cshow :: PaymentMethodData -> String
showsPrec :: Int -> PaymentMethodData -> ShowS
$cshowsPrec :: Int -> PaymentMethodData -> ShowS
Show)
deriving
( Value -> Parser [PaymentMethodData]
Value -> Parser PaymentMethodData
(Value -> Parser PaymentMethodData)
-> (Value -> Parser [PaymentMethodData])
-> FromJSON PaymentMethodData
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentMethodData]
$cparseJSONList :: Value -> Parser [PaymentMethodData]
parseJSON :: Value -> Parser PaymentMethodData
$cparseJSON :: Value -> Parser PaymentMethodData
FromJSON,
[PaymentMethodData] -> Encoding
[PaymentMethodData] -> Value
PaymentMethodData -> Encoding
PaymentMethodData -> Value
(PaymentMethodData -> Value)
-> (PaymentMethodData -> Encoding)
-> ([PaymentMethodData] -> Value)
-> ([PaymentMethodData] -> Encoding)
-> ToJSON PaymentMethodData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentMethodData] -> Encoding
$ctoEncodingList :: [PaymentMethodData] -> Encoding
toJSONList :: [PaymentMethodData] -> Value
$ctoJSONList :: [PaymentMethodData] -> Value
toEncoding :: PaymentMethodData -> Encoding
$ctoEncoding :: PaymentMethodData -> Encoding
toJSON :: PaymentMethodData -> Value
$ctoJSON :: PaymentMethodData -> Value
ToJSON
)
via (Autodocodec PaymentMethodData)
instance HasCodec PaymentMethodData where
codec :: JSONCodec PaymentMethodData
codec =
Text
-> ObjectCodec PaymentMethodData PaymentMethodData
-> JSONCodec PaymentMethodData
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"PaymentMethodData" (ObjectCodec PaymentMethodData PaymentMethodData
-> JSONCodec PaymentMethodData)
-> ObjectCodec PaymentMethodData PaymentMethodData
-> JSONCodec PaymentMethodData
forall a b. (a -> b) -> a -> b
$
Text -> Chain -> Maybe HexString -> PaymentMethodData
PaymentMethodData
(Text -> Chain -> Maybe HexString -> PaymentMethodData)
-> Codec Object PaymentMethodData Text
-> Codec
Object
PaymentMethodData
(Chain -> Maybe HexString -> PaymentMethodData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec Text Text
-> (PaymentMethodData -> Text)
-> Codec Object PaymentMethodData Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentMethodData -> Text
paymentMethodType
Codec
Object
PaymentMethodData
(Chain -> Maybe HexString -> PaymentMethodData)
-> Codec Object PaymentMethodData Chain
-> Codec
Object PaymentMethodData (Maybe HexString -> PaymentMethodData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Chain Chain
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"chain" ObjectCodec Chain Chain
-> (PaymentMethodData -> Chain)
-> Codec Object PaymentMethodData Chain
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentMethodData -> Chain
paymentMethodDataChain
Codec
Object PaymentMethodData (Maybe HexString -> PaymentMethodData)
-> Codec Object PaymentMethodData (Maybe HexString)
-> ObjectCodec PaymentMethodData PaymentMethodData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe HexString) (Maybe HexString)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"address" ObjectCodec (Maybe HexString) (Maybe HexString)
-> (PaymentMethodData -> Maybe HexString)
-> Codec Object PaymentMethodData (Maybe HexString)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= PaymentMethodData -> Maybe HexString
paymentMethodDataAddress
data TimelineData = TimelineData
{ TimelineData -> PaymentIntentStatus
timelineDataStatus :: !PaymentIntentStatus,
TimelineData -> PaymentIntentContext
timelineDataContext :: !PaymentIntentContext,
TimelineData -> UTCTime
timelineDataTime :: !UTCTime
}
deriving (TimelineData -> TimelineData -> Bool
(TimelineData -> TimelineData -> Bool)
-> (TimelineData -> TimelineData -> Bool) -> Eq TimelineData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimelineData -> TimelineData -> Bool
$c/= :: TimelineData -> TimelineData -> Bool
== :: TimelineData -> TimelineData -> Bool
$c== :: TimelineData -> TimelineData -> Bool
Eq, Int -> TimelineData -> ShowS
[TimelineData] -> ShowS
TimelineData -> String
(Int -> TimelineData -> ShowS)
-> (TimelineData -> String)
-> ([TimelineData] -> ShowS)
-> Show TimelineData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimelineData] -> ShowS
$cshowList :: [TimelineData] -> ShowS
show :: TimelineData -> String
$cshow :: TimelineData -> String
showsPrec :: Int -> TimelineData -> ShowS
$cshowsPrec :: Int -> TimelineData -> ShowS
Show)
deriving
( Value -> Parser [TimelineData]
Value -> Parser TimelineData
(Value -> Parser TimelineData)
-> (Value -> Parser [TimelineData]) -> FromJSON TimelineData
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TimelineData]
$cparseJSONList :: Value -> Parser [TimelineData]
parseJSON :: Value -> Parser TimelineData
$cparseJSON :: Value -> Parser TimelineData
FromJSON,
[TimelineData] -> Encoding
[TimelineData] -> Value
TimelineData -> Encoding
TimelineData -> Value
(TimelineData -> Value)
-> (TimelineData -> Encoding)
-> ([TimelineData] -> Value)
-> ([TimelineData] -> Encoding)
-> ToJSON TimelineData
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TimelineData] -> Encoding
$ctoEncodingList :: [TimelineData] -> Encoding
toJSONList :: [TimelineData] -> Value
$ctoJSONList :: [TimelineData] -> Value
toEncoding :: TimelineData -> Encoding
$ctoEncoding :: TimelineData -> Encoding
toJSON :: TimelineData -> Value
$ctoJSON :: TimelineData -> Value
ToJSON
)
via (Autodocodec TimelineData)
instance HasCodec TimelineData where
codec :: JSONCodec TimelineData
codec =
Text
-> ObjectCodec TimelineData TimelineData -> JSONCodec TimelineData
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"TimelineData" (ObjectCodec TimelineData TimelineData -> JSONCodec TimelineData)
-> ObjectCodec TimelineData TimelineData -> JSONCodec TimelineData
forall a b. (a -> b) -> a -> b
$
PaymentIntentStatus
-> PaymentIntentContext -> UTCTime -> TimelineData
TimelineData
(PaymentIntentStatus
-> PaymentIntentContext -> UTCTime -> TimelineData)
-> Codec Object TimelineData PaymentIntentStatus
-> Codec
Object
TimelineData
(PaymentIntentContext -> UTCTime -> TimelineData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec PaymentIntentStatus PaymentIntentStatus
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"status" ObjectCodec PaymentIntentStatus PaymentIntentStatus
-> (TimelineData -> PaymentIntentStatus)
-> Codec Object TimelineData PaymentIntentStatus
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TimelineData -> PaymentIntentStatus
timelineDataStatus
Codec
Object
TimelineData
(PaymentIntentContext -> UTCTime -> TimelineData)
-> Codec Object TimelineData PaymentIntentContext
-> Codec Object TimelineData (UTCTime -> TimelineData)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PaymentIntentContext PaymentIntentContext
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"context" ObjectCodec PaymentIntentContext PaymentIntentContext
-> (TimelineData -> PaymentIntentContext)
-> Codec Object TimelineData PaymentIntentContext
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TimelineData -> PaymentIntentContext
timelineDataContext
Codec Object TimelineData (UTCTime -> TimelineData)
-> Codec Object TimelineData UTCTime
-> ObjectCodec TimelineData TimelineData
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UTCTime UTCTime
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"time" ObjectCodec UTCTime UTCTime
-> (TimelineData -> UTCTime) -> Codec Object TimelineData UTCTime
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TimelineData -> UTCTime
timelineDataTime
data ReturnsRequest
type instance CircleRequest ReturnsRequest = CircleResponseBody [PayoutReturnResponseBody]
instance CircleHasParam ReturnsRequest PaginationQueryParams
instance CircleHasParam ReturnsRequest FromQueryParam
instance CircleHasParam ReturnsRequest ToQueryParam
instance CircleHasParam ReturnsRequest PageSizeQueryParam
data WalletRequest
type instance CircleRequest WalletRequest = CircleResponseBody WalletResponseBody
data WalletsRequest
type instance CircleRequest WalletsRequest = CircleResponseBody [WalletResponseBody]
instance CircleHasParam WalletsRequest PaginationQueryParams
instance CircleHasParam WalletsRequest FromQueryParam
instance CircleHasParam WalletsRequest ToQueryParam
instance CircleHasParam WalletsRequest PageSizeQueryParam
data WalletResponseBody = WalletResponseBody
{ WalletResponseBody -> WalletId
walletResponseBodyWalletId :: !WalletId,
WalletResponseBody -> UUID
walletResponseBodyEntityId :: !UUID,
WalletResponseBody -> Text
walletResponseBodyType :: !Text,
WalletResponseBody -> Maybe Text
walletResponseBodyDescription :: !(Maybe Text),
WalletResponseBody -> [MoneyAmount]
walletResponseBodyBalances :: [MoneyAmount]
}
deriving (WalletResponseBody -> WalletResponseBody -> Bool
(WalletResponseBody -> WalletResponseBody -> Bool)
-> (WalletResponseBody -> WalletResponseBody -> Bool)
-> Eq WalletResponseBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletResponseBody -> WalletResponseBody -> Bool
$c/= :: WalletResponseBody -> WalletResponseBody -> Bool
== :: WalletResponseBody -> WalletResponseBody -> Bool
$c== :: WalletResponseBody -> WalletResponseBody -> Bool
Eq, Int -> WalletResponseBody -> ShowS
[WalletResponseBody] -> ShowS
WalletResponseBody -> String
(Int -> WalletResponseBody -> ShowS)
-> (WalletResponseBody -> String)
-> ([WalletResponseBody] -> ShowS)
-> Show WalletResponseBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletResponseBody] -> ShowS
$cshowList :: [WalletResponseBody] -> ShowS
show :: WalletResponseBody -> String
$cshow :: WalletResponseBody -> String
showsPrec :: Int -> WalletResponseBody -> ShowS
$cshowsPrec :: Int -> WalletResponseBody -> ShowS
Show)
deriving
( Value -> Parser [WalletResponseBody]
Value -> Parser WalletResponseBody
(Value -> Parser WalletResponseBody)
-> (Value -> Parser [WalletResponseBody])
-> FromJSON WalletResponseBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WalletResponseBody]
$cparseJSONList :: Value -> Parser [WalletResponseBody]
parseJSON :: Value -> Parser WalletResponseBody
$cparseJSON :: Value -> Parser WalletResponseBody
FromJSON,
[WalletResponseBody] -> Encoding
[WalletResponseBody] -> Value
WalletResponseBody -> Encoding
WalletResponseBody -> Value
(WalletResponseBody -> Value)
-> (WalletResponseBody -> Encoding)
-> ([WalletResponseBody] -> Value)
-> ([WalletResponseBody] -> Encoding)
-> ToJSON WalletResponseBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WalletResponseBody] -> Encoding
$ctoEncodingList :: [WalletResponseBody] -> Encoding
toJSONList :: [WalletResponseBody] -> Value
$ctoJSONList :: [WalletResponseBody] -> Value
toEncoding :: WalletResponseBody -> Encoding
$ctoEncoding :: WalletResponseBody -> Encoding
toJSON :: WalletResponseBody -> Value
$ctoJSON :: WalletResponseBody -> Value
ToJSON
)
via (Autodocodec WalletResponseBody)
instance HasCodec WalletResponseBody where
codec :: JSONCodec WalletResponseBody
codec =
Text
-> ObjectCodec WalletResponseBody WalletResponseBody
-> JSONCodec WalletResponseBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"WalletResponseBody" (ObjectCodec WalletResponseBody WalletResponseBody
-> JSONCodec WalletResponseBody)
-> ObjectCodec WalletResponseBody WalletResponseBody
-> JSONCodec WalletResponseBody
forall a b. (a -> b) -> a -> b
$
WalletId
-> UUID
-> Text
-> Maybe Text
-> [MoneyAmount]
-> WalletResponseBody
WalletResponseBody
(WalletId
-> UUID
-> Text
-> Maybe Text
-> [MoneyAmount]
-> WalletResponseBody)
-> Codec Object WalletResponseBody WalletId
-> Codec
Object
WalletResponseBody
(UUID -> Text -> Maybe Text -> [MoneyAmount] -> WalletResponseBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec WalletId WalletId
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"walletId" ObjectCodec WalletId WalletId
-> (WalletResponseBody -> WalletId)
-> Codec Object WalletResponseBody WalletId
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WalletResponseBody -> WalletId
walletResponseBodyWalletId
Codec
Object
WalletResponseBody
(UUID -> Text -> Maybe Text -> [MoneyAmount] -> WalletResponseBody)
-> Codec Object WalletResponseBody UUID
-> Codec
Object
WalletResponseBody
(Text -> Maybe Text -> [MoneyAmount] -> WalletResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"entityId" ObjectCodec UUID UUID
-> (WalletResponseBody -> UUID)
-> Codec Object WalletResponseBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WalletResponseBody -> UUID
walletResponseBodyEntityId
Codec
Object
WalletResponseBody
(Text -> Maybe Text -> [MoneyAmount] -> WalletResponseBody)
-> Codec Object WalletResponseBody Text
-> Codec
Object
WalletResponseBody
(Maybe Text -> [MoneyAmount] -> WalletResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec Text Text
-> (WalletResponseBody -> Text)
-> Codec Object WalletResponseBody Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WalletResponseBody -> Text
walletResponseBodyType
Codec
Object
WalletResponseBody
(Maybe Text -> [MoneyAmount] -> WalletResponseBody)
-> Codec Object WalletResponseBody (Maybe Text)
-> Codec
Object WalletResponseBody ([MoneyAmount] -> WalletResponseBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"description" ObjectCodec (Maybe Text) (Maybe Text)
-> (WalletResponseBody -> Maybe Text)
-> Codec Object WalletResponseBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WalletResponseBody -> Maybe Text
walletResponseBodyDescription
Codec
Object WalletResponseBody ([MoneyAmount] -> WalletResponseBody)
-> Codec Object WalletResponseBody [MoneyAmount]
-> ObjectCodec WalletResponseBody WalletResponseBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec [MoneyAmount] [MoneyAmount]
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"balances" ObjectCodec [MoneyAmount] [MoneyAmount]
-> (WalletResponseBody -> [MoneyAmount])
-> Codec Object WalletResponseBody [MoneyAmount]
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= WalletResponseBody -> [MoneyAmount]
walletResponseBodyBalances
data CreateWalletRequestBody = CreateWalletRequestBody
{ CreateWalletRequestBody -> UUID
createWalletRequestBodyIdempotencyKey :: !UUID,
CreateWalletRequestBody -> Maybe Text
createWalletRequestBodyDescription :: !(Maybe Text)
}
deriving (CreateWalletRequestBody -> CreateWalletRequestBody -> Bool
(CreateWalletRequestBody -> CreateWalletRequestBody -> Bool)
-> (CreateWalletRequestBody -> CreateWalletRequestBody -> Bool)
-> Eq CreateWalletRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWalletRequestBody -> CreateWalletRequestBody -> Bool
$c/= :: CreateWalletRequestBody -> CreateWalletRequestBody -> Bool
== :: CreateWalletRequestBody -> CreateWalletRequestBody -> Bool
$c== :: CreateWalletRequestBody -> CreateWalletRequestBody -> Bool
Eq, Int -> CreateWalletRequestBody -> ShowS
[CreateWalletRequestBody] -> ShowS
CreateWalletRequestBody -> String
(Int -> CreateWalletRequestBody -> ShowS)
-> (CreateWalletRequestBody -> String)
-> ([CreateWalletRequestBody] -> ShowS)
-> Show CreateWalletRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWalletRequestBody] -> ShowS
$cshowList :: [CreateWalletRequestBody] -> ShowS
show :: CreateWalletRequestBody -> String
$cshow :: CreateWalletRequestBody -> String
showsPrec :: Int -> CreateWalletRequestBody -> ShowS
$cshowsPrec :: Int -> CreateWalletRequestBody -> ShowS
Show)
deriving
( Value -> Parser [CreateWalletRequestBody]
Value -> Parser CreateWalletRequestBody
(Value -> Parser CreateWalletRequestBody)
-> (Value -> Parser [CreateWalletRequestBody])
-> FromJSON CreateWalletRequestBody
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CreateWalletRequestBody]
$cparseJSONList :: Value -> Parser [CreateWalletRequestBody]
parseJSON :: Value -> Parser CreateWalletRequestBody
$cparseJSON :: Value -> Parser CreateWalletRequestBody
FromJSON,
[CreateWalletRequestBody] -> Encoding
[CreateWalletRequestBody] -> Value
CreateWalletRequestBody -> Encoding
CreateWalletRequestBody -> Value
(CreateWalletRequestBody -> Value)
-> (CreateWalletRequestBody -> Encoding)
-> ([CreateWalletRequestBody] -> Value)
-> ([CreateWalletRequestBody] -> Encoding)
-> ToJSON CreateWalletRequestBody
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CreateWalletRequestBody] -> Encoding
$ctoEncodingList :: [CreateWalletRequestBody] -> Encoding
toJSONList :: [CreateWalletRequestBody] -> Value
$ctoJSONList :: [CreateWalletRequestBody] -> Value
toEncoding :: CreateWalletRequestBody -> Encoding
$ctoEncoding :: CreateWalletRequestBody -> Encoding
toJSON :: CreateWalletRequestBody -> Value
$ctoJSON :: CreateWalletRequestBody -> Value
ToJSON
)
via (Autodocodec CreateWalletRequestBody)
instance HasCodec CreateWalletRequestBody where
codec :: JSONCodec CreateWalletRequestBody
codec =
Text
-> ObjectCodec CreateWalletRequestBody CreateWalletRequestBody
-> JSONCodec CreateWalletRequestBody
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"CreateWalletRequestBody" (ObjectCodec CreateWalletRequestBody CreateWalletRequestBody
-> JSONCodec CreateWalletRequestBody)
-> ObjectCodec CreateWalletRequestBody CreateWalletRequestBody
-> JSONCodec CreateWalletRequestBody
forall a b. (a -> b) -> a -> b
$
UUID -> Maybe Text -> CreateWalletRequestBody
CreateWalletRequestBody
(UUID -> Maybe Text -> CreateWalletRequestBody)
-> Codec Object CreateWalletRequestBody UUID
-> Codec
Object
CreateWalletRequestBody
(Maybe Text -> CreateWalletRequestBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"idempotencyKey" ObjectCodec UUID UUID
-> (CreateWalletRequestBody -> UUID)
-> Codec Object CreateWalletRequestBody UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateWalletRequestBody -> UUID
createWalletRequestBodyIdempotencyKey
Codec
Object
CreateWalletRequestBody
(Maybe Text -> CreateWalletRequestBody)
-> Codec Object CreateWalletRequestBody (Maybe Text)
-> ObjectCodec CreateWalletRequestBody CreateWalletRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"description" ObjectCodec (Maybe Text) (Maybe Text)
-> (CreateWalletRequestBody -> Maybe Text)
-> Codec Object CreateWalletRequestBody (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= CreateWalletRequestBody -> Maybe Text
createWalletRequestBodyDescription
utcToCircle :: UTCTime -> Text
utcToCircle :: UTCTime -> Text
utcToCircle UTCTime
ut =
Day -> Text
forall a. Show a => a -> Text
tshow Day
day Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"T" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
clockTime Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-00:00"
where
day :: Day
day = UTCTime -> Day
utctDay UTCTime
ut
time :: DiffTime
time = UTCTime -> DiffTime
utctDayTime UTCTime
ut
tod :: TimeOfDay
tod = (Integer, TimeOfDay) -> TimeOfDay
forall a b. (a, b) -> b
snd ((Integer, TimeOfDay) -> TimeOfDay)
-> (Integer, TimeOfDay) -> TimeOfDay
forall a b. (a -> b) -> a -> b
$ TimeZone -> TimeOfDay -> (Integer, TimeOfDay)
utcToLocalTimeOfDay TimeZone
utc (DiffTime -> TimeOfDay
timeToTimeOfDay DiffTime
time)
atLeastTwo :: Text -> Int -> Text
atLeastTwo :: Text -> Int -> Text
atLeastTwo Text
t Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
10 = Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
i
| Bool
otherwise = Int -> Text
forall a. Show a => a -> Text
tshow Int
i
clockTime :: Text
clockTime =
Text -> Int -> Text
atLeastTwo Text
"0" (TimeOfDay -> Int
todHour TimeOfDay
tod)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Int -> Text
atLeastTwo Text
"0" (TimeOfDay -> Int
todMin TimeOfDay
tod)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Int -> Text
atLeastTwo Text
"0" (Pico -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor (Pico -> Int) -> Pico -> Int
forall a b. (a -> b) -> a -> b
$ TimeOfDay -> Pico
todSec TimeOfDay
tod)
tshow :: Show a => a -> Text
tshow :: a -> Text
tshow = String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
data ThisOrThat a b = This a | That b
deriving stock (ThisOrThat a b -> ThisOrThat a b -> Bool
(ThisOrThat a b -> ThisOrThat a b -> Bool)
-> (ThisOrThat a b -> ThisOrThat a b -> Bool)
-> Eq (ThisOrThat a b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b.
(Eq a, Eq b) =>
ThisOrThat a b -> ThisOrThat a b -> Bool
/= :: ThisOrThat a b -> ThisOrThat a b -> Bool
$c/= :: forall a b.
(Eq a, Eq b) =>
ThisOrThat a b -> ThisOrThat a b -> Bool
== :: ThisOrThat a b -> ThisOrThat a b -> Bool
$c== :: forall a b.
(Eq a, Eq b) =>
ThisOrThat a b -> ThisOrThat a b -> Bool
Eq, (forall x. ThisOrThat a b -> Rep (ThisOrThat a b) x)
-> (forall x. Rep (ThisOrThat a b) x -> ThisOrThat a b)
-> Generic (ThisOrThat a b)
forall x. Rep (ThisOrThat a b) x -> ThisOrThat a b
forall x. ThisOrThat a b -> Rep (ThisOrThat a b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a b x. Rep (ThisOrThat a b) x -> ThisOrThat a b
forall a b x. ThisOrThat a b -> Rep (ThisOrThat a b) x
$cto :: forall a b x. Rep (ThisOrThat a b) x -> ThisOrThat a b
$cfrom :: forall a b x. ThisOrThat a b -> Rep (ThisOrThat a b) x
Generic)
catThises :: [ThisOrThat a b] -> [a]
catThises :: [ThisOrThat a b] -> [a]
catThises [ThisOrThat a b]
lst = [ThisOrThat a b]
lst [ThisOrThat a b] -> (ThisOrThat a b -> [a]) -> [a]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ThisOrThat a b -> [a]
forall a b. ThisOrThat a b -> [a]
toThis
where
toThis :: ThisOrThat a b -> [a]
toThis = \case
This a
a -> [a
a]
ThisOrThat a b
_ -> []
catThats :: [ThisOrThat a b] -> [b]
catThats :: [ThisOrThat a b] -> [b]
catThats [ThisOrThat a b]
lst = [ThisOrThat a b]
lst [ThisOrThat a b] -> (ThisOrThat a b -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ThisOrThat a b -> [b]
forall a a. ThisOrThat a a -> [a]
toThat
where
toThat :: ThisOrThat a a -> [a]
toThat = \case
That a
b -> [a
b]
ThisOrThat a a
_ -> []
instance (Show a, Show b) => Show (ThisOrThat a b) where
show :: ThisOrThat a b -> String
show = \case
This a
a -> a -> String
forall a. Show a => a -> String
show a
a
That b
b -> b -> String
forall a. Show a => a -> String
show b
b
instance (ToJSON a, ToJSON b) => ToJSON (ThisOrThat a b) where
toJSON :: ThisOrThat a b -> Value
toJSON (This a
a) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
a
toJSON (That b
b) = b -> Value
forall a. ToJSON a => a -> Value
toJSON b
b
toEncoding :: ThisOrThat a b -> Encoding
toEncoding (This a
a) = a -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding a
a
toEncoding (That b
b) = b -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding b
b
instance (FromJSON a, FromJSON b) => FromJSON (ThisOrThat a b) where
parseJSON :: Value -> Parser (ThisOrThat a b)
parseJSON Value
val = do
let parsedA :: Result a
parsedA = Value -> Result a
forall a. FromJSON a => Value -> Result a
fromJSON Value
val
parsedB :: Result b
parsedB = Value -> Result b
forall a. FromJSON a => Value -> Result a
fromJSON Value
val
case (Result a
parsedA, Result b
parsedB) of
(Success a
a, Result b
_) -> ThisOrThat a b -> Parser (ThisOrThat a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ThisOrThat a b -> Parser (ThisOrThat a b))
-> ThisOrThat a b -> Parser (ThisOrThat a b)
forall a b. (a -> b) -> a -> b
$ a -> ThisOrThat a b
forall a b. a -> ThisOrThat a b
This a
a
(Result a
_, Success b
b) -> ThisOrThat a b -> Parser (ThisOrThat a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ThisOrThat a b -> Parser (ThisOrThat a b))
-> ThisOrThat a b -> Parser (ThisOrThat a b)
forall a b. (a -> b) -> a -> b
$ b -> ThisOrThat a b
forall a b. b -> ThisOrThat a b
That b
b
(Error String
thisError, Error String
thatError) ->
String -> Parser (ThisOrThat a b)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (ThisOrThat a b))
-> String -> Parser (ThisOrThat a b)
forall a b. (a -> b) -> a -> b
$
[String] -> String
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold
[ String
"Failed when parsing a ThisOrThat from JSON.\n",
String
"Error on the This: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
thisError String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"\n",
String
"Error on the That: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
thatError
]
instance Bifunctor ThisOrThat where
bimap :: (a -> b) -> (c -> d) -> ThisOrThat a c -> ThisOrThat b d
bimap a -> b
f c -> d
_ (This a
a) = b -> ThisOrThat b d
forall a b. a -> ThisOrThat a b
This (a -> b
f a
a)
bimap a -> b
_ c -> d
g (That c
b) = d -> ThisOrThat b d
forall a b. b -> ThisOrThat a b
That (c -> d
g c
b)
thisOrThatToEither :: ThisOrThat a b -> Either a b
thisOrThatToEither :: ThisOrThat a b -> Either a b
thisOrThatToEither = \case
This a
a -> a -> Either a b
forall a b. a -> Either a b
Left a
a
That b
b -> b -> Either a b
forall a b. b -> Either a b
Right b
b
thisOrThat :: (a -> c) -> (b -> c) -> ThisOrThat a b -> c
thisOrThat :: (a -> c) -> (b -> c) -> ThisOrThat a b -> c
thisOrThat a -> c
f b -> c
g ThisOrThat a b
tot = (a -> c) -> (b -> c) -> Either a b -> c
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> c
f b -> c
g (Either a b -> c) -> Either a b -> c
forall a b. (a -> b) -> a -> b
$ ThisOrThat a b -> Either a b
forall a b. ThisOrThat a b -> Either a b
thisOrThatToEither ThisOrThat a b
tot
data Status = Pending | Complete | Failed
deriving (Int -> Status -> ShowS
[Status] -> ShowS
Status -> String
(Int -> Status -> ShowS)
-> (Status -> String) -> ([Status] -> ShowS) -> Show Status
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Status] -> ShowS
$cshowList :: [Status] -> ShowS
show :: Status -> String
$cshow :: Status -> String
showsPrec :: Int -> Status -> ShowS
$cshowsPrec :: Int -> Status -> ShowS
Show, Status -> Status -> Bool
(Status -> Status -> Bool)
-> (Status -> Status -> Bool) -> Eq Status
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Eq)
deriving
( Value -> Parser [Status]
Value -> Parser Status
(Value -> Parser Status)
-> (Value -> Parser [Status]) -> FromJSON Status
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Status]
$cparseJSONList :: Value -> Parser [Status]
parseJSON :: Value -> Parser Status
$cparseJSON :: Value -> Parser Status
FromJSON,
[Status] -> Encoding
[Status] -> Value
Status -> Encoding
Status -> Value
(Status -> Value)
-> (Status -> Encoding)
-> ([Status] -> Value)
-> ([Status] -> Encoding)
-> ToJSON Status
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Status] -> Encoding
$ctoEncodingList :: [Status] -> Encoding
toJSONList :: [Status] -> Value
$ctoJSONList :: [Status] -> Value
toEncoding :: Status -> Encoding
$ctoEncoding :: Status -> Encoding
toJSON :: Status -> Value
$ctoJSON :: Status -> Value
ToJSON
)
via (Autodocodec Status)
instance HasCodec Status where
codec :: JSONCodec Status
codec = NonEmpty (Status, Text) -> JSONCodec Status
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (Status, Text) -> JSONCodec Status)
-> NonEmpty (Status, Text) -> JSONCodec Status
forall a b. (a -> b) -> a -> b
$ [(Status, Text)] -> NonEmpty (Status, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(Status
Pending, Text
"pending"), (Status
Complete, Text
"complete"), (Status
Failed, Text
"failed")]
data PaymentStatus
= PaymentPending
| Confirmed
| Paid
| PaymentFailed
| ActionRequired
deriving (Int -> PaymentStatus -> ShowS
[PaymentStatus] -> ShowS
PaymentStatus -> String
(Int -> PaymentStatus -> ShowS)
-> (PaymentStatus -> String)
-> ([PaymentStatus] -> ShowS)
-> Show PaymentStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentStatus] -> ShowS
$cshowList :: [PaymentStatus] -> ShowS
show :: PaymentStatus -> String
$cshow :: PaymentStatus -> String
showsPrec :: Int -> PaymentStatus -> ShowS
$cshowsPrec :: Int -> PaymentStatus -> ShowS
Show, PaymentStatus -> PaymentStatus -> Bool
(PaymentStatus -> PaymentStatus -> Bool)
-> (PaymentStatus -> PaymentStatus -> Bool) -> Eq PaymentStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentStatus -> PaymentStatus -> Bool
$c/= :: PaymentStatus -> PaymentStatus -> Bool
== :: PaymentStatus -> PaymentStatus -> Bool
$c== :: PaymentStatus -> PaymentStatus -> Bool
Eq)
deriving
( Value -> Parser [PaymentStatus]
Value -> Parser PaymentStatus
(Value -> Parser PaymentStatus)
-> (Value -> Parser [PaymentStatus]) -> FromJSON PaymentStatus
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentStatus]
$cparseJSONList :: Value -> Parser [PaymentStatus]
parseJSON :: Value -> Parser PaymentStatus
$cparseJSON :: Value -> Parser PaymentStatus
FromJSON,
[PaymentStatus] -> Encoding
[PaymentStatus] -> Value
PaymentStatus -> Encoding
PaymentStatus -> Value
(PaymentStatus -> Value)
-> (PaymentStatus -> Encoding)
-> ([PaymentStatus] -> Value)
-> ([PaymentStatus] -> Encoding)
-> ToJSON PaymentStatus
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentStatus] -> Encoding
$ctoEncodingList :: [PaymentStatus] -> Encoding
toJSONList :: [PaymentStatus] -> Value
$ctoJSONList :: [PaymentStatus] -> Value
toEncoding :: PaymentStatus -> Encoding
$ctoEncoding :: PaymentStatus -> Encoding
toJSON :: PaymentStatus -> Value
$ctoJSON :: PaymentStatus -> Value
ToJSON
)
via (Autodocodec PaymentStatus)
instance HasCodec PaymentStatus where
codec :: JSONCodec PaymentStatus
codec =
NonEmpty (PaymentStatus, Text) -> JSONCodec PaymentStatus
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (PaymentStatus, Text) -> JSONCodec PaymentStatus)
-> NonEmpty (PaymentStatus, Text) -> JSONCodec PaymentStatus
forall a b. (a -> b) -> a -> b
$
[(PaymentStatus, Text)] -> NonEmpty (PaymentStatus, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (PaymentStatus
Confirmed, Text
"confirmed"),
(PaymentStatus
PaymentPending, Text
"pending"),
(PaymentStatus
Paid, Text
"paid"),
(PaymentStatus
PaymentFailed, Text
"failed"),
(PaymentStatus
ActionRequired, Text
"action_required")
]
data PaymentIntentStatus
= PaymentIntentCreated
| PaymentIntentPending
| PaymentIntentComplete
| PaymentIntentExpired
| PaymentIntentFailed
deriving (Int -> PaymentIntentStatus -> ShowS
[PaymentIntentStatus] -> ShowS
PaymentIntentStatus -> String
(Int -> PaymentIntentStatus -> ShowS)
-> (PaymentIntentStatus -> String)
-> ([PaymentIntentStatus] -> ShowS)
-> Show PaymentIntentStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentIntentStatus] -> ShowS
$cshowList :: [PaymentIntentStatus] -> ShowS
show :: PaymentIntentStatus -> String
$cshow :: PaymentIntentStatus -> String
showsPrec :: Int -> PaymentIntentStatus -> ShowS
$cshowsPrec :: Int -> PaymentIntentStatus -> ShowS
Show, PaymentIntentStatus -> PaymentIntentStatus -> Bool
(PaymentIntentStatus -> PaymentIntentStatus -> Bool)
-> (PaymentIntentStatus -> PaymentIntentStatus -> Bool)
-> Eq PaymentIntentStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentIntentStatus -> PaymentIntentStatus -> Bool
$c/= :: PaymentIntentStatus -> PaymentIntentStatus -> Bool
== :: PaymentIntentStatus -> PaymentIntentStatus -> Bool
$c== :: PaymentIntentStatus -> PaymentIntentStatus -> Bool
Eq)
deriving
( Value -> Parser [PaymentIntentStatus]
Value -> Parser PaymentIntentStatus
(Value -> Parser PaymentIntentStatus)
-> (Value -> Parser [PaymentIntentStatus])
-> FromJSON PaymentIntentStatus
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentIntentStatus]
$cparseJSONList :: Value -> Parser [PaymentIntentStatus]
parseJSON :: Value -> Parser PaymentIntentStatus
$cparseJSON :: Value -> Parser PaymentIntentStatus
FromJSON,
[PaymentIntentStatus] -> Encoding
[PaymentIntentStatus] -> Value
PaymentIntentStatus -> Encoding
PaymentIntentStatus -> Value
(PaymentIntentStatus -> Value)
-> (PaymentIntentStatus -> Encoding)
-> ([PaymentIntentStatus] -> Value)
-> ([PaymentIntentStatus] -> Encoding)
-> ToJSON PaymentIntentStatus
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentIntentStatus] -> Encoding
$ctoEncodingList :: [PaymentIntentStatus] -> Encoding
toJSONList :: [PaymentIntentStatus] -> Value
$ctoJSONList :: [PaymentIntentStatus] -> Value
toEncoding :: PaymentIntentStatus -> Encoding
$ctoEncoding :: PaymentIntentStatus -> Encoding
toJSON :: PaymentIntentStatus -> Value
$ctoJSON :: PaymentIntentStatus -> Value
ToJSON
)
via (Autodocodec PaymentIntentStatus)
instance HasCodec PaymentIntentStatus where
codec :: JSONCodec PaymentIntentStatus
codec =
NonEmpty (PaymentIntentStatus, Text)
-> JSONCodec PaymentIntentStatus
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (PaymentIntentStatus, Text)
-> JSONCodec PaymentIntentStatus)
-> NonEmpty (PaymentIntentStatus, Text)
-> JSONCodec PaymentIntentStatus
forall a b. (a -> b) -> a -> b
$
[(PaymentIntentStatus, Text)]
-> NonEmpty (PaymentIntentStatus, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (PaymentIntentStatus
PaymentIntentCreated, Text
"created"),
(PaymentIntentStatus
PaymentIntentPending, Text
"pending"),
(PaymentIntentStatus
PaymentIntentComplete, Text
"complete"),
(PaymentIntentStatus
PaymentIntentExpired, Text
"expired"),
(PaymentIntentStatus
PaymentIntentFailed, Text
"failed")
]
data PaymentIntentContext
= ContextUnderpaid
| ContextPaid
| ContextOverpaid
deriving (Int -> PaymentIntentContext -> ShowS
[PaymentIntentContext] -> ShowS
PaymentIntentContext -> String
(Int -> PaymentIntentContext -> ShowS)
-> (PaymentIntentContext -> String)
-> ([PaymentIntentContext] -> ShowS)
-> Show PaymentIntentContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentIntentContext] -> ShowS
$cshowList :: [PaymentIntentContext] -> ShowS
show :: PaymentIntentContext -> String
$cshow :: PaymentIntentContext -> String
showsPrec :: Int -> PaymentIntentContext -> ShowS
$cshowsPrec :: Int -> PaymentIntentContext -> ShowS
Show, PaymentIntentContext -> PaymentIntentContext -> Bool
(PaymentIntentContext -> PaymentIntentContext -> Bool)
-> (PaymentIntentContext -> PaymentIntentContext -> Bool)
-> Eq PaymentIntentContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentIntentContext -> PaymentIntentContext -> Bool
$c/= :: PaymentIntentContext -> PaymentIntentContext -> Bool
== :: PaymentIntentContext -> PaymentIntentContext -> Bool
$c== :: PaymentIntentContext -> PaymentIntentContext -> Bool
Eq)
deriving
( Value -> Parser [PaymentIntentContext]
Value -> Parser PaymentIntentContext
(Value -> Parser PaymentIntentContext)
-> (Value -> Parser [PaymentIntentContext])
-> FromJSON PaymentIntentContext
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaymentIntentContext]
$cparseJSONList :: Value -> Parser [PaymentIntentContext]
parseJSON :: Value -> Parser PaymentIntentContext
$cparseJSON :: Value -> Parser PaymentIntentContext
FromJSON,
[PaymentIntentContext] -> Encoding
[PaymentIntentContext] -> Value
PaymentIntentContext -> Encoding
PaymentIntentContext -> Value
(PaymentIntentContext -> Value)
-> (PaymentIntentContext -> Encoding)
-> ([PaymentIntentContext] -> Value)
-> ([PaymentIntentContext] -> Encoding)
-> ToJSON PaymentIntentContext
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaymentIntentContext] -> Encoding
$ctoEncodingList :: [PaymentIntentContext] -> Encoding
toJSONList :: [PaymentIntentContext] -> Value
$ctoJSONList :: [PaymentIntentContext] -> Value
toEncoding :: PaymentIntentContext -> Encoding
$ctoEncoding :: PaymentIntentContext -> Encoding
toJSON :: PaymentIntentContext -> Value
$ctoJSON :: PaymentIntentContext -> Value
ToJSON
)
via (Autodocodec PaymentIntentContext)
instance HasCodec PaymentIntentContext where
codec :: JSONCodec PaymentIntentContext
codec =
NonEmpty (PaymentIntentContext, Text)
-> JSONCodec PaymentIntentContext
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (PaymentIntentContext, Text)
-> JSONCodec PaymentIntentContext)
-> NonEmpty (PaymentIntentContext, Text)
-> JSONCodec PaymentIntentContext
forall a b. (a -> b) -> a -> b
$
[(PaymentIntentContext, Text)]
-> NonEmpty (PaymentIntentContext, Text)
forall a. [a] -> NonEmpty a
NE.fromList
[ (PaymentIntentContext
ContextUnderpaid, Text
"underpaid"),
(PaymentIntentContext
ContextPaid, Text
"paid"),
(PaymentIntentContext
ContextOverpaid, Text
"overpaid")
]
data Address = Address
{ Address -> Maybe City
addressCity :: !(Maybe City),
Address -> Maybe ISO3166Alpha2
addressCountry :: !(Maybe ISO3166Alpha2),
Address -> Maybe AddressLine
addressLine1 :: !(Maybe AddressLine),
Address -> Maybe AddressLine
addressLine2 :: !(Maybe AddressLine),
Address -> Maybe District
addressDistrict :: !(Maybe District)
}
deriving (Address -> Address -> Bool
(Address -> Address -> Bool)
-> (Address -> Address -> Bool) -> Eq Address
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Address -> Address -> Bool
$c/= :: Address -> Address -> Bool
== :: Address -> Address -> Bool
$c== :: Address -> Address -> Bool
Eq, Int -> Address -> ShowS
[Address] -> ShowS
Address -> String
(Int -> Address -> ShowS)
-> (Address -> String) -> ([Address] -> ShowS) -> Show Address
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Address] -> ShowS
$cshowList :: [Address] -> ShowS
show :: Address -> String
$cshow :: Address -> String
showsPrec :: Int -> Address -> ShowS
$cshowsPrec :: Int -> Address -> ShowS
Show)
deriving
( [Address] -> Encoding
[Address] -> Value
Address -> Encoding
Address -> Value
(Address -> Value)
-> (Address -> Encoding)
-> ([Address] -> Value)
-> ([Address] -> Encoding)
-> ToJSON Address
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Address] -> Encoding
$ctoEncodingList :: [Address] -> Encoding
toJSONList :: [Address] -> Value
$ctoJSONList :: [Address] -> Value
toEncoding :: Address -> Encoding
$ctoEncoding :: Address -> Encoding
toJSON :: Address -> Value
$ctoJSON :: Address -> Value
ToJSON,
Value -> Parser [Address]
Value -> Parser Address
(Value -> Parser Address)
-> (Value -> Parser [Address]) -> FromJSON Address
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Address]
$cparseJSONList :: Value -> Parser [Address]
parseJSON :: Value -> Parser Address
$cparseJSON :: Value -> Parser Address
FromJSON
)
via (Autodocodec Address)
instance HasCodec Address where
codec :: JSONCodec Address
codec =
Text -> ObjectCodec Address Address -> JSONCodec Address
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"Address" (ObjectCodec Address Address -> JSONCodec Address)
-> ObjectCodec Address Address -> JSONCodec Address
forall a b. (a -> b) -> a -> b
$
Maybe City
-> Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> Address
Address
(Maybe City
-> Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> Address)
-> Codec Object Address (Maybe City)
-> Codec
Object
Address
(Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> Address)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec (Maybe City) (Maybe City)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"city" ObjectCodec (Maybe City) (Maybe City)
-> (Address -> Maybe City) -> Codec Object Address (Maybe City)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Address -> Maybe City
addressCity
Codec
Object
Address
(Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> Address)
-> Codec Object Address (Maybe ISO3166Alpha2)
-> Codec
Object
Address
(Maybe AddressLine
-> Maybe AddressLine -> Maybe District -> Address)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"country" ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
-> (Address -> Maybe ISO3166Alpha2)
-> Codec Object Address (Maybe ISO3166Alpha2)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Address -> Maybe ISO3166Alpha2
addressCountry
Codec
Object
Address
(Maybe AddressLine
-> Maybe AddressLine -> Maybe District -> Address)
-> Codec Object Address (Maybe AddressLine)
-> Codec
Object Address (Maybe AddressLine -> Maybe District -> Address)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"line1" ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
-> (Address -> Maybe AddressLine)
-> Codec Object Address (Maybe AddressLine)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Address -> Maybe AddressLine
addressLine1
Codec
Object Address (Maybe AddressLine -> Maybe District -> Address)
-> Codec Object Address (Maybe AddressLine)
-> Codec Object Address (Maybe District -> Address)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"line2" ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
-> (Address -> Maybe AddressLine)
-> Codec Object Address (Maybe AddressLine)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Address -> Maybe AddressLine
addressLine2
Codec Object Address (Maybe District -> Address)
-> Codec Object Address (Maybe District)
-> ObjectCodec Address Address
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe District) (Maybe District)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"district" ObjectCodec (Maybe District) (Maybe District)
-> (Address -> Maybe District)
-> Codec Object Address (Maybe District)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Address -> Maybe District
addressDistrict
data BankAccountType = Wire | Sen
deriving (BankAccountType -> BankAccountType -> Bool
(BankAccountType -> BankAccountType -> Bool)
-> (BankAccountType -> BankAccountType -> Bool)
-> Eq BankAccountType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BankAccountType -> BankAccountType -> Bool
$c/= :: BankAccountType -> BankAccountType -> Bool
== :: BankAccountType -> BankAccountType -> Bool
$c== :: BankAccountType -> BankAccountType -> Bool
Eq, Int -> BankAccountType -> ShowS
[BankAccountType] -> ShowS
BankAccountType -> String
(Int -> BankAccountType -> ShowS)
-> (BankAccountType -> String)
-> ([BankAccountType] -> ShowS)
-> Show BankAccountType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BankAccountType] -> ShowS
$cshowList :: [BankAccountType] -> ShowS
show :: BankAccountType -> String
$cshow :: BankAccountType -> String
showsPrec :: Int -> BankAccountType -> ShowS
$cshowsPrec :: Int -> BankAccountType -> ShowS
Show)
deriving
( Value -> Parser [BankAccountType]
Value -> Parser BankAccountType
(Value -> Parser BankAccountType)
-> (Value -> Parser [BankAccountType]) -> FromJSON BankAccountType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BankAccountType]
$cparseJSONList :: Value -> Parser [BankAccountType]
parseJSON :: Value -> Parser BankAccountType
$cparseJSON :: Value -> Parser BankAccountType
FromJSON,
[BankAccountType] -> Encoding
[BankAccountType] -> Value
BankAccountType -> Encoding
BankAccountType -> Value
(BankAccountType -> Value)
-> (BankAccountType -> Encoding)
-> ([BankAccountType] -> Value)
-> ([BankAccountType] -> Encoding)
-> ToJSON BankAccountType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BankAccountType] -> Encoding
$ctoEncodingList :: [BankAccountType] -> Encoding
toJSONList :: [BankAccountType] -> Value
$ctoJSONList :: [BankAccountType] -> Value
toEncoding :: BankAccountType -> Encoding
$ctoEncoding :: BankAccountType -> Encoding
toJSON :: BankAccountType -> Value
$ctoJSON :: BankAccountType -> Value
ToJSON
)
via (Autodocodec BankAccountType)
instance HasCodec BankAccountType where
codec :: JSONCodec BankAccountType
codec = NonEmpty (BankAccountType, Text) -> JSONCodec BankAccountType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (BankAccountType, Text) -> JSONCodec BankAccountType)
-> NonEmpty (BankAccountType, Text) -> JSONCodec BankAccountType
forall a b. (a -> b) -> a -> b
$ [(BankAccountType, Text)] -> NonEmpty (BankAccountType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(BankAccountType
Wire, Text
"wire"), (BankAccountType
Sen, Text
"sen")]
data ACHBankAccountType = RetailType | BusinessType
deriving (ACHBankAccountType -> ACHBankAccountType -> Bool
(ACHBankAccountType -> ACHBankAccountType -> Bool)
-> (ACHBankAccountType -> ACHBankAccountType -> Bool)
-> Eq ACHBankAccountType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ACHBankAccountType -> ACHBankAccountType -> Bool
$c/= :: ACHBankAccountType -> ACHBankAccountType -> Bool
== :: ACHBankAccountType -> ACHBankAccountType -> Bool
$c== :: ACHBankAccountType -> ACHBankAccountType -> Bool
Eq, Int -> ACHBankAccountType -> ShowS
[ACHBankAccountType] -> ShowS
ACHBankAccountType -> String
(Int -> ACHBankAccountType -> ShowS)
-> (ACHBankAccountType -> String)
-> ([ACHBankAccountType] -> ShowS)
-> Show ACHBankAccountType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ACHBankAccountType] -> ShowS
$cshowList :: [ACHBankAccountType] -> ShowS
show :: ACHBankAccountType -> String
$cshow :: ACHBankAccountType -> String
showsPrec :: Int -> ACHBankAccountType -> ShowS
$cshowsPrec :: Int -> ACHBankAccountType -> ShowS
Show)
deriving
( Value -> Parser [ACHBankAccountType]
Value -> Parser ACHBankAccountType
(Value -> Parser ACHBankAccountType)
-> (Value -> Parser [ACHBankAccountType])
-> FromJSON ACHBankAccountType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ACHBankAccountType]
$cparseJSONList :: Value -> Parser [ACHBankAccountType]
parseJSON :: Value -> Parser ACHBankAccountType
$cparseJSON :: Value -> Parser ACHBankAccountType
FromJSON,
[ACHBankAccountType] -> Encoding
[ACHBankAccountType] -> Value
ACHBankAccountType -> Encoding
ACHBankAccountType -> Value
(ACHBankAccountType -> Value)
-> (ACHBankAccountType -> Encoding)
-> ([ACHBankAccountType] -> Value)
-> ([ACHBankAccountType] -> Encoding)
-> ToJSON ACHBankAccountType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ACHBankAccountType] -> Encoding
$ctoEncodingList :: [ACHBankAccountType] -> Encoding
toJSONList :: [ACHBankAccountType] -> Value
$ctoJSONList :: [ACHBankAccountType] -> Value
toEncoding :: ACHBankAccountType -> Encoding
$ctoEncoding :: ACHBankAccountType -> Encoding
toJSON :: ACHBankAccountType -> Value
$ctoJSON :: ACHBankAccountType -> Value
ToJSON
)
via (Autodocodec ACHBankAccountType)
instance HasCodec ACHBankAccountType where
codec :: JSONCodec ACHBankAccountType
codec = NonEmpty (ACHBankAccountType, Text) -> JSONCodec ACHBankAccountType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (ACHBankAccountType, Text)
-> JSONCodec ACHBankAccountType)
-> NonEmpty (ACHBankAccountType, Text)
-> JSONCodec ACHBankAccountType
forall a b. (a -> b) -> a -> b
$ [(ACHBankAccountType, Text)] -> NonEmpty (ACHBankAccountType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(ACHBankAccountType
RetailType, Text
"retail"), (ACHBankAccountType
BusinessType, Text
"business")]
data DestinationBankAccount = DestinationBankAccount
{ DestinationBankAccount -> BankAccountType
destinationBankAccountType :: !BankAccountType,
DestinationBankAccount -> UUID
destinationBankAccountId :: !UUID,
DestinationBankAccount -> Maybe Text
destinationBankAccountName :: !(Maybe Text)
}
deriving (DestinationBankAccount -> DestinationBankAccount -> Bool
(DestinationBankAccount -> DestinationBankAccount -> Bool)
-> (DestinationBankAccount -> DestinationBankAccount -> Bool)
-> Eq DestinationBankAccount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DestinationBankAccount -> DestinationBankAccount -> Bool
$c/= :: DestinationBankAccount -> DestinationBankAccount -> Bool
== :: DestinationBankAccount -> DestinationBankAccount -> Bool
$c== :: DestinationBankAccount -> DestinationBankAccount -> Bool
Eq, Int -> DestinationBankAccount -> ShowS
[DestinationBankAccount] -> ShowS
DestinationBankAccount -> String
(Int -> DestinationBankAccount -> ShowS)
-> (DestinationBankAccount -> String)
-> ([DestinationBankAccount] -> ShowS)
-> Show DestinationBankAccount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DestinationBankAccount] -> ShowS
$cshowList :: [DestinationBankAccount] -> ShowS
show :: DestinationBankAccount -> String
$cshow :: DestinationBankAccount -> String
showsPrec :: Int -> DestinationBankAccount -> ShowS
$cshowsPrec :: Int -> DestinationBankAccount -> ShowS
Show)
deriving
( [DestinationBankAccount] -> Encoding
[DestinationBankAccount] -> Value
DestinationBankAccount -> Encoding
DestinationBankAccount -> Value
(DestinationBankAccount -> Value)
-> (DestinationBankAccount -> Encoding)
-> ([DestinationBankAccount] -> Value)
-> ([DestinationBankAccount] -> Encoding)
-> ToJSON DestinationBankAccount
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DestinationBankAccount] -> Encoding
$ctoEncodingList :: [DestinationBankAccount] -> Encoding
toJSONList :: [DestinationBankAccount] -> Value
$ctoJSONList :: [DestinationBankAccount] -> Value
toEncoding :: DestinationBankAccount -> Encoding
$ctoEncoding :: DestinationBankAccount -> Encoding
toJSON :: DestinationBankAccount -> Value
$ctoJSON :: DestinationBankAccount -> Value
ToJSON,
Value -> Parser [DestinationBankAccount]
Value -> Parser DestinationBankAccount
(Value -> Parser DestinationBankAccount)
-> (Value -> Parser [DestinationBankAccount])
-> FromJSON DestinationBankAccount
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DestinationBankAccount]
$cparseJSONList :: Value -> Parser [DestinationBankAccount]
parseJSON :: Value -> Parser DestinationBankAccount
$cparseJSON :: Value -> Parser DestinationBankAccount
FromJSON
)
via (Autodocodec DestinationBankAccount)
instance HasCodec DestinationBankAccount where
codec :: JSONCodec DestinationBankAccount
codec =
Text
-> ObjectCodec DestinationBankAccount DestinationBankAccount
-> JSONCodec DestinationBankAccount
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"DestinationBankAccount" (ObjectCodec DestinationBankAccount DestinationBankAccount
-> JSONCodec DestinationBankAccount)
-> ObjectCodec DestinationBankAccount DestinationBankAccount
-> JSONCodec DestinationBankAccount
forall a b. (a -> b) -> a -> b
$
BankAccountType -> UUID -> Maybe Text -> DestinationBankAccount
DestinationBankAccount
(BankAccountType -> UUID -> Maybe Text -> DestinationBankAccount)
-> Codec Object DestinationBankAccount BankAccountType
-> Codec
Object
DestinationBankAccount
(UUID -> Maybe Text -> DestinationBankAccount)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec BankAccountType BankAccountType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec BankAccountType BankAccountType
-> (DestinationBankAccount -> BankAccountType)
-> Codec Object DestinationBankAccount BankAccountType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationBankAccount -> BankAccountType
destinationBankAccountType
Codec
Object
DestinationBankAccount
(UUID -> Maybe Text -> DestinationBankAccount)
-> Codec Object DestinationBankAccount UUID
-> Codec
Object
DestinationBankAccount
(Maybe Text -> DestinationBankAccount)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec UUID UUID
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"id" ObjectCodec UUID UUID
-> (DestinationBankAccount -> UUID)
-> Codec Object DestinationBankAccount UUID
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationBankAccount -> UUID
destinationBankAccountId
Codec
Object
DestinationBankAccount
(Maybe Text -> DestinationBankAccount)
-> Codec Object DestinationBankAccount (Maybe Text)
-> ObjectCodec DestinationBankAccount DestinationBankAccount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"name" ObjectCodec (Maybe Text) (Maybe Text)
-> (DestinationBankAccount -> Maybe Text)
-> Codec Object DestinationBankAccount (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= DestinationBankAccount -> Maybe Text
destinationBankAccountName
data SupportedCurrencies = USD | EUR | BTC | ETH
deriving (SupportedCurrencies -> SupportedCurrencies -> Bool
(SupportedCurrencies -> SupportedCurrencies -> Bool)
-> (SupportedCurrencies -> SupportedCurrencies -> Bool)
-> Eq SupportedCurrencies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SupportedCurrencies -> SupportedCurrencies -> Bool
$c/= :: SupportedCurrencies -> SupportedCurrencies -> Bool
== :: SupportedCurrencies -> SupportedCurrencies -> Bool
$c== :: SupportedCurrencies -> SupportedCurrencies -> Bool
Eq, Int -> SupportedCurrencies -> ShowS
[SupportedCurrencies] -> ShowS
SupportedCurrencies -> String
(Int -> SupportedCurrencies -> ShowS)
-> (SupportedCurrencies -> String)
-> ([SupportedCurrencies] -> ShowS)
-> Show SupportedCurrencies
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SupportedCurrencies] -> ShowS
$cshowList :: [SupportedCurrencies] -> ShowS
show :: SupportedCurrencies -> String
$cshow :: SupportedCurrencies -> String
showsPrec :: Int -> SupportedCurrencies -> ShowS
$cshowsPrec :: Int -> SupportedCurrencies -> ShowS
Show, Int -> SupportedCurrencies
SupportedCurrencies -> Int
SupportedCurrencies -> [SupportedCurrencies]
SupportedCurrencies -> SupportedCurrencies
SupportedCurrencies -> SupportedCurrencies -> [SupportedCurrencies]
SupportedCurrencies
-> SupportedCurrencies
-> SupportedCurrencies
-> [SupportedCurrencies]
(SupportedCurrencies -> SupportedCurrencies)
-> (SupportedCurrencies -> SupportedCurrencies)
-> (Int -> SupportedCurrencies)
-> (SupportedCurrencies -> Int)
-> (SupportedCurrencies -> [SupportedCurrencies])
-> (SupportedCurrencies
-> SupportedCurrencies -> [SupportedCurrencies])
-> (SupportedCurrencies
-> SupportedCurrencies -> [SupportedCurrencies])
-> (SupportedCurrencies
-> SupportedCurrencies
-> SupportedCurrencies
-> [SupportedCurrencies])
-> Enum SupportedCurrencies
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SupportedCurrencies
-> SupportedCurrencies
-> SupportedCurrencies
-> [SupportedCurrencies]
$cenumFromThenTo :: SupportedCurrencies
-> SupportedCurrencies
-> SupportedCurrencies
-> [SupportedCurrencies]
enumFromTo :: SupportedCurrencies -> SupportedCurrencies -> [SupportedCurrencies]
$cenumFromTo :: SupportedCurrencies -> SupportedCurrencies -> [SupportedCurrencies]
enumFromThen :: SupportedCurrencies -> SupportedCurrencies -> [SupportedCurrencies]
$cenumFromThen :: SupportedCurrencies -> SupportedCurrencies -> [SupportedCurrencies]
enumFrom :: SupportedCurrencies -> [SupportedCurrencies]
$cenumFrom :: SupportedCurrencies -> [SupportedCurrencies]
fromEnum :: SupportedCurrencies -> Int
$cfromEnum :: SupportedCurrencies -> Int
toEnum :: Int -> SupportedCurrencies
$ctoEnum :: Int -> SupportedCurrencies
pred :: SupportedCurrencies -> SupportedCurrencies
$cpred :: SupportedCurrencies -> SupportedCurrencies
succ :: SupportedCurrencies -> SupportedCurrencies
$csucc :: SupportedCurrencies -> SupportedCurrencies
Enum, SupportedCurrencies
SupportedCurrencies
-> SupportedCurrencies -> Bounded SupportedCurrencies
forall a. a -> a -> Bounded a
maxBound :: SupportedCurrencies
$cmaxBound :: SupportedCurrencies
minBound :: SupportedCurrencies
$cminBound :: SupportedCurrencies
Bounded)
deriving
( Value -> Parser [SupportedCurrencies]
Value -> Parser SupportedCurrencies
(Value -> Parser SupportedCurrencies)
-> (Value -> Parser [SupportedCurrencies])
-> FromJSON SupportedCurrencies
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [SupportedCurrencies]
$cparseJSONList :: Value -> Parser [SupportedCurrencies]
parseJSON :: Value -> Parser SupportedCurrencies
$cparseJSON :: Value -> Parser SupportedCurrencies
FromJSON,
[SupportedCurrencies] -> Encoding
[SupportedCurrencies] -> Value
SupportedCurrencies -> Encoding
SupportedCurrencies -> Value
(SupportedCurrencies -> Value)
-> (SupportedCurrencies -> Encoding)
-> ([SupportedCurrencies] -> Value)
-> ([SupportedCurrencies] -> Encoding)
-> ToJSON SupportedCurrencies
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SupportedCurrencies] -> Encoding
$ctoEncodingList :: [SupportedCurrencies] -> Encoding
toJSONList :: [SupportedCurrencies] -> Value
$ctoJSONList :: [SupportedCurrencies] -> Value
toEncoding :: SupportedCurrencies -> Encoding
$ctoEncoding :: SupportedCurrencies -> Encoding
toJSON :: SupportedCurrencies -> Value
$ctoJSON :: SupportedCurrencies -> Value
ToJSON
)
via (Autodocodec SupportedCurrencies)
instance HasCodec SupportedCurrencies where
codec :: JSONCodec SupportedCurrencies
codec = JSONCodec SupportedCurrencies
forall enum.
(Show enum, Eq enum, Enum enum, Bounded enum) =>
JSONCodec enum
shownBoundedEnumCodec
newtype Amount = Amount
{ Amount -> Text
unAmount :: Text
}
deriving (Amount -> Amount -> Bool
(Amount -> Amount -> Bool)
-> (Amount -> Amount -> Bool) -> Eq Amount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Amount -> Amount -> Bool
$c/= :: Amount -> Amount -> Bool
== :: Amount -> Amount -> Bool
$c== :: Amount -> Amount -> Bool
Eq, Int -> Amount -> ShowS
[Amount] -> ShowS
Amount -> String
(Int -> Amount -> ShowS)
-> (Amount -> String) -> ([Amount] -> ShowS) -> Show Amount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Amount] -> ShowS
$cshowList :: [Amount] -> ShowS
show :: Amount -> String
$cshow :: Amount -> String
showsPrec :: Int -> Amount -> ShowS
$cshowsPrec :: Int -> Amount -> ShowS
Show, [Amount] -> Encoding
[Amount] -> Value
Amount -> Encoding
Amount -> Value
(Amount -> Value)
-> (Amount -> Encoding)
-> ([Amount] -> Value)
-> ([Amount] -> Encoding)
-> ToJSON Amount
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Amount] -> Encoding
$ctoEncodingList :: [Amount] -> Encoding
toJSONList :: [Amount] -> Value
$ctoJSONList :: [Amount] -> Value
toEncoding :: Amount -> Encoding
$ctoEncoding :: Amount -> Encoding
toJSON :: Amount -> Value
$ctoJSON :: Amount -> Value
ToJSON, Value -> Parser [Amount]
Value -> Parser Amount
(Value -> Parser Amount)
-> (Value -> Parser [Amount]) -> FromJSON Amount
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Amount]
$cparseJSONList :: Value -> Parser [Amount]
parseJSON :: Value -> Parser Amount
$cparseJSON :: Value -> Parser Amount
FromJSON)
instance HasCodec Amount where
codec :: JSONCodec Amount
codec = (Text -> Amount)
-> (Amount -> Text) -> Codec Value Text Text -> JSONCodec Amount
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> Amount
Amount Amount -> Text
unAmount Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
data BlockchainFeeType = BlockchainLeaseFee | TotalPaymentFees
deriving (BlockchainFeeType -> BlockchainFeeType -> Bool
(BlockchainFeeType -> BlockchainFeeType -> Bool)
-> (BlockchainFeeType -> BlockchainFeeType -> Bool)
-> Eq BlockchainFeeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockchainFeeType -> BlockchainFeeType -> Bool
$c/= :: BlockchainFeeType -> BlockchainFeeType -> Bool
== :: BlockchainFeeType -> BlockchainFeeType -> Bool
$c== :: BlockchainFeeType -> BlockchainFeeType -> Bool
Eq, Int -> BlockchainFeeType -> ShowS
[BlockchainFeeType] -> ShowS
BlockchainFeeType -> String
(Int -> BlockchainFeeType -> ShowS)
-> (BlockchainFeeType -> String)
-> ([BlockchainFeeType] -> ShowS)
-> Show BlockchainFeeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockchainFeeType] -> ShowS
$cshowList :: [BlockchainFeeType] -> ShowS
show :: BlockchainFeeType -> String
$cshow :: BlockchainFeeType -> String
showsPrec :: Int -> BlockchainFeeType -> ShowS
$cshowsPrec :: Int -> BlockchainFeeType -> ShowS
Show)
deriving
( Value -> Parser [BlockchainFeeType]
Value -> Parser BlockchainFeeType
(Value -> Parser BlockchainFeeType)
-> (Value -> Parser [BlockchainFeeType])
-> FromJSON BlockchainFeeType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BlockchainFeeType]
$cparseJSONList :: Value -> Parser [BlockchainFeeType]
parseJSON :: Value -> Parser BlockchainFeeType
$cparseJSON :: Value -> Parser BlockchainFeeType
FromJSON,
[BlockchainFeeType] -> Encoding
[BlockchainFeeType] -> Value
BlockchainFeeType -> Encoding
BlockchainFeeType -> Value
(BlockchainFeeType -> Value)
-> (BlockchainFeeType -> Encoding)
-> ([BlockchainFeeType] -> Value)
-> ([BlockchainFeeType] -> Encoding)
-> ToJSON BlockchainFeeType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BlockchainFeeType] -> Encoding
$ctoEncodingList :: [BlockchainFeeType] -> Encoding
toJSONList :: [BlockchainFeeType] -> Value
$ctoJSONList :: [BlockchainFeeType] -> Value
toEncoding :: BlockchainFeeType -> Encoding
$ctoEncoding :: BlockchainFeeType -> Encoding
toJSON :: BlockchainFeeType -> Value
$ctoJSON :: BlockchainFeeType -> Value
ToJSON
)
via (Autodocodec BlockchainFeeType)
instance HasCodec BlockchainFeeType where
codec :: JSONCodec BlockchainFeeType
codec = NonEmpty (BlockchainFeeType, Text) -> JSONCodec BlockchainFeeType
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (BlockchainFeeType, Text) -> JSONCodec BlockchainFeeType)
-> NonEmpty (BlockchainFeeType, Text)
-> JSONCodec BlockchainFeeType
forall a b. (a -> b) -> a -> b
$ [(BlockchainFeeType, Text)] -> NonEmpty (BlockchainFeeType, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(BlockchainFeeType
BlockchainLeaseFee, Text
"blockChainLeaseFee"), (BlockchainFeeType
TotalPaymentFees, Text
"totalPaymentFees")]
data BlockchainFeeMoneyAmount = BlockchainFeeMoneyAmount
{ BlockchainFeeMoneyAmount -> BlockchainFeeType
blockchainFeeMoneyAmountType :: !BlockchainFeeType,
BlockchainFeeMoneyAmount -> Amount
blockchainFeeMoneyAmountAmount :: !Amount,
BlockchainFeeMoneyAmount -> SupportedCurrencies
blockchainFeeMoneyAmountCurrency :: !SupportedCurrencies
}
deriving (BlockchainFeeMoneyAmount -> BlockchainFeeMoneyAmount -> Bool
(BlockchainFeeMoneyAmount -> BlockchainFeeMoneyAmount -> Bool)
-> (BlockchainFeeMoneyAmount -> BlockchainFeeMoneyAmount -> Bool)
-> Eq BlockchainFeeMoneyAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockchainFeeMoneyAmount -> BlockchainFeeMoneyAmount -> Bool
$c/= :: BlockchainFeeMoneyAmount -> BlockchainFeeMoneyAmount -> Bool
== :: BlockchainFeeMoneyAmount -> BlockchainFeeMoneyAmount -> Bool
$c== :: BlockchainFeeMoneyAmount -> BlockchainFeeMoneyAmount -> Bool
Eq, Int -> BlockchainFeeMoneyAmount -> ShowS
[BlockchainFeeMoneyAmount] -> ShowS
BlockchainFeeMoneyAmount -> String
(Int -> BlockchainFeeMoneyAmount -> ShowS)
-> (BlockchainFeeMoneyAmount -> String)
-> ([BlockchainFeeMoneyAmount] -> ShowS)
-> Show BlockchainFeeMoneyAmount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockchainFeeMoneyAmount] -> ShowS
$cshowList :: [BlockchainFeeMoneyAmount] -> ShowS
show :: BlockchainFeeMoneyAmount -> String
$cshow :: BlockchainFeeMoneyAmount -> String
showsPrec :: Int -> BlockchainFeeMoneyAmount -> ShowS
$cshowsPrec :: Int -> BlockchainFeeMoneyAmount -> ShowS
Show, (forall x.
BlockchainFeeMoneyAmount -> Rep BlockchainFeeMoneyAmount x)
-> (forall x.
Rep BlockchainFeeMoneyAmount x -> BlockchainFeeMoneyAmount)
-> Generic BlockchainFeeMoneyAmount
forall x.
Rep BlockchainFeeMoneyAmount x -> BlockchainFeeMoneyAmount
forall x.
BlockchainFeeMoneyAmount -> Rep BlockchainFeeMoneyAmount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BlockchainFeeMoneyAmount x -> BlockchainFeeMoneyAmount
$cfrom :: forall x.
BlockchainFeeMoneyAmount -> Rep BlockchainFeeMoneyAmount x
Generic)
deriving
( [BlockchainFeeMoneyAmount] -> Encoding
[BlockchainFeeMoneyAmount] -> Value
BlockchainFeeMoneyAmount -> Encoding
BlockchainFeeMoneyAmount -> Value
(BlockchainFeeMoneyAmount -> Value)
-> (BlockchainFeeMoneyAmount -> Encoding)
-> ([BlockchainFeeMoneyAmount] -> Value)
-> ([BlockchainFeeMoneyAmount] -> Encoding)
-> ToJSON BlockchainFeeMoneyAmount
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BlockchainFeeMoneyAmount] -> Encoding
$ctoEncodingList :: [BlockchainFeeMoneyAmount] -> Encoding
toJSONList :: [BlockchainFeeMoneyAmount] -> Value
$ctoJSONList :: [BlockchainFeeMoneyAmount] -> Value
toEncoding :: BlockchainFeeMoneyAmount -> Encoding
$ctoEncoding :: BlockchainFeeMoneyAmount -> Encoding
toJSON :: BlockchainFeeMoneyAmount -> Value
$ctoJSON :: BlockchainFeeMoneyAmount -> Value
ToJSON,
Value -> Parser [BlockchainFeeMoneyAmount]
Value -> Parser BlockchainFeeMoneyAmount
(Value -> Parser BlockchainFeeMoneyAmount)
-> (Value -> Parser [BlockchainFeeMoneyAmount])
-> FromJSON BlockchainFeeMoneyAmount
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BlockchainFeeMoneyAmount]
$cparseJSONList :: Value -> Parser [BlockchainFeeMoneyAmount]
parseJSON :: Value -> Parser BlockchainFeeMoneyAmount
$cparseJSON :: Value -> Parser BlockchainFeeMoneyAmount
FromJSON
)
via (Autodocodec BlockchainFeeMoneyAmount)
instance HasCodec BlockchainFeeMoneyAmount where
codec :: JSONCodec BlockchainFeeMoneyAmount
codec =
Text
-> ObjectCodec BlockchainFeeMoneyAmount BlockchainFeeMoneyAmount
-> JSONCodec BlockchainFeeMoneyAmount
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BlockchainFeeMoneyAmount" (ObjectCodec BlockchainFeeMoneyAmount BlockchainFeeMoneyAmount
-> JSONCodec BlockchainFeeMoneyAmount)
-> ObjectCodec BlockchainFeeMoneyAmount BlockchainFeeMoneyAmount
-> JSONCodec BlockchainFeeMoneyAmount
forall a b. (a -> b) -> a -> b
$
BlockchainFeeType
-> Amount -> SupportedCurrencies -> BlockchainFeeMoneyAmount
BlockchainFeeMoneyAmount
(BlockchainFeeType
-> Amount -> SupportedCurrencies -> BlockchainFeeMoneyAmount)
-> Codec Object BlockchainFeeMoneyAmount BlockchainFeeType
-> Codec
Object
BlockchainFeeMoneyAmount
(Amount -> SupportedCurrencies -> BlockchainFeeMoneyAmount)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec BlockchainFeeType BlockchainFeeType
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec BlockchainFeeType BlockchainFeeType
-> (BlockchainFeeMoneyAmount -> BlockchainFeeType)
-> Codec Object BlockchainFeeMoneyAmount BlockchainFeeType
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BlockchainFeeMoneyAmount -> BlockchainFeeType
blockchainFeeMoneyAmountType
Codec
Object
BlockchainFeeMoneyAmount
(Amount -> SupportedCurrencies -> BlockchainFeeMoneyAmount)
-> Codec Object BlockchainFeeMoneyAmount Amount
-> Codec
Object
BlockchainFeeMoneyAmount
(SupportedCurrencies -> BlockchainFeeMoneyAmount)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Amount Amount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec Amount Amount
-> (BlockchainFeeMoneyAmount -> Amount)
-> Codec Object BlockchainFeeMoneyAmount Amount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BlockchainFeeMoneyAmount -> Amount
blockchainFeeMoneyAmountAmount
Codec
Object
BlockchainFeeMoneyAmount
(SupportedCurrencies -> BlockchainFeeMoneyAmount)
-> Codec Object BlockchainFeeMoneyAmount SupportedCurrencies
-> ObjectCodec BlockchainFeeMoneyAmount BlockchainFeeMoneyAmount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (BlockchainFeeMoneyAmount -> SupportedCurrencies)
-> Codec Object BlockchainFeeMoneyAmount SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BlockchainFeeMoneyAmount -> SupportedCurrencies
blockchainFeeMoneyAmountCurrency
data MoneyAmount = MoneyAmount
{ MoneyAmount -> Amount
moneyAmountAmount :: !Amount,
MoneyAmount -> SupportedCurrencies
moneyAmountCurrency :: !SupportedCurrencies
}
deriving (MoneyAmount -> MoneyAmount -> Bool
(MoneyAmount -> MoneyAmount -> Bool)
-> (MoneyAmount -> MoneyAmount -> Bool) -> Eq MoneyAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MoneyAmount -> MoneyAmount -> Bool
$c/= :: MoneyAmount -> MoneyAmount -> Bool
== :: MoneyAmount -> MoneyAmount -> Bool
$c== :: MoneyAmount -> MoneyAmount -> Bool
Eq, Int -> MoneyAmount -> ShowS
[MoneyAmount] -> ShowS
MoneyAmount -> String
(Int -> MoneyAmount -> ShowS)
-> (MoneyAmount -> String)
-> ([MoneyAmount] -> ShowS)
-> Show MoneyAmount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MoneyAmount] -> ShowS
$cshowList :: [MoneyAmount] -> ShowS
show :: MoneyAmount -> String
$cshow :: MoneyAmount -> String
showsPrec :: Int -> MoneyAmount -> ShowS
$cshowsPrec :: Int -> MoneyAmount -> ShowS
Show, (forall x. MoneyAmount -> Rep MoneyAmount x)
-> (forall x. Rep MoneyAmount x -> MoneyAmount)
-> Generic MoneyAmount
forall x. Rep MoneyAmount x -> MoneyAmount
forall x. MoneyAmount -> Rep MoneyAmount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MoneyAmount x -> MoneyAmount
$cfrom :: forall x. MoneyAmount -> Rep MoneyAmount x
Generic)
deriving
( [MoneyAmount] -> Encoding
[MoneyAmount] -> Value
MoneyAmount -> Encoding
MoneyAmount -> Value
(MoneyAmount -> Value)
-> (MoneyAmount -> Encoding)
-> ([MoneyAmount] -> Value)
-> ([MoneyAmount] -> Encoding)
-> ToJSON MoneyAmount
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MoneyAmount] -> Encoding
$ctoEncodingList :: [MoneyAmount] -> Encoding
toJSONList :: [MoneyAmount] -> Value
$ctoJSONList :: [MoneyAmount] -> Value
toEncoding :: MoneyAmount -> Encoding
$ctoEncoding :: MoneyAmount -> Encoding
toJSON :: MoneyAmount -> Value
$ctoJSON :: MoneyAmount -> Value
ToJSON,
Value -> Parser [MoneyAmount]
Value -> Parser MoneyAmount
(Value -> Parser MoneyAmount)
-> (Value -> Parser [MoneyAmount]) -> FromJSON MoneyAmount
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MoneyAmount]
$cparseJSONList :: Value -> Parser [MoneyAmount]
parseJSON :: Value -> Parser MoneyAmount
$cparseJSON :: Value -> Parser MoneyAmount
FromJSON
)
via (Autodocodec MoneyAmount)
instance HasCodec MoneyAmount where
codec :: JSONCodec MoneyAmount
codec =
Text
-> ObjectCodec MoneyAmount MoneyAmount -> JSONCodec MoneyAmount
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"MoneyAmount" (ObjectCodec MoneyAmount MoneyAmount -> JSONCodec MoneyAmount)
-> ObjectCodec MoneyAmount MoneyAmount -> JSONCodec MoneyAmount
forall a b. (a -> b) -> a -> b
$
Amount -> SupportedCurrencies -> MoneyAmount
MoneyAmount
(Amount -> SupportedCurrencies -> MoneyAmount)
-> Codec Object MoneyAmount Amount
-> Codec Object MoneyAmount (SupportedCurrencies -> MoneyAmount)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Amount Amount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec Amount Amount
-> (MoneyAmount -> Amount) -> Codec Object MoneyAmount Amount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MoneyAmount -> Amount
moneyAmountAmount
Codec Object MoneyAmount (SupportedCurrencies -> MoneyAmount)
-> Codec Object MoneyAmount SupportedCurrencies
-> ObjectCodec MoneyAmount MoneyAmount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (MoneyAmount -> SupportedCurrencies)
-> Codec Object MoneyAmount SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= MoneyAmount -> SupportedCurrencies
moneyAmountCurrency
data TransferFeeAmount = TransferFeeAmount
{ TransferFeeAmount -> Amount
transferFeeAmountAmount :: !Amount,
TransferFeeAmount -> SupportedCurrencies
transferFeeAmountCurrency :: !SupportedCurrencies,
TransferFeeAmount -> Text
transferFeeAmountType :: !Text
}
deriving (TransferFeeAmount -> TransferFeeAmount -> Bool
(TransferFeeAmount -> TransferFeeAmount -> Bool)
-> (TransferFeeAmount -> TransferFeeAmount -> Bool)
-> Eq TransferFeeAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferFeeAmount -> TransferFeeAmount -> Bool
$c/= :: TransferFeeAmount -> TransferFeeAmount -> Bool
== :: TransferFeeAmount -> TransferFeeAmount -> Bool
$c== :: TransferFeeAmount -> TransferFeeAmount -> Bool
Eq, Int -> TransferFeeAmount -> ShowS
[TransferFeeAmount] -> ShowS
TransferFeeAmount -> String
(Int -> TransferFeeAmount -> ShowS)
-> (TransferFeeAmount -> String)
-> ([TransferFeeAmount] -> ShowS)
-> Show TransferFeeAmount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferFeeAmount] -> ShowS
$cshowList :: [TransferFeeAmount] -> ShowS
show :: TransferFeeAmount -> String
$cshow :: TransferFeeAmount -> String
showsPrec :: Int -> TransferFeeAmount -> ShowS
$cshowsPrec :: Int -> TransferFeeAmount -> ShowS
Show, (forall x. TransferFeeAmount -> Rep TransferFeeAmount x)
-> (forall x. Rep TransferFeeAmount x -> TransferFeeAmount)
-> Generic TransferFeeAmount
forall x. Rep TransferFeeAmount x -> TransferFeeAmount
forall x. TransferFeeAmount -> Rep TransferFeeAmount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransferFeeAmount x -> TransferFeeAmount
$cfrom :: forall x. TransferFeeAmount -> Rep TransferFeeAmount x
Generic)
deriving
( [TransferFeeAmount] -> Encoding
[TransferFeeAmount] -> Value
TransferFeeAmount -> Encoding
TransferFeeAmount -> Value
(TransferFeeAmount -> Value)
-> (TransferFeeAmount -> Encoding)
-> ([TransferFeeAmount] -> Value)
-> ([TransferFeeAmount] -> Encoding)
-> ToJSON TransferFeeAmount
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TransferFeeAmount] -> Encoding
$ctoEncodingList :: [TransferFeeAmount] -> Encoding
toJSONList :: [TransferFeeAmount] -> Value
$ctoJSONList :: [TransferFeeAmount] -> Value
toEncoding :: TransferFeeAmount -> Encoding
$ctoEncoding :: TransferFeeAmount -> Encoding
toJSON :: TransferFeeAmount -> Value
$ctoJSON :: TransferFeeAmount -> Value
ToJSON,
Value -> Parser [TransferFeeAmount]
Value -> Parser TransferFeeAmount
(Value -> Parser TransferFeeAmount)
-> (Value -> Parser [TransferFeeAmount])
-> FromJSON TransferFeeAmount
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TransferFeeAmount]
$cparseJSONList :: Value -> Parser [TransferFeeAmount]
parseJSON :: Value -> Parser TransferFeeAmount
$cparseJSON :: Value -> Parser TransferFeeAmount
FromJSON
)
via (Autodocodec TransferFeeAmount)
instance HasCodec TransferFeeAmount where
codec :: JSONCodec TransferFeeAmount
codec =
Text
-> ObjectCodec TransferFeeAmount TransferFeeAmount
-> JSONCodec TransferFeeAmount
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"TransferFeeAmount" (ObjectCodec TransferFeeAmount TransferFeeAmount
-> JSONCodec TransferFeeAmount)
-> ObjectCodec TransferFeeAmount TransferFeeAmount
-> JSONCodec TransferFeeAmount
forall a b. (a -> b) -> a -> b
$
Amount -> SupportedCurrencies -> Text -> TransferFeeAmount
TransferFeeAmount
(Amount -> SupportedCurrencies -> Text -> TransferFeeAmount)
-> Codec Object TransferFeeAmount Amount
-> Codec
Object
TransferFeeAmount
(SupportedCurrencies -> Text -> TransferFeeAmount)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Amount Amount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"amount" ObjectCodec Amount Amount
-> (TransferFeeAmount -> Amount)
-> Codec Object TransferFeeAmount Amount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferFeeAmount -> Amount
transferFeeAmountAmount
Codec
Object
TransferFeeAmount
(SupportedCurrencies -> Text -> TransferFeeAmount)
-> Codec Object TransferFeeAmount SupportedCurrencies
-> Codec Object TransferFeeAmount (Text -> TransferFeeAmount)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (TransferFeeAmount -> SupportedCurrencies)
-> Codec Object TransferFeeAmount SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferFeeAmount -> SupportedCurrencies
transferFeeAmountCurrency
Codec Object TransferFeeAmount (Text -> TransferFeeAmount)
-> Codec Object TransferFeeAmount Text
-> ObjectCodec TransferFeeAmount TransferFeeAmount
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"type" ObjectCodec Text Text
-> (TransferFeeAmount -> Text)
-> Codec Object TransferFeeAmount Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= TransferFeeAmount -> Text
transferFeeAmountType
data Decision = Approved | Denied | Review
deriving (Decision -> Decision -> Bool
(Decision -> Decision -> Bool)
-> (Decision -> Decision -> Bool) -> Eq Decision
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Decision -> Decision -> Bool
$c/= :: Decision -> Decision -> Bool
== :: Decision -> Decision -> Bool
$c== :: Decision -> Decision -> Bool
Eq, Int -> Decision -> ShowS
[Decision] -> ShowS
Decision -> String
(Int -> Decision -> ShowS)
-> (Decision -> String) -> ([Decision] -> ShowS) -> Show Decision
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Decision] -> ShowS
$cshowList :: [Decision] -> ShowS
show :: Decision -> String
$cshow :: Decision -> String
showsPrec :: Int -> Decision -> ShowS
$cshowsPrec :: Int -> Decision -> ShowS
Show, (forall x. Decision -> Rep Decision x)
-> (forall x. Rep Decision x -> Decision) -> Generic Decision
forall x. Rep Decision x -> Decision
forall x. Decision -> Rep Decision x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Decision x -> Decision
$cfrom :: forall x. Decision -> Rep Decision x
Generic)
deriving
( [Decision] -> Encoding
[Decision] -> Value
Decision -> Encoding
Decision -> Value
(Decision -> Value)
-> (Decision -> Encoding)
-> ([Decision] -> Value)
-> ([Decision] -> Encoding)
-> ToJSON Decision
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Decision] -> Encoding
$ctoEncodingList :: [Decision] -> Encoding
toJSONList :: [Decision] -> Value
$ctoJSONList :: [Decision] -> Value
toEncoding :: Decision -> Encoding
$ctoEncoding :: Decision -> Encoding
toJSON :: Decision -> Value
$ctoJSON :: Decision -> Value
ToJSON,
Value -> Parser [Decision]
Value -> Parser Decision
(Value -> Parser Decision)
-> (Value -> Parser [Decision]) -> FromJSON Decision
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Decision]
$cparseJSONList :: Value -> Parser [Decision]
parseJSON :: Value -> Parser Decision
$cparseJSON :: Value -> Parser Decision
FromJSON
)
via (Autodocodec Decision)
instance HasCodec Decision where
codec :: JSONCodec Decision
codec = NonEmpty (Decision, Text) -> JSONCodec Decision
forall constant.
Eq constant =>
NonEmpty (constant, Text) -> JSONCodec constant
stringConstCodec (NonEmpty (Decision, Text) -> JSONCodec Decision)
-> NonEmpty (Decision, Text) -> JSONCodec Decision
forall a b. (a -> b) -> a -> b
$ [(Decision, Text)] -> NonEmpty (Decision, Text)
forall a. [a] -> NonEmpty a
NE.fromList [(Decision
Approved, Text
"approved"), (Decision
Denied, Text
"denied"), (Decision
Review, Text
"review")]
data RiskEvaluation = RiskEvaluation
{ RiskEvaluation -> Decision
riskEvaluationDecision :: !Decision,
RiskEvaluation -> Text
riskEvaluationReason :: !Text
}
deriving (RiskEvaluation -> RiskEvaluation -> Bool
(RiskEvaluation -> RiskEvaluation -> Bool)
-> (RiskEvaluation -> RiskEvaluation -> Bool) -> Eq RiskEvaluation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RiskEvaluation -> RiskEvaluation -> Bool
$c/= :: RiskEvaluation -> RiskEvaluation -> Bool
== :: RiskEvaluation -> RiskEvaluation -> Bool
$c== :: RiskEvaluation -> RiskEvaluation -> Bool
Eq, Int -> RiskEvaluation -> ShowS
[RiskEvaluation] -> ShowS
RiskEvaluation -> String
(Int -> RiskEvaluation -> ShowS)
-> (RiskEvaluation -> String)
-> ([RiskEvaluation] -> ShowS)
-> Show RiskEvaluation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RiskEvaluation] -> ShowS
$cshowList :: [RiskEvaluation] -> ShowS
show :: RiskEvaluation -> String
$cshow :: RiskEvaluation -> String
showsPrec :: Int -> RiskEvaluation -> ShowS
$cshowsPrec :: Int -> RiskEvaluation -> ShowS
Show, (forall x. RiskEvaluation -> Rep RiskEvaluation x)
-> (forall x. Rep RiskEvaluation x -> RiskEvaluation)
-> Generic RiskEvaluation
forall x. Rep RiskEvaluation x -> RiskEvaluation
forall x. RiskEvaluation -> Rep RiskEvaluation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RiskEvaluation x -> RiskEvaluation
$cfrom :: forall x. RiskEvaluation -> Rep RiskEvaluation x
Generic)
deriving
( [RiskEvaluation] -> Encoding
[RiskEvaluation] -> Value
RiskEvaluation -> Encoding
RiskEvaluation -> Value
(RiskEvaluation -> Value)
-> (RiskEvaluation -> Encoding)
-> ([RiskEvaluation] -> Value)
-> ([RiskEvaluation] -> Encoding)
-> ToJSON RiskEvaluation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RiskEvaluation] -> Encoding
$ctoEncodingList :: [RiskEvaluation] -> Encoding
toJSONList :: [RiskEvaluation] -> Value
$ctoJSONList :: [RiskEvaluation] -> Value
toEncoding :: RiskEvaluation -> Encoding
$ctoEncoding :: RiskEvaluation -> Encoding
toJSON :: RiskEvaluation -> Value
$ctoJSON :: RiskEvaluation -> Value
ToJSON,
Value -> Parser [RiskEvaluation]
Value -> Parser RiskEvaluation
(Value -> Parser RiskEvaluation)
-> (Value -> Parser [RiskEvaluation]) -> FromJSON RiskEvaluation
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RiskEvaluation]
$cparseJSONList :: Value -> Parser [RiskEvaluation]
parseJSON :: Value -> Parser RiskEvaluation
$cparseJSON :: Value -> Parser RiskEvaluation
FromJSON
)
via (Autodocodec RiskEvaluation)
instance HasCodec RiskEvaluation where
codec :: JSONCodec RiskEvaluation
codec =
Text
-> ObjectCodec RiskEvaluation RiskEvaluation
-> JSONCodec RiskEvaluation
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"RiskEvaluation" (ObjectCodec RiskEvaluation RiskEvaluation
-> JSONCodec RiskEvaluation)
-> ObjectCodec RiskEvaluation RiskEvaluation
-> JSONCodec RiskEvaluation
forall a b. (a -> b) -> a -> b
$
Decision -> Text -> RiskEvaluation
RiskEvaluation
(Decision -> Text -> RiskEvaluation)
-> Codec Object RiskEvaluation Decision
-> Codec Object RiskEvaluation (Text -> RiskEvaluation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Decision Decision
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"decision" ObjectCodec Decision Decision
-> (RiskEvaluation -> Decision)
-> Codec Object RiskEvaluation Decision
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RiskEvaluation -> Decision
riskEvaluationDecision
Codec Object RiskEvaluation (Text -> RiskEvaluation)
-> Codec Object RiskEvaluation Text
-> ObjectCodec RiskEvaluation RiskEvaluation
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"reason" ObjectCodec Text Text
-> (RiskEvaluation -> Text) -> Codec Object RiskEvaluation Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= RiskEvaluation -> Text
riskEvaluationReason
data Adjustments = Adjustments
{ Adjustments -> MoneyAmount
adjustmentsFXCredit :: !MoneyAmount,
Adjustments -> MoneyAmount
adjustmentsFXDebit :: !MoneyAmount
}
deriving (Adjustments -> Adjustments -> Bool
(Adjustments -> Adjustments -> Bool)
-> (Adjustments -> Adjustments -> Bool) -> Eq Adjustments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Adjustments -> Adjustments -> Bool
$c/= :: Adjustments -> Adjustments -> Bool
== :: Adjustments -> Adjustments -> Bool
$c== :: Adjustments -> Adjustments -> Bool
Eq, Int -> Adjustments -> ShowS
[Adjustments] -> ShowS
Adjustments -> String
(Int -> Adjustments -> ShowS)
-> (Adjustments -> String)
-> ([Adjustments] -> ShowS)
-> Show Adjustments
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Adjustments] -> ShowS
$cshowList :: [Adjustments] -> ShowS
show :: Adjustments -> String
$cshow :: Adjustments -> String
showsPrec :: Int -> Adjustments -> ShowS
$cshowsPrec :: Int -> Adjustments -> ShowS
Show, (forall x. Adjustments -> Rep Adjustments x)
-> (forall x. Rep Adjustments x -> Adjustments)
-> Generic Adjustments
forall x. Rep Adjustments x -> Adjustments
forall x. Adjustments -> Rep Adjustments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Adjustments x -> Adjustments
$cfrom :: forall x. Adjustments -> Rep Adjustments x
Generic)
deriving
( [Adjustments] -> Encoding
[Adjustments] -> Value
Adjustments -> Encoding
Adjustments -> Value
(Adjustments -> Value)
-> (Adjustments -> Encoding)
-> ([Adjustments] -> Value)
-> ([Adjustments] -> Encoding)
-> ToJSON Adjustments
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Adjustments] -> Encoding
$ctoEncodingList :: [Adjustments] -> Encoding
toJSONList :: [Adjustments] -> Value
$ctoJSONList :: [Adjustments] -> Value
toEncoding :: Adjustments -> Encoding
$ctoEncoding :: Adjustments -> Encoding
toJSON :: Adjustments -> Value
$ctoJSON :: Adjustments -> Value
ToJSON,
Value -> Parser [Adjustments]
Value -> Parser Adjustments
(Value -> Parser Adjustments)
-> (Value -> Parser [Adjustments]) -> FromJSON Adjustments
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Adjustments]
$cparseJSONList :: Value -> Parser [Adjustments]
parseJSON :: Value -> Parser Adjustments
$cparseJSON :: Value -> Parser Adjustments
FromJSON
)
via (Autodocodec Adjustments)
instance HasCodec Adjustments where
codec :: JSONCodec Adjustments
codec =
Text
-> ObjectCodec Adjustments Adjustments -> JSONCodec Adjustments
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"Adjustments" (ObjectCodec Adjustments Adjustments -> JSONCodec Adjustments)
-> ObjectCodec Adjustments Adjustments -> JSONCodec Adjustments
forall a b. (a -> b) -> a -> b
$
MoneyAmount -> MoneyAmount -> Adjustments
Adjustments
(MoneyAmount -> MoneyAmount -> Adjustments)
-> Codec Object Adjustments MoneyAmount
-> Codec Object Adjustments (MoneyAmount -> Adjustments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fxCredit" ObjectCodec MoneyAmount MoneyAmount
-> (Adjustments -> MoneyAmount)
-> Codec Object Adjustments MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Adjustments -> MoneyAmount
adjustmentsFXCredit
Codec Object Adjustments (MoneyAmount -> Adjustments)
-> Codec Object Adjustments MoneyAmount
-> ObjectCodec Adjustments Adjustments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec MoneyAmount MoneyAmount
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"fxDebit" ObjectCodec MoneyAmount MoneyAmount
-> (Adjustments -> MoneyAmount)
-> Codec Object Adjustments MoneyAmount
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= Adjustments -> MoneyAmount
adjustmentsFXDebit
data BillingDetails = BillingDetails
{ BillingDetails -> Text
billingDetailsName :: !Text,
BillingDetails -> City
billingDetailsCity :: !City,
BillingDetails -> ISO3166Alpha2
billingDetailsCountry :: !ISO3166Alpha2,
BillingDetails -> AddressLine
billingDetailsLine1 :: !AddressLine,
BillingDetails -> Maybe AddressLine
billingDetailsLine2 :: !(Maybe AddressLine),
BillingDetails -> Maybe District
billingDetailsDistrict :: !(Maybe District),
BillingDetails -> PostalCode
billingDetailsPostalCode :: !PostalCode
}
deriving (BillingDetails -> BillingDetails -> Bool
(BillingDetails -> BillingDetails -> Bool)
-> (BillingDetails -> BillingDetails -> Bool) -> Eq BillingDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BillingDetails -> BillingDetails -> Bool
$c/= :: BillingDetails -> BillingDetails -> Bool
== :: BillingDetails -> BillingDetails -> Bool
$c== :: BillingDetails -> BillingDetails -> Bool
Eq, Int -> BillingDetails -> ShowS
[BillingDetails] -> ShowS
BillingDetails -> String
(Int -> BillingDetails -> ShowS)
-> (BillingDetails -> String)
-> ([BillingDetails] -> ShowS)
-> Show BillingDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BillingDetails] -> ShowS
$cshowList :: [BillingDetails] -> ShowS
show :: BillingDetails -> String
$cshow :: BillingDetails -> String
showsPrec :: Int -> BillingDetails -> ShowS
$cshowsPrec :: Int -> BillingDetails -> ShowS
Show, (forall x. BillingDetails -> Rep BillingDetails x)
-> (forall x. Rep BillingDetails x -> BillingDetails)
-> Generic BillingDetails
forall x. Rep BillingDetails x -> BillingDetails
forall x. BillingDetails -> Rep BillingDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BillingDetails x -> BillingDetails
$cfrom :: forall x. BillingDetails -> Rep BillingDetails x
Generic)
deriving
( [BillingDetails] -> Encoding
[BillingDetails] -> Value
BillingDetails -> Encoding
BillingDetails -> Value
(BillingDetails -> Value)
-> (BillingDetails -> Encoding)
-> ([BillingDetails] -> Value)
-> ([BillingDetails] -> Encoding)
-> ToJSON BillingDetails
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BillingDetails] -> Encoding
$ctoEncodingList :: [BillingDetails] -> Encoding
toJSONList :: [BillingDetails] -> Value
$ctoJSONList :: [BillingDetails] -> Value
toEncoding :: BillingDetails -> Encoding
$ctoEncoding :: BillingDetails -> Encoding
toJSON :: BillingDetails -> Value
$ctoJSON :: BillingDetails -> Value
ToJSON,
Value -> Parser [BillingDetails]
Value -> Parser BillingDetails
(Value -> Parser BillingDetails)
-> (Value -> Parser [BillingDetails]) -> FromJSON BillingDetails
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BillingDetails]
$cparseJSONList :: Value -> Parser [BillingDetails]
parseJSON :: Value -> Parser BillingDetails
$cparseJSON :: Value -> Parser BillingDetails
FromJSON
)
via (Autodocodec BillingDetails)
instance HasCodec BillingDetails where
codec :: JSONCodec BillingDetails
codec =
Text
-> ObjectCodec BillingDetails BillingDetails
-> JSONCodec BillingDetails
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BillingDetails" (ObjectCodec BillingDetails BillingDetails
-> JSONCodec BillingDetails)
-> ObjectCodec BillingDetails BillingDetails
-> JSONCodec BillingDetails
forall a b. (a -> b) -> a -> b
$
Text
-> City
-> ISO3166Alpha2
-> AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails
BillingDetails
(Text
-> City
-> ISO3166Alpha2
-> AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails)
-> Codec Object BillingDetails Text
-> Codec
Object
BillingDetails
(City
-> ISO3166Alpha2
-> AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"name" ObjectCodec Text Text
-> (BillingDetails -> Text) -> Codec Object BillingDetails Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BillingDetails -> Text
billingDetailsName
Codec
Object
BillingDetails
(City
-> ISO3166Alpha2
-> AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails)
-> Codec Object BillingDetails City
-> Codec
Object
BillingDetails
(ISO3166Alpha2
-> AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec City City
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"city" ObjectCodec City City
-> (BillingDetails -> City) -> Codec Object BillingDetails City
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BillingDetails -> City
billingDetailsCity
Codec
Object
BillingDetails
(ISO3166Alpha2
-> AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails)
-> Codec Object BillingDetails ISO3166Alpha2
-> Codec
Object
BillingDetails
(AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ISO3166Alpha2 ISO3166Alpha2
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"country" ObjectCodec ISO3166Alpha2 ISO3166Alpha2
-> (BillingDetails -> ISO3166Alpha2)
-> Codec Object BillingDetails ISO3166Alpha2
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BillingDetails -> ISO3166Alpha2
billingDetailsCountry
Codec
Object
BillingDetails
(AddressLine
-> Maybe AddressLine
-> Maybe District
-> PostalCode
-> BillingDetails)
-> Codec Object BillingDetails AddressLine
-> Codec
Object
BillingDetails
(Maybe AddressLine
-> Maybe District -> PostalCode -> BillingDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AddressLine AddressLine
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"line1" ObjectCodec AddressLine AddressLine
-> (BillingDetails -> AddressLine)
-> Codec Object BillingDetails AddressLine
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BillingDetails -> AddressLine
billingDetailsLine1
Codec
Object
BillingDetails
(Maybe AddressLine
-> Maybe District -> PostalCode -> BillingDetails)
-> Codec Object BillingDetails (Maybe AddressLine)
-> Codec
Object
BillingDetails
(Maybe District -> PostalCode -> BillingDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"line2" ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
-> (BillingDetails -> Maybe AddressLine)
-> Codec Object BillingDetails (Maybe AddressLine)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BillingDetails -> Maybe AddressLine
billingDetailsLine2
Codec
Object
BillingDetails
(Maybe District -> PostalCode -> BillingDetails)
-> Codec Object BillingDetails (Maybe District)
-> Codec Object BillingDetails (PostalCode -> BillingDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe District) (Maybe District)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"district" ObjectCodec (Maybe District) (Maybe District)
-> (BillingDetails -> Maybe District)
-> Codec Object BillingDetails (Maybe District)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BillingDetails -> Maybe District
billingDetailsDistrict
Codec Object BillingDetails (PostalCode -> BillingDetails)
-> Codec Object BillingDetails PostalCode
-> ObjectCodec BillingDetails BillingDetails
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PostalCode PostalCode
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"postalCode" ObjectCodec PostalCode PostalCode
-> (BillingDetails -> PostalCode)
-> Codec Object BillingDetails PostalCode
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BillingDetails -> PostalCode
billingDetailsPostalCode
data BankAddress = BankAddress
{ BankAddress -> Maybe Text
bankAddressName :: !(Maybe Text),
BankAddress -> Maybe City
bankAddressCity :: !(Maybe City),
BankAddress -> Maybe ISO3166Alpha2
bankAddressCountry :: !(Maybe ISO3166Alpha2),
BankAddress -> Maybe AddressLine
bankAddressLine1 :: !(Maybe AddressLine),
BankAddress -> Maybe AddressLine
bankAddressLine2 :: !(Maybe AddressLine),
BankAddress -> Maybe District
bankAddressDistrict :: !(Maybe District)
}
deriving (BankAddress -> BankAddress -> Bool
(BankAddress -> BankAddress -> Bool)
-> (BankAddress -> BankAddress -> Bool) -> Eq BankAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BankAddress -> BankAddress -> Bool
$c/= :: BankAddress -> BankAddress -> Bool
== :: BankAddress -> BankAddress -> Bool
$c== :: BankAddress -> BankAddress -> Bool
Eq, Int -> BankAddress -> ShowS
[BankAddress] -> ShowS
BankAddress -> String
(Int -> BankAddress -> ShowS)
-> (BankAddress -> String)
-> ([BankAddress] -> ShowS)
-> Show BankAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BankAddress] -> ShowS
$cshowList :: [BankAddress] -> ShowS
show :: BankAddress -> String
$cshow :: BankAddress -> String
showsPrec :: Int -> BankAddress -> ShowS
$cshowsPrec :: Int -> BankAddress -> ShowS
Show)
deriving
( Value -> Parser [BankAddress]
Value -> Parser BankAddress
(Value -> Parser BankAddress)
-> (Value -> Parser [BankAddress]) -> FromJSON BankAddress
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BankAddress]
$cparseJSONList :: Value -> Parser [BankAddress]
parseJSON :: Value -> Parser BankAddress
$cparseJSON :: Value -> Parser BankAddress
FromJSON,
[BankAddress] -> Encoding
[BankAddress] -> Value
BankAddress -> Encoding
BankAddress -> Value
(BankAddress -> Value)
-> (BankAddress -> Encoding)
-> ([BankAddress] -> Value)
-> ([BankAddress] -> Encoding)
-> ToJSON BankAddress
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BankAddress] -> Encoding
$ctoEncodingList :: [BankAddress] -> Encoding
toJSONList :: [BankAddress] -> Value
$ctoJSONList :: [BankAddress] -> Value
toEncoding :: BankAddress -> Encoding
$ctoEncoding :: BankAddress -> Encoding
toJSON :: BankAddress -> Value
$ctoJSON :: BankAddress -> Value
ToJSON
)
via (Autodocodec BankAddress)
instance HasCodec BankAddress where
codec :: JSONCodec BankAddress
codec =
Text
-> ObjectCodec BankAddress BankAddress -> JSONCodec BankAddress
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BankAddress" (ObjectCodec BankAddress BankAddress -> JSONCodec BankAddress)
-> ObjectCodec BankAddress BankAddress -> JSONCodec BankAddress
forall a b. (a -> b) -> a -> b
$
Maybe Text
-> Maybe City
-> Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> BankAddress
BankAddress
(Maybe Text
-> Maybe City
-> Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> BankAddress)
-> Codec Object BankAddress (Maybe Text)
-> Codec
Object
BankAddress
(Maybe City
-> Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> BankAddress)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"name" ObjectCodec (Maybe Text) (Maybe Text)
-> (BankAddress -> Maybe Text)
-> Codec Object BankAddress (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BankAddress -> Maybe Text
bankAddressName
Codec
Object
BankAddress
(Maybe City
-> Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> BankAddress)
-> Codec Object BankAddress (Maybe City)
-> Codec
Object
BankAddress
(Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> BankAddress)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe City) (Maybe City)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"city" ObjectCodec (Maybe City) (Maybe City)
-> (BankAddress -> Maybe City)
-> Codec Object BankAddress (Maybe City)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BankAddress -> Maybe City
bankAddressCity
Codec
Object
BankAddress
(Maybe ISO3166Alpha2
-> Maybe AddressLine
-> Maybe AddressLine
-> Maybe District
-> BankAddress)
-> Codec Object BankAddress (Maybe ISO3166Alpha2)
-> Codec
Object
BankAddress
(Maybe AddressLine
-> Maybe AddressLine -> Maybe District -> BankAddress)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"country" ObjectCodec (Maybe ISO3166Alpha2) (Maybe ISO3166Alpha2)
-> (BankAddress -> Maybe ISO3166Alpha2)
-> Codec Object BankAddress (Maybe ISO3166Alpha2)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BankAddress -> Maybe ISO3166Alpha2
bankAddressCountry
Codec
Object
BankAddress
(Maybe AddressLine
-> Maybe AddressLine -> Maybe District -> BankAddress)
-> Codec Object BankAddress (Maybe AddressLine)
-> Codec
Object
BankAddress
(Maybe AddressLine -> Maybe District -> BankAddress)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"line1" ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
-> (BankAddress -> Maybe AddressLine)
-> Codec Object BankAddress (Maybe AddressLine)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BankAddress -> Maybe AddressLine
bankAddressLine1
Codec
Object
BankAddress
(Maybe AddressLine -> Maybe District -> BankAddress)
-> Codec Object BankAddress (Maybe AddressLine)
-> Codec Object BankAddress (Maybe District -> BankAddress)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"line2" ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
-> (BankAddress -> Maybe AddressLine)
-> Codec Object BankAddress (Maybe AddressLine)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BankAddress -> Maybe AddressLine
bankAddressLine2
Codec Object BankAddress (Maybe District -> BankAddress)
-> Codec Object BankAddress (Maybe District)
-> ObjectCodec BankAddress BankAddress
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe District) (Maybe District)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"district" ObjectCodec (Maybe District) (Maybe District)
-> (BankAddress -> Maybe District)
-> Codec Object BankAddress (Maybe District)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BankAddress -> Maybe District
bankAddressDistrict
data BeneficiaryDetails = BeneficiaryDetails
{ BeneficiaryDetails -> Text
beneficiaryDetailsName :: !Text,
BeneficiaryDetails -> Maybe AddressLine
beneficiaryDetailsAddress1 :: !(Maybe AddressLine),
BeneficiaryDetails -> Maybe AddressLine
beneficiaryDetailsAddress2 :: !(Maybe AddressLine)
}
deriving (BeneficiaryDetails -> BeneficiaryDetails -> Bool
(BeneficiaryDetails -> BeneficiaryDetails -> Bool)
-> (BeneficiaryDetails -> BeneficiaryDetails -> Bool)
-> Eq BeneficiaryDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BeneficiaryDetails -> BeneficiaryDetails -> Bool
$c/= :: BeneficiaryDetails -> BeneficiaryDetails -> Bool
== :: BeneficiaryDetails -> BeneficiaryDetails -> Bool
$c== :: BeneficiaryDetails -> BeneficiaryDetails -> Bool
Eq, Int -> BeneficiaryDetails -> ShowS
[BeneficiaryDetails] -> ShowS
BeneficiaryDetails -> String
(Int -> BeneficiaryDetails -> ShowS)
-> (BeneficiaryDetails -> String)
-> ([BeneficiaryDetails] -> ShowS)
-> Show BeneficiaryDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BeneficiaryDetails] -> ShowS
$cshowList :: [BeneficiaryDetails] -> ShowS
show :: BeneficiaryDetails -> String
$cshow :: BeneficiaryDetails -> String
showsPrec :: Int -> BeneficiaryDetails -> ShowS
$cshowsPrec :: Int -> BeneficiaryDetails -> ShowS
Show)
deriving
( Value -> Parser [BeneficiaryDetails]
Value -> Parser BeneficiaryDetails
(Value -> Parser BeneficiaryDetails)
-> (Value -> Parser [BeneficiaryDetails])
-> FromJSON BeneficiaryDetails
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BeneficiaryDetails]
$cparseJSONList :: Value -> Parser [BeneficiaryDetails]
parseJSON :: Value -> Parser BeneficiaryDetails
$cparseJSON :: Value -> Parser BeneficiaryDetails
FromJSON,
[BeneficiaryDetails] -> Encoding
[BeneficiaryDetails] -> Value
BeneficiaryDetails -> Encoding
BeneficiaryDetails -> Value
(BeneficiaryDetails -> Value)
-> (BeneficiaryDetails -> Encoding)
-> ([BeneficiaryDetails] -> Value)
-> ([BeneficiaryDetails] -> Encoding)
-> ToJSON BeneficiaryDetails
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BeneficiaryDetails] -> Encoding
$ctoEncodingList :: [BeneficiaryDetails] -> Encoding
toJSONList :: [BeneficiaryDetails] -> Value
$ctoJSONList :: [BeneficiaryDetails] -> Value
toEncoding :: BeneficiaryDetails -> Encoding
$ctoEncoding :: BeneficiaryDetails -> Encoding
toJSON :: BeneficiaryDetails -> Value
$ctoJSON :: BeneficiaryDetails -> Value
ToJSON
)
via (Autodocodec BeneficiaryDetails)
instance HasCodec BeneficiaryDetails where
codec :: JSONCodec BeneficiaryDetails
codec =
Text
-> ObjectCodec BeneficiaryDetails BeneficiaryDetails
-> JSONCodec BeneficiaryDetails
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BeneficiaryDetails" (ObjectCodec BeneficiaryDetails BeneficiaryDetails
-> JSONCodec BeneficiaryDetails)
-> ObjectCodec BeneficiaryDetails BeneficiaryDetails
-> JSONCodec BeneficiaryDetails
forall a b. (a -> b) -> a -> b
$
Text
-> Maybe AddressLine -> Maybe AddressLine -> BeneficiaryDetails
BeneficiaryDetails
(Text
-> Maybe AddressLine -> Maybe AddressLine -> BeneficiaryDetails)
-> Codec Object BeneficiaryDetails Text
-> Codec
Object
BeneficiaryDetails
(Maybe AddressLine -> Maybe AddressLine -> BeneficiaryDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"name" ObjectCodec Text Text
-> (BeneficiaryDetails -> Text)
-> Codec Object BeneficiaryDetails Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryDetails -> Text
beneficiaryDetailsName
Codec
Object
BeneficiaryDetails
(Maybe AddressLine -> Maybe AddressLine -> BeneficiaryDetails)
-> Codec Object BeneficiaryDetails (Maybe AddressLine)
-> Codec
Object BeneficiaryDetails (Maybe AddressLine -> BeneficiaryDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"address1" ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
-> (BeneficiaryDetails -> Maybe AddressLine)
-> Codec Object BeneficiaryDetails (Maybe AddressLine)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryDetails -> Maybe AddressLine
beneficiaryDetailsAddress1
Codec
Object BeneficiaryDetails (Maybe AddressLine -> BeneficiaryDetails)
-> Codec Object BeneficiaryDetails (Maybe AddressLine)
-> ObjectCodec BeneficiaryDetails BeneficiaryDetails
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
forall output.
HasCodec output =>
Text -> ObjectCodec (Maybe output) (Maybe output)
optionalField' Text
"address2" ObjectCodec (Maybe AddressLine) (Maybe AddressLine)
-> (BeneficiaryDetails -> Maybe AddressLine)
-> Codec Object BeneficiaryDetails (Maybe AddressLine)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryDetails -> Maybe AddressLine
beneficiaryDetailsAddress2
data BeneficiaryBankDetails = BeneficiaryBankDetails
{ BeneficiaryBankDetails -> Text
beneficiaryBankDetailsName :: !Text,
BeneficiaryBankDetails -> SwiftCode
beneficiaryBankDetailsSwiftCode :: !SwiftCode,
BeneficiaryBankDetails -> RoutingNumber
beneficiaryBankDetailsRoutingNumber :: !RoutingNumber,
BeneficiaryBankDetails -> AccountNumber
beneficiaryBankDetailsAccountNumber :: !AccountNumber,
BeneficiaryBankDetails -> SupportedCurrencies
beneficiaryBankDetailsCurrency :: !SupportedCurrencies,
BeneficiaryBankDetails -> AddressLine
beneficiaryBankDetailsAddress :: !AddressLine,
BeneficiaryBankDetails -> City
beneficiaryBankDetailsCity :: !City,
BeneficiaryBankDetails -> PostalCode
beneficiaryBankDetailsPostalCode :: !PostalCode,
BeneficiaryBankDetails -> ISO3166Alpha2
beneficiaryBankDetailsCountry :: !ISO3166Alpha2
}
deriving (BeneficiaryBankDetails -> BeneficiaryBankDetails -> Bool
(BeneficiaryBankDetails -> BeneficiaryBankDetails -> Bool)
-> (BeneficiaryBankDetails -> BeneficiaryBankDetails -> Bool)
-> Eq BeneficiaryBankDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BeneficiaryBankDetails -> BeneficiaryBankDetails -> Bool
$c/= :: BeneficiaryBankDetails -> BeneficiaryBankDetails -> Bool
== :: BeneficiaryBankDetails -> BeneficiaryBankDetails -> Bool
$c== :: BeneficiaryBankDetails -> BeneficiaryBankDetails -> Bool
Eq, Int -> BeneficiaryBankDetails -> ShowS
[BeneficiaryBankDetails] -> ShowS
BeneficiaryBankDetails -> String
(Int -> BeneficiaryBankDetails -> ShowS)
-> (BeneficiaryBankDetails -> String)
-> ([BeneficiaryBankDetails] -> ShowS)
-> Show BeneficiaryBankDetails
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BeneficiaryBankDetails] -> ShowS
$cshowList :: [BeneficiaryBankDetails] -> ShowS
show :: BeneficiaryBankDetails -> String
$cshow :: BeneficiaryBankDetails -> String
showsPrec :: Int -> BeneficiaryBankDetails -> ShowS
$cshowsPrec :: Int -> BeneficiaryBankDetails -> ShowS
Show)
deriving
( Value -> Parser [BeneficiaryBankDetails]
Value -> Parser BeneficiaryBankDetails
(Value -> Parser BeneficiaryBankDetails)
-> (Value -> Parser [BeneficiaryBankDetails])
-> FromJSON BeneficiaryBankDetails
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BeneficiaryBankDetails]
$cparseJSONList :: Value -> Parser [BeneficiaryBankDetails]
parseJSON :: Value -> Parser BeneficiaryBankDetails
$cparseJSON :: Value -> Parser BeneficiaryBankDetails
FromJSON,
[BeneficiaryBankDetails] -> Encoding
[BeneficiaryBankDetails] -> Value
BeneficiaryBankDetails -> Encoding
BeneficiaryBankDetails -> Value
(BeneficiaryBankDetails -> Value)
-> (BeneficiaryBankDetails -> Encoding)
-> ([BeneficiaryBankDetails] -> Value)
-> ([BeneficiaryBankDetails] -> Encoding)
-> ToJSON BeneficiaryBankDetails
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [BeneficiaryBankDetails] -> Encoding
$ctoEncodingList :: [BeneficiaryBankDetails] -> Encoding
toJSONList :: [BeneficiaryBankDetails] -> Value
$ctoJSONList :: [BeneficiaryBankDetails] -> Value
toEncoding :: BeneficiaryBankDetails -> Encoding
$ctoEncoding :: BeneficiaryBankDetails -> Encoding
toJSON :: BeneficiaryBankDetails -> Value
$ctoJSON :: BeneficiaryBankDetails -> Value
ToJSON
)
via (Autodocodec BeneficiaryBankDetails)
instance HasCodec BeneficiaryBankDetails where
codec :: JSONCodec BeneficiaryBankDetails
codec =
Text
-> ObjectCodec BeneficiaryBankDetails BeneficiaryBankDetails
-> JSONCodec BeneficiaryBankDetails
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
object Text
"BeneficiaryBankDetails" (ObjectCodec BeneficiaryBankDetails BeneficiaryBankDetails
-> JSONCodec BeneficiaryBankDetails)
-> ObjectCodec BeneficiaryBankDetails BeneficiaryBankDetails
-> JSONCodec BeneficiaryBankDetails
forall a b. (a -> b) -> a -> b
$
Text
-> SwiftCode
-> RoutingNumber
-> AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails
BeneficiaryBankDetails
(Text
-> SwiftCode
-> RoutingNumber
-> AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails Text
-> Codec
Object
BeneficiaryBankDetails
(SwiftCode
-> RoutingNumber
-> AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ObjectCodec Text Text
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"name" ObjectCodec Text Text
-> (BeneficiaryBankDetails -> Text)
-> Codec Object BeneficiaryBankDetails Text
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> Text
beneficiaryBankDetailsName
Codec
Object
BeneficiaryBankDetails
(SwiftCode
-> RoutingNumber
-> AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails SwiftCode
-> Codec
Object
BeneficiaryBankDetails
(RoutingNumber
-> AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SwiftCode SwiftCode
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"swiftCode" ObjectCodec SwiftCode SwiftCode
-> (BeneficiaryBankDetails -> SwiftCode)
-> Codec Object BeneficiaryBankDetails SwiftCode
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> SwiftCode
beneficiaryBankDetailsSwiftCode
Codec
Object
BeneficiaryBankDetails
(RoutingNumber
-> AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails RoutingNumber
-> Codec
Object
BeneficiaryBankDetails
(AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec RoutingNumber RoutingNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"routingNumber" ObjectCodec RoutingNumber RoutingNumber
-> (BeneficiaryBankDetails -> RoutingNumber)
-> Codec Object BeneficiaryBankDetails RoutingNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> RoutingNumber
beneficiaryBankDetailsRoutingNumber
Codec
Object
BeneficiaryBankDetails
(AccountNumber
-> SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails AccountNumber
-> Codec
Object
BeneficiaryBankDetails
(SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AccountNumber AccountNumber
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"accountNumber" ObjectCodec AccountNumber AccountNumber
-> (BeneficiaryBankDetails -> AccountNumber)
-> Codec Object BeneficiaryBankDetails AccountNumber
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> AccountNumber
beneficiaryBankDetailsAccountNumber
Codec
Object
BeneficiaryBankDetails
(SupportedCurrencies
-> AddressLine
-> City
-> PostalCode
-> ISO3166Alpha2
-> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails SupportedCurrencies
-> Codec
Object
BeneficiaryBankDetails
(AddressLine
-> City -> PostalCode -> ISO3166Alpha2 -> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec SupportedCurrencies SupportedCurrencies
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"currency" ObjectCodec SupportedCurrencies SupportedCurrencies
-> (BeneficiaryBankDetails -> SupportedCurrencies)
-> Codec Object BeneficiaryBankDetails SupportedCurrencies
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> SupportedCurrencies
beneficiaryBankDetailsCurrency
Codec
Object
BeneficiaryBankDetails
(AddressLine
-> City -> PostalCode -> ISO3166Alpha2 -> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails AddressLine
-> Codec
Object
BeneficiaryBankDetails
(City -> PostalCode -> ISO3166Alpha2 -> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec AddressLine AddressLine
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"address" ObjectCodec AddressLine AddressLine
-> (BeneficiaryBankDetails -> AddressLine)
-> Codec Object BeneficiaryBankDetails AddressLine
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> AddressLine
beneficiaryBankDetailsAddress
Codec
Object
BeneficiaryBankDetails
(City -> PostalCode -> ISO3166Alpha2 -> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails City
-> Codec
Object
BeneficiaryBankDetails
(PostalCode -> ISO3166Alpha2 -> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec City City
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"city" ObjectCodec City City
-> (BeneficiaryBankDetails -> City)
-> Codec Object BeneficiaryBankDetails City
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> City
beneficiaryBankDetailsCity
Codec
Object
BeneficiaryBankDetails
(PostalCode -> ISO3166Alpha2 -> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails PostalCode
-> Codec
Object
BeneficiaryBankDetails
(ISO3166Alpha2 -> BeneficiaryBankDetails)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec PostalCode PostalCode
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"postalCode" ObjectCodec PostalCode PostalCode
-> (BeneficiaryBankDetails -> PostalCode)
-> Codec Object BeneficiaryBankDetails PostalCode
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> PostalCode
beneficiaryBankDetailsPostalCode
Codec
Object
BeneficiaryBankDetails
(ISO3166Alpha2 -> BeneficiaryBankDetails)
-> Codec Object BeneficiaryBankDetails ISO3166Alpha2
-> ObjectCodec BeneficiaryBankDetails BeneficiaryBankDetails
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ObjectCodec ISO3166Alpha2 ISO3166Alpha2
forall output. HasCodec output => Text -> ObjectCodec output output
requiredField' Text
"country" ObjectCodec ISO3166Alpha2 ISO3166Alpha2
-> (BeneficiaryBankDetails -> ISO3166Alpha2)
-> Codec Object BeneficiaryBankDetails ISO3166Alpha2
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
.= BeneficiaryBankDetails -> ISO3166Alpha2
beneficiaryBankDetailsCountry
newtype ProcessorToken = ProcessorToken
{ ProcessorToken -> Text
unProcessorToken :: Text
}
deriving (ProcessorToken -> ProcessorToken -> Bool
(ProcessorToken -> ProcessorToken -> Bool)
-> (ProcessorToken -> ProcessorToken -> Bool) -> Eq ProcessorToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProcessorToken -> ProcessorToken -> Bool
$c/= :: ProcessorToken -> ProcessorToken -> Bool
== :: ProcessorToken -> ProcessorToken -> Bool
$c== :: ProcessorToken -> ProcessorToken -> Bool
Eq, Int -> ProcessorToken -> ShowS
[ProcessorToken] -> ShowS
ProcessorToken -> String
(Int -> ProcessorToken -> ShowS)
-> (ProcessorToken -> String)
-> ([ProcessorToken] -> ShowS)
-> Show ProcessorToken
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProcessorToken] -> ShowS
$cshowList :: [ProcessorToken] -> ShowS
show :: ProcessorToken -> String
$cshow :: ProcessorToken -> String
showsPrec :: Int -> ProcessorToken -> ShowS
$cshowsPrec :: Int -> ProcessorToken -> ShowS
Show, [ProcessorToken] -> Encoding
[ProcessorToken] -> Value
ProcessorToken -> Encoding
ProcessorToken -> Value
(ProcessorToken -> Value)
-> (ProcessorToken -> Encoding)
-> ([ProcessorToken] -> Value)
-> ([ProcessorToken] -> Encoding)
-> ToJSON ProcessorToken
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ProcessorToken] -> Encoding
$ctoEncodingList :: [ProcessorToken] -> Encoding
toJSONList :: [ProcessorToken] -> Value
$ctoJSONList :: [ProcessorToken] -> Value
toEncoding :: ProcessorToken -> Encoding
$ctoEncoding :: ProcessorToken -> Encoding
toJSON :: ProcessorToken -> Value
$ctoJSON :: ProcessorToken -> Value
ToJSON, Value -> Parser [ProcessorToken]
Value -> Parser ProcessorToken
(Value -> Parser ProcessorToken)
-> (Value -> Parser [ProcessorToken]) -> FromJSON ProcessorToken
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ProcessorToken]
$cparseJSONList :: Value -> Parser [ProcessorToken]
parseJSON :: Value -> Parser ProcessorToken
$cparseJSON :: Value -> Parser ProcessorToken
FromJSON)
instance HasCodec ProcessorToken where
codec :: JSONCodec ProcessorToken
codec = (Text -> ProcessorToken)
-> (ProcessorToken -> Text)
-> Codec Value Text Text
-> JSONCodec ProcessorToken
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> ProcessorToken
ProcessorToken ProcessorToken -> Text
unProcessorToken Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype AddressLine = AddressLine
{ AddressLine -> Text
unAddressLine :: Text
}
deriving (AddressLine -> AddressLine -> Bool
(AddressLine -> AddressLine -> Bool)
-> (AddressLine -> AddressLine -> Bool) -> Eq AddressLine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddressLine -> AddressLine -> Bool
$c/= :: AddressLine -> AddressLine -> Bool
== :: AddressLine -> AddressLine -> Bool
$c== :: AddressLine -> AddressLine -> Bool
Eq, Int -> AddressLine -> ShowS
[AddressLine] -> ShowS
AddressLine -> String
(Int -> AddressLine -> ShowS)
-> (AddressLine -> String)
-> ([AddressLine] -> ShowS)
-> Show AddressLine
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddressLine] -> ShowS
$cshowList :: [AddressLine] -> ShowS
show :: AddressLine -> String
$cshow :: AddressLine -> String
showsPrec :: Int -> AddressLine -> ShowS
$cshowsPrec :: Int -> AddressLine -> ShowS
Show, [AddressLine] -> Encoding
[AddressLine] -> Value
AddressLine -> Encoding
AddressLine -> Value
(AddressLine -> Value)
-> (AddressLine -> Encoding)
-> ([AddressLine] -> Value)
-> ([AddressLine] -> Encoding)
-> ToJSON AddressLine
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AddressLine] -> Encoding
$ctoEncodingList :: [AddressLine] -> Encoding
toJSONList :: [AddressLine] -> Value
$ctoJSONList :: [AddressLine] -> Value
toEncoding :: AddressLine -> Encoding
$ctoEncoding :: AddressLine -> Encoding
toJSON :: AddressLine -> Value
$ctoJSON :: AddressLine -> Value
ToJSON, Value -> Parser [AddressLine]
Value -> Parser AddressLine
(Value -> Parser AddressLine)
-> (Value -> Parser [AddressLine]) -> FromJSON AddressLine
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [AddressLine]
$cparseJSONList :: Value -> Parser [AddressLine]
parseJSON :: Value -> Parser AddressLine
$cparseJSON :: Value -> Parser AddressLine
FromJSON)
instance HasCodec AddressLine where
codec :: JSONCodec AddressLine
codec = (Text -> AddressLine)
-> (AddressLine -> Text)
-> Codec Value Text Text
-> JSONCodec AddressLine
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> AddressLine
AddressLine AddressLine -> Text
unAddressLine Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype URL = URL {URL -> Text
unURL :: Text}
deriving stock (URL -> URL -> Bool
(URL -> URL -> Bool) -> (URL -> URL -> Bool) -> Eq URL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: URL -> URL -> Bool
$c/= :: URL -> URL -> Bool
== :: URL -> URL -> Bool
$c== :: URL -> URL -> Bool
Eq, Int -> URL -> ShowS
[URL] -> ShowS
URL -> String
(Int -> URL -> ShowS)
-> (URL -> String) -> ([URL] -> ShowS) -> Show URL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [URL] -> ShowS
$cshowList :: [URL] -> ShowS
show :: URL -> String
$cshow :: URL -> String
showsPrec :: Int -> URL -> ShowS
$cshowsPrec :: Int -> URL -> ShowS
Show, URL -> Q Exp
URL -> Q (TExp URL)
(URL -> Q Exp) -> (URL -> Q (TExp URL)) -> Lift URL
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: URL -> Q (TExp URL)
$cliftTyped :: URL -> Q (TExp URL)
lift :: URL -> Q Exp
$clift :: URL -> Q Exp
Lift)
deriving newtype ([URL] -> Encoding
[URL] -> Value
URL -> Encoding
URL -> Value
(URL -> Value)
-> (URL -> Encoding)
-> ([URL] -> Value)
-> ([URL] -> Encoding)
-> ToJSON URL
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [URL] -> Encoding
$ctoEncodingList :: [URL] -> Encoding
toJSONList :: [URL] -> Value
$ctoJSONList :: [URL] -> Value
toEncoding :: URL -> Encoding
$ctoEncoding :: URL -> Encoding
toJSON :: URL -> Value
$ctoJSON :: URL -> Value
ToJSON)
urlRegex :: Regex
urlRegex :: Regex
urlRegex =
[re|(?i)\b((?:[a-z][\w-]+:(?:/{1,3}|[a-z0-9%])|www\d{0,3}[.]|[a-z0-9.\-]+[.][a-z]{2,4}/)(?:[^\s()<>]+|\(([^\s()<>]+|(\([^\s()<>]+\)))*\))+(?:\(([^\s()<>]+|(\([^\s()<>]+\)))*\)|[^\s`!()\[\]{};:'".,<>?«»“”‘’]))|]
mkURL :: Text -> Maybe URL
mkURL :: Text -> Maybe URL
mkURL Text
t =
if Text
t Text -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ Regex
urlRegex
then URL -> Maybe URL
forall a. a -> Maybe a
Just (Text -> URL
URL Text
t)
else Maybe URL
forall a. Maybe a
Nothing
urlToText :: URL -> Text
urlToText :: URL -> Text
urlToText (URL Text
t) = Text
t
urlToByteString :: URL -> BS8.ByteString
urlToByteString :: URL -> ByteString
urlToByteString URL
url = Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ URL -> Text
urlToText URL
url
instance FromJSON URL where
parseJSON :: Value -> Parser URL
parseJSON = String -> (Text -> Parser URL) -> Value -> Parser URL
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"URL" ((Text -> Parser URL) -> Value -> Parser URL)
-> (Text -> Parser URL) -> Value -> Parser URL
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text -> Maybe URL
mkURL Text
t of
Maybe URL
Nothing -> String -> Parser URL
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser URL) -> String -> Parser URL
forall a b. (a -> b) -> a -> b
$ String
"Invalid URL: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
Just URL
url -> URL -> Parser URL
forall (f :: * -> *) a. Applicative f => a -> f a
pure URL
url
instance HasCodec URL where
codec :: JSONCodec URL
codec = (Text -> URL)
-> (URL -> Text) -> Codec Value Text Text -> JSONCodec URL
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> URL
URL URL -> Text
unURL Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype AccountNumber = AccountNumber {AccountNumber -> Text
unAccountNumber :: Text}
deriving stock (AccountNumber -> AccountNumber -> Bool
(AccountNumber -> AccountNumber -> Bool)
-> (AccountNumber -> AccountNumber -> Bool) -> Eq AccountNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountNumber -> AccountNumber -> Bool
$c/= :: AccountNumber -> AccountNumber -> Bool
== :: AccountNumber -> AccountNumber -> Bool
$c== :: AccountNumber -> AccountNumber -> Bool
Eq, Int -> AccountNumber -> ShowS
[AccountNumber] -> ShowS
AccountNumber -> String
(Int -> AccountNumber -> ShowS)
-> (AccountNumber -> String)
-> ([AccountNumber] -> ShowS)
-> Show AccountNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountNumber] -> ShowS
$cshowList :: [AccountNumber] -> ShowS
show :: AccountNumber -> String
$cshow :: AccountNumber -> String
showsPrec :: Int -> AccountNumber -> ShowS
$cshowsPrec :: Int -> AccountNumber -> ShowS
Show, AccountNumber -> Q Exp
AccountNumber -> Q (TExp AccountNumber)
(AccountNumber -> Q Exp)
-> (AccountNumber -> Q (TExp AccountNumber)) -> Lift AccountNumber
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: AccountNumber -> Q (TExp AccountNumber)
$cliftTyped :: AccountNumber -> Q (TExp AccountNumber)
lift :: AccountNumber -> Q Exp
$clift :: AccountNumber -> Q Exp
Lift)
deriving newtype ([AccountNumber] -> Encoding
[AccountNumber] -> Value
AccountNumber -> Encoding
AccountNumber -> Value
(AccountNumber -> Value)
-> (AccountNumber -> Encoding)
-> ([AccountNumber] -> Value)
-> ([AccountNumber] -> Encoding)
-> ToJSON AccountNumber
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [AccountNumber] -> Encoding
$ctoEncodingList :: [AccountNumber] -> Encoding
toJSONList :: [AccountNumber] -> Value
$ctoJSONList :: [AccountNumber] -> Value
toEncoding :: AccountNumber -> Encoding
$ctoEncoding :: AccountNumber -> Encoding
toJSON :: AccountNumber -> Value
$ctoJSON :: AccountNumber -> Value
ToJSON)
accountNumberRegex :: Regex
accountNumberRegex :: Regex
accountNumberRegex = [re|^[A-Z0-9]{4,17}$|]
mkAccountNumber :: Text -> Maybe AccountNumber
mkAccountNumber :: Text -> Maybe AccountNumber
mkAccountNumber Text
t =
if Text
t Text -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ Regex
accountNumberRegex
then AccountNumber -> Maybe AccountNumber
forall a. a -> Maybe a
Just (Text -> AccountNumber
AccountNumber Text
t)
else Maybe AccountNumber
forall a. Maybe a
Nothing
accountNumberToText :: AccountNumber -> Text
accountNumberToText :: AccountNumber -> Text
accountNumberToText (AccountNumber Text
t) = Text
t
type AccountNumberMask = Refined (SizeEqualTo 4) Text
accountNumberLastFour :: AccountNumber -> AccountNumberMask
accountNumberLastFour :: AccountNumber -> AccountNumberMask
accountNumberLastFour (AccountNumber Text
n) =
Text -> AccountNumberMask
forall k x (p :: k). x -> Refined p x
reallyUnsafeRefine
(Text -> AccountNumberMask)
-> (Text -> Text) -> Text -> AccountNumberMask
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> Text
T.takeEnd Int
4
(Text -> AccountNumberMask) -> Text -> AccountNumberMask
forall a b. (a -> b) -> a -> b
$ Text
n
accountNumberToByteString :: AccountNumber -> BS8.ByteString
accountNumberToByteString :: AccountNumber -> ByteString
accountNumberToByteString AccountNumber
accountNumber = Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ AccountNumber -> Text
accountNumberToText AccountNumber
accountNumber
instance FromJSON AccountNumber where
parseJSON :: Value -> Parser AccountNumber
parseJSON = String
-> (Text -> Parser AccountNumber) -> Value -> Parser AccountNumber
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"AccountNumber" ((Text -> Parser AccountNumber) -> Value -> Parser AccountNumber)
-> (Text -> Parser AccountNumber) -> Value -> Parser AccountNumber
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text -> Maybe AccountNumber
mkAccountNumber Text
t of
Maybe AccountNumber
Nothing -> String -> Parser AccountNumber
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser AccountNumber) -> String -> Parser AccountNumber
forall a b. (a -> b) -> a -> b
$ String
"Invalid AccountNumber: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
Just AccountNumber
accountNumber -> AccountNumber -> Parser AccountNumber
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccountNumber
accountNumber
instance HasCodec AccountNumber where
codec :: Codec Value AccountNumber AccountNumber
codec = (Text -> AccountNumber)
-> (AccountNumber -> Text)
-> Codec Value Text Text
-> Codec Value AccountNumber AccountNumber
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> AccountNumber
AccountNumber AccountNumber -> Text
unAccountNumber Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
compileAccountNumber :: QuasiQuoter
compileAccountNumber :: QuasiQuoter
compileAccountNumber =
QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter
{ quoteExp :: String -> Q Exp
quoteExp = String -> Q Exp
compileAccountNumber',
quotePat :: String -> Q Pat
quotePat = String -> String -> Q Pat
forall a. HasCallStack => String -> a
error String
"AccountNumber is not a pattern; use accountNumberToText instead",
quoteDec :: String -> Q [Dec]
quoteDec = String -> String -> Q [Dec]
forall a. HasCallStack => String -> a
error String
"accountNumber is not supported at top-level",
quoteType :: String -> Q Type
quoteType = String -> String -> Q Type
forall a. HasCallStack => String -> a
error String
"accountNumber is not supported as a type"
}
where
compileAccountNumber' :: String -> Q Exp
compileAccountNumber' :: String -> Q Exp
compileAccountNumber' String
s = case Text -> Maybe AccountNumber
mkAccountNumber (String -> Text
T.pack String
s) of
Maybe AccountNumber
Nothing -> String -> Q Exp
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invalid AccountNumber: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
". Must be 4-17 digits, with no other characters.")
Just AccountNumber
accountNumber -> [|accountNumber|]
newtype RoutingNumber = RoutingNumber {RoutingNumber -> Text
unRoutingNumber :: Text}
deriving stock (Int -> RoutingNumber -> ShowS
[RoutingNumber] -> ShowS
RoutingNumber -> String
(Int -> RoutingNumber -> ShowS)
-> (RoutingNumber -> String)
-> ([RoutingNumber] -> ShowS)
-> Show RoutingNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoutingNumber] -> ShowS
$cshowList :: [RoutingNumber] -> ShowS
show :: RoutingNumber -> String
$cshow :: RoutingNumber -> String
showsPrec :: Int -> RoutingNumber -> ShowS
$cshowsPrec :: Int -> RoutingNumber -> ShowS
Show, RoutingNumber -> Q Exp
RoutingNumber -> Q (TExp RoutingNumber)
(RoutingNumber -> Q Exp)
-> (RoutingNumber -> Q (TExp RoutingNumber)) -> Lift RoutingNumber
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: RoutingNumber -> Q (TExp RoutingNumber)
$cliftTyped :: RoutingNumber -> Q (TExp RoutingNumber)
lift :: RoutingNumber -> Q Exp
$clift :: RoutingNumber -> Q Exp
Lift)
deriving newtype (RoutingNumber -> RoutingNumber -> Bool
(RoutingNumber -> RoutingNumber -> Bool)
-> (RoutingNumber -> RoutingNumber -> Bool) -> Eq RoutingNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoutingNumber -> RoutingNumber -> Bool
$c/= :: RoutingNumber -> RoutingNumber -> Bool
== :: RoutingNumber -> RoutingNumber -> Bool
$c== :: RoutingNumber -> RoutingNumber -> Bool
Eq, [RoutingNumber] -> Encoding
[RoutingNumber] -> Value
RoutingNumber -> Encoding
RoutingNumber -> Value
(RoutingNumber -> Value)
-> (RoutingNumber -> Encoding)
-> ([RoutingNumber] -> Value)
-> ([RoutingNumber] -> Encoding)
-> ToJSON RoutingNumber
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RoutingNumber] -> Encoding
$ctoEncodingList :: [RoutingNumber] -> Encoding
toJSONList :: [RoutingNumber] -> Value
$ctoJSONList :: [RoutingNumber] -> Value
toEncoding :: RoutingNumber -> Encoding
$ctoEncoding :: RoutingNumber -> Encoding
toJSON :: RoutingNumber -> Value
$ctoJSON :: RoutingNumber -> Value
ToJSON)
routingNumberRegex :: Regex
routingNumberRegex :: Regex
routingNumberRegex = [re|^[0-9]{9}$|]
mkRoutingNumber :: Text -> Maybe RoutingNumber
mkRoutingNumber :: Text -> Maybe RoutingNumber
mkRoutingNumber Text
t =
if Text
t Text -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ Regex
routingNumberRegex
then RoutingNumber -> Maybe RoutingNumber
forall a. a -> Maybe a
Just (Text -> RoutingNumber
RoutingNumber Text
t)
else Maybe RoutingNumber
forall a. Maybe a
Nothing
routingNumberToText :: RoutingNumber -> Text
routingNumberToText :: RoutingNumber -> Text
routingNumberToText (RoutingNumber Text
t) = Text
t
routingNumberToByteString :: RoutingNumber -> BS8.ByteString
routingNumberToByteString :: RoutingNumber -> ByteString
routingNumberToByteString RoutingNumber
routingNumber = Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ RoutingNumber -> Text
routingNumberToText RoutingNumber
routingNumber
instance HasCodec RoutingNumber where
codec :: JSONCodec RoutingNumber
codec = (Text -> RoutingNumber)
-> (RoutingNumber -> Text)
-> Codec Value Text Text
-> JSONCodec RoutingNumber
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> RoutingNumber
RoutingNumber RoutingNumber -> Text
unRoutingNumber Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
instance FromJSON RoutingNumber where
parseJSON :: Value -> Parser RoutingNumber
parseJSON = String
-> (Text -> Parser RoutingNumber) -> Value -> Parser RoutingNumber
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"RoutingNumber" ((Text -> Parser RoutingNumber) -> Value -> Parser RoutingNumber)
-> (Text -> Parser RoutingNumber) -> Value -> Parser RoutingNumber
forall a b. (a -> b) -> a -> b
$ \Text
t ->
case Text -> Maybe RoutingNumber
mkRoutingNumber Text
t of
Maybe RoutingNumber
Nothing -> String -> Parser RoutingNumber
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser RoutingNumber) -> String -> Parser RoutingNumber
forall a b. (a -> b) -> a -> b
$ String
"Invalid RoutingNumber: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
Just RoutingNumber
routingNumber -> RoutingNumber -> Parser RoutingNumber
forall (f :: * -> *) a. Applicative f => a -> f a
pure RoutingNumber
routingNumber
compileRoutingNumber :: QuasiQuoter
compileRoutingNumber :: QuasiQuoter
compileRoutingNumber =
QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter
{ quoteExp :: String -> Q Exp
quoteExp = String -> Q Exp
compileRoutingNumber',
quotePat :: String -> Q Pat
quotePat = String -> String -> Q Pat
forall a. HasCallStack => String -> a
error String
"RoutingNumber is not a pattern; use routingNumberToText instead",
quoteDec :: String -> Q [Dec]
quoteDec = String -> String -> Q [Dec]
forall a. HasCallStack => String -> a
error String
"routingNumber is not supported at top-level",
quoteType :: String -> Q Type
quoteType = String -> String -> Q Type
forall a. HasCallStack => String -> a
error String
"routingNumber is not supported as a type"
}
where
compileRoutingNumber' :: String -> Q Exp
compileRoutingNumber' :: String -> Q Exp
compileRoutingNumber' String
s = case Text -> Maybe RoutingNumber
mkRoutingNumber (String -> Text
T.pack String
s) of
Maybe RoutingNumber
Nothing -> String -> Q Exp
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invalid RoutingNumber: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
". Must be nine digits, with no other characters.")
Just RoutingNumber
routingNumber -> [|routingNumber|]
newtype Iban = Iban {Iban -> Text
unIban :: Text}
deriving stock (Int -> Iban -> ShowS
[Iban] -> ShowS
Iban -> String
(Int -> Iban -> ShowS)
-> (Iban -> String) -> ([Iban] -> ShowS) -> Show Iban
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Iban] -> ShowS
$cshowList :: [Iban] -> ShowS
show :: Iban -> String
$cshow :: Iban -> String
showsPrec :: Int -> Iban -> ShowS
$cshowsPrec :: Int -> Iban -> ShowS
Show, ReadPrec [Iban]
ReadPrec Iban
Int -> ReadS Iban
ReadS [Iban]
(Int -> ReadS Iban)
-> ReadS [Iban] -> ReadPrec Iban -> ReadPrec [Iban] -> Read Iban
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Iban]
$creadListPrec :: ReadPrec [Iban]
readPrec :: ReadPrec Iban
$creadPrec :: ReadPrec Iban
readList :: ReadS [Iban]
$creadList :: ReadS [Iban]
readsPrec :: Int -> ReadS Iban
$creadsPrec :: Int -> ReadS Iban
Read, Iban -> Q Exp
Iban -> Q (TExp Iban)
(Iban -> Q Exp) -> (Iban -> Q (TExp Iban)) -> Lift Iban
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: Iban -> Q (TExp Iban)
$cliftTyped :: Iban -> Q (TExp Iban)
lift :: Iban -> Q Exp
$clift :: Iban -> Q Exp
Lift)
deriving newtype (Iban -> Iban -> Bool
(Iban -> Iban -> Bool) -> (Iban -> Iban -> Bool) -> Eq Iban
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Iban -> Iban -> Bool
$c/= :: Iban -> Iban -> Bool
== :: Iban -> Iban -> Bool
$c== :: Iban -> Iban -> Bool
Eq, [Iban] -> Encoding
[Iban] -> Value
Iban -> Encoding
Iban -> Value
(Iban -> Value)
-> (Iban -> Encoding)
-> ([Iban] -> Value)
-> ([Iban] -> Encoding)
-> ToJSON Iban
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Iban] -> Encoding
$ctoEncodingList :: [Iban] -> Encoding
toJSONList :: [Iban] -> Value
$ctoJSONList :: [Iban] -> Value
toEncoding :: Iban -> Encoding
$ctoEncoding :: Iban -> Encoding
toJSON :: Iban -> Value
$ctoJSON :: Iban -> Value
ToJSON)
mkIban :: Text -> Maybe Iban
mkIban :: Text -> Maybe Iban
mkIban Text
t = if Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
34 then Iban -> Maybe Iban
forall a. a -> Maybe a
Just (Text -> Iban
Iban Text
t) else Maybe Iban
forall a. Maybe a
Nothing
instance FromJSON Iban where
parseJSON :: Value -> Parser Iban
parseJSON = String -> (Text -> Parser Iban) -> Value -> Parser Iban
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Iban" ((Text -> Parser Iban) -> Value -> Parser Iban)
-> (Text -> Parser Iban) -> Value -> Parser Iban
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Maybe Iban
mkIban Text
t of
Maybe Iban
Nothing -> String -> Parser Iban
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Iban) -> String -> Parser Iban
forall a b. (a -> b) -> a -> b
$ String
"Invalid Iban: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
Just Iban
iban -> Iban -> Parser Iban
forall (f :: * -> *) a. Applicative f => a -> f a
pure Iban
iban
instance HasCodec Iban where
codec :: JSONCodec Iban
codec = (Text -> Iban)
-> (Iban -> Text) -> Codec Value Text Text -> JSONCodec Iban
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> Iban
Iban Iban -> Text
unIban Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
compileIban :: QuasiQuoter
compileIban :: QuasiQuoter
compileIban =
QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter
{ quoteExp :: String -> Q Exp
quoteExp = String -> Q Exp
compileIban',
quotePat :: String -> Q Pat
quotePat = String -> String -> Q Pat
forall a. HasCallStack => String -> a
error String
"Iban is not a pattern - use `ibanToText` instead",
quoteDec :: String -> Q [Dec]
quoteDec = String -> String -> Q [Dec]
forall a. HasCallStack => String -> a
error String
"Iban is not supported at top-level",
quoteType :: String -> Q Type
quoteType = String -> String -> Q Type
forall a. HasCallStack => String -> a
error String
"Iban is not supported as a type"
}
where
compileIban' :: String -> Q Exp
compileIban' :: String -> Q Exp
compileIban' String
s = case Text -> Maybe Iban
mkIban (String -> Text
T.pack String
s) of
Maybe Iban
Nothing -> String -> Q Exp
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q Exp) -> String -> Q Exp
forall a b. (a -> b) -> a -> b
$ String
"Invalid Iban: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s
Just Iban
txt -> [|txt|]
ibanToText :: Iban -> Text
ibanToText :: Iban -> Text
ibanToText (Iban Text
t) = Text
t
newtype Email = Email {Email -> Text
getEmailText :: Text}
deriving stock (Int -> Email -> ShowS
[Email] -> ShowS
Email -> String
(Int -> Email -> ShowS)
-> (Email -> String) -> ([Email] -> ShowS) -> Show Email
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Email] -> ShowS
$cshowList :: [Email] -> ShowS
show :: Email -> String
$cshow :: Email -> String
showsPrec :: Int -> Email -> ShowS
$cshowsPrec :: Int -> Email -> ShowS
Show, Email -> Q Exp
Email -> Q (TExp Email)
(Email -> Q Exp) -> (Email -> Q (TExp Email)) -> Lift Email
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: Email -> Q (TExp Email)
$cliftTyped :: Email -> Q (TExp Email)
lift :: Email -> Q Exp
$clift :: Email -> Q Exp
Lift)
deriving newtype (Email -> Email -> Bool
(Email -> Email -> Bool) -> (Email -> Email -> Bool) -> Eq Email
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Email -> Email -> Bool
$c/= :: Email -> Email -> Bool
== :: Email -> Email -> Bool
$c== :: Email -> Email -> Bool
Eq, Eq Email
Eq Email
-> (Email -> Email -> Ordering)
-> (Email -> Email -> Bool)
-> (Email -> Email -> Bool)
-> (Email -> Email -> Bool)
-> (Email -> Email -> Bool)
-> (Email -> Email -> Email)
-> (Email -> Email -> Email)
-> Ord Email
Email -> Email -> Bool
Email -> Email -> Ordering
Email -> Email -> Email
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
min :: Email -> Email -> Email
$cmin :: Email -> Email -> Email
max :: Email -> Email -> Email
$cmax :: Email -> Email -> Email
>= :: Email -> Email -> Bool
$c>= :: Email -> Email -> Bool
> :: Email -> Email -> Bool
$c> :: Email -> Email -> Bool
<= :: Email -> Email -> Bool
$c<= :: Email -> Email -> Bool
< :: Email -> Email -> Bool
$c< :: Email -> Email -> Bool
compare :: Email -> Email -> Ordering
$ccompare :: Email -> Email -> Ordering
$cp1Ord :: Eq Email
Ord, [Email] -> Encoding
[Email] -> Value
Email -> Encoding
Email -> Value
(Email -> Value)
-> (Email -> Encoding)
-> ([Email] -> Value)
-> ([Email] -> Encoding)
-> ToJSON Email
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Email] -> Encoding
$ctoEncodingList :: [Email] -> Encoding
toJSONList :: [Email] -> Value
$ctoJSONList :: [Email] -> Value
toEncoding :: Email -> Encoding
$ctoEncoding :: Email -> Encoding
toJSON :: Email -> Value
$ctoJSON :: Email -> Value
ToJSON)
emailRegex :: Regex
emailRegex :: Regex
emailRegex = [re|^[a-zA-Z0-9.!#$%&'*+/=?^_`{|}~-]+@[a-zA-Z0-9](?:[a-zA-Z0-9-]{0,61}[a-zA-Z0-9])?(?:\.[a-zA-Z0-9](?:[a-zA-Z0-9-]{0,61}[a-zA-Z0-9])?)*$|]
mkEmail :: Text -> Maybe Email
mkEmail :: Text -> Maybe Email
mkEmail Text
t =
if Text
t Text -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ Regex
emailRegex
then Email -> Maybe Email
forall a. a -> Maybe a
Just (Text -> Email
Email Text
t)
else Maybe Email
forall a. Maybe a
Nothing
emailToText :: Email -> Text
emailToText :: Email -> Text
emailToText = Email -> Text
getEmailText
emailToByteString :: Email -> BS8.ByteString
emailToByteString :: Email -> ByteString
emailToByteString Email
email = Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Email -> Text
emailToText Email
email
instance HasCodec Email where
codec :: JSONCodec Email
codec = (Text -> Email)
-> (Email -> Text) -> Codec Value Text Text -> JSONCodec Email
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> Email
Email Email -> Text
getEmailText Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
instance FromJSON Email where
parseJSON :: Value -> Parser Email
parseJSON (Aeson.String Text
t) = case Text -> Maybe Email
mkEmail Text
t of
Maybe Email
Nothing -> String -> Parser Email
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Email) -> String -> Parser Email
forall a b. (a -> b) -> a -> b
$ String
"Invalid email address: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
t
Just Email
email -> Email -> Parser Email
forall (f :: * -> *) a. Applicative f => a -> f a
pure Email
email
parseJSON Value
v = String -> Parser Email
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser Email) -> String -> Parser Email
forall a b. (a -> b) -> a -> b
$ String
"When trying to parse an Email, expected String, encountered " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Value -> String
forall a. Show a => a -> String
show Value
v
compileEmail :: QuasiQuoter
compileEmail :: QuasiQuoter
compileEmail =
QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter
{ quoteExp :: String -> Q Exp
quoteExp = String -> Q Exp
compileEmail',
quotePat :: String -> Q Pat
quotePat = String -> String -> Q Pat
forall a. HasCallStack => String -> a
error String
"Email is not a pattern; use `emailToText` instead",
quoteDec :: String -> Q [Dec]
quoteDec = String -> String -> Q [Dec]
forall a. HasCallStack => String -> a
error String
"email is not supported at top-level",
quoteType :: String -> Q Type
quoteType = String -> String -> Q Type
forall a. HasCallStack => String -> a
error String
"email is not supported as a type"
}
where
compileEmail' :: String -> Q Exp
compileEmail' :: String -> Q Exp
compileEmail' String
s = case Text -> Maybe Email
mkEmail (String -> Text
T.pack String
s) of
Maybe Email
Nothing -> String -> Q Exp
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"Invalid Email: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
". Make sure you aren't wrapping the email in quotes.")
Just Email
email -> [|email|]
newtype City = City
{ City -> Text
unCity :: Text
}
deriving (City -> City -> Bool
(City -> City -> Bool) -> (City -> City -> Bool) -> Eq City
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: City -> City -> Bool
$c/= :: City -> City -> Bool
== :: City -> City -> Bool
$c== :: City -> City -> Bool
Eq, Int -> City -> ShowS
[City] -> ShowS
City -> String
(Int -> City -> ShowS)
-> (City -> String) -> ([City] -> ShowS) -> Show City
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [City] -> ShowS
$cshowList :: [City] -> ShowS
show :: City -> String
$cshow :: City -> String
showsPrec :: Int -> City -> ShowS
$cshowsPrec :: Int -> City -> ShowS
Show, [City] -> Encoding
[City] -> Value
City -> Encoding
City -> Value
(City -> Value)
-> (City -> Encoding)
-> ([City] -> Value)
-> ([City] -> Encoding)
-> ToJSON City
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [City] -> Encoding
$ctoEncodingList :: [City] -> Encoding
toJSONList :: [City] -> Value
$ctoJSONList :: [City] -> Value
toEncoding :: City -> Encoding
$ctoEncoding :: City -> Encoding
toJSON :: City -> Value
$ctoJSON :: City -> Value
ToJSON, Value -> Parser [City]
Value -> Parser City
(Value -> Parser City) -> (Value -> Parser [City]) -> FromJSON City
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [City]
$cparseJSONList :: Value -> Parser [City]
parseJSON :: Value -> Parser City
$cparseJSON :: Value -> Parser City
FromJSON)
instance HasCodec City where
codec :: JSONCodec City
codec = (Text -> City)
-> (City -> Text) -> Codec Value Text Text -> JSONCodec City
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> City
City City -> Text
unCity Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype PostalCode = PostalCode
{ PostalCode -> Text
unPostalCode :: Text
}
deriving (PostalCode -> PostalCode -> Bool
(PostalCode -> PostalCode -> Bool)
-> (PostalCode -> PostalCode -> Bool) -> Eq PostalCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostalCode -> PostalCode -> Bool
$c/= :: PostalCode -> PostalCode -> Bool
== :: PostalCode -> PostalCode -> Bool
$c== :: PostalCode -> PostalCode -> Bool
Eq, Int -> PostalCode -> ShowS
[PostalCode] -> ShowS
PostalCode -> String
(Int -> PostalCode -> ShowS)
-> (PostalCode -> String)
-> ([PostalCode] -> ShowS)
-> Show PostalCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostalCode] -> ShowS
$cshowList :: [PostalCode] -> ShowS
show :: PostalCode -> String
$cshow :: PostalCode -> String
showsPrec :: Int -> PostalCode -> ShowS
$cshowsPrec :: Int -> PostalCode -> ShowS
Show, [PostalCode] -> Encoding
[PostalCode] -> Value
PostalCode -> Encoding
PostalCode -> Value
(PostalCode -> Value)
-> (PostalCode -> Encoding)
-> ([PostalCode] -> Value)
-> ([PostalCode] -> Encoding)
-> ToJSON PostalCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PostalCode] -> Encoding
$ctoEncodingList :: [PostalCode] -> Encoding
toJSONList :: [PostalCode] -> Value
$ctoJSONList :: [PostalCode] -> Value
toEncoding :: PostalCode -> Encoding
$ctoEncoding :: PostalCode -> Encoding
toJSON :: PostalCode -> Value
$ctoJSON :: PostalCode -> Value
ToJSON, Value -> Parser [PostalCode]
Value -> Parser PostalCode
(Value -> Parser PostalCode)
-> (Value -> Parser [PostalCode]) -> FromJSON PostalCode
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PostalCode]
$cparseJSONList :: Value -> Parser [PostalCode]
parseJSON :: Value -> Parser PostalCode
$cparseJSON :: Value -> Parser PostalCode
FromJSON)
instance HasCodec PostalCode where
codec :: JSONCodec PostalCode
codec = (Text -> PostalCode)
-> (PostalCode -> Text)
-> Codec Value Text Text
-> JSONCodec PostalCode
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> PostalCode
PostalCode PostalCode -> Text
unPostalCode Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype SwiftCode = SwiftCode
{ SwiftCode -> Text
unSwiftCode :: Text
}
deriving stock (Int -> SwiftCode -> ShowS
[SwiftCode] -> ShowS
SwiftCode -> String
(Int -> SwiftCode -> ShowS)
-> (SwiftCode -> String)
-> ([SwiftCode] -> ShowS)
-> Show SwiftCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwiftCode] -> ShowS
$cshowList :: [SwiftCode] -> ShowS
show :: SwiftCode -> String
$cshow :: SwiftCode -> String
showsPrec :: Int -> SwiftCode -> ShowS
$cshowsPrec :: Int -> SwiftCode -> ShowS
Show, SwiftCode -> Q Exp
SwiftCode -> Q (TExp SwiftCode)
(SwiftCode -> Q Exp)
-> (SwiftCode -> Q (TExp SwiftCode)) -> Lift SwiftCode
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: SwiftCode -> Q (TExp SwiftCode)
$cliftTyped :: SwiftCode -> Q (TExp SwiftCode)
lift :: SwiftCode -> Q Exp
$clift :: SwiftCode -> Q Exp
Lift)
deriving newtype (SwiftCode -> SwiftCode -> Bool
(SwiftCode -> SwiftCode -> Bool)
-> (SwiftCode -> SwiftCode -> Bool) -> Eq SwiftCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwiftCode -> SwiftCode -> Bool
$c/= :: SwiftCode -> SwiftCode -> Bool
== :: SwiftCode -> SwiftCode -> Bool
$c== :: SwiftCode -> SwiftCode -> Bool
Eq, Eq SwiftCode
Eq SwiftCode
-> (SwiftCode -> SwiftCode -> Ordering)
-> (SwiftCode -> SwiftCode -> Bool)
-> (SwiftCode -> SwiftCode -> Bool)
-> (SwiftCode -> SwiftCode -> Bool)
-> (SwiftCode -> SwiftCode -> Bool)
-> (SwiftCode -> SwiftCode -> SwiftCode)
-> (SwiftCode -> SwiftCode -> SwiftCode)
-> Ord SwiftCode
SwiftCode -> SwiftCode -> Bool
SwiftCode -> SwiftCode -> Ordering
SwiftCode -> SwiftCode -> SwiftCode
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
min :: SwiftCode -> SwiftCode -> SwiftCode
$cmin :: SwiftCode -> SwiftCode -> SwiftCode
max :: SwiftCode -> SwiftCode -> SwiftCode
$cmax :: SwiftCode -> SwiftCode -> SwiftCode
>= :: SwiftCode -> SwiftCode -> Bool
$c>= :: SwiftCode -> SwiftCode -> Bool
> :: SwiftCode -> SwiftCode -> Bool
$c> :: SwiftCode -> SwiftCode -> Bool
<= :: SwiftCode -> SwiftCode -> Bool
$c<= :: SwiftCode -> SwiftCode -> Bool
< :: SwiftCode -> SwiftCode -> Bool
$c< :: SwiftCode -> SwiftCode -> Bool
compare :: SwiftCode -> SwiftCode -> Ordering
$ccompare :: SwiftCode -> SwiftCode -> Ordering
$cp1Ord :: Eq SwiftCode
Ord, [SwiftCode] -> Encoding
[SwiftCode] -> Value
SwiftCode -> Encoding
SwiftCode -> Value
(SwiftCode -> Value)
-> (SwiftCode -> Encoding)
-> ([SwiftCode] -> Value)
-> ([SwiftCode] -> Encoding)
-> ToJSON SwiftCode
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [SwiftCode] -> Encoding
$ctoEncodingList :: [SwiftCode] -> Encoding
toJSONList :: [SwiftCode] -> Value
$ctoJSONList :: [SwiftCode] -> Value
toEncoding :: SwiftCode -> Encoding
$ctoEncoding :: SwiftCode -> Encoding
toJSON :: SwiftCode -> Value
$ctoJSON :: SwiftCode -> Value
ToJSON)
swiftCountryCodes :: Set.Set Text
swiftCountryCodes :: Set Text
swiftCountryCodes = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ([Text] -> Set Text) -> [Text] -> Set Text
forall a b. (a -> b) -> a -> b
$ Text
"XK" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (Country -> Text
alphaTwoUpper (Country -> Text) -> [Country] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Country
forall a. Bounded a => a
minBound .. Country
forall a. Bounded a => a
maxBound] :: [Country]))
swiftCodeRegex :: Regex
swiftCodeRegex :: Regex
swiftCodeRegex = [re|^[A-Z]{6}[A-Z0-9]{2}(?:[A-Z0-9]{3})?$|]
mkSwiftCode :: Text -> Maybe SwiftCode
mkSwiftCode :: Text -> Maybe SwiftCode
mkSwiftCode Text
txt = do
let t :: Text
t = Text -> Text
T.toUpper (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip Text
txt
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text
t Text -> Regex -> Bool
forall a. ConvertibleStrings a ByteString => a -> Regex -> Bool
=~ Regex
swiftCodeRegex
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member (Text -> Text
getCountryFromSwiftCodeText Text
t) Set Text
swiftCountryCodes
SwiftCode -> Maybe SwiftCode
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SwiftCode -> Maybe SwiftCode) -> SwiftCode -> Maybe SwiftCode
forall a b. (a -> b) -> a -> b
$ Text -> SwiftCode
SwiftCode Text
t
instance HasCodec SwiftCode where
codec :: JSONCodec SwiftCode
codec = (Text -> SwiftCode)
-> (SwiftCode -> Text)
-> Codec Value Text Text
-> JSONCodec SwiftCode
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> SwiftCode
SwiftCode SwiftCode -> Text
unSwiftCode Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
instance FromJSON SwiftCode where
parseJSON :: Value -> Parser SwiftCode
parseJSON = String -> (Text -> Parser SwiftCode) -> Value -> Parser SwiftCode
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"SwiftCode" ((Text -> Parser SwiftCode) -> Value -> Parser SwiftCode)
-> (Text -> Parser SwiftCode) -> Value -> Parser SwiftCode
forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Maybe SwiftCode
mkSwiftCode Text
t of
Maybe SwiftCode
Nothing -> String -> Parser SwiftCode
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser SwiftCode) -> String -> Parser SwiftCode
forall a b. (a -> b) -> a -> b
$ String
"Invalid SwiftCode: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
t
Just SwiftCode
swift -> SwiftCode -> Parser SwiftCode
forall (f :: * -> *) a. Applicative f => a -> f a
pure SwiftCode
swift
compileSwiftCode :: QuasiQuoter
compileSwiftCode :: QuasiQuoter
compileSwiftCode =
QuasiQuoter :: (String -> Q Exp)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
QuasiQuoter
{ quoteExp :: String -> Q Exp
quoteExp = String -> Q Exp
compileSwiftCode',
quotePat :: String -> Q Pat
quotePat = String -> String -> Q Pat
forall a. HasCallStack => String -> a
error String
"SwiftCode is not a pattern; use swiftCodeToText instead",
quoteDec :: String -> Q [Dec]
quoteDec = String -> String -> Q [Dec]
forall a. HasCallStack => String -> a
error String
"SwiftCode is not supported at top-level",
quoteType :: String -> Q Type
quoteType = String -> String -> Q Type
forall a. HasCallStack => String -> a
error String
"SwiftCode is not supported as a type"
}
where
compileSwiftCode' :: String -> Q Exp
compileSwiftCode' :: String -> Q Exp
compileSwiftCode' String
s = case Text -> Maybe SwiftCode
mkSwiftCode (String -> Text
T.pack String
s) of
Maybe SwiftCode
Nothing -> String -> Q Exp
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q Exp) -> String -> Q Exp
forall a b. (a -> b) -> a -> b
$ String
"Invalid SwiftCode: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
s
Just SwiftCode
txt -> [|txt|]
swiftCodeToText :: SwiftCode -> Text
swiftCodeToText :: SwiftCode -> Text
swiftCodeToText (SwiftCode Text
t) = Text
t
getCountryFromSwiftCodeText :: Text -> Text
getCountryFromSwiftCodeText :: Text -> Text
getCountryFromSwiftCodeText = Int -> Text -> Text
T.take Int
2 (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> Text
T.drop Int
4
getCountryFromSwiftCode :: SwiftCode -> Text
getCountryFromSwiftCode :: SwiftCode -> Text
getCountryFromSwiftCode = Text -> Text
getCountryFromSwiftCodeText (Text -> Text) -> (SwiftCode -> Text) -> SwiftCode -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SwiftCode -> Text
swiftCodeToText
get8DigitSwiftCode :: SwiftCode -> SwiftCode
get8DigitSwiftCode :: SwiftCode -> SwiftCode
get8DigitSwiftCode = Text -> SwiftCode
coerce (Text -> SwiftCode)
-> (SwiftCode -> Text) -> SwiftCode -> SwiftCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> Text
T.take Int
8 (Text -> Text) -> (SwiftCode -> Text) -> SwiftCode -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SwiftCode -> Text
coerce
getBranchCodeFromSwiftCode :: SwiftCode -> Maybe Text
getBranchCodeFromSwiftCode :: SwiftCode -> Maybe Text
getBranchCodeFromSwiftCode SwiftCode
swiftCode = do
let swiftCodeText :: Text
swiftCodeText = SwiftCode -> Text
swiftCodeToText SwiftCode
swiftCode
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text -> Int
T.length Text
swiftCodeText Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
11)
Text -> Maybe Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int -> Text -> Text
T.drop Int
8 Text
swiftCodeText)
newtype District = District
{ District -> Text
unDistrict :: Text
}
deriving (District -> District -> Bool
(District -> District -> Bool)
-> (District -> District -> Bool) -> Eq District
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: District -> District -> Bool
$c/= :: District -> District -> Bool
== :: District -> District -> Bool
$c== :: District -> District -> Bool
Eq, Int -> District -> ShowS
[District] -> ShowS
District -> String
(Int -> District -> ShowS)
-> (District -> String) -> ([District] -> ShowS) -> Show District
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [District] -> ShowS
$cshowList :: [District] -> ShowS
show :: District -> String
$cshow :: District -> String
showsPrec :: Int -> District -> ShowS
$cshowsPrec :: Int -> District -> ShowS
Show)
deriving
( Value -> Parser [District]
Value -> Parser District
(Value -> Parser District)
-> (Value -> Parser [District]) -> FromJSON District
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [District]
$cparseJSONList :: Value -> Parser [District]
parseJSON :: Value -> Parser District
$cparseJSON :: Value -> Parser District
FromJSON,
[District] -> Encoding
[District] -> Value
District -> Encoding
District -> Value
(District -> Value)
-> (District -> Encoding)
-> ([District] -> Value)
-> ([District] -> Encoding)
-> ToJSON District
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [District] -> Encoding
$ctoEncodingList :: [District] -> Encoding
toJSONList :: [District] -> Value
$ctoJSONList :: [District] -> Value
toEncoding :: District -> Encoding
$ctoEncoding :: District -> Encoding
toJSON :: District -> Value
$ctoJSON :: District -> Value
ToJSON
)
via (Autodocodec District)
instance HasCodec District where
codec :: JSONCodec District
codec = (Text -> District)
-> (District -> Text)
-> Codec Value Text Text
-> JSONCodec District
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> District
District District -> Text
unDistrict Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype ISO3166Alpha2 = ISO3166Alpha2
{ ISO3166Alpha2 -> Text
unISO3166Alpha2 :: Text
}
deriving newtype (ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
(ISO3166Alpha2 -> ISO3166Alpha2 -> Bool)
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> Bool) -> Eq ISO3166Alpha2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
$c/= :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
== :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
$c== :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
Eq, Int -> ISO3166Alpha2 -> ShowS
[ISO3166Alpha2] -> ShowS
ISO3166Alpha2 -> String
(Int -> ISO3166Alpha2 -> ShowS)
-> (ISO3166Alpha2 -> String)
-> ([ISO3166Alpha2] -> ShowS)
-> Show ISO3166Alpha2
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ISO3166Alpha2] -> ShowS
$cshowList :: [ISO3166Alpha2] -> ShowS
show :: ISO3166Alpha2 -> String
$cshow :: ISO3166Alpha2 -> String
showsPrec :: Int -> ISO3166Alpha2 -> ShowS
$cshowsPrec :: Int -> ISO3166Alpha2 -> ShowS
Show, Eq ISO3166Alpha2
Eq ISO3166Alpha2
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> Ordering)
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> Bool)
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> Bool)
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> Bool)
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> Bool)
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> ISO3166Alpha2)
-> (ISO3166Alpha2 -> ISO3166Alpha2 -> ISO3166Alpha2)
-> Ord ISO3166Alpha2
ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
ISO3166Alpha2 -> ISO3166Alpha2 -> Ordering
ISO3166Alpha2 -> ISO3166Alpha2 -> ISO3166Alpha2
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
min :: ISO3166Alpha2 -> ISO3166Alpha2 -> ISO3166Alpha2
$cmin :: ISO3166Alpha2 -> ISO3166Alpha2 -> ISO3166Alpha2
max :: ISO3166Alpha2 -> ISO3166Alpha2 -> ISO3166Alpha2
$cmax :: ISO3166Alpha2 -> ISO3166Alpha2 -> ISO3166Alpha2
>= :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
$c>= :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
> :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
$c> :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
<= :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
$c<= :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
< :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
$c< :: ISO3166Alpha2 -> ISO3166Alpha2 -> Bool
compare :: ISO3166Alpha2 -> ISO3166Alpha2 -> Ordering
$ccompare :: ISO3166Alpha2 -> ISO3166Alpha2 -> Ordering
$cp1Ord :: Eq ISO3166Alpha2
Ord)
deriving
( Value -> Parser [ISO3166Alpha2]
Value -> Parser ISO3166Alpha2
(Value -> Parser ISO3166Alpha2)
-> (Value -> Parser [ISO3166Alpha2]) -> FromJSON ISO3166Alpha2
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ISO3166Alpha2]
$cparseJSONList :: Value -> Parser [ISO3166Alpha2]
parseJSON :: Value -> Parser ISO3166Alpha2
$cparseJSON :: Value -> Parser ISO3166Alpha2
FromJSON,
[ISO3166Alpha2] -> Encoding
[ISO3166Alpha2] -> Value
ISO3166Alpha2 -> Encoding
ISO3166Alpha2 -> Value
(ISO3166Alpha2 -> Value)
-> (ISO3166Alpha2 -> Encoding)
-> ([ISO3166Alpha2] -> Value)
-> ([ISO3166Alpha2] -> Encoding)
-> ToJSON ISO3166Alpha2
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ISO3166Alpha2] -> Encoding
$ctoEncodingList :: [ISO3166Alpha2] -> Encoding
toJSONList :: [ISO3166Alpha2] -> Value
$ctoJSONList :: [ISO3166Alpha2] -> Value
toEncoding :: ISO3166Alpha2 -> Encoding
$ctoEncoding :: ISO3166Alpha2 -> Encoding
toJSON :: ISO3166Alpha2 -> Value
$ctoJSON :: ISO3166Alpha2 -> Value
ToJSON
)
via (Autodocodec ISO3166Alpha2)
instance HasCodec ISO3166Alpha2 where
codec :: JSONCodec ISO3166Alpha2
codec = (Text -> ISO3166Alpha2)
-> (ISO3166Alpha2 -> Text)
-> Codec Value Text Text
-> JSONCodec ISO3166Alpha2
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> ISO3166Alpha2
ISO3166Alpha2 ISO3166Alpha2 -> Text
unISO3166Alpha2 Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype TrackingReference = TrackingReference
{ TrackingReference -> Text
unTrackingReference :: Text
}
deriving (TrackingReference -> TrackingReference -> Bool
(TrackingReference -> TrackingReference -> Bool)
-> (TrackingReference -> TrackingReference -> Bool)
-> Eq TrackingReference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrackingReference -> TrackingReference -> Bool
$c/= :: TrackingReference -> TrackingReference -> Bool
== :: TrackingReference -> TrackingReference -> Bool
$c== :: TrackingReference -> TrackingReference -> Bool
Eq, Int -> TrackingReference -> ShowS
[TrackingReference] -> ShowS
TrackingReference -> String
(Int -> TrackingReference -> ShowS)
-> (TrackingReference -> String)
-> ([TrackingReference] -> ShowS)
-> Show TrackingReference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrackingReference] -> ShowS
$cshowList :: [TrackingReference] -> ShowS
show :: TrackingReference -> String
$cshow :: TrackingReference -> String
showsPrec :: Int -> TrackingReference -> ShowS
$cshowsPrec :: Int -> TrackingReference -> ShowS
Show, [TrackingReference] -> Encoding
[TrackingReference] -> Value
TrackingReference -> Encoding
TrackingReference -> Value
(TrackingReference -> Value)
-> (TrackingReference -> Encoding)
-> ([TrackingReference] -> Value)
-> ([TrackingReference] -> Encoding)
-> ToJSON TrackingReference
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TrackingReference] -> Encoding
$ctoEncodingList :: [TrackingReference] -> Encoding
toJSONList :: [TrackingReference] -> Value
$ctoJSONList :: [TrackingReference] -> Value
toEncoding :: TrackingReference -> Encoding
$ctoEncoding :: TrackingReference -> Encoding
toJSON :: TrackingReference -> Value
$ctoJSON :: TrackingReference -> Value
ToJSON, Value -> Parser [TrackingReference]
Value -> Parser TrackingReference
(Value -> Parser TrackingReference)
-> (Value -> Parser [TrackingReference])
-> FromJSON TrackingReference
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TrackingReference]
$cparseJSONList :: Value -> Parser [TrackingReference]
parseJSON :: Value -> Parser TrackingReference
$cparseJSON :: Value -> Parser TrackingReference
FromJSON)
instance HasCodec TrackingReference where
codec :: JSONCodec TrackingReference
codec = (Text -> TrackingReference)
-> (TrackingReference -> Text)
-> Codec Value Text Text
-> JSONCodec TrackingReference
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> TrackingReference
TrackingReference TrackingReference -> Text
unTrackingReference Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype HexString = HexString
{ HexString -> Text
unHexString :: Text
}
deriving (HexString -> HexString -> Bool
(HexString -> HexString -> Bool)
-> (HexString -> HexString -> Bool) -> Eq HexString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HexString -> HexString -> Bool
$c/= :: HexString -> HexString -> Bool
== :: HexString -> HexString -> Bool
$c== :: HexString -> HexString -> Bool
Eq, Int -> HexString -> ShowS
[HexString] -> ShowS
HexString -> String
(Int -> HexString -> ShowS)
-> (HexString -> String)
-> ([HexString] -> ShowS)
-> Show HexString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HexString] -> ShowS
$cshowList :: [HexString] -> ShowS
show :: HexString -> String
$cshow :: HexString -> String
showsPrec :: Int -> HexString -> ShowS
$cshowsPrec :: Int -> HexString -> ShowS
Show, [HexString] -> Encoding
[HexString] -> Value
HexString -> Encoding
HexString -> Value
(HexString -> Value)
-> (HexString -> Encoding)
-> ([HexString] -> Value)
-> ([HexString] -> Encoding)
-> ToJSON HexString
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [HexString] -> Encoding
$ctoEncodingList :: [HexString] -> Encoding
toJSONList :: [HexString] -> Value
$ctoJSONList :: [HexString] -> Value
toEncoding :: HexString -> Encoding
$ctoEncoding :: HexString -> Encoding
toJSON :: HexString -> Value
$ctoJSON :: HexString -> Value
ToJSON, Value -> Parser [HexString]
Value -> Parser HexString
(Value -> Parser HexString)
-> (Value -> Parser [HexString]) -> FromJSON HexString
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [HexString]
$cparseJSONList :: Value -> Parser [HexString]
parseJSON :: Value -> Parser HexString
$cparseJSON :: Value -> Parser HexString
FromJSON)
instance HasCodec HexString where
codec :: JSONCodec HexString
codec = (Text -> HexString)
-> (HexString -> Text)
-> Codec Value Text Text
-> JSONCodec HexString
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> HexString
HexString HexString -> Text
unHexString Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
newtype WalletId = WalletId
{ WalletId -> Text
unWalletId :: Text
}
deriving (WalletId -> WalletId -> Bool
(WalletId -> WalletId -> Bool)
-> (WalletId -> WalletId -> Bool) -> Eq WalletId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WalletId -> WalletId -> Bool
$c/= :: WalletId -> WalletId -> Bool
== :: WalletId -> WalletId -> Bool
$c== :: WalletId -> WalletId -> Bool
Eq, Int -> WalletId -> ShowS
[WalletId] -> ShowS
WalletId -> String
(Int -> WalletId -> ShowS)
-> (WalletId -> String) -> ([WalletId] -> ShowS) -> Show WalletId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WalletId] -> ShowS
$cshowList :: [WalletId] -> ShowS
show :: WalletId -> String
$cshow :: WalletId -> String
showsPrec :: Int -> WalletId -> ShowS
$cshowsPrec :: Int -> WalletId -> ShowS
Show, [WalletId] -> Encoding
[WalletId] -> Value
WalletId -> Encoding
WalletId -> Value
(WalletId -> Value)
-> (WalletId -> Encoding)
-> ([WalletId] -> Value)
-> ([WalletId] -> Encoding)
-> ToJSON WalletId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WalletId] -> Encoding
$ctoEncodingList :: [WalletId] -> Encoding
toJSONList :: [WalletId] -> Value
$ctoJSONList :: [WalletId] -> Value
toEncoding :: WalletId -> Encoding
$ctoEncoding :: WalletId -> Encoding
toJSON :: WalletId -> Value
$ctoJSON :: WalletId -> Value
ToJSON, Value -> Parser [WalletId]
Value -> Parser WalletId
(Value -> Parser WalletId)
-> (Value -> Parser [WalletId]) -> FromJSON WalletId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WalletId]
$cparseJSONList :: Value -> Parser [WalletId]
parseJSON :: Value -> Parser WalletId
$cparseJSON :: Value -> Parser WalletId
FromJSON)
instance HasCodec WalletId where
codec :: JSONCodec WalletId
codec = (Text -> WalletId)
-> (WalletId -> Text)
-> Codec Value Text Text
-> JSONCodec WalletId
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
dimapCodec Text -> WalletId
WalletId WalletId -> Text
unWalletId Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
instance HasCodec UUID where
codec :: JSONCodec UUID
codec = (Text -> Either String UUID)
-> (UUID -> Text) -> Codec Value Text Text -> JSONCodec UUID
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> Either String newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
bimapCodec Text -> Either String UUID
forall a. IsString a => Text -> Either a UUID
f UUID -> Text
UUID.toText Codec Value Text Text
forall value. HasCodec value => JSONCodec value
codec
where
f :: Text -> Either a UUID
f Text
t =
case Text -> Maybe UUID
UUID.fromText Text
t of
Maybe UUID
Nothing -> a -> Either a UUID
forall a b. a -> Either a b
Left a
"Invalid Text when parsing UUID"
Just UUID
u -> UUID -> Either a UUID
forall a b. b -> Either a b
Right UUID
u