updated bootstrap, jquery. Added sortable/partially hidable tables
This commit is contained in:
@ -1,6 +1,7 @@
|
||||
module Handler.Item where
|
||||
|
||||
import Import
|
||||
import Yesod.Default.Util (widgetFileReload)
|
||||
|
||||
itemsPerPage :: Int
|
||||
itemsPerPage = 100
|
||||
@ -17,77 +18,6 @@ getItemPagedR tid page
|
||||
let offset = itemsPerPage * page
|
||||
let maxPages = total `div` itemsPerPage
|
||||
let paginatePages = [1..maxPages+1]
|
||||
loginLayout user $ [whamlet|
|
||||
<div .panel .panel-default>
|
||||
$if page > 0
|
||||
<div .panel-heading>#{itemsPerPage} Transactions (starting at #{offset}) of #{total}
|
||||
$else
|
||||
<div .panel-heading>#{itemsPerPage} Transactions of #{total}
|
||||
<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
|
||||
|
||||
<td>#{transactionClientName t}
|
||||
<td>#{transactionStationName t}
|
||||
<td>
|
||||
<td>
|
||||
<ul class="pagination">
|
||||
$forall p <- paginatePages
|
||||
$if p == page
|
||||
<li .active><a href="@{ItemPagedR tid p}">#{p}</a>
|
||||
$else
|
||||
<li><a href="@{ItemPagedR tid p}">#{p}</a>
|
||||
|]
|
||||
loginLayout user $ $(widgetFileReload def "item")
|
||||
)
|
||||
|
||||
|
@ -5,6 +5,7 @@ module Handler.Stock where
|
||||
import Import
|
||||
--import Database.Esqueleto as E
|
||||
import Database.Persist.Sql (rawSql,RawSql(..))
|
||||
import Yesod.Default.Util (widgetFileReload)
|
||||
|
||||
|
||||
data Stock = Stock
|
||||
@ -40,23 +41,6 @@ instance RawSql Stock where
|
||||
|
||||
getStockR :: Handler Html
|
||||
getStockR = loginOrDo (\(uid,user) -> do
|
||||
--items <- runDB $ selectList [TransactionUser ==. uid, TransactionInStock >. 0] [Asc TransactionTypeName]
|
||||
--persist cannot do groupBy
|
||||
{-(items :: [(E.Value Text,
|
||||
E.Value Text,
|
||||
E.Value (Maybe Rational),
|
||||
E.Value (Maybe Rational))]) <-
|
||||
runDB $ select $ from $ \trans -> do
|
||||
where_ (trans ^. TransactionInStock E.>. (val 0))
|
||||
E.groupBy $ trans ^. TransactionTypeId
|
||||
E.groupBy $ trans ^. TransactionTypeName
|
||||
E.groupBy $ trans ^. TransactionStationName
|
||||
orderBy [asc (trans ^. TransactionTypeName)]
|
||||
return (trans ^. TransactionTypeName
|
||||
,trans ^. TransactionStationName
|
||||
,sum_ $ trans ^. TransactionInStock
|
||||
,avg_ $ (trans ^. TransactionPriceCents) *. (trans ^. TransactionInStock))-}
|
||||
--esqueleto does not work because we reference tables outside of the model, so we come back to raw SQL:
|
||||
let sql = "select t.type_id, t.station_id, t.station_name, t.type_name, \
|
||||
sum(t.in_stock) as in_stock, \
|
||||
sum(t.in_stock*t.price_cents) as worth, \
|
||||
@ -81,36 +65,7 @@ getStockR = loginOrDo (\(uid,user) -> do
|
||||
(items :: [Stock]) <- runDB $ rawSql sql [toPersistValue uid]
|
||||
let items' = convertStock <$> items
|
||||
let total = foldl' sumTotal 0 items'
|
||||
loginLayout user $ [whamlet|
|
||||
<div .panel .panel-default>
|
||||
<div .panel-heading>Current Stock:
|
||||
<table .table .table-condensed .small .table-bordered>
|
||||
<tr>
|
||||
<th .text-center>Bought
|
||||
<th .text-center>Item name
|
||||
<th .text-center>Quantity
|
||||
<th .text-center>Buy price
|
||||
<th .text-center>Required sell
|
||||
<th .text-center>Total
|
||||
<th .text-center>Station name
|
||||
$forall DisCols tid sid sn tn is wrth avg' dt taxed <- items'
|
||||
<tr>
|
||||
<td>#{showDateTime dt}
|
||||
<td><a href="@{ItemR tid}">#{tn}</a>
|
||||
<td .numeric>#{is}
|
||||
<td .numeric>#{prettyISK avg'}
|
||||
<td .numeric>#{prettyISK taxed}
|
||||
<td .numeric>#{prettyISK wrth}
|
||||
<td>#{sn}
|
||||
<tr .total>
|
||||
<th .text-center>Total
|
||||
<td>
|
||||
<td .numeric>
|
||||
<td .numeric>
|
||||
<td .numeric>
|
||||
<td .numeric>#{prettyISK total}
|
||||
<td>
|
||||
|]
|
||||
loginLayout user $ $(widgetFileReload def "curStock")
|
||||
)
|
||||
|
||||
convertStock :: Stock -> DisCols
|
||||
|
@ -70,122 +70,7 @@ getWalletDetailsR hrs days = loginOrDo (\(uid,user) -> do
|
||||
extract(day from (now() at time zone 'utc')-date(date_time at time zone 'utc')) asc"
|
||||
(profits :: [Profit]) <- runDB $ rawSql profitquery [toPersistValue uid, toPersistValue days]
|
||||
let profitssum = foldl' addProfit (ProfitSum 0 0 0 0 0) profits
|
||||
loginLayout user $ [whamlet|
|
||||
<div .panel .panel-default>
|
||||
<div .panel-heading>Transactions in the last #{hrs} hours:
|
||||
<div .btn-group .btn-group-justified role="group">
|
||||
$forall (hrs',cap) <- buttonIntervals
|
||||
$if hrs == hrs'
|
||||
<a href="@{WalletDetailsR hrs' days}" .btn .active role="button">#{cap}
|
||||
$else
|
||||
<a href="@{WalletDetailsR hrs' days}" .btn role="button">#{cap}
|
||||
<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 <- trans
|
||||
<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><a href="@{ItemR (transactionTypeId t)}">#{transactionTypeName t}</a>
|
||||
<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
|
||||
|
||||
<td>#{transactionClientName t}
|
||||
<td>#{transactionStationName t}
|
||||
<td>
|
||||
<td>
|
||||
|
||||
<div .panel .panel-default>
|
||||
<div .panel-heading>Statistices for the last #{days} days:
|
||||
<div .btn-group .btn-group-justified role="group">
|
||||
$forall days' <- profitIntervals
|
||||
$if days == days'
|
||||
<a href="@{WalletDetailsR hrs days'}" .btn .active role="button">#{days'} days
|
||||
$else
|
||||
<a href="@{WalletDetailsR hrs days'}" .btn role="button">#{days'} days
|
||||
<table .table .table-condensed .small>
|
||||
<tr>
|
||||
<th .text-center>Date
|
||||
<th .text-center>ISK Buy
|
||||
<th .text-center>ISK Sell
|
||||
<th .text-center>ISK Profit
|
||||
<th .text-center>ISK Broker Fee
|
||||
<th .text-center>ISK Transaction Tax
|
||||
<th .text-center>Real Profit
|
||||
<th .text-center>%
|
||||
$forall (Profit t b s p bf tt) <- profits
|
||||
<tr>
|
||||
<td>#{show t}
|
||||
<td .numeric>#{prettyISK b}
|
||||
<td .numeric>#{prettyISK s}
|
||||
<td .numeric>#{prettyISK p}
|
||||
<td .numeric>#{prettyISK bf}
|
||||
<td .numeric>#{prettyISK tt}
|
||||
<td .numeric>#{transRealProfit' p bf tt}
|
||||
<td .numeric>
|
||||
$maybe pp <- profitPercent' p bf tt s
|
||||
#{pp}
|
||||
$nothing
|
||||
|
||||
$with (ProfitSum b s p bf tt) <- profitssum
|
||||
<tr .total>
|
||||
<th .text-center>Total
|
||||
<td .numeric>#{prettyISK b}
|
||||
<td .numeric>#{prettyISK s}
|
||||
<td .numeric>#{prettyISK p}
|
||||
<td .numeric>#{prettyISK bf}
|
||||
<td .numeric>#{prettyISK tt}
|
||||
<td .numeric>#{transRealProfit' p bf tt}
|
||||
<td .numeric>
|
||||
$maybe pp <- profitPercent' p bf tt s
|
||||
#{pp}
|
||||
$nothing
|
||||
|
||||
|]
|
||||
loginLayout user $ $(widgetFile "wallet")
|
||||
)
|
||||
|
||||
transRealProfit' :: Int64 -> Int64 -> Int64 -> String
|
||||
|
Reference in New Issue
Block a user