2019-05-25 15:27:55 +03:00
{- |
2019-06-11 01:22:29 +03:00
Convert amounts to some related value in various ways . This involves
looking up historical market prices ( exchange rates ) between commodities .
2019-05-25 15:27:55 +03:00
- }
2019-06-04 03:26:27 +03:00
{- # LANGUAGE NamedFieldPuns # -}
2019-05-25 15:27:55 +03:00
{- # LANGUAGE OverloadedStrings # -}
{- # LANGUAGE RecordWildCards # -}
2019-06-04 03:26:27 +03:00
{- # LANGUAGE ScopedTypeVariables # -}
2020-08-31 07:56:38 +03:00
{- # LANGUAGE DeriveGeneric # -}
2019-05-25 15:27:55 +03:00
2019-06-15 02:17:06 +03:00
module Hledger.Data.Valuation (
2019-08-19 04:21:30 +03:00
ValuationType ( .. )
, PriceOracle
, journalPriceOracle
2020-02-25 03:16:14 +03:00
, unsupportedValueThenError
2019-08-19 04:16:39 +03:00
-- ,amountApplyValuation
2019-08-19 13:59:32 +03:00
-- ,amountValueAtDate
2019-06-02 01:28:10 +03:00
, mixedAmountApplyValuation
2019-08-19 13:59:32 +03:00
, mixedAmountValueAtDate
2019-08-19 14:30:54 +03:00
, marketPriceReverse
, priceDirectiveToMarketPrice
2019-08-19 13:59:32 +03:00
-- ,priceLookup
2019-06-15 02:17:06 +03:00
, tests_Valuation
2019-05-25 15:27:55 +03:00
)
where
2019-06-02 01:28:10 +03:00
import Control.Applicative ( ( <|> ) )
2019-06-11 01:22:29 +03:00
import Data.Decimal ( roundTo )
2020-05-24 04:19:43 +03:00
import Data.Function ( ( & ) , on )
2019-06-12 01:08:09 +03:00
import Data.Graph.Inductive ( Gr , Node , NodeMap , mkMapGraph , mkNode , lab , out , sp )
2019-05-25 15:27:55 +03:00
import Data.List
2019-07-13 10:13:33 +03:00
import Data.List.Extra ( nubSortBy )
2019-06-02 01:28:10 +03:00
import qualified Data.Map as M
2019-06-11 01:22:29 +03:00
import Data.Maybe
2019-05-25 15:27:55 +03:00
import qualified Data.Text as T
2020-08-26 11:11:20 +03:00
import Data.Time.Calendar ( Day , fromGregorian )
2019-08-19 04:16:39 +03:00
import Data.MemoUgly ( memo )
2019-08-19 04:21:30 +03:00
import GHC.Generics ( Generic )
2019-06-02 01:28:10 +03:00
import Safe ( headMay )
2019-05-25 15:27:55 +03:00
import Hledger.Utils
import Hledger.Data.Types
2019-06-02 01:28:10 +03:00
import Hledger.Data.Amount
2020-10-19 06:48:14 +03:00
import Hledger.Data.Dates ( nulldate )
2019-05-25 15:27:55 +03:00
2019-06-02 01:28:10 +03:00
2019-08-19 04:21:30 +03:00
------------------------------------------------------------------------------
-- Types
2020-06-19 03:09:59 +03:00
-- | What kind of value conversion should be done on amounts ?
-- CLI: --value=cost|then|end|now|DATE[,COMM]
data ValuationType =
AtCost ( Maybe CommoditySymbol ) -- ^ convert to cost commodity using transaction prices, then optionally to given commodity using market prices at posting date
| AtThen ( Maybe CommoditySymbol ) -- ^ convert to default or given valuation commodity, using market prices at each posting's date
| AtEnd ( Maybe CommoditySymbol ) -- ^ convert to default or given valuation commodity, using market prices at period end(s)
| AtNow ( Maybe CommoditySymbol ) -- ^ convert to default or given valuation commodity, using current market prices
| AtDate Day ( Maybe CommoditySymbol ) -- ^ convert to default or given valuation commodity, using market prices on some date
| AtDefault ( Maybe CommoditySymbol ) -- ^ works like AtNow in single period reports, like AtEnd in multiperiod reports
2020-08-31 07:56:38 +03:00
deriving ( Show , Eq )
2020-06-19 03:09:59 +03:00
2019-08-19 04:21:30 +03:00
-- | A snapshot of the known exchange rates between commodity pairs at a given date,
-- as a graph allowing fast lookup and path finding, along with some helper data.
data PriceGraph = PriceGraph {
prGraph :: Gr CommoditySymbol Quantity
-- ^ A directed graph of exchange rates between commodity pairs.
-- Node labels are commodities and edge labels are exchange rates,
2020-05-24 04:19:43 +03:00
-- which were either:
-- declared by P directives,
2020-06-19 03:09:59 +03:00
-- inferred from transaction prices,
2020-05-24 04:19:43 +03:00
-- inferred by reversing a declared rate,
2020-06-19 03:09:59 +03:00
-- or inferred by reversing a transaction-inferred rate.
2019-08-19 04:21:30 +03:00
-- There will be at most one edge between each directed pair of commodities,
-- eg there can be one USD->EUR and one EUR->USD.
, prNodemap :: NodeMap CommoditySymbol
-- ^ Mapping of graph node ids to commodity symbols.
2020-05-24 04:19:43 +03:00
, prDefaultValuationCommodities :: M . Map CommoditySymbol CommoditySymbol
-- ^ The default valuation commodity for each source commodity.
-- These are used when a valuation commodity is not specified
-- (-V). They are the destination commodity of the latest
2020-06-19 03:09:59 +03:00
-- (declared or inferred, but not reverse) each
2020-05-24 04:19:43 +03:00
-- source commodity's latest market price (on the date of this
-- graph).
2019-08-19 04:21:30 +03:00
}
deriving ( Show , Generic )
2020-06-19 03:09:59 +03:00
-- | A price oracle is a magic memoising function that efficiently
-- looks up market prices (exchange rates) from one commodity to
-- another (or if unspecified, to a default valuation commodity) on a
-- given date.
2019-08-19 04:21:30 +03:00
type PriceOracle = ( Day , CommoditySymbol , Maybe CommoditySymbol ) -> Maybe ( CommoditySymbol , Quantity )
2020-06-19 03:09:59 +03:00
-- | Generate a price oracle (memoising price lookup function) from a
-- journal's directive-declared and transaction-inferred market
-- prices. For best performance, generate this only once per journal,
-- reusing it across reports if there are more than one, as
-- compoundBalanceCommand does.
2020-06-20 00:33:34 +03:00
-- The boolean argument is whether to infer market prices from
-- transactions or not.
journalPriceOracle :: Bool -> Journal -> PriceOracle
journalPriceOracle infer Journal { jpricedirectives , jinferredmarketprices } =
2020-06-19 03:09:59 +03:00
let
declaredprices = map priceDirectiveToMarketPrice jpricedirectives
2020-06-20 00:33:34 +03:00
inferredprices = if infer then jinferredmarketprices else []
makepricegraph = memo $ makePriceGraph declaredprices inferredprices
2020-06-19 03:09:59 +03:00
in
memo $ uncurry3 $ priceLookup makepricegraph
2019-08-19 04:21:30 +03:00
2020-06-19 03:09:59 +03:00
priceDirectiveToMarketPrice :: PriceDirective -> MarketPrice
priceDirectiveToMarketPrice PriceDirective { .. } =
MarketPrice { mpdate = pddate
, mpfrom = pdcommodity
, mpto = acommodity pdamount
, mprate = aquantity pdamount
}
2019-08-19 04:16:39 +03:00
2019-06-04 03:26:27 +03:00
------------------------------------------------------------------------------
2020-06-19 03:09:59 +03:00
-- Converting things to value
2019-07-15 13:28:52 +03:00
2019-09-05 23:41:36 +03:00
-- | Apply a specified valuation to this mixed amount, using the
-- provided price oracle, commodity styles, reference dates, and
-- whether this is for a multiperiod report or not.
-- See amountApplyValuation.
mixedAmountApplyValuation :: PriceOracle -> M . Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> MixedAmount -> MixedAmount
mixedAmountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v ( Mixed as ) =
Mixed $ map ( amountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v ) as
2019-06-04 03:26:27 +03:00
-- | Apply a specified valuation to this amount, using the provided
2019-09-05 23:41:36 +03:00
-- price oracle, reference dates, and whether this is for a
-- multiperiod report or not. Also fix up its display style using the
-- provided commodity styles.
--
-- When the valuation requires converting to another commodity, a
-- valuation (conversion) date is chosen based on the valuation type,
-- the provided reference dates, and whether this is for a
-- single-period or multi-period report. It will be one of:
--
-- - a fixed date specified by the ValuationType itself
-- (--value=DATE).
--
-- - the provided "period end" date - this is typically the last day
-- of a subperiod (--value=end with a multi-period report), or of
-- the specified report period or the journal (--value=end with a
-- single-period report).
--
-- - the provided "report end" date - the last day of the specified
-- report period, if any (-V/-X with a report end date).
--
-- - the provided "today" date - (--value=now, or -V/X with no report
-- end date).
--
2020-02-10 19:09:52 +03:00
-- Note --value=then is not supported by this function, and will cause an error;
-- use postingApplyValuation for that.
--
2019-09-05 23:41:36 +03:00
-- This is all a bit complicated. See the reference doc at
2020-06-13 22:41:02 +03:00
-- https://hledger.org/hledger.html#effect-of-valuation-on-reports
-- (hledger_options.m4.md "Effect of valuation on reports"), and #1083.
2019-09-05 23:41:36 +03:00
--
amountApplyValuation :: PriceOracle -> M . Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> Amount -> Amount
amountApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod v a =
2019-06-04 03:26:27 +03:00
case v of
2020-06-01 01:48:08 +03:00
AtCost Nothing -> styleAmount styles $ amountCost a
AtCost mc -> amountValueAtDate priceoracle styles mc periodlast $ styleAmount styles $ amountCost a
2020-08-06 02:05:56 +03:00
AtThen _mc -> error ' u n s u p p o r t e d V a l u e T h e n E r r o r - - P A R T I A L :
2020-02-10 19:09:52 +03:00
-- amountValueAtDate priceoracle styles mc periodlast a -- posting date unknown, handle like AtEnd
2019-09-05 23:41:36 +03:00
AtEnd mc -> amountValueAtDate priceoracle styles mc periodlast a
AtNow mc -> amountValueAtDate priceoracle styles mc today a
AtDefault mc | ismultiperiod -> amountValueAtDate priceoracle styles mc periodlast a
AtDefault mc -> amountValueAtDate priceoracle styles mc ( fromMaybe today mreportlast ) a
AtDate d mc -> amountValueAtDate priceoracle styles mc d a
2019-08-19 04:16:39 +03:00
2020-02-25 03:16:14 +03:00
-- | Standard error message for a report not supporting --value=then.
unsupportedValueThenError :: String
2020-09-19 18:10:39 +03:00
unsupportedValueThenError = " Sorry, --value=then is not yet supported for this kind of report. "
2020-02-25 03:16:14 +03:00
2019-08-19 04:16:39 +03:00
-- | Find the market value of each component amount in the given
-- commodity, or its default valuation commodity, at the given
-- valuation date, using the given market price oracle.
-- When market prices available on that date are not sufficient to
-- calculate the value, amounts are left unchanged.
mixedAmountValueAtDate :: PriceOracle -> M . Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount
mixedAmountValueAtDate priceoracle styles mc d ( Mixed as ) = Mixed $ map ( amountValueAtDate priceoracle styles mc d ) as
2019-06-02 01:28:10 +03:00
2019-06-04 03:26:27 +03:00
-- | Find the market value of this amount in the given valuation
-- commodity if any, otherwise the default valuation commodity, at the
-- given valuation date. (The default valuation commodity is the
-- commodity of the latest applicable market price before the
-- valuation date.)
2019-06-15 04:52:13 +03:00
--
-- The returned amount will have its commodity's canonical style applied,
-- but with the precision adjusted to show all significant decimal digits
-- up to a maximum of 8. (experimental)
--
2019-06-04 03:26:27 +03:00
-- If the market prices available on that date are not sufficient to
-- calculate this value, the amount is left unchanged.
2019-08-19 04:16:39 +03:00
amountValueAtDate :: PriceOracle -> M . Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> Amount -> Amount
amountValueAtDate priceoracle styles mto d a =
case priceoracle ( d , acommodity a , mto ) of
2019-06-11 01:22:29 +03:00
Nothing -> a
2019-06-15 04:52:13 +03:00
Just ( comm , rate ) ->
-- setNaturalPrecisionUpTo 8 $ -- XXX force higher precision in case amount appears to be zero ?
-- Make default display style use precision 2 instead of 0 ?
-- Leave as is for now; mentioned in manual.
styleAmount styles
amount { acommodity = comm , aquantity = rate * aquantity a }
2019-06-04 03:26:27 +03:00
------------------------------------------------------------------------------
2019-06-11 01:22:29 +03:00
-- Market price lookup
2019-07-15 13:28:52 +03:00
2020-06-19 03:09:59 +03:00
-- | Given a memoising price graph generator, a valuation date, a
-- source commodity and an optional valuation commodity, find the
-- value on that date of one unit of the source commodity in the
-- valuation commodity, or in a default valuation commodity. Returns
-- the valuation commodity that was specified or chosen, and the
-- quantity of it that one unit of the source commodity is worth. Or
-- if no applicable market price can be found or calculated, or if the
-- source commodity and the valuation commodity are the same, returns
-- Nothing.
2020-05-24 04:19:43 +03:00
--
2020-06-19 03:09:59 +03:00
-- See makePriceGraph for how prices are determined.
-- Note that both market prices and default valuation commodities can
-- vary with valuation date, since that determines which market prices
-- are visible.
2019-06-02 01:28:10 +03:00
--
2019-08-19 04:16:39 +03:00
priceLookup :: ( Day -> PriceGraph ) -> Day -> CommoditySymbol -> Maybe CommoditySymbol -> Maybe ( CommoditySymbol , Quantity )
2020-06-19 03:09:59 +03:00
priceLookup makepricegraph d from mto =
2019-08-19 04:16:39 +03:00
-- trace ("priceLookup ("++show d++", "++show from++", "++show mto++")") $
2019-06-11 01:22:29 +03:00
let
-- build a graph of the commodity exchange rates in effect on this day
2019-06-11 03:42:51 +03:00
-- XXX should hide these fgl details better
2020-06-20 00:33:34 +03:00
PriceGraph { prGraph = g , prNodemap = m , prDefaultValuationCommodities = defaultdests } =
traceAt 1 ( " valuation date: " ++ show d ) $ makepricegraph d
2019-06-11 01:22:29 +03:00
fromnode = node m from
mto' = mto <|> mdefaultto
where
2020-06-15 03:17:09 +03:00
mdefaultto = dbg1 ( " default valuation commodity for " ++ T . unpack from ) $
2020-05-24 04:19:43 +03:00
M . lookup from defaultdests
2019-06-11 01:22:29 +03:00
in
case mto' of
Nothing -> Nothing
Just to | to == from -> Nothing
Just to ->
2019-06-11 03:42:51 +03:00
-- We have a commodity to convert to. Find the most direct price available.
2019-06-12 01:08:09 +03:00
case mindirectprice of
Nothing -> Nothing
Just q -> Just ( to , q )
2019-06-11 01:22:29 +03:00
where
tonode = node m to
mindirectprice :: Maybe Quantity =
-- Find the shortest path, if any, between from and to.
2019-06-12 01:08:09 +03:00
case sp fromnode tonode g :: Maybe [ Node ] of
2019-06-11 01:22:29 +03:00
Nothing -> Nothing
Just nodes ->
2020-06-15 03:17:09 +03:00
dbg ( " market price for " ++ intercalate " -> " ( map T . unpack comms ) ) $
2020-07-14 20:21:45 +03:00
-- TODO: it would be nice to include price date as part of the label
-- in PriceGraph, so we could show the dates of market prices here
2019-06-12 01:08:09 +03:00
Just $ product $ pathEdgeLabels g nodes -- convert to a single exchange rate
2019-06-11 01:22:29 +03:00
where comms = catMaybes $ map ( lab g ) nodes
-- log a message and a Maybe Quantity, hiding Just/Nothing and limiting decimal places
2020-06-15 03:17:09 +03:00
dbg msg = dbg1With ( ( ( msg ++ " : " ) ++ ) . maybe " " ( show . roundTo 8 ) )
2019-06-11 01:22:29 +03:00
2019-08-19 04:16:39 +03:00
tests_priceLookup =
let
2020-08-26 11:11:20 +03:00
p y m d from q to = MarketPrice { mpdate = fromGregorian y m d , mpfrom = from , mpto = to , mprate = q }
2019-08-19 04:16:39 +03:00
ps1 = [
2020-08-26 11:11:20 +03:00
p 2000 01 01 " A " 10 " B "
, p 2000 01 01 " B " 10 " C "
, p 2000 01 01 " C " 10 " D "
, p 2000 01 01 " E " 2 " D "
, p 2001 01 01 " A " 11 " B "
2019-08-19 04:16:39 +03:00
]
2020-06-19 03:09:59 +03:00
makepricegraph = makePriceGraph ps1 []
2019-11-29 02:29:03 +03:00
in test " priceLookup " $ do
2020-08-26 11:11:20 +03:00
priceLookup makepricegraph ( fromGregorian 1999 01 01 ) " A " Nothing @?= Nothing
priceLookup makepricegraph ( fromGregorian 2000 01 01 ) " A " Nothing @?= Just ( " B " , 10 )
priceLookup makepricegraph ( fromGregorian 2000 01 01 ) " B " ( Just " A " ) @?= Just ( " A " , 0.1 )
priceLookup makepricegraph ( fromGregorian 2000 01 01 ) " A " ( Just " E " ) @?= Just ( " E " , 500 )
2020-06-19 03:09:59 +03:00
-- | Build the graph of commodity conversion prices for a given day.
-- Converts a list of declared market prices in parse order, and a
-- list of transaction-inferred market prices in parse order, to a
-- graph of all known exchange rates between commodity pairs in effect
-- on that day. Cf hledger.m4.md -> Valuation:
--
-- hledger looks for a market price (exchange rate) from commodity A
-- to commodity B in one or more of these ways, in this order of
-- preference:
--
-- 1. A *declared market price* or *inferred market price*:
-- A's latest market price in B on or before the valuation date
2020-06-20 00:33:34 +03:00
-- as declared by a P directive, or (with the `--infer-value` flag)
2020-06-19 03:09:59 +03:00
-- inferred from transaction prices.
--
-- 2. A *reverse market price*:
-- the inverse of a declared or inferred market price from B to A.
--
-- 3. A *chained market price*:
-- a synthetic price formed by combining the shortest chain of market
-- prices (any of the above types) leading from A to B.
--
-- 1 and 2 form the edges of the price graph, and we can query it for
-- 3 (which is the reason we use a graph).
--
-- We also identify each commodity's default valuation commodity, if
-- any. For each commodity A, hledger picks a default valuation
2020-06-20 00:33:34 +03:00
-- commodity as follows, in this order of preference:
2020-06-19 03:09:59 +03:00
--
2020-06-20 00:33:34 +03:00
-- 1. The price commodity from the latest declared market price for A
-- on or before valuation date.
2020-06-19 03:09:59 +03:00
--
2020-06-20 00:33:34 +03:00
-- 2. The price commodity from the latest declared market price for A
-- on any date. (Allows conversion to proceed if there are inferred
-- prices before the valuation date.)
--
-- 3. If there are no P directives at all (any commodity or date), and
-- the `--infer-value` flag is used, then the price commodity from
-- the latest transaction price for A on or before valuation date.
2020-06-19 03:09:59 +03:00
--
makePriceGraph :: [ MarketPrice ] -> [ MarketPrice ] -> Day -> PriceGraph
makePriceGraph alldeclaredprices allinferredprices d =
dbg9 ( " makePriceGraph " ++ show d ) $
2020-05-24 04:19:43 +03:00
PriceGraph { prGraph = g , prNodemap = m , prDefaultValuationCommodities = defaultdests }
2019-08-01 19:27:32 +03:00
where
2020-06-19 03:09:59 +03:00
-- prices in effect on date d, either declared or inferred
2020-06-20 00:33:34 +03:00
visibledeclaredprices = filter ( ( <= d ) . mpdate ) alldeclaredprices
visibleinferredprices = filter ( ( <= d ) . mpdate ) allinferredprices
2020-06-19 03:09:59 +03:00
declaredandinferredprices = dbg2 " declaredandinferredprices " $
2020-06-20 00:33:34 +03:00
effectiveMarketPrices visibledeclaredprices visibleinferredprices
2019-08-01 19:27:32 +03:00
2020-06-19 03:09:59 +03:00
-- infer any additional reverse prices not already declared or inferred
2020-06-15 03:17:09 +03:00
reverseprices = dbg2 " reverseprices " $
2020-06-19 03:09:59 +03:00
map marketPriceReverse declaredandinferredprices \\ declaredandinferredprices
2019-08-01 19:27:32 +03:00
-- build the graph and associated node map
( g , m ) =
mkMapGraph
2020-06-15 03:17:09 +03:00
( dbg9 " price graph labels " $ sort allcomms ) -- this must include all nodes mentioned in edges
( dbg9 " price graph edges " $ [ ( mpfrom , mpto , mprate ) | MarketPrice { .. } <- prices ] )
2019-08-01 19:27:32 +03:00
:: ( Gr CommoditySymbol Quantity , NodeMap CommoditySymbol )
where
2020-06-19 03:09:59 +03:00
prices = declaredandinferredprices ++ reverseprices
2019-08-01 19:27:32 +03:00
allcomms = map mpfrom prices
2020-06-20 00:33:34 +03:00
-- determine a default valuation commodity for each source commodity
-- somewhat but not quite like effectiveMarketPrices
defaultdests = M . fromList [ ( mpfrom , mpto ) | MarketPrice { .. } <- pricesfordefaultcomms ]
where
pricesfordefaultcomms = dbg2 " prices for choosing default valuation commodities, by date then parse order " $
ps
& zip [ 1 .. ] -- label items with their parse order
& sortBy ( compare ` on ` ( \ ( parseorder , MarketPrice { .. } ) -> ( mpdate , parseorder ) ) ) -- sort by increasing date then increasing parse order
& map snd -- discard labels
where
ps | not $ null visibledeclaredprices = visibledeclaredprices
| not $ null alldeclaredprices = alldeclaredprices
| otherwise = visibleinferredprices -- will be null without --infer-value
-- | Given a list of P-declared market prices in parse order and a
-- list of transaction-inferred market prices in parse order, select
-- just the latest prices that are in effect for each commodity pair.
-- That is, for each commodity pair, the latest price by date then
-- parse order, with declared prices having precedence over inferred
-- prices on the same day.
effectiveMarketPrices :: [ MarketPrice ] -> [ MarketPrice ] -> [ MarketPrice ]
effectiveMarketPrices declaredprices inferredprices =
2020-05-24 04:19:43 +03:00
let
2020-06-20 00:33:34 +03:00
-- label each item with its same-day precedence, then parse order
declaredprices' = [ ( 1 , i , p ) | ( i , p ) <- zip [ 1 .. ] declaredprices ]
inferredprices' = [ ( 0 , i , p ) | ( i , p ) <- zip [ 1 .. ] inferredprices ]
2020-05-24 04:19:43 +03:00
in
-- combine
2020-06-19 03:09:59 +03:00
declaredprices' ++ inferredprices'
2020-06-20 00:33:34 +03:00
-- sort by decreasing date then decreasing precedence then decreasing parse order
2020-05-24 04:19:43 +03:00
& sortBy ( flip compare ` on ` ( \ ( precedence , parseorder , mp ) -> ( mpdate mp , precedence , parseorder ) ) )
-- discard the sorting labels
& map third3
2020-06-19 03:09:59 +03:00
-- keep only the first (ie the newest, highest precedence, latest parsed) price for each pair
2020-05-24 04:19:43 +03:00
& nubSortBy ( compare ` on ` ( \ ( MarketPrice { .. } ) -> ( mpfrom , mpto ) ) )
2019-08-01 19:27:32 +03:00
marketPriceReverse :: MarketPrice -> MarketPrice
2020-10-19 06:48:14 +03:00
marketPriceReverse mp @ MarketPrice { .. } =
mp { mpfrom = mpto , mpto = mpfrom , mprate = if mprate == 0 then 0 else 1 / mprate } -- PARTIAL: /
2019-08-01 19:27:32 +03:00
2019-06-11 01:22:29 +03:00
------------------------------------------------------------------------------
-- fgl helpers
2019-06-11 03:42:51 +03:00
-- | Look up an existing graph node by its label.
2019-06-11 01:22:29 +03:00
-- (If the node does not exist, a new one will be generated, but not
-- persisted in the nodemap.)
node :: Ord a => NodeMap a -> a -> Node
node m = fst . fst . mkNode m
2019-06-11 03:42:51 +03:00
-- | Convert a valid path within the given graph to the corresponding
2019-06-11 01:22:29 +03:00
-- edge labels. When there are multiple edges between two nodes, the
-- lowest-sorting label is used.
pathEdgeLabels :: ( Show b , Ord b ) => Gr a b -> [ Node ] -> [ b ]
pathEdgeLabels g = map frommaybe . map ( nodesEdgeLabel g ) . pathEdges
2020-08-06 02:05:56 +03:00
where frommaybe = fromMaybe ( error ' " p a t h E d g e L a b e l s : e x p e c t e d n o N o t h i n g s h e r e " ) - - P A R T I A L :
2019-07-15 13:28:52 +03:00
2019-06-11 01:22:29 +03:00
-- | Convert a path to node pairs representing the path's edges.
pathEdges :: [ Node ] -> [ ( Node , Node ) ]
pathEdges p = [ ( f , t ) | f : t : _ <- tails p ]
-- | Get the label of a graph edge from one node to another.
-- When there are multiple such edges, the lowest-sorting label is used.
nodesEdgeLabel :: Ord b => Gr a b -> ( Node , Node ) -> Maybe b
nodesEdgeLabel g ( from , to ) = headMay $ sort [ l | ( _ , t , l ) <- out g from , t == to ]
2019-05-25 15:27:55 +03:00
2020-10-19 06:48:14 +03:00
nullmarketprice :: MarketPrice
nullmarketprice = MarketPrice {
mpdate = nulldate
, mpfrom = " "
, mpto = " "
, mprate = 0
}
2019-06-04 03:26:27 +03:00
------------------------------------------------------------------------------
2019-11-27 23:46:29 +03:00
tests_Valuation = tests " Valuation " [
tests_priceLookup
2020-10-19 06:48:14 +03:00
, test " marketPriceReverse " $ do
marketPriceReverse nullmarketprice { mprate = 2 } @?= nullmarketprice { mprate = 0.5 }
marketPriceReverse nullmarketprice @?= nullmarketprice -- the reverse of a 0 price is a 0 price
2019-11-27 23:46:29 +03:00
]