{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveGeneric #-}
module Hledger.Data.Valuation (
   Costing(..)
  ,ValuationType(..)
  ,PriceOracle
  ,journalPriceOracle
  ,mixedAmountToCost
  ,mixedAmountApplyValuation
  ,mixedAmountValueAtDate
  ,mixedAmountApplyGain
  ,mixedAmountGainAtDate
  ,marketPriceReverse
  ,priceDirectiveToMarketPrice
  
  ,tests_Valuation
)
where
import Control.Applicative ((<|>))
import Data.Function ((&), on)
import Data.List (partition, intercalate, sortBy)
import Data.List.Extra (nubSortBy)
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Text as T
import Data.Time.Calendar (Day, fromGregorian)
import Data.MemoUgly (memo)
import GHC.Generics (Generic)
import Safe (headMay, lastMay)
import Hledger.Utils
import Hledger.Data.Types
import Hledger.Data.Amount
import Hledger.Data.Dates (nulldate)
import Text.Printf (printf)
data Costing = Cost | NoCost
  deriving (Int -> Costing -> ShowS
[Costing] -> ShowS
Costing -> String
(Int -> Costing -> ShowS)
-> (Costing -> String) -> ([Costing] -> ShowS) -> Show Costing
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Costing] -> ShowS
$cshowList :: [Costing] -> ShowS
show :: Costing -> String
$cshow :: Costing -> String
showsPrec :: Int -> Costing -> ShowS
$cshowsPrec :: Int -> Costing -> ShowS
Show,Costing -> Costing -> Bool
(Costing -> Costing -> Bool)
-> (Costing -> Costing -> Bool) -> Eq Costing
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Costing -> Costing -> Bool
$c/= :: Costing -> Costing -> Bool
== :: Costing -> Costing -> Bool
$c== :: Costing -> Costing -> Bool
Eq)
data ValuationType =
    AtThen     (Maybe CommoditySymbol)  
  | AtEnd      (Maybe CommoditySymbol)  
  | AtNow      (Maybe CommoditySymbol)  
  | AtDate Day (Maybe CommoditySymbol)  
  deriving (Int -> ValuationType -> ShowS
[ValuationType] -> ShowS
ValuationType -> String
(Int -> ValuationType -> ShowS)
-> (ValuationType -> String)
-> ([ValuationType] -> ShowS)
-> Show ValuationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValuationType] -> ShowS
$cshowList :: [ValuationType] -> ShowS
show :: ValuationType -> String
$cshow :: ValuationType -> String
showsPrec :: Int -> ValuationType -> ShowS
$cshowsPrec :: Int -> ValuationType -> ShowS
Show,ValuationType -> ValuationType -> Bool
(ValuationType -> ValuationType -> Bool)
-> (ValuationType -> ValuationType -> Bool) -> Eq ValuationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValuationType -> ValuationType -> Bool
$c/= :: ValuationType -> ValuationType -> Bool
== :: ValuationType -> ValuationType -> Bool
$c== :: ValuationType -> ValuationType -> Bool
Eq)
type PriceOracle = (Day, CommoditySymbol, Maybe CommoditySymbol) -> Maybe (CommoditySymbol, Quantity)
journalPriceOracle :: Bool -> Journal -> PriceOracle
journalPriceOracle :: Bool -> Journal -> PriceOracle
journalPriceOracle Bool
infer Journal{[PriceDirective]
jpricedirectives :: Journal -> [PriceDirective]
jpricedirectives :: [PriceDirective]
jpricedirectives, [MarketPrice]
jinferredmarketprices :: Journal -> [MarketPrice]
jinferredmarketprices :: [MarketPrice]
jinferredmarketprices} =
  let
    declaredprices :: [MarketPrice]
declaredprices = (PriceDirective -> MarketPrice)
-> [PriceDirective] -> [MarketPrice]
forall a b. (a -> b) -> [a] -> [b]
map PriceDirective -> MarketPrice
priceDirectiveToMarketPrice [PriceDirective]
jpricedirectives
    inferredprices :: [MarketPrice]
inferredprices = if Bool
infer then [MarketPrice]
jinferredmarketprices else []
    makepricegraph :: Day -> PriceGraph
makepricegraph = (Day -> PriceGraph) -> Day -> PriceGraph
forall a b. Ord a => (a -> b) -> a -> b
memo ((Day -> PriceGraph) -> Day -> PriceGraph)
-> (Day -> PriceGraph) -> Day -> PriceGraph
forall a b. (a -> b) -> a -> b
$ [MarketPrice] -> [MarketPrice] -> Day -> PriceGraph
makePriceGraph [MarketPrice]
declaredprices [MarketPrice]
inferredprices
  in
    PriceOracle -> PriceOracle
forall a b. Ord a => (a -> b) -> a -> b
memo (PriceOracle -> PriceOracle) -> PriceOracle -> PriceOracle
forall a b. (a -> b) -> a -> b
$ (Day
 -> CommoditySymbol
 -> Maybe CommoditySymbol
 -> Maybe (CommoditySymbol, Quantity))
-> PriceOracle
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 ((Day
  -> CommoditySymbol
  -> Maybe CommoditySymbol
  -> Maybe (CommoditySymbol, Quantity))
 -> PriceOracle)
-> (Day
    -> CommoditySymbol
    -> Maybe CommoditySymbol
    -> Maybe (CommoditySymbol, Quantity))
-> PriceOracle
forall a b. (a -> b) -> a -> b
$ (Day -> PriceGraph)
-> Day
-> CommoditySymbol
-> Maybe CommoditySymbol
-> Maybe (CommoditySymbol, Quantity)
priceLookup Day -> PriceGraph
makepricegraph
priceDirectiveToMarketPrice :: PriceDirective -> MarketPrice
priceDirectiveToMarketPrice :: PriceDirective -> MarketPrice
priceDirectiveToMarketPrice PriceDirective{CommoditySymbol
Day
Amount
pdamount :: PriceDirective -> Amount
pdcommodity :: PriceDirective -> CommoditySymbol
pddate :: PriceDirective -> Day
pdamount :: Amount
pdcommodity :: CommoditySymbol
pddate :: Day
..} =
  MarketPrice :: Day
