module Handler.Wallet where
import Import
import Data.List (unfoldr)
import Data.Time.Clock
import Text.Printf
getWalletR :: Handler Html
getWalletR = getWalletDetailsR 6 7
getWalletDetailsR :: Int64 -> Int64 -> Handler Html
getWalletDetailsR hrs days = loginOrDo (\(uid,user) -> do
now <- liftIO getCurrentTime
trans <- runDB $ selectList [TransactionDateTime >. (addUTCTime ((fromIntegral $ -(hrs*3600)) :: NominalDiffTime) now)] [Desc TransactionDateTime]
defaultLayout $ [whamlet|
show last 7 days
Transactions in the last #{hrs} hours
Time | P/C | B/S | Item | Quantity | ISK/Item | ISK total | ISK profit | % | Time | Client | Station | ? | $forall Entity _ t <- trans | ||||
---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|---|
#{show $ utctDay $ transactionDateTime $ t} #{show $ utctDayTime $ transactionDateTime $ t} $if transactionTransForCorp t | C $else | P $if transactionTransIsSell t | S $else | B | #{transactionTypeName t} | #{transactionQuantity t} | #{prettyISK $ transactionPriceCents t} | #{prettyISK $ transactionQuantity t * transactionPriceCents t} $maybe profit <- transRealProfit t | #{prettyISK $ profit} | #{profitPercent profit t} $nothing | - | $maybe secs <- transactionSecondsToSell t #{secs} $nothing | #{transactionClientName t} | #{transactionStationName t} |
Statistices for the last #{days} days |] ) transRealProfit :: Transaction -> Maybe Int64 transRealProfit t = (\a b c -> a - b - c) <$> transactionProfit t <*> transactionFee t <*> transactionTax t profitPercent :: Int64 -> Transaction -> String profitPercent p t = printf "%.2f" $ (100*(fromIntegral p) / (fromIntegral (transactionQuantity t * transactionPriceCents t)) :: Double) prettyISK :: Int64 -> String prettyISK isk = pretty++","++ printf "%02u" cents where (isk',cents) = divMod isk 100 thousands = unfoldr (\b -> if b == 0 then Nothing else Just (b `mod` 1000, b `div` 1000)) isk' (ht:t) = reverse thousands pretty = intercalate "." $ [show ht] ++ (printf "%03u" <$> t) |