module Handler.Wallet where import Import import Data.List (unfoldr) import Data.Time.Clock import Text.Printf buttonIntervals :: [(Int64,String)] buttonIntervals = [ (2,"2 hours") , (6,"6 hours") , (12,"12 hours") , (24,"1 day") , (48,"2 days") , (7*24,"7 days") , (31*24,"31 days") ] 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|
Transactions in the last #{hrs} hours:
$forall (hrs',cap) <- buttonIntervals $if hrs == hrs' #{cap} $else #{cap}
Time P/C B/S Item ## ISK/Item ISK total ISK profit % Time Client Station ? $forall Entity _ t <- trans
#{show $ utctDay $ transactionDateTime $ t} #{showTime $ round $ 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 $if (&&) (transactionTransIsSell t) (profit > 0) #{prettyISK $ profit} $elseif (&&) (transactionTransIsSell t) (profit < 0) #{prettyISK $ profit} $elseif not (transactionTransIsSell t) #{prettyISK $ profit} $else #{prettyISK $ profit} #{profitPercent profit t}% $nothing - $maybe secs <- transactionSecondsToSell t #{showSecsToSell secs} $nothing   #{transactionClientName t} #{transactionStationName t}
Statistices for the last #{days} days:
TODO |] ) transRealProfit :: Transaction -> Maybe Int64 transRealProfit t = if transactionTransIsSell t then (\a b c -> a - b - c) <$> transactionProfit t <*> transactionFee t <*> transactionTax t else negate <$> ((+) <$> 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 = signIsk++pretty++","++ printf "%02u" cents where signIsk = if isk > 0 then "" else "-" (isk',cents) = divMod (abs 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) showTime :: Int64 -> String showTime t = printf "%2u" hours ++ ":" ++ printf "%02u" minutes ++ ":" ++ printf "%02u" seconds where (hours, minutes') = divMod t 3600 (minutes, seconds) = divMod minutes' 60 showSecsToSell :: Int64 -> String showSecsToSell t | t > 4*7*86400 = pp (fromIntegral t / (7*86400) :: Double) ++ "w" | t > 86400 = pp (fromIntegral t / 86400 :: Double) ++ "d" | t > 3600 = pp (fromIntegral t / 3600 :: Double) ++ "h" | t > 60 = pp (fromIntegral t / 60 :: Double) ++ "m" | otherwise = pp (fromIntegral t :: Double) ++ "s" where pp x = printf "%.2f" x