created history as stated in #5 - not paginated yet.

This commit is contained in:
Nicole Dresselhaus 2015-09-18 00:41:37 +02:00
parent 2b55cf8178
commit 6235692988
11 changed files with 117 additions and 20 deletions

View File

@ -38,6 +38,7 @@ import Handler.Update
import Handler.Stock import Handler.Stock
import Handler.ProfitItems import Handler.ProfitItems
import Handler.Orders import Handler.Orders
import Handler.Item
-- This line actually creates our YesodDispatch instance. It is the second half -- This line actually creates our YesodDispatch instance. It is the second half
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the -- of the call to mkYesodData which occurs in Foundation.hs. Please see the

84
Handler/Item.hs Normal file
View File

@ -0,0 +1,84 @@
module Handler.Item where
import Import
itemsPerPage :: Int
itemsPerPage = 100
getItemR :: Int64 -> Handler Html
getItemR transactionTypeId = getItemPagedR transactionTypeId 0
getItemPagedR :: Int64 -> Int -> Handler Html
getItemPagedR tid page =
loginOrDo (\(uid,user) -> do
items <- runDB $ selectList [TransactionTypeId ==. tid] [Desc TransactionDateTime, LimitTo itemsPerPage, OffsetBy (itemsPerPage*page)]
total <- runDB $ count [TransactionTypeId ==. tid]
let offset = itemsPerPage * page
loginLayout user $ [whamlet|
<div .panel .panel-default>
$if page > 0
<div .panel-heading>#{itemsPerPage} Transactions (starting at #{offset})
$else
<div .panel-heading>#{itemsPerPage} Transactions
<table .table .table-condensed .small>
<tr>
<th .text-center>Time
<th .text-center>P/C
<th .text-center>B/S
<th .text-center>Item
<th .text-center>##
<th .text-center>ISK/Item
<th .text-center>ISK total
<th .text-center>ISK profit
<th .text-center>%
<th .text-center>Time
<th .text-center>Client
<th .text-center>Station
<th .text-center>?
<th .text-center>
$forall Entity _ t <- items
<tr>
<td>#{showDateTime $ transactionDateTime $ t}
$if transactionTransForCorp t
<td .corpTransaction .text-center>C
$else
<td .personalTransaction .text-center>P
$if transactionTransIsSell t
<td .sellTransaction .text-center>S
$else
<td .buyTransaction .text-center>B
<td>#{transactionTypeName t}
<td .numeric>#{transactionQuantity t}
<td .numeric>#{prettyISK $ transactionPriceCents t}
<td .numeric>#{prettyISK $ transactionQuantity t * transactionPriceCents t}
$maybe profit <- transRealProfit t
$if (&&) (transactionTransIsSell t) (profit > 0)
<td .numeric .profit>
#{prettyISK $ profit}
$elseif (&&) (transactionTransIsSell t) (profit < 0)
<td .numeric .loss>
#{prettyISK $ profit}
$elseif not (transactionTransIsSell t)
<td .numeric .buyfee>
#{prettyISK $ profit}
$else
<td .numeric>
#{prettyISK $ profit}
<td .numeric>
#{profitPercent profit t}%
$nothing
<td>
-
<td>
<td .duration>
$maybe secs <- transactionSecondsToSell t
#{showSecsToSell secs}
$nothing
&nbsp;
<td>#{transactionClientName t}
<td>#{transactionStationName t}
<td>
<td>
|]
)

View File

