hledger/hledger-lib/Hledger/Data/MarketPrice.hs
Justin Le 6bccb847d5 Added a simple 'showMarketPrice' function to show market price directives in a journal-compatible way (#505)
* added showMarketPrice and Hledger.Data.MarketPrice module

* showMarketPrice implemented using showDate

* attempted to add tests to Hledger.Data.MarketPrice

* moved MarketPrice test to Hledger.Read.JournalReader; fixed documentation on MarketPrice; added MarketPrice module to package.yaml
2017-02-03 18:20:00 -08:00

33 lines
899 B
Haskell

{-|
A 'MarketPrice' represents a historical exchange rate between two
commodities. (Ledger calls them historical prices.) For example, prices
published by a stock exchange or the foreign exchange market. Some
commands (balance, currently) can use this information to show the market
value of things at a given date.
-}
{-# LANGUAGE OverloadedStrings, LambdaCase #-}
module Hledger.Data.MarketPrice
where
import qualified Data.Text as T
import Test.HUnit
import Hledger.Data.Amount
import Hledger.Data.Dates
import Hledger.Data.Types
-- | Get the string representation of an market price, based on its
-- commodity's display settings.
showMarketPrice :: MarketPrice -> String
showMarketPrice mp = unwords
[ "P"
, showDate (mpdate mp)
, T.unpack (mpcommodity mp)
, (showAmount . setAmountPrecision maxprecision) (mpamount mp)
]
tests_Hledger_Data_MarketPrice = TestList []