{-# LANGUAGE RecordWildCards #-}

-- | Generate & write/print CoinTracking import files.
module Console.SolanaStaking.CoinTracking
    ( makeCoinTrackingImport
    , writeOrPrintImportData
    , makeImportData
    , sol
    ) where

import Control.Monad ((>=>))
import Data.Time (utcToLocalZonedTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Web.CoinTracking.Imports
    ( Amount (..)
    , CTImportData (..)
    , CTTransactionType (Staking)
    , Currency (..)
    , coinTrackingCsvImport
    , writeImportDataToFile
    )

import Console.SolanaStaking.Api
    ( StakeReward (..)
    , StakingAccount (..)
    , StakingPubKey (..)
    , scientificLamports
    )

import Data.ByteString.Lazy.Char8 qualified as LBC
import Data.Text qualified as T


-- | Generate the Import file for CoinTracking & write to destination or
-- print to stdout.
makeCoinTrackingImport :: FilePath -> [(StakingAccount, StakeReward)] -> IO ()
makeCoinTrackingImport :: FilePath -> [(StakingAccount, StakeReward)] -> IO ()
makeCoinTrackingImport FilePath
dest = [(StakingAccount, StakeReward)] -> IO [CTImportData]
makeImportData ([(StakingAccount, StakeReward)] -> IO [CTImportData])
-> ([CTImportData] -> IO ())
-> [(StakingAccount, StakeReward)]
-> IO ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> FilePath -> [CTImportData] -> IO ()
writeOrPrintImportData FilePath
dest


-- | Write or print the generated import data.
writeOrPrintImportData :: FilePath -> [CTImportData] -> IO ()
writeOrPrintImportData :: FilePath -> [CTImportData] -> IO ()
writeOrPrintImportData FilePath
dest [CTImportData]
importData =
    if FilePath
dest FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
"-"
        then ByteString -> IO ()
LBC.putStrLn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ [CTImportData] -> ByteString
coinTrackingCsvImport [CTImportData]
importData
        else FilePath -> [CTImportData] -> IO ()
writeImportDataToFile FilePath
dest [CTImportData]
importData


-- | Turn a 'StakeReward' into a 'CTImportData', localizing the reward
-- time.
makeImportData :: [(StakingAccount, StakeReward)] -> IO [CTImportData]
makeImportData :: [(StakingAccount, StakeReward)] -> IO [CTImportData]
makeImportData = ((StakingAccount, StakeReward) -> IO CTImportData)
-> [(StakingAccount, StakeReward)] -> IO [CTImportData]
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 (((StakingAccount, StakeReward) -> IO CTImportData)
 -> [(StakingAccount, StakeReward)] -> IO [CTImportData])
-> ((StakingAccount, StakeReward) -> IO CTImportData)
-> [(StakingAccount, StakeReward)]
-> IO [CTImportData]
forall a b. (a -> b) -> a -> b
$ \(StakingAccount {Text
Lamports
StakingPubKey
saPubKey :: StakingPubKey
saLamports :: Lamports
saValidatorName :: Text
saPubKey :: StakingAccount -> StakingPubKey
saLamports :: StakingAccount -> Lamports
saValidatorName :: StakingAccount -> Text
..}, StakeReward {Integer
POSIXTime
Lamports
srEpoch :: Integer
srSlot :: Integer
srAmount :: Lamports
srTimestamp :: POSIXTime
srEpoch :: StakeReward -> Integer
srSlot :: StakeReward -> Integer
srAmount :: StakeReward -> Lamports
srTimestamp :: StakeReward -> POSIXTime
..}) -> do
    ZonedTime
zonedTime <- UTCTime -> IO ZonedTime
utcToLocalZonedTime (UTCTime -> IO ZonedTime) -> UTCTime -> IO ZonedTime
forall a b. (a -> b) -> a -> b
$ POSIXTime -> UTCTime
posixSecondsToUTCTime POSIXTime
srTimestamp
    CTImportData -> IO CTImportData
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
        CTImportData
            { ctidType :: CTTransactionType
ctidType = CTTransactionType
Staking
            , ctidBuy :: Maybe Amount
ctidBuy = Amount -> Maybe Amount
forall a. a -> Maybe a
Just (Amount -> Maybe Amount) -> Amount -> Maybe Amount
forall a b. (a -> b) -> a -> b
$ Scientific -> Currency -> Amount
Amount (Lamports -> Scientific
scientificLamports Lamports
srAmount) Currency
sol
            , ctidSell :: Maybe Amount
ctidSell = Maybe Amount
forall a. Maybe a
Nothing
            , ctidFee :: Maybe Amount
ctidFee = Maybe Amount
forall a. Maybe a
Nothing
            , ctidExchange :: Text
ctidExchange = Text
"Solana Staking"
            , ctidGroup :: Text
ctidGroup = Text
"Staking"
            , ctidComment :: Text
ctidComment = Text
"Imported from solana-staking-csvs"
            , ctidDate :: ZonedTime
ctidDate = ZonedTime
zonedTime
            , ctidTradeId :: Text
ctidTradeId =
                Text
"SOL-STAKE-"
                    Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> StakingPubKey -> Text
fromStakingPubKey StakingPubKey
saPubKey
                    Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-"
                    Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
T.pack
                        (Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
srEpoch)
            , ctidBuyValue :: Maybe Amount
ctidBuyValue = Maybe Amount
forall a. Maybe a
Nothing
            , ctidSellValue :: Maybe Amount
ctidSellValue = Maybe Amount
forall a. Maybe a
Nothing
            }


-- | @SOL@ currency with the @SOL2@ ticker & 9 decimals of precision.
sol :: Currency
sol :: Currency
sol = Int -> Text -> Currency
Currency Int
9 Text
"SOL2"