@ -42,7 +42,7 @@ getOrdersR = loginOrDo (\(uid,user) -> do
$forall (Entity _ o, Single name, Single stationname, Single regionid) <- sellorders $forall (Entity _ o, Single name, Single stationname, Single regionid) <- sellorders
<tr .order data="#{orderTypeId o};#{regionid};#{orderPriceCents o}"> <tr .order data="#{orderTypeId o};#{regionid};#{orderPriceCents o}">
<td>#{showDateTime $ orderIssued $ o} <td>#{showDateTime $ orderIssued $ o}
<td>#{name} <td><a href="@{ItemR (orderTypeId o)}">#{name}</a>
<td .numeric .price>#{prettyISK $ orderPriceCents o} <td .numeric .price>#{prettyISK $ orderPriceCents o}
<td .numeric>#{orderVolRemaining o}/#{orderVolEntered o} (#{orderMinVolume o}) <td .numeric>#{orderVolRemaining o}/#{orderVolEntered o} (#{orderMinVolume o})
<td .numeric>#{prettyISK $ orderVolRemaining o * orderPriceCents o} <td .numeric>#{prettyISK $ orderVolRemaining o * orderPriceCents o}
@ -76,7 +76,7 @@ getOrdersR = loginOrDo (\(uid,user) -> do
$forall (Entity _ o, Single name, Single stationname, Single regionid) <- buyorders $forall (Entity _ o, Single name, Single stationname, Single regionid) <- buyorders
<tr .order data="#{orderTypeId o};#{regionid};#{orderPriceCents o}"> <tr .order data="#{orderTypeId o};#{regionid};#{orderPriceCents o}">
<td>#{showDateTime $ orderIssued $ o} <td>#{showDateTime $ orderIssued $ o}
<td>#{name} <td><a href="@{ItemR (orderTypeId o)}">#{name}</a>
<td .numeric .price>#{prettyISK $ orderPriceCents o} <td .numeric .price>#{prettyISK $ orderPriceCents o}
<td .numeric>#{orderVolRemaining o}/#{orderVolEntered o} (#{orderMinVolume o}) <td .numeric>#{orderVolRemaining o}/#{orderVolEntered o} (#{orderMinVolume o})
<td .numeric>#{prettyISK $ orderPriceCents o * orderVolRemaining o} <td .numeric>#{prettyISK $ orderPriceCents o * orderVolRemaining o}

View File

@ -77,7 +77,7 @@ getProfitItemsDetailsR days = loginOrDo (\(uid,user) -> do
<th .text-center>%/Day <th .text-center>%/Day
$forall (Profit tn tid quant pc f t a sc) <- items $forall (Profit tn tid quant pc f t a sc) <- items
<tr> <tr>
<td>#{tn} <td><a href="@{ItemR tid}">#{tn}</a>
<td .numeric>#{prettyISK pc} <td .numeric>#{prettyISK pc}
<td .numeric>#{prettyISK f} <td .numeric>#{prettyISK f}
<td .numeric>#{prettyISK t} <td .numeric>#{prettyISK t}
@ -85,7 +85,7 @@ getProfitItemsDetailsR days = loginOrDo (\(uid,user) -> do
<td .numeric>#{showSecsToSell a} <td .numeric>#{showSecsToSell a}
<td .numeric>#{quant} <td .numeric>#{quant}
<td .numeric>#{prettyISK $ profitPerDay pc f t a} <td .numeric>#{prettyISK $ profitPerDay pc f t a}
<td .numeric>#{profitPercent pc f t sc} <td .numeric>#{profitPercent' pc f t sc}
<td .numeric>#{profitPercentDay pc f t sc a} <td .numeric>#{profitPercentDay pc f t sc a}
|] |]
) )
@ -98,9 +98,9 @@ profitPerDay :: Int64 -> Int64 -> Int64 -> Int64 -> Int64
profitPerDay _ _ _ 0 = 0 profitPerDay _ _ _ 0 = 0
profitPerDay p f t a = ((p-f-t) * 86400) `div` a profitPerDay p f t a = ((p-f-t) * 86400) `div` a
profitPercent :: Int64 -> Int64 -> Int64 -> Int64 -> String profitPercent' :: Int64 -> Int64 -> Int64 -> Int64 -> String
profitPercent _ _ _ 0 = printf "%.2f" $ (0 :: Double) profitPercent' _ _ _ 0 = printf "%.2f" $ (0 :: Double)
profitPercent p f t s = printf "%.2f" $ (100*(fromIntegral (p-f-t)) / (fromIntegral s) :: Double) profitPercent' p f t s = printf "%.2f" $ (100*(fromIntegral (p-f-t)) / (fromIntegral s) :: Double)
profitPercentDay :: Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> String profitPercentDay :: Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> String
profitPercentDay _ _ _ 0 _ = printf "%.2f" $ (0 :: Double) profitPercentDay _ _ _ 0 _ = printf "%.2f" $ (0 :: Double)

View File