-> CommoditySymbol -> CommoditySymbol -> Quantity -> MarketPrice
MarketPrice{ mpdate :: Day
mpdate = Day
pddate
             , mpfrom :: CommoditySymbol
mpfrom = CommoditySymbol
pdcommodity
             , mpto :: CommoditySymbol
mpto   = Amount -> CommoditySymbol
acommodity Amount
pdamount
             , mprate :: Quantity
mprate = Amount -> Quantity
aquantity Amount
pdamount
             }
mixedAmountToCost :: Costing -> M.Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
mixedAmountToCost :: Costing
-> Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
mixedAmountToCost Costing
cost Map CommoditySymbol AmountStyle
styles = (Amount -> Amount) -> MixedAmount -> MixedAmount
mapMixedAmount (Costing -> Map CommoditySymbol AmountStyle -> Amount -> Amount
amountToCost Costing
cost Map CommoditySymbol AmountStyle
styles)
mixedAmountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount
mixedAmountApplyValuation :: PriceOracle
-> Map CommoditySymbol AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyValuation PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Day
periodlast Day
today Day
postingdate ValuationType
v =
  (Amount -> Amount) -> MixedAmount -> MixedAmount
mapMixedAmount (PriceOracle
-> Map CommoditySymbol AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> Amount
-> Amount
amountApplyValuation PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Day
periodlast Day
today Day
postingdate ValuationType
v)
amountToCost :: Costing -> M.Map CommoditySymbol AmountStyle -> Amount -> Amount
amountToCost :: Costing -> Map CommoditySymbol AmountStyle -> Amount -> Amount
amountToCost Costing
NoCost Map CommoditySymbol AmountStyle
_      = Amount -> Amount
forall a. a -> a
id
amountToCost Costing
Cost   Map CommoditySymbol AmountStyle
styles = Map CommoditySymbol AmountStyle -> Amount -> Amount
styleAmount Map CommoditySymbol AmountStyle
styles (Amount -> Amount) -> (Amount -> Amount) -> Amount -> Amount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Amount
amountCost
amountApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> Amount -> Amount
amountApplyValuation :: PriceOracle
-> Map CommoditySymbol AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> Amount
-> Amount
amountApplyValuation PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Day
periodlast Day
today Day
postingdate ValuationType
v Amount
a =
  case ValuationType
v of
    AtThen    Maybe CommoditySymbol
mc      -> PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> Amount
-> Amount
amountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mc Day
postingdate Amount
a
    AtEnd     Maybe CommoditySymbol
mc      -> PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> Amount
-> Amount
amountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mc Day
periodlast Amount
a
    AtNow     Maybe CommoditySymbol
mc      -> PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> Amount
-> Amount
amountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mc Day
today Amount
a
    AtDate Day
d  Maybe CommoditySymbol
mc      -> PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> Amount
-> Amount
amountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mc Day
d Amount
a
mixedAmountValueAtDate :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount
mixedAmountValueAtDate :: PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> MixedAmount
-> MixedAmount
mixedAmountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mc Day
d = (Amount -> Amount) -> MixedAmount -> MixedAmount
mapMixedAmount (PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> Amount
-> Amount
amountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mc Day
d)
amountValueAtDate :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> Amount -> Amount
amountValueAtDate :: PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> Amount
-> Amount
amountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mto Day
d Amount
a =
  case PriceOracle
priceoracle (Day
d, Amount -> CommoditySymbol
acommodity Amount
a, Maybe CommoditySymbol
mto) of
    Maybe (CommoditySymbol, Quantity)
Nothing           -> Amount
a
    Just (CommoditySymbol
comm, Quantity
rate) ->
      
                                      
                                      
      Map CommoditySymbol AmountStyle -> Amount -> Amount
styleAmount Map CommoditySymbol AmountStyle
styles
      Amount
amount{acommodity :: CommoditySymbol
acommodity=CommoditySymbol
comm, aquantity :: Quantity
aquantity=Quantity
rate Quantity -> Quantity -> Quantity
forall a. Num a => a -> a -> a
* Amount -> Quantity
aquantity Amount
a}
mixedAmountApplyGain :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount
mixedAmountApplyGain :: PriceOracle
-> Map CommoditySymbol AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyGain PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Day
periodlast Day
today Day
postingdate ValuationType
v MixedAmount
ma =
  PriceOracle
-> Map CommoditySymbol AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyValuation PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Day
periodlast Day
today Day
postingdate ValuationType
v (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount
ma MixedAmount -> MixedAmount -> MixedAmount
`maMinus` MixedAmount -> MixedAmount
mixedAmountCost MixedAmount
ma
mixedAmountGainAtDate :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount
mixedAmountGainAtDate :: PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> MixedAmount
-> MixedAmount
mixedAmountGainAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mto Day
d MixedAmount
ma =
  PriceOracle
-> Map CommoditySymbol AmountStyle
-> Maybe CommoditySymbol
-> Day
-> MixedAmount
-> MixedAmount
mixedAmountValueAtDate PriceOracle
priceoracle Map CommoditySymbol AmountStyle
styles Maybe CommoditySymbol
mto Day
d (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount
ma MixedAmount -> MixedAmount -> MixedAmount
`maMinus` MixedAmount -> MixedAmount
mixedAmountCost MixedAmount
ma
priceLookup :: (Day -> PriceGraph) -> Day -> CommoditySymbol -> Maybe CommoditySymbol -> Maybe (CommoditySymbol, Quantity)
priceLookup :: (Day -> PriceGraph)
-> Day
-> CommoditySymbol
-> Maybe CommoditySymbol
-> Maybe (CommoditySymbol, Quantity)
priceLookup Day -> PriceGraph
makepricegraph Day
d CommoditySymbol
from Maybe CommoditySymbol
mto =
  
  let
    PriceGraph{pgEdges :: PriceGraph -> [MarketPrice]
pgEdges=[MarketPrice]
forwardprices
              ,pgEdgesRev :: PriceGraph -> [MarketPrice]
pgEdgesRev=[MarketPrice]
allprices
              ,pgDefaultValuationCommodities :: PriceGraph -> Map CommoditySymbol CommoditySymbol
pgDefaultValuationCommodities=Map CommoditySymbol CommoditySymbol
defaultdests
              } =
      Int -> String -> PriceGraph -> PriceGraph
forall a. Int -> String -> a -> a
traceAt Int
1 (String
"valuation date: "String -> ShowS
forall a. [a] -> [a] -> [a]
++Day -> String
forall a. Show a => a -> String
show Day
d) (PriceGraph -> PriceGraph) -> PriceGraph -> PriceGraph
forall a b. (a -> b) -> a -> b
$ Day -> PriceGraph
makepricegraph Day
d
    mto' :: Maybe CommoditySymbol
mto' = Maybe CommoditySymbol
mto Maybe CommoditySymbol
-> Maybe CommoditySymbol -> Maybe CommoditySymbol
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe CommoditySymbol
mdefaultto
      where
        mdefaultto :: Maybe CommoditySymbol
mdefaultto = String -> Maybe CommoditySymbol -> Maybe CommoditySymbol
forall a. Show a => String -> a -> a
dbg1 (String
"default valuation commodity for "String -> ShowS
forall a. [a] -> [a] -> [a]
++CommoditySymbol -> String
T.unpack CommoditySymbol
from) (Maybe CommoditySymbol -> Maybe CommoditySymbol)
-> Maybe CommoditySymbol -> Maybe CommoditySymbol
forall a b. (a -> b) -> a -> b
$
                     CommoditySymbol
-> Map CommoditySymbol CommoditySymbol -> Maybe CommoditySymbol
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup CommoditySymbol
from Map CommoditySymbol CommoditySymbol
defaultdests
  in
    case Maybe CommoditySymbol
mto' of
      Maybe CommoditySymbol
Nothing            -> Maybe (CommoditySymbol, Quantity)
forall a. Maybe a
Nothing
      Just CommoditySymbol
to | CommoditySymbol
toCommoditySymbol -> CommoditySymbol -> Bool
forall a. Eq a => a -> a -> Bool
==CommoditySymbol
from -> Maybe (CommoditySymbol, Quantity)
forall a. Maybe a
Nothing
      Just CommoditySymbol
to            ->
        
        
        let msg :: String
msg = String -> CommoditySymbol -> CommoditySymbol -> String
forall r. PrintfType r => String -> r
printf String
"seeking %s to %s price" (CommoditySymbol -> CommoditySymbol
showCommoditySymbol CommoditySymbol
from) (CommoditySymbol -> CommoditySymbol
showCommoditySymbol CommoditySymbol
to)
        in case 
          (Int -> String -> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a. Int -> String -> a -> a
traceAt Int
2 (String
msgString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" using forward prices") (Maybe [MarketPrice] -> Maybe [MarketPrice])
-> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a b. (a -> b) -> a -> b
$ 
            CommoditySymbol
-> CommoditySymbol -> [MarketPrice] -> Maybe [MarketPrice]
pricesShortestPath CommoditySymbol
from CommoditySymbol
to [MarketPrice]
forwardprices)
          Maybe [MarketPrice] -> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> 
          (Int -> String -> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a. Int -> String -> a -> a
traceAt Int
2 (String
msgString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" using forward and reverse prices") (Maybe [MarketPrice] -> Maybe [MarketPrice])
-> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a b. (a -> b) -> a -> b
$ 
            CommoditySymbol
-> CommoditySymbol -> [MarketPrice] -> Maybe [MarketPrice]
pricesShortestPath CommoditySymbol
from CommoditySymbol
to [MarketPrice]
allprices)
        of
          Maybe [MarketPrice]
Nothing -> Maybe (CommoditySymbol, Quantity)
forall a. Maybe a
Nothing
          Just [] -> Maybe (CommoditySymbol, Quantity)
forall a. Maybe a
Nothing
          Just [MarketPrice]
ps -> (CommoditySymbol, Quantity) -> Maybe (CommoditySymbol, Quantity)
forall a. a -> Maybe a
Just (MarketPrice -> CommoditySymbol
mpto (MarketPrice -> CommoditySymbol) -> MarketPrice -> CommoditySymbol
forall a b. (a -> b) -> a -> b
$ [MarketPrice] -> MarketPrice
forall a. [a] -> a
last [MarketPrice]
ps, [Quantity] -> Quantity
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product ([Quantity] -> Quantity) -> [Quantity] -> Quantity
forall a b. (a -> b) -> a -> b
$ (MarketPrice -> Quantity) -> [MarketPrice] -> [Quantity]
forall a b. (a -> b) -> [a] -> [b]
map MarketPrice -> Quantity
mprate [MarketPrice]
ps)
tests_priceLookup :: TestTree
tests_priceLookup =
  let
    p :: Integer
-> Int
-> Int
-> CommoditySymbol
-> Quantity
-> CommoditySymbol
-> MarketPrice
p Integer
y Int
m Int
d CommoditySymbol
from Quantity
q CommoditySymbol
to = MarketPrice :: Day
-> CommoditySymbol -> CommoditySymbol -> Quantity -> MarketPrice
MarketPrice{mpdate :: Day
mpdate=Integer -> Int -> Int -> Day
fromGregorian Integer
y Int
m Int
d, mpfrom :: CommoditySymbol
mpfrom=CommoditySymbol
from, mpto :: CommoditySymbol
mpto=CommoditySymbol
to, mprate :: Quantity
mprate=Quantity
q}
    ps1 :: [MarketPrice]
ps1 = [
       Integer
-> Int
-> Int
-> CommoditySymbol
-> Quantity
-> CommoditySymbol
-> MarketPrice
p Integer
2000 Int
01 Int
01 CommoditySymbol
"A" Quantity
10 CommoditySymbol
"B"
      ,Integer
-> Int
-> Int
-> CommoditySymbol
-> Quantity
-> CommoditySymbol
-> MarketPrice
p Integer
2000 Int
01 Int
01 CommoditySymbol
"B" Quantity
10 CommoditySymbol
"C"
      ,Integer
-> Int
-> Int
-> CommoditySymbol
-> Quantity
-> CommoditySymbol
-> MarketPrice
p Integer
2000 Int
01 Int
01 CommoditySymbol
"C" Quantity
10 CommoditySymbol
"D"
      ,Integer
-> Int
-> Int
-> CommoditySymbol
-> Quantity
-> CommoditySymbol
-> MarketPrice
p Integer
2000 Int
01 Int
01 CommoditySymbol
"E"  Quantity
2 CommoditySymbol
"D"
      ,Integer
-> Int
-> Int
-> CommoditySymbol
-> Quantity
-> CommoditySymbol
-> MarketPrice
p Integer
2001 Int
01 Int
01 CommoditySymbol
"A" Quantity
11 CommoditySymbol
"B"
      ]
    makepricegraph :: Day -> PriceGraph
makepricegraph = [MarketPrice] -> [MarketPrice] -> Day -> PriceGraph
makePriceGraph [MarketPrice]
ps1 []
  in String -> Assertion -> TestTree
testCase String
"priceLookup" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
    (Day -> PriceGraph)
-> Day
-> CommoditySymbol
-> Maybe CommoditySymbol
-> Maybe (CommoditySymbol, Quantity)
priceLookup Day -> PriceGraph
makepricegraph (Integer -> Int -> Int -> Day
fromGregorian Integer
1999 Int
01 Int
01) CommoditySymbol
"A" Maybe CommoditySymbol
forall a. Maybe a
Nothing    Maybe (CommoditySymbol, Quantity)
-> Maybe (CommoditySymbol, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Maybe (CommoditySymbol, Quantity)
forall a. Maybe a
Nothing
    (Day -> PriceGraph)
-> Day
-> CommoditySymbol
-> Maybe CommoditySymbol
-> Maybe (CommoditySymbol, Quantity)
priceLookup Day -> PriceGraph
makepricegraph (Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
01) CommoditySymbol
"A" Maybe CommoditySymbol
forall a. Maybe a
Nothing    Maybe (CommoditySymbol, Quantity)
-> Maybe (CommoditySymbol, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (CommoditySymbol, Quantity) -> Maybe (CommoditySymbol, Quantity)
forall a. a -> Maybe a
Just (CommoditySymbol
"B",Quantity
10)
    (Day -> PriceGraph)
-> Day
-> CommoditySymbol
-> Maybe CommoditySymbol
-> Maybe (CommoditySymbol, Quantity)
priceLookup Day -> PriceGraph
makepricegraph (Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
01) CommoditySymbol
"B" (CommoditySymbol -> Maybe CommoditySymbol
forall a. a -> Maybe a
Just CommoditySymbol
"A") Maybe (CommoditySymbol, Quantity)
-> Maybe (CommoditySymbol, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (CommoditySymbol, Quantity) -> Maybe (CommoditySymbol, Quantity)
forall a. a -> Maybe a
Just (CommoditySymbol
"A",Quantity
0.1)
    (Day -> PriceGraph)
-> Day
-> CommoditySymbol
-> Maybe CommoditySymbol
-> Maybe (CommoditySymbol, Quantity)
priceLookup Day -> PriceGraph
makepricegraph (Integer -> Int -> Int -> Day
fromGregorian Integer
2000 Int
01 Int
01) CommoditySymbol
"A" (CommoditySymbol -> Maybe CommoditySymbol
forall a. a -> Maybe a
Just CommoditySymbol
"E") Maybe (CommoditySymbol, Quantity)
-> Maybe (CommoditySymbol, Quantity) -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= (CommoditySymbol, Quantity) -> Maybe (CommoditySymbol, Quantity)
forall a. a -> Maybe a
Just (CommoditySymbol
"E",Quantity
500)
type Edge = MarketPrice
type Path = [Edge]
data PriceGraph = PriceGraph {
   PriceGraph -> Day
pgDate :: Day
    
  ,PriceGraph -> [MarketPrice]
pgEdges :: [Edge]
    
    
    
  ,PriceGraph -> [MarketPrice]
pgEdgesRev :: [Edge]
    
    
    
    
    
  ,PriceGraph -> Map CommoditySymbol CommoditySymbol
pgDefaultValuationCommodities :: M.Map CommoditySymbol CommoditySymbol
    
    
    
    
    
  }
  deriving (Int -> PriceGraph -> ShowS
[PriceGraph] -> ShowS
PriceGraph -> String
(Int -> PriceGraph -> ShowS)
-> (PriceGraph -> String)
-> ([PriceGraph] -> ShowS)
-> Show PriceGraph
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PriceGraph] -> ShowS
$cshowList :: [PriceGraph] -> ShowS
show :: PriceGraph -> String
$cshow :: PriceGraph -> String
showsPrec :: Int -> PriceGraph -> ShowS
$cshowsPrec :: Int -> PriceGraph -> ShowS
Show,(forall x. PriceGraph -> Rep PriceGraph x)
-> (forall x. Rep PriceGraph x -> PriceGraph) -> Generic PriceGraph
forall x. Rep PriceGraph x -> PriceGraph
forall x. PriceGraph -> Rep PriceGraph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PriceGraph x -> PriceGraph
$cfrom :: forall x. PriceGraph -> Rep PriceGraph x
Generic)
pricesShortestPath :: CommoditySymbol -> CommoditySymbol -> [Edge] -> Maybe Path
pricesShortestPath :: CommoditySymbol
-> CommoditySymbol -> [MarketPrice] -> Maybe [MarketPrice]
pricesShortestPath CommoditySymbol
start CommoditySymbol
end [MarketPrice]
edges =
  
  let label :: String
label = String -> CommoditySymbol -> CommoditySymbol -> String
forall r. PrintfType r => String -> r
printf String
"shortest path from %s to %s: " (CommoditySymbol -> CommoditySymbol
showCommoditySymbol CommoditySymbol
start) (CommoditySymbol -> CommoditySymbol
showCommoditySymbol CommoditySymbol
end) in
  ([MarketPrice] -> [MarketPrice])
-> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([MarketPrice] -> String) -> [MarketPrice] -> [MarketPrice]
forall a. Show a => (a -> String) -> a -> a
dbg2With ((String
"price chain:\n"String -> ShowS
forall a. [a] -> [a] -> [a]
++)ShowS -> ([MarketPrice] -> String) -> [MarketPrice] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[MarketPrice] -> String
forall a. Show a => a -> String
pshow)) (Maybe [MarketPrice] -> Maybe [MarketPrice])
-> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a b. (a -> b) -> a -> b
$ 
  (Maybe [MarketPrice] -> String)
-> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a. Show a => (a -> String) -> a -> a
dbg2With ((String
labelString -> ShowS
forall a. [a] -> [a] -> [a]
++)ShowS
-> (Maybe [MarketPrice] -> String) -> Maybe [MarketPrice] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(String
-> ([MarketPrice] -> String) -> Maybe [MarketPrice] -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"none found" (String -> [MarketPrice] -> String
pshowpath String
""))) (Maybe [MarketPrice] -> Maybe [MarketPrice])
-> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a b. (a -> b) -> a -> b
$
  [([MarketPrice], [MarketPrice])] -> Maybe [MarketPrice]
find [([],[MarketPrice]
edges)]
  where
    
    find :: [(Path,[Edge])] -> Maybe Path
    find :: [([MarketPrice], [MarketPrice])] -> Maybe [MarketPrice]
find [([MarketPrice], [MarketPrice])]
paths =
      case (([MarketPrice], [MarketPrice])
 -> [([MarketPrice], [MarketPrice])])
-> [([MarketPrice], [MarketPrice])]
-> [([MarketPrice], [MarketPrice])]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([MarketPrice], [MarketPrice]) -> [([MarketPrice], [MarketPrice])]
extend [([MarketPrice], [MarketPrice])]
paths of
        [] -> Maybe [MarketPrice]
forall a. Maybe a
Nothing 
        [([MarketPrice], [MarketPrice])]
_ | Int
pathlength Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
maxpathlength -> 
          String -> Maybe [MarketPrice] -> Maybe [MarketPrice]
forall a. String -> a -> a
trace (String
"gave up searching for a price chain at length "String -> ShowS
forall a. [a] -> [a] -> [a]
++Int -> String
forall a. Show a => a -> String
show Int
maxpathlengthString -> ShowS
forall a. [a] -> [a] -> [a]
++String
", please report a bug")
          Maybe [MarketPrice]
forall a. Maybe a
Nothing
          where 
            pathlength :: Int
pathlength = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
-> (([MarketPrice], [MarketPrice]) -> Int)
-> Maybe ([MarketPrice], [MarketPrice])
-> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 ([MarketPrice] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([MarketPrice] -> Int)
-> (([MarketPrice], [MarketPrice]) -> [MarketPrice])
-> ([MarketPrice], [MarketPrice])
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([MarketPrice], [MarketPrice]) -> [MarketPrice]
forall a b. (a, b) -> a
fst) ([([MarketPrice], [MarketPrice])]
-> Maybe ([MarketPrice], [MarketPrice])
forall a. [a] -> Maybe a
headMay [([MarketPrice], [MarketPrice])]
paths)
            maxpathlength :: Int
maxpathlength = Int
1000
        [([MarketPrice], [MarketPrice])]
paths' -> 
          case [[MarketPrice]]
completepaths of
                [MarketPrice]
p:[[MarketPrice]]
_ -> [MarketPrice] -> Maybe [MarketPrice]
forall a. a -> Maybe a
Just [MarketPrice]
p  
                []  -> [([MarketPrice], [MarketPrice])] -> Maybe [MarketPrice]
find [([MarketPrice], [MarketPrice])]
paths'
          where completepaths :: [[MarketPrice]]
completepaths = [[MarketPrice]
p | ([MarketPrice]
p,[MarketPrice]
_) <- [([MarketPrice], [MarketPrice])]
paths', (MarketPrice -> CommoditySymbol
mpto (MarketPrice -> CommoditySymbol)
-> Maybe MarketPrice -> Maybe CommoditySymbol
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [MarketPrice] -> Maybe MarketPrice
forall a. [a] -> Maybe a
lastMay [MarketPrice]
p) Maybe CommoditySymbol -> Maybe CommoditySymbol -> Bool
forall a. Eq a => a -> a -> Bool
== CommoditySymbol -> Maybe CommoditySymbol
forall a. a -> Maybe a
Just CommoditySymbol
end]
    
    
    extend :: (Path,[Edge]) -> [(Path,[Edge])]
    extend :: ([MarketPrice], [MarketPrice]) -> [([MarketPrice], [MarketPrice])]
extend ([MarketPrice]
path,[MarketPrice]
unusededges) =
      let
        pathnodes :: [CommoditySymbol]
pathnodes = CommoditySymbol
start CommoditySymbol -> [CommoditySymbol] -> [CommoditySymbol]
forall a. a -> [a] -> [a]
: (MarketPrice -> CommoditySymbol)
-> [MarketPrice] -> [CommoditySymbol]
forall a b. (a -> b) -> [a] -> [b]
map MarketPrice -> CommoditySymbol
mpto [MarketPrice]
path
        pathend :: CommoditySymbol
pathend = CommoditySymbol
-> (MarketPrice -> CommoditySymbol)
-> Maybe MarketPrice
-> CommoditySymbol
forall b a. b -> (a -> b) -> Maybe a -> b
maybe CommoditySymbol
start MarketPrice -> CommoditySymbol
mpto (Maybe MarketPrice -> CommoditySymbol)
-> Maybe MarketPrice -> CommoditySymbol
forall a b. (a -> b) -> a -> b
$ [MarketPrice] -> Maybe MarketPrice
forall a. [a] -> Maybe a
lastMay [MarketPrice]
path
        ([MarketPrice]
nextedges,[MarketPrice]
remainingedges) = (MarketPrice -> Bool)
-> [MarketPrice] -> ([MarketPrice], [MarketPrice])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((CommoditySymbol -> CommoditySymbol -> Bool
forall a. Eq a => a -> a -> Bool
==CommoditySymbol
pathend)(CommoditySymbol -> Bool)
-> (MarketPrice -> CommoditySymbol) -> MarketPrice -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.MarketPrice -> CommoditySymbol
mpfrom) [MarketPrice]
unusededges
      in
        [ ([MarketPrice]
path', [MarketPrice]
remainingedges')
        | MarketPrice
e <- [MarketPrice]
nextedges
        , let path' :: [MarketPrice]
path' = String -> [MarketPrice] -> [MarketPrice]
dbgpath String
"trying" ([MarketPrice] -> [MarketPrice]) -> [MarketPrice] -> [MarketPrice]
forall a b. (a -> b) -> a -> b
$ [MarketPrice]
path [MarketPrice] -> [MarketPrice] -> [MarketPrice]
forall a. [a] -> [a] -> [a]
++ [MarketPrice
e]  
        , let pathnodes' :: [CommoditySymbol]
pathnodes' = MarketPrice -> CommoditySymbol
mpto MarketPrice
e CommoditySymbol -> [CommoditySymbol] -> [CommoditySymbol]
forall a. a -> [a] -> [a]
: [CommoditySymbol]
pathnodes
        , let remainingedges' :: [MarketPrice]
remainingedges' = [MarketPrice
r | MarketPrice
r <- [MarketPrice]
remainingedges, MarketPrice -> CommoditySymbol
mpto MarketPrice
r CommoditySymbol -> [CommoditySymbol] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [CommoditySymbol]
pathnodes' ]
        ]
dbgpath :: String -> [MarketPrice] -> [MarketPrice]
dbgpath  String
label = ([MarketPrice] -> String) -> [MarketPrice] -> [MarketPrice]
forall a. Show a => (a -> String) -> a -> a
dbg2With (String -> [MarketPrice] -> String
pshowpath String
label)
pshowpath :: String -> [MarketPrice] -> String
pshowpath String
label = \case
  []      -> String -> ShowS
prefix String
label String
""
  p :: [MarketPrice]
p@(MarketPrice
e:[MarketPrice]
_) -> String -> ShowS
prefix String
label ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ CommoditySymbol -> String
pshownode (MarketPrice -> CommoditySymbol
mpfrom MarketPrice
e) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
">" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
">" ((MarketPrice -> String) -> [MarketPrice] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (CommoditySymbol -> String
pshownode (CommoditySymbol -> String)
-> (MarketPrice -> CommoditySymbol) -> MarketPrice -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MarketPrice -> CommoditySymbol
mpto) [MarketPrice]
p)
pshownode :: CommoditySymbol -> String
pshownode = CommoditySymbol -> String
T.unpack (CommoditySymbol -> String)
-> (CommoditySymbol -> CommoditySymbol)
-> CommoditySymbol
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CommoditySymbol -> CommoditySymbol
showCommoditySymbol
prefix :: String -> ShowS
prefix String
l = if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
l then (String
""String -> ShowS
forall a. [a] -> [a] -> [a]
++) else ((String
lString -> ShowS
forall a. [a] -> [a] -> [a]
++String
": ")String -> ShowS
forall a. [a] -> [a] -> [a]
++)
makePriceGraph :: [MarketPrice] -> [MarketPrice] -> Day -> PriceGraph
makePriceGraph :: [MarketPrice] -> [MarketPrice] -> Day -> PriceGraph
makePriceGraph [MarketPrice]
alldeclaredprices [MarketPrice]
allinferredprices Day
d =
  String -> PriceGraph -> PriceGraph
forall a. Show a => String -> a -> a
dbg9 (String
"makePriceGraph "String -> ShowS
forall a. [a] -> [a] -> [a]
++Day -> String
forall a. Show a => a -> String
show Day
d) (PriceGraph -> PriceGraph) -> PriceGraph -> PriceGraph
forall a b. (a -> b) -> a -> b
$
  PriceGraph :: Day
-> [MarketPrice]
-> [MarketPrice]
-> Map CommoditySymbol CommoditySymbol
-> PriceGraph
PriceGraph{
     pgDate :: Day
pgDate = Day
d
    ,pgEdges :: [MarketPrice]
pgEdges=[MarketPrice]
forwardprices
    ,pgEdgesRev :: [MarketPrice]
pgEdgesRev=[MarketPrice]
allprices
    ,pgDefaultValuationCommodities :: Map CommoditySymbol CommoditySymbol
pgDefaultValuationCommodities=Map CommoditySymbol CommoditySymbol
defaultdests
    }
  where
    
    visibledeclaredprices :: [MarketPrice]
visibledeclaredprices = String -> [MarketPrice] -> [MarketPrice]
forall a. Show a => String -> a -> a
dbg9 String
"visibledeclaredprices" ([MarketPrice] -> [MarketPrice]) -> [MarketPrice] -> [MarketPrice]
forall a b. (a -> b) -> a -> b
$ (MarketPrice -> Bool) -> [MarketPrice] -> [MarketPrice]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Day -> Day -> Bool
forall a. Ord a => a -> a -> Bool
<=Day
d)(Day -> Bool) -> (MarketPrice -> Day) -> MarketPrice -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.MarketPrice -> Day
mpdate) [MarketPrice]
alldeclaredprices
    visibleinferredprices :: [MarketPrice]
visibleinferredprices = String -> [MarketPrice] -> [MarketPrice]
forall a. Show a => String -> a -> a
dbg9 String
"visibleinferredprices" ([MarketPrice] -> [MarketPrice]) -> [MarketPrice] -> [MarketPrice]
forall a b. (a -> b) -> a -> b
$ (MarketPrice -> Bool) -> [MarketPrice] -> [MarketPrice]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Day -> Day -> Bool
forall a. Ord a => a -> a -> Bool
<=Day
d)(Day -> Bool) -> (MarketPrice -> Day) -> MarketPrice -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.MarketPrice -> Day
mpdate) [MarketPrice]
allinferredprices
    forwardprices :: [MarketPrice]
