did a bit of beautification on the html-side

This commit is contained in:
Nicole Dresselhaus 2015-08-07 23:41:37 +02:00
parent ac00ceebef
commit 941717f776
3 changed files with 68 additions and 14 deletions

View File

@ -7,7 +7,7 @@ getStockR = loginOrDo (\(uid,user) -> do
items <- runDB $ selectList [TransactionUser ==. uid, TransactionInStock >. 0] [Asc TransactionTypeName]
defaultLayout $ [whamlet|
<h1>Current Stock
<table>
<table .table>
<tr>
<th>Item name
<th>Quantity

View File

@ -8,6 +8,7 @@ import qualified Eve.Api.Types as T
import qualified Eve.Api.Char.Standings as ST
import qualified Eve.Api.Char.Skills as SK
import Database.Persist.Sql
import Data.Time.Clock
accountingId :: Int64
accountingId = 16622
@ -93,10 +94,15 @@ updateProfits dat = updateProfits' [] dat
&& transactionInStock ct > 0
&& transactionInStock t < 0 then
let m = min (transactionInStock t * (-1)) (transactionInStock ct)
t' = t {transactionInStock = transactionInStock t + m}
t' = t { transactionInStock = transactionInStock t + m
, transactionProfit = maybe (Just prof') (\a -> Just (a + prof')) (transactionProfit t)
, transactionSecondsToSell = maybe (Just secs) (\a -> Just ((a*done + secs * m)`div`(done+m))) (transactionSecondsToSell t)
}
ct' = ct {transactionInStock = transactionInStock ct - m}
prof' = (transactionPriceCents t - transactionPriceCents ct) * m
(t'',ct'') = updateProfits'' (Entity et (t' { transactionProfit = maybe (Just prof') (\a -> Just (a + prof')) (transactionProfit t')})) ts
secs = round $ diffUTCTime (transactionDateTime t) (transactionDateTime ct)
done = (transactionQuantity t + transactionInStock t)
(t'',ct'') = updateProfits'' (Entity et t') ts
in
(t'' ,(Entity cet ct'):ct'')
else

View File

@ -2,7 +2,9 @@ module Handler.Wallet where
import Import
import Data.List (unfoldr)
import Data.Time.Clock
import Text.Printf
getWalletR :: Handler Html
getWalletR = getWalletDetailsR 6 7
@ -14,22 +16,55 @@ getWalletDetailsR hrs days = loginOrDo (\(uid,user) -> do
defaultLayout $ [whamlet|
<a href=@{WalletDetailsR 168 days}>show last 7 days
<h1>Transactions in the last #{hrs} hours
<table>
<table .table>
<tr>
<th>Time
<th>Price
<th>Name
<th>Profit
<th>P/C
<th>B/S
<th>Item
<th>Quantity
<th>ISK/Item
<th>ISK total
<th>ISK profit
<th>%
<th>Time
<th>Client
<th>Station
<th>?
<th>
$forall Entity _ t <- trans
<tr>
<td>#{show $ transactionDateTime t}
<td>#{transactionPriceCents t}
<td>#{transactionClientName t}
<td>
$maybe profit <- transRealProfit t
#{profit}
$nothing
<td>#{show $ utctDay $ transactionDateTime $ t} #{show $ utctDayTime $ transactionDateTime $ t}
$if transactionTransForCorp t
<td .corpTransaction>C
$else
<td .personalTransaction>P
$if transactionTransIsSell t
<td .sellTransaction>S
$else
<td .buyTransaction>B
<td>#{transactionTypeName t}
<td>#{transactionQuantity t}
<td>#{prettyISK $ transactionPriceCents t}
<td>#{prettyISK $ transactionQuantity t * transactionPriceCents t}
$maybe profit <- transRealProfit t
<td>
#{prettyISK $ profit}
<td>
#{profitPercent profit t}
$nothing
<td>
-
<td>
<td>
$maybe secs <- transactionSecondsToSell t
#{secs}
$nothing
&nbsp;
<td>#{transactionClientName t}
<td>#{transactionStationName t}
<td>
<td>
<h1>Statistices for the last #{days} days
|]
@ -37,3 +72,16 @@ getWalletDetailsR hrs days = loginOrDo (\(uid,user) -> do
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)