-- | This module provides template-haskell functions for various "Haspara"
-- definitions.

module Haspara.TH where

import           Data.Function              (fix)
import           Data.Scientific            (Scientific)
import qualified Data.Text                  as T
import           GHC.TypeLits               (KnownNat)
import           Haspara.Currency           (Currency, CurrencyPair(CurrencyPair), mkCurrencyError)
import           Haspara.Quantity           (Quantity, mkQuantityLossless)
import qualified Language.Haskell.TH.Syntax as TH


-- | Constructs a 'Quantity' value at compile-time using @-XTemplateHaskell@.
--
-- >>> $$(quantityTH 0.00) :: Quantity 2
-- 0.00
-- >>> $$(quantityTH 0.09) :: Quantity 2
-- 0.09
-- >>> $$(quantityTH 0.009) :: Quantity 2
-- ...
-- ..."Underflow while trying to create quantity: 9.0e-3"
-- ...
-- >>> $$(quantityTH 0.009) :: Quantity 3
-- 0.009
quantityTH :: KnownNat s => Scientific -> TH.Q (TH.TExp (Quantity s))
quantityTH :: Scientific -> Q (TExp (Quantity s))
quantityTH = ((Scientific -> Q (TExp (Quantity s)))
 -> Scientific -> Q (TExp (Quantity s)))
-> Scientific -> Q (TExp (Quantity s))
forall a. (a -> a) -> a
fix (((Scientific -> Q (TExp (Quantity s)))
  -> Scientific -> Q (TExp (Quantity s)))
 -> Scientific -> Q (TExp (Quantity s)))
-> ((Scientific -> Q (TExp (Quantity s)))
    -> Scientific -> Q (TExp (Quantity s)))
-> Scientific
-> Q (TExp (Quantity s))
forall a b. (a -> b) -> a -> b
$ \Scientific -> Q (TExp (Quantity s))
loop -> (Exp -> TExp (Quantity s)) -> Q Exp -> Q (TExp (Quantity s))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> TExp (Quantity s)
forall a. Exp -> TExp a
TH.TExp (Q Exp -> Q (TExp (Quantity s)))
-> (Scientific -> Q Exp) -> Scientific -> Q (TExp (Quantity s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Q Exp)
-> (Quantity s -> Q Exp) -> Either String (Quantity s) -> Q Exp
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Q Exp
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q Exp) -> (String -> String) -> String -> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. Show a => a -> String
show) Quantity s -> Q Exp
forall t. Lift t => t -> Q Exp
TH.lift (Either String (Quantity s) -> Q Exp)
-> (Scientific -> Either String (Quantity s))
-> Scientific
-> Q Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Q (TExp (Quantity s)) -> Scientific -> Either String (Quantity s)
forall (s :: Nat).
KnownNat s =>
Q (TExp (Quantity s)) -> Scientific -> Either String (Quantity s)
quantityWE (Scientific -> Q (TExp (Quantity s))
loop Scientific
forall a. HasCallStack => a
undefined)
  where
    -- This provides a work-around for the type-inference due the `s` type parameter.
    -- Trick is borrowed from the Haskell `refined` library.
    quantityWE :: KnownNat s => TH.Q (TH.TExp (Quantity s)) -> Scientific -> Either String (Quantity s)
    quantityWE :: Q (TExp (Quantity s)) -> Scientific -> Either String (Quantity s)
quantityWE = (Scientific -> Either String (Quantity s))
-> Q (TExp (Quantity s))
-> Scientific
-> Either String (Quantity s)
forall a b. a -> b -> a
const Scientific -> Either String (Quantity s)
forall (s :: Nat) (m :: * -> *).
(KnownNat s, MonadError String m) =>
Scientific -> m (Quantity s)
mkQuantityLossless


