{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Hledger.Data.Commodity
where
import Control.Applicative (liftA2)
import Data.Char (isDigit)
import Data.List
import Data.Maybe (fromMaybe)
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid
#endif
import qualified Data.Text as T
import Hledger.Data.Types
import Hledger.Utils
isNonsimpleCommodityChar :: Char -> Bool
isNonsimpleCommodityChar :: Char -> Bool
isNonsimpleCommodityChar = (Bool -> Bool -> Bool)
-> (Char -> Bool) -> (Char -> Bool) -> Char -> Bool
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Bool -> Bool -> Bool
(||) Char -> Bool
isDigit Char -> Bool
isOther
  where
    otherChars :: Text
otherChars = Text
"-+.@*;\t\n \"{}=" :: T.Text
    isOther :: Char -> Bool
isOther Char
c = (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
c) Text
otherChars
quoteCommoditySymbolIfNeeded :: T.Text -> T.Text
quoteCommoditySymbolIfNeeded :: Text -> Text
quoteCommoditySymbolIfNeeded Text
s
  | (Char -> Bool) -> Text -> Bool
T.any Char -> Bool
isNonsimpleCommodityChar Text
s = Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
  | Bool
otherwise = Text
s
commodity :: [Char]
commodity = [Char]
""
commoditysymbols :: [([Char], Text)]
commoditysymbols =
  [([Char]
"unknown",Text
"")
  ,([Char]
"usd",Text
"$")
  ,([Char]
"eur",Text
"€")
  ,([Char]
"gbp",Text
"£")
  ,([Char]
"hour",Text
"h")
  ]
comm :: String -> CommoditySymbol
comm :: [Char] -> Text
comm [Char]
name = ([Char], Text) -> Text
forall a b. (a, b) -> b
snd (([Char], Text) -> Text) -> ([Char], Text) -> Text
forall a b. (a -> b) -> a -> b
$ ([Char], Text) -> Maybe ([Char], Text) -> ([Char], Text)
forall a. a -> Maybe a -> a
fromMaybe
              ([Char] -> ([Char], Text)
forall a. [Char] -> a
error' [Char]
"commodity lookup failed")  
              ((([Char], Text) -> Bool)
-> [([Char], Text)] -> Maybe ([Char], Text)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\([Char], Text)
n -> ([Char], Text) -> [Char]
forall a b. (a, b) -> a
fst ([Char], Text)
n [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
name) [([Char], Text)]
commoditysymbols)
conversionRate :: CommoditySymbol -> CommoditySymbol -> Double
conversionRate :: Text -> Text -> Double
conversionRate Text
_ Text
_ = Double
1