{-# LANGUAGE NumericUnderscores #-}
module Blockfrost.Types.Shared.Amount
where
import Blockfrost.Types.Shared.Ada (Lovelaces)
import Data.Aeson
( FromJSON (..)
, ToJSON (..)
, Value (Object)
, object
, withObject
, (.:)
, (.=)
)
import GHC.Generics
import qualified Money
import Servant.Docs (ToSample (..), samples)
import qualified Text.Read
data Amount =
AdaAmount Lovelaces
| AssetAmount Money.SomeDiscrete
deriving (Amount -> Amount -> Bool
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
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, Eq Amount
Amount -> Amount -> Bool
Amount -> Amount -> Ordering
Amount -> Amount -> Amount
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 :: Amount -> Amount -> Amount
$cmin :: Amount -> Amount -> Amount
max :: Amount -> Amount -> Amount
$cmax :: Amount -> Amount -> Amount
>= :: Amount -> Amount -> Bool
$c>= :: Amount -> Amount -> Bool
> :: Amount -> Amount -> Bool
$c> :: Amount -> Amount -> Bool
<= :: Amount -> Amount -> Bool
$c<= :: Amount -> Amount -> Bool
< :: Amount -> Amount -> Bool
$c< :: Amount -> Amount -> Bool
compare :: Amount -> Amount -> Ordering
$ccompare :: Amount -> Amount -> Ordering
Ord, forall x. Rep Amount x -> Amount
forall x. Amount -> Rep Amount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Amount x -> Amount
$cfrom :: forall x. Amount -> Rep Amount x
Generic)
unitScale :: Money.Scale
unitScale :: Scale
unitScale = let (Just Scale
s) = Rational -> Maybe Scale
Money.scaleFromRational Rational
1 in Scale
s
instance ToJSON Money.SomeDiscrete where
toJSON :: SomeDiscrete -> Value
toJSON SomeDiscrete
sd =
[Pair] -> Value
object [ Key
"unit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SomeDiscrete -> Text
Money.someDiscreteCurrency SomeDiscrete
sd
, Key
"quantity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. Show a => a -> String
show (SomeDiscrete -> Integer
Money.someDiscreteAmount SomeDiscrete
sd)
]
instance FromJSON Money.SomeDiscrete where
parseJSON :: Value -> Parser SomeDiscrete
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"amount" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Text
u <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"unit"
(String
strQuant :: String) <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"quantity"
case forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
strQuant of
Maybe Integer
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Unable to read quantity as Integer"
Just Integer
quant -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Text -> Scale -> Integer -> SomeDiscrete
Money.mkSomeDiscrete Text
u Scale
unitScale Integer
quant
instance ToJSON Amount where
toJSON :: Amount -> Value
toJSON (AdaAmount Lovelaces
lovelaces) =
[Pair] -> Value
object [ Key
"unit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= (String
"lovelace" :: String)
, Key
"quantity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON Lovelaces
lovelaces
]
toJSON (AssetAmount SomeDiscrete
av) = forall a. ToJSON a => a -> Value
toJSON SomeDiscrete
av
instance FromJSON Amount where
parseJSON :: Value -> Parser Amount
parseJSON x :: Value
x@(Object Object
o) = do
(String
u :: String) <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"unit"
Value
v <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"quantity"
case String
u of
String
"lovelace" -> Lovelaces -> Amount
AdaAmount forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
String
_ -> SomeDiscrete -> Amount
AssetAmount forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
x
parseJSON Value
other = forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Amount expecting object, got" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Value
other
instance ToSample Amount where
toSamples :: Proxy Amount -> [(Text, Amount)]
toSamples = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [(Text, a)]
samples
[ Lovelaces -> Amount
AdaAmount Discrete' "ADA" '(1000000, 1)
42000000
, SomeDiscrete -> Amount
AssetAmount
forall a b. (a -> b) -> a -> b
$ forall (currency :: Symbol) (scale :: (Natural, Natural)).
(KnownSymbol currency, GoodScale scale) =>
Discrete' currency scale -> SomeDiscrete
Money.toSomeDiscrete
(Discrete'
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
'(1, 1)
12 :: Money.Discrete'
"b0d07d45fe9514f80213f4020e5a61241458be626841cde717cb38a76e7574636f696e"
'(1,1))
, SomeDiscrete -> Amount
AssetAmount
forall a b. (a -> b) -> a -> b
$ forall (currency :: Symbol) (scale :: (Natural, Natural)).
(KnownSymbol currency, GoodScale scale) =>
Discrete' currency scale -> SomeDiscrete
Money.toSomeDiscrete
(Discrete'
"6804edf9712d2b619edb6ac86861fe93a730693183a262b165fcc1ba1bc99cad"
'(1, 1)
18605647 :: Money.Discrete'
"6804edf9712d2b619edb6ac86861fe93a730693183a262b165fcc1ba1bc99cad"
'(1,1))
]