@ -96,7 +96,7 @@ getStockR = loginOrDo (\(uid,user) -> do
$forall DisCols tid sid sn tn is wrth avg' dt taxed <- items' $forall DisCols tid sid sn tn is wrth avg' dt taxed <- items'
<tr> <tr>
<td>#{showDateTime dt} <td>#{showDateTime dt}
<td>#{tn} <td><a href="@{ItemR tid}">#{tn}</a>
<td .numeric>#{is} <td .numeric>#{is}
<td .numeric>#{prettyISK avg'} <td .numeric>#{prettyISK avg'}
<td .numeric>#{prettyISK taxed} <td .numeric>#{prettyISK taxed}

View File

@ -106,7 +106,7 @@ getWalletDetailsR hrs days = loginOrDo (\(uid,user) -> do
<td .sellTransaction .text-center>S <td .sellTransaction .text-center>S
$else $else
<td .buyTransaction .text-center>B <td .buyTransaction .text-center>B
<td>#{transactionTypeName t} <td><a href="@{ItemR (transactionTypeId t)}">#{transactionTypeName t}</a>
<td .numeric>#{transactionQuantity t} <td .numeric>#{transactionQuantity t}
<td .numeric>#{prettyISK $ transactionPriceCents t} <td .numeric>#{prettyISK $ transactionPriceCents t}
<td .numeric>#{prettyISK $ transactionQuantity t * transactionPriceCents t} <td .numeric>#{prettyISK $ transactionQuantity t * transactionPriceCents t}
@ -188,12 +188,6 @@ getWalletDetailsR hrs days = loginOrDo (\(uid,user) -> do
|] |]
) )
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)
transRealProfit' :: Int64 -> Int64 -> Int64 -> String transRealProfit' :: Int64 -> Int64 -> Int64 -> String
transRealProfit' p bf tt = prettyISK (p-bf-tt) transRealProfit' p bf tt = prettyISK (p-bf-tt)
@ -201,8 +195,5 @@ profitPercent' :: Int64 -> Int64 -> Int64 -> Int64 -> Maybe String
profitPercent' p bf tt s = if s == 0 then Nothing profitPercent' p bf tt s = if s == 0 then Nothing
else Just . printf "%.2f" $ 100*(fromIntegral (p - bf - tt) / fromIntegral s :: Double) else Just . printf "%.2f" $ 100*(fromIntegral (p - bf - tt) / fromIntegral s :: Double)
profitPercent :: Int64 -> Transaction -> String
profitPercent p t = printf "%.2f" $ (100*(fromIntegral p) / (fromIntegral (transactionQuantity t * transactionPriceCents t)) :: Double)
addProfit :: ProfitSum -> Profit -> ProfitSum addProfit :: ProfitSum -> Profit -> ProfitSum
addProfit (ProfitSum b' s' p' bf' tt') (Profit _ b s p bf tt) = ProfitSum (b+b') (s+s') (p+p') (bf+bf') (tt+tt') addProfit (ProfitSum b' s' p' bf' tt') (Profit _ b s p bf tt) = ProfitSum (b+b') (s+s') (p+p') (bf+bf') (tt+tt')

View File

@ -76,3 +76,12 @@ showSecsToSell t
| otherwise = pp (fromIntegral t :: Double) ++ "s" | otherwise = pp (fromIntegral t :: Double) ++ "s"
where where
pp = printf "%.2f" pp = printf "%.2f"
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)

View File

@ -14,3 +14,4 @@
/analysis/items ProfitItemsR GET /analysis/items ProfitItemsR GET
/analysis/items/#Int64 ProfitItemsDetailsR GET /analysis/items/#Int64 ProfitItemsDetailsR GET
/orders OrdersR GET /orders OrdersR GET
/history/#Int64 ItemR GET

View File

@ -28,6 +28,7 @@ library
Handler.Stock Handler.Stock
Handler.ProfitItems Handler.ProfitItems
Handler.Orders Handler.Orders
Handler.Item
if flag(dev) || flag(library-only) if flag(dev) || flag(library-only)
cpp-options: -DDEVELOPMENT cpp-options: -DDEVELOPMENT

View File

@ -5,8 +5,8 @@ neat utility functions
Number.prototype.formatMoney = function(c, d, t) { Number.prototype.formatMoney = function(c, d, t) {
var n = this, var n = this,
c = isNaN(c = Math.abs(c)) ? 2 : c, c = isNaN(c = Math.abs(c)) ? 2 : c,
d = d == undefined ? "." : t, d = d == undefined ? "." : d,
t = t == undefined ? "," : d, t = t == undefined ? "," : t,
s = n < 0 ? "-" : "", s = n < 0 ? "-" : "",
i = parseInt(n = Math.abs(+n || 0).toFixed(c)) + "", i = parseInt(n = Math.abs(+n || 0).toFixed(c)) + "",
j = (j = i.length) > 3 ? j % 3 : 0; j = (j = i.length) > 3 ? j % 3 : 0;

10
test/Handler/ItemSpec.hs Normal file
View File

@ -0,0 +1,10 @@
module Handler.ItemSpec (spec) where
import TestImport
spec :: Spec
spec = withApp $ do
describe "getItemR" $ do
error "Spec not implemented: getItemRR"