{-# LANGUAGE RecordWildCards #-}
module Console.BnbStaking.Csv
( makeCsvContents
, ExportData (..)
, convertReward
, MyZonedTime (..)
) where
import Data.Csv
( DefaultOrdered
, ToField (..)
, ToNamedRecord
, encodeDefaultOrderedByName
)
import Data.Scientific
( FPFormat (..)
, formatScientific
)
import Data.Time
( ZonedTime (..)
, defaultTimeLocale
, formatTime
, utcToLocalZonedTime
)
import GHC.Generics (Generic)
import Console.BnbStaking.Api (Reward (..))
import Data.ByteString.Lazy qualified as LBS
import Data.Text qualified as T
makeCsvContents :: [Reward] -> IO LBS.ByteString
makeCsvContents :: [Reward] -> IO ByteString
makeCsvContents = ([ExportData] -> ByteString) -> IO [ExportData] -> IO ByteString
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [ExportData] -> ByteString
forall a. (DefaultOrdered a, ToNamedRecord a) => [a] -> ByteString
encodeDefaultOrderedByName (IO [ExportData] -> IO ByteString)
-> ([Reward] -> IO [ExportData]) -> [Reward] -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Reward -> IO ExportData) -> [Reward] -> IO [ExportData]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Reward -> IO ExportData
convertReward
data ExportData = ExportData
{ ExportData -> MyZonedTime
time :: MyZonedTime
, ExportData -> Text
amount :: T.Text
, ExportData -> Text
currency :: T.Text
, ExportData -> Text
delegator :: T.Text
, ExportData -> Text
validator :: T.Text
, ExportData -> Text
validatorAddress :: T.Text
, ExportData -> Integer
height :: Integer
}
deriving (Int -> ExportData -> ShowS
[ExportData] -> ShowS
ExportData -> String
(Int -> ExportData -> ShowS)
-> (ExportData -> String)
-> ([ExportData] -> ShowS)
-> Show ExportData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExportData -> ShowS
showsPrec :: Int -> ExportData -> ShowS
$cshow :: ExportData -> String
show :: ExportData -> String
$cshowList :: [ExportData] -> ShowS
showList :: [ExportData] -> ShowS
Show, ReadPrec [ExportData]
ReadPrec ExportData
Int -> ReadS ExportData
ReadS [ExportData]
(Int -> ReadS ExportData)
-> ReadS [ExportData]
-> ReadPrec ExportData
-> ReadPrec [ExportData]
-> Read ExportData
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExportData
readsPrec :: Int -> ReadS ExportData
$creadList :: ReadS [ExportData]
readList :: ReadS [ExportData]
$creadPrec :: ReadPrec ExportData
readPrec :: ReadPrec ExportData
$creadListPrec :: ReadPrec [ExportData]
readListPrec :: ReadPrec [ExportData]
Read, (forall x. ExportData -> Rep ExportData x)
-> (forall x. Rep ExportData x -> ExportData) -> Generic ExportData
forall x. Rep ExportData x -> ExportData
forall x. ExportData -> Rep ExportData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ExportData -> Rep ExportData x
from :: forall x. ExportData -> Rep ExportData x
$cto :: forall x. Rep ExportData x -> ExportData
to :: forall x. Rep ExportData x -> ExportData
Generic)
instance ToNamedRecord ExportData
instance DefaultOrdered ExportData
convertReward :: Reward -> IO ExportData
convertReward :: Reward -> IO ExportData
convertReward Reward {Integer
Text
Scientific
UTCTime
rValidatorName :: Text
rValidatorAddress :: Text
rDelegator :: Text
rChainId :: Text
rHeight :: Integer
rReward :: Scientific
rRewardTime :: UTCTime
rValidatorName :: Reward -> Text
rValidatorAddress :: Reward -> Text
rDelegator :: Reward -> Text
rChainId :: Reward -> Text
rHeight :: Reward -> Integer
rReward :: Reward -> Scientific
rRewardTime :: Reward -> UTCTime
..} = do
ZonedTime
localRewardTime <- UTCTime -> IO ZonedTime
utcToLocalZonedTime UTCTime
rRewardTime
ExportData -> IO ExportData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ExportData -> IO ExportData) -> ExportData -> IO ExportData
forall a b. (a -> b) -> a -> b
$
ExportData
{ time :: MyZonedTime
time = ZonedTime -> MyZonedTime
MyZonedTime ZonedTime
localRewardTime
, amount :: Text
amount = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ FPFormat -> Maybe Int -> Scientific -> String
formatScientific FPFormat
Fixed (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
8) Scientific
rReward
, currency :: Text
currency = Text
"BNB"
, delegator :: Text
delegator = Text
rDelegator
, validator :: Text
validator = Text
rValidatorName
, validatorAddress :: Text
validatorAddress = Text
rValidatorAddress
, height :: Integer
height = Integer
rHeight
}
newtype MyZonedTime = MyZonedTime {MyZonedTime -> ZonedTime
fromMyZonedTime :: ZonedTime} deriving (Int -> MyZonedTime -> ShowS
[MyZonedTime] -> ShowS
MyZonedTime -> String
(Int -> MyZonedTime -> ShowS)
-> (MyZonedTime -> String)
-> ([MyZonedTime] -> ShowS)
-> Show MyZonedTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MyZonedTime -> ShowS
showsPrec :: Int -> MyZonedTime -> ShowS
$cshow :: MyZonedTime -> String
show :: MyZonedTime -> String
$cshowList :: [MyZonedTime] -> ShowS
showList :: [MyZonedTime] -> ShowS
Show, ReadPrec [MyZonedTime]
ReadPrec MyZonedTime
Int -> ReadS MyZonedTime
ReadS [MyZonedTime]
(Int -> ReadS MyZonedTime)
-> ReadS [MyZonedTime]
-> ReadPrec MyZonedTime
-> ReadPrec [MyZonedTime]
-> Read MyZonedTime
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MyZonedTime
readsPrec :: Int -> ReadS MyZonedTime
$creadList :: ReadS [MyZonedTime]
readList :: ReadS [MyZonedTime]
$creadPrec :: ReadPrec MyZonedTime
readPrec :: ReadPrec MyZonedTime
$creadListPrec :: ReadPrec [MyZonedTime]
readListPrec :: ReadPrec [MyZonedTime]
Read)
instance ToField MyZonedTime where
toField :: MyZonedTime -> ByteString
toField (MyZonedTime ZonedTime
zt) =
String -> ByteString
forall a. ToField a => a -> ByteString
toField (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ TimeLocale -> String -> ZonedTime -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%FT%T%Q%Ez" ZonedTime
zt