-- | Constructs a 'Currency' value at compile-time using @-XTemplateHaskell@.
--
-- >>> $$(currencyTH "USD")
-- USD
-- >>> $$(currencyTH "usd")
-- ...
-- ...Currency code error! Expecting at least 3 uppercase ASCII letters, but received: usd
-- ...
currencyTH :: T.Text -> TH.Q (TH.TExp Currency)
currencyTH :: Text -> Q (TExp Currency)
currencyTH = (Text -> Q (TExp Currency))
-> (Currency -> Q (TExp Currency))
-> Either Text Currency
-> Q (TExp Currency)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Q (TExp Currency)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q (TExp Currency))
-> (Text -> String) -> Text -> Q (TExp Currency)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack) ((Exp -> TExp Currency) -> Q Exp -> Q (TExp Currency)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> TExp Currency
forall a. Exp -> TExp a
TH.TExp (Q Exp -> Q (TExp Currency))
-> (Currency -> Q Exp) -> Currency -> Q (TExp Currency)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Currency -> Q Exp
forall t. Lift t => t -> Q Exp
TH.lift) (Either Text Currency -> Q (TExp Currency))
-> (Text -> Either Text Currency) -> Text -> Q (TExp Currency)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text Currency
forall (m :: * -> *). MonadError Text m => Text -> m Currency
mkCurrencyError


-- | Constructs a 'CurrencyPair' value at compile-time using @-XTemplateHaskell@.
--
-- >>> $$(currencyPairTH "EUR" "USD")
-- EUR/USD
-- >>> $$(currencyPairTH "USD" "USD")
-- USD/USD
-- >>> $$(currencyPairTH "USD" "eur")
-- ...
-- ...Currency code error! Expecting at least 3 uppercase ASCII letters, but received: eur
-- ...
currencyPairTH :: T.Text -> T.Text -> TH.Q (TH.TExp CurrencyPair)
currencyPairTH :: Text -> Text -> Q (TExp CurrencyPair)
currencyPairTH = ((Text -> Q (TExp CurrencyPair))
-> (CurrencyPair -> Q (TExp CurrencyPair))
-> Either Text CurrencyPair
-> Q (TExp CurrencyPair)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Q (TExp CurrencyPair)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Q (TExp CurrencyPair))
-> (Text -> String) -> Text -> Q (TExp CurrencyPair)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack) ((Exp -> TExp CurrencyPair) -> Q Exp -> Q (TExp CurrencyPair)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Exp -> TExp CurrencyPair
forall a. Exp -> TExp a
TH.TExp (Q Exp -> Q (TExp CurrencyPair))
-> (CurrencyPair -> Q Exp) -> CurrencyPair -> Q (TExp CurrencyPair)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CurrencyPair -> Q Exp
forall t. Lift t => t -> Q Exp
TH.lift) (Either Text CurrencyPair -> Q (TExp CurrencyPair))
-> (Text -> Either Text CurrencyPair)
-> Text
-> Q (TExp CurrencyPair)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Text -> Either Text CurrencyPair)
 -> Text -> Q (TExp CurrencyPair))
-> (Text -> Text -> Either Text CurrencyPair)
-> Text
-> Text
-> Q (TExp CurrencyPair)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Either Text CurrencyPair
mkPair
  where
    mkPair :: T.Text -> T.Text -> Either T.Text CurrencyPair
    mkPair :: Text -> Text -> Either Text CurrencyPair
mkPair Text
x Text
y = Currency -> Currency -> CurrencyPair
CurrencyPair (Currency -> Currency -> CurrencyPair)
-> Either Text Currency -> Either Text (Currency -> CurrencyPair)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Either Text Currency
forall (m :: * -> *). MonadError Text m => Text -> m Currency
mkCurrencyError Text
x Either Text (Currency -> CurrencyPair)
-> Either Text Currency -> Either Text CurrencyPair
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Either Text Currency
forall (m :: * -> *). MonadError Text m => Text -> m Currency
mkCurrencyError Text
y