forwardprices = [MarketPrice] -> [MarketPrice] -> [MarketPrice]
effectiveMarketPrices [MarketPrice]
visibledeclaredprices [MarketPrice]
visibleinferredprices
    
    reverseprices :: [MarketPrice]
reverseprices = String -> [MarketPrice] -> [MarketPrice]
forall a. Show a => String -> a -> a
dbg9 String
"additional reverse prices" ([MarketPrice] -> [MarketPrice]) -> [MarketPrice] -> [MarketPrice]
forall a b. (a -> b) -> a -> b
$
      [MarketPrice
p | p :: MarketPrice
p@MarketPrice{Quantity
CommoditySymbol
Day
mprate :: Quantity
mpto :: CommoditySymbol
mpfrom :: CommoditySymbol
mpdate :: Day
mprate :: MarketPrice -> Quantity
mpto :: MarketPrice -> CommoditySymbol
mpfrom :: MarketPrice -> CommoditySymbol
mpdate :: MarketPrice -> Day
..} <- (MarketPrice -> MarketPrice) -> [MarketPrice] -> [MarketPrice]
forall a b. (a -> b) -> [a] -> [b]
map MarketPrice -> MarketPrice
marketPriceReverse [MarketPrice]
forwardprices
         , Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (CommoditySymbol
mpfrom,CommoditySymbol
mpto) (CommoditySymbol, CommoditySymbol)
-> Set (CommoditySymbol, CommoditySymbol) -> Bool
forall a. Ord a => a -> Set a -> Bool
`S.member` Set (CommoditySymbol, CommoditySymbol)
forwardpairs
      ]
      where
        forwardpairs :: Set (CommoditySymbol, CommoditySymbol)
