Safe Haskell | None |
---|---|
Language | Haskell2010 |
Convert amounts to some related value in various ways. This involves looking up historical market prices (exchange rates) between commodities.
Synopsis
- data ValuationType
- type PriceOracle = (Day, CommoditySymbol, Maybe CommoditySymbol) -> Maybe (CommoditySymbol, Quantity)
- journalPriceOracle :: Journal -> PriceOracle
- mixedAmountApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> MixedAmount -> MixedAmount
- mixedAmountValueAtDate :: PriceOracle -> Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount
- marketPriceReverse :: MarketPrice -> MarketPrice
- priceDirectiveToMarketPrice :: PriceDirective -> MarketPrice
- tests_Valuation :: TestTree
Documentation
data ValuationType Source #
What kind of value conversion should be done on amounts ? UI: --value=cost|end|now|DATE[,COMM]
AtCost (Maybe CommoditySymbol) | convert to cost commodity using transaction prices, then optionally to given commodity using market prices at posting date |
AtEnd (Maybe CommoditySymbol) | convert to default valuation commodity or given commodity, using market prices at period end(s) |
AtNow (Maybe CommoditySymbol) | convert to default valuation commodity or given commodity, using current market prices |
AtDate Day (Maybe CommoditySymbol) | convert to default valuation commodity or given commodity, using market prices on some date |
AtDefault (Maybe CommoditySymbol) | works like AtNow in single period reports, like AtEnd in multiperiod reports |
Instances
Eq ValuationType Source # | |
Defined in Hledger.Data.Valuation (==) :: ValuationType -> ValuationType -> Bool # (/=) :: ValuationType -> ValuationType -> Bool # | |
Data ValuationType Source # | |
Defined in Hledger.Data.Valuation gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ValuationType -> c ValuationType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ValuationType # toConstr :: ValuationType -> Constr # dataTypeOf :: ValuationType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ValuationType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ValuationType) # gmapT :: (forall b. Data b => b -> b) -> ValuationType -> ValuationType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ValuationType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ValuationType -> r # gmapQ :: (forall d. Data d => d -> u) -> ValuationType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ValuationType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ValuationType -> m ValuationType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ValuationType -> m ValuationType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ValuationType -> m ValuationType # | |
Show ValuationType Source # | |
Defined in Hledger.Data.Valuation showsPrec :: Int -> ValuationType -> ShowS # show :: ValuationType -> String # showList :: [ValuationType] -> ShowS # |
type PriceOracle = (Day, CommoditySymbol, Maybe CommoditySymbol) -> Maybe (CommoditySymbol, Quantity) Source #
A price oracle is a magic function that looks up market prices (exchange rates) from one commodity to another (or if unspecified, to a default valuation commodity) on a given date, somewhat efficiently.
mixedAmountApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> ValuationType -> MixedAmount -> MixedAmount Source #
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.
mixedAmountValueAtDate :: PriceOracle -> Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount Source #
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.