forwardpairs = [(CommoditySymbol, CommoditySymbol)]
-> Set (CommoditySymbol, CommoditySymbol)
forall a. Ord a => [a] -> Set a
S.fromList [(CommoditySymbol
mpfrom,CommoditySymbol
mpto) | MarketPrice{Quantity
CommoditySymbol
Day
mprate :: Quantity
mpdate :: Day
mpto :: CommoditySymbol
mpfrom :: CommoditySymbol
mprate :: MarketPrice -> Quantity
mpto :: MarketPrice -> CommoditySymbol
mpfrom :: MarketPrice -> CommoditySymbol
mpdate :: MarketPrice -> Day
..} <- [MarketPrice]
forwardprices]
    allprices :: [MarketPrice]
allprices = [MarketPrice]
forwardprices [MarketPrice] -> [MarketPrice] -> [MarketPrice]
forall a. [a] -> [a] -> [a]
++ [MarketPrice]
reverseprices
    
    
    defaultdests :: Map CommoditySymbol CommoditySymbol
defaultdests = [(CommoditySymbol, CommoditySymbol)]
-> Map CommoditySymbol CommoditySymbol
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(CommoditySymbol
mpfrom,CommoditySymbol
mpto) | MarketPrice{Quantity
CommoditySymbol
Day
mprate :: Quantity
mpdate :: Day
mpto :: CommoditySymbol
mpfrom :: CommoditySymbol
mprate :: MarketPrice -> Quantity
mpto :: MarketPrice -> CommoditySymbol
mpfrom :: MarketPrice -> CommoditySymbol
mpdate :: MarketPrice -> Day
..} <- [MarketPrice]
pricesfordefaultcomms]
      where
        pricesfordefaultcomms :: [MarketPrice]
pricesfordefaultcomms = String -> [MarketPrice] -> [MarketPrice]
forall a. Show a => String -> a -> a
dbg9 String
"prices for choosing default valuation commodities, by date then parse order" ([MarketPrice] -> [MarketPrice]) -> [MarketPrice] -> [MarketPrice]
forall a b. (a -> b) -> a -> b
$
          [MarketPrice]
ps
          [MarketPrice]
-> ([MarketPrice] -> [(Integer, MarketPrice)])
-> [(Integer, MarketPrice)]
forall a b. a -> (a -> b) -> b
& [Integer] -> [MarketPrice] -> [(Integer, MarketPrice)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
1..]  
          [(Integer, MarketPrice)]
-> ([(Integer, MarketPrice)] -> [(Integer, MarketPrice)])
-> [(Integer, MarketPrice)]
forall a b. a -> (a -> b) -> b
& ((Integer, MarketPrice) -> (Integer, MarketPrice) -> Ordering)
-> [(Integer, MarketPrice)] -> [(Integer, MarketPrice)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy ((Day, Integer) -> (Day, Integer) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ((Day, Integer) -> (Day, Integer) -> Ordering)
-> ((Integer, MarketPrice) -> (Day, Integer))
-> (Integer, MarketPrice)
-> (Integer, MarketPrice)
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (\(Integer
parseorder,MarketPrice{Quantity
CommoditySymbol
Day
mprate :: Quantity
mpto :: CommoditySymbol
mpfrom :: CommoditySymbol
mpdate :: Day
mprate :: MarketPrice -> Quantity
mpto :: MarketPrice -> CommoditySymbol
mpfrom :: MarketPrice -> CommoditySymbol
mpdate :: MarketPrice -> Day
..})->(Day
mpdate,Integer
parseorder)))  
          [(Integer, MarketPrice)]
-> ([(Integer, MarketPrice)] -> [MarketPrice]) -> [MarketPrice]
forall a b. a -> (a -> b) -> b
& ((Integer, MarketPrice) -> MarketPrice)
-> [(Integer, MarketPrice)] -> [MarketPrice]
forall a b. (a -> b) -> [a] -> [b]
map (Integer, MarketPrice) -> MarketPrice
forall a b. (a, b) -> b
snd    
          where
            ps :: [MarketPrice]
ps | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [MarketPrice] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MarketPrice]
visibledeclaredprices = [MarketPrice]
visibledeclaredprices
               | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [MarketPrice] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [MarketPrice]
alldeclaredprices     = [MarketPrice]
alldeclaredprices
               | Bool
otherwise                        = [MarketPrice]
visibleinferredprices  
effectiveMarketPrices :: [MarketPrice] -> [MarketPrice] -> [MarketPrice]
effectiveMarketPrices :: [MarketPrice] -> [MarketPrice] -> [MarketPrice]
effectiveMarketPrices [MarketPrice]
declaredprices [MarketPrice]
inferredprices =
  let
    
    declaredprices' :: [(Integer, Integer, MarketPrice)]
declaredprices' = [(Integer
1, Integer
i, MarketPrice
p) | (Integer
i,MarketPrice
p) <- [Integer] -> [MarketPrice] -> [(Integer, MarketPrice)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
1..] [MarketPrice]
declaredprices]
    inferredprices' :: [(Integer, Integer, MarketPrice)]
inferredprices' = [(Integer
0, Integer
i, MarketPrice
p) | (Integer
i,MarketPrice
p) <- [Integer] -> [MarketPrice] -> [(Integer, MarketPrice)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Integer
1..] [MarketPrice]
inferredprices]
  in
    String -> [MarketPrice] -> [MarketPrice]
forall a. Show a => String -> a -> a
dbg9 String
"effective forward prices" ([MarketPrice] -> [MarketPrice]) -> [MarketPrice] -> [MarketPrice]
forall a b. (a -> b) -> a -> b
$
    
    [(Integer, Integer, MarketPrice)]
declaredprices' [(Integer, Integer, MarketPrice)]
-> [(Integer, Integer, MarketPrice)]
-> [(Integer, Integer, MarketPrice)]
forall a. [a] -> [a] -> [a]
++ [(Integer, Integer, MarketPrice)]
inferredprices'
    
    [(Integer, Integer, MarketPrice)]
-> ([(Integer, Integer, MarketPrice)]
    -> [(Integer, Integer, MarketPrice)])
-> [(Integer, Integer, MarketPrice)]
forall a b. a -> (a -> b) -> b
& ((Integer, Integer, MarketPrice)
 -> (Integer, Integer, MarketPrice) -> Ordering)
-> [(Integer, Integer, MarketPrice)]
-> [(Integer, Integer, MarketPrice)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((Day, Integer, Integer) -> (Day, Integer, Integer) -> Ordering)
-> (Day, Integer, Integer) -> (Day, Integer, Integer) -> Ordering
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Day, Integer, Integer) -> (Day, Integer, Integer) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ((Day, Integer, Integer) -> (Day, Integer, Integer) -> Ordering)
-> ((Integer, Integer, MarketPrice) -> (Day, Integer, Integer))
-> (Integer, Integer, MarketPrice)
-> (Integer, Integer, MarketPrice)
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (\(Integer
precedence,Integer
parseorder,MarketPrice
mp)->(MarketPrice -> Day
mpdate MarketPrice
mp,Integer
precedence,Integer
parseorder)))
    
    [(Integer, Integer, MarketPrice)]
-> ([(Integer, Integer, MarketPrice)] -> [MarketPrice])
-> [MarketPrice]
forall a b. a -> (a -> b) -> b
& ((Integer, Integer, MarketPrice) -> MarketPrice)
-> [(Integer, Integer, MarketPrice)] -> [MarketPrice]
forall a b. (a -> b) -> [a] -> [b]
map (Integer, Integer, MarketPrice) -> MarketPrice
forall a b c. (a, b, c) -> c
third3
    
    [MarketPrice] -> ([MarketPrice] -> [MarketPrice]) -> [MarketPrice]
forall a b. a -> (a -> b) -> b
& (MarketPrice -> MarketPrice -> Ordering)
-> [MarketPrice] -> [MarketPrice]
forall a. (a -> a -> Ordering) -> [a] -> [a]
nubSortBy ((CommoditySymbol, CommoditySymbol)
-> (CommoditySymbol, CommoditySymbol) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ((CommoditySymbol, CommoditySymbol)
 -> (CommoditySymbol, CommoditySymbol) -> Ordering)
-> (MarketPrice -> (CommoditySymbol, CommoditySymbol))
-> MarketPrice
-> MarketPrice
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (\(MarketPrice{Quantity
CommoditySymbol
Day
mprate :: Quantity
mpto :: CommoditySymbol
mpfrom :: CommoditySymbol
mpdate :: Day
mprate :: MarketPrice -> Quantity
mpto :: MarketPrice -> CommoditySymbol
mpfrom :: MarketPrice -> CommoditySymbol
mpdate :: MarketPrice -> Day
..})->(CommoditySymbol
mpfrom,CommoditySymbol
mpto)))
marketPriceReverse :: MarketPrice -> MarketPrice
marketPriceReverse :: MarketPrice -> MarketPrice
marketPriceReverse mp :: MarketPrice
mp@MarketPrice{Quantity
CommoditySymbol
Day
mprate :: Quantity
mpto :: CommoditySymbol
mpfrom :: CommoditySymbol
mpdate :: Day
mprate :: MarketPrice -> Quantity
mpto :: MarketPrice -> CommoditySymbol
mpfrom :: MarketPrice -> CommoditySymbol
mpdate :: MarketPrice -> Day
..} = 
  MarketPrice
mp{mpfrom :: CommoditySymbol
mpfrom=CommoditySymbol
mpto, mpto :: CommoditySymbol
mpto=CommoditySymbol
mpfrom, mprate :: Quantity
mprate=if Quantity
mprateQuantity -> Quantity -> Bool
forall a. Eq a => a -> a -> Bool
==Quantity
0 then Quantity
0 else Quantity
1Quantity -> Quantity -> Quantity
forall a. Fractional a => a -> a -> a
/Quantity
mprate}  
nullmarketprice :: MarketPrice
nullmarketprice :: MarketPrice
nullmarketprice = MarketPrice :: Day
-> CommoditySymbol -> CommoditySymbol -> Quantity -> MarketPrice
MarketPrice {
   mpdate :: Day
mpdate=Day
nulldate
  ,mpfrom :: CommoditySymbol
mpfrom=CommoditySymbol
""
  ,mpto :: CommoditySymbol
mpto=CommoditySymbol
""
  ,mprate :: Quantity
mprate=Quantity
0
  }
tests_Valuation :: TestTree
tests_Valuation = String -> [TestTree] -> TestTree
testGroup String
"Valuation" [
   TestTree
tests_priceLookup
  ,String -> Assertion -> TestTree
testCase String
"marketPriceReverse" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
    MarketPrice -> MarketPrice
marketPriceReverse MarketPrice
nullmarketprice{mprate :: Quantity
mprate=Quantity
2} MarketPrice -> MarketPrice -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= MarketPrice
nullmarketprice{mprate :: Quantity
mprate=Quantity
0.5}
    MarketPrice -> MarketPrice
marketPriceReverse MarketPrice
nullmarketprice MarketPrice -> MarketPrice -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= MarketPrice
nullmarketprice  
  ]