{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Network.Ethereum.Unit
(
Unit(..)
, Wei
, Babbage
, Lovelace
, Shannon
, Szabo
, Finney
, Ether
, KEther
) where
import Data.Proxy (Proxy (..))
import Data.Text.Lazy (Text, unpack)
import GHC.Generics (Generic)
import GHC.Read
import Text.ParserCombinators.ReadPrec
import Text.Printf
import qualified Text.Read.Lex as L
class (Read a, Show a, UnitSpec a, Fractional a) => Unit a where
fromWei :: Integral b => b -> a
toWei :: Integral b => a -> b
class UnitSpec a where
divider :: RealFrac b => proxy a -> b
name :: proxy a -> Text
newtype Value a = MkValue { unValue :: Integer }
deriving (Eq, Ord, Generic)
mkValue :: forall a b . (UnitSpec a, RealFrac b) => b -> Value a
mkValue = MkValue . round . (* divider (Proxy :: Proxy a))
instance UnitSpec a => Unit (Value a) where
fromWei = MkValue . toInteger
toWei = fromInteger . unValue
instance UnitSpec a => UnitSpec (Value a) where
divider = const $ divider (Proxy :: Proxy a)
name = const $ name (Proxy :: Proxy a)
instance UnitSpec a => Num (Value a) where
a + b = MkValue (unValue a + unValue b)
a - b = MkValue (unValue a - unValue b)
a * b = MkValue (unValue a * unValue b)
signum (MkValue a) = MkValue (abs a)
abs (MkValue a) = MkValue (abs a)
fromInteger = mkValue . fromIntegral
instance UnitSpec a => Fractional (Value a) where
a / b = MkValue (unValue a `div` unValue b)
fromRational = mkValue
instance UnitSpec a => Show (Value a) where
show val = printf "%F %s" (x / d :: Double) (name val)
where
x = fromIntegral (unValue val)
d = divider val
instance UnitSpec a => Read (Value a) where
readPrec = parens $ do
x <- readPrec
let res = mkValue x
resName = unpack (name res)
step $ expectP (L.Ident resName)
return res
data U0
data U1
data U2
data U3
data U4
data U5
data U6
data U7
type Wei = Value U0
instance UnitSpec U0 where
divider = const 1
name = const "wei"
type Babbage = Value U1
instance UnitSpec U1 where
divider = const 1e3
name = const "babbage"
type Lovelace = Value U2
instance UnitSpec U2 where
divider = const 1e6
name = const "lovelace"
type Shannon = Value U3
instance UnitSpec U3 where
divider = const 1e9
name = const "shannon"
type Szabo = Value U4
instance UnitSpec U4 where
divider = const 1e12
name = const "szabo"
type Finney = Value U5
instance UnitSpec U5 where
divider = const 1e15
name = const "finney"
type Ether = Value U6
instance UnitSpec U6 where
divider = const 1e18
name = const "ether"
type KEther = Value U7
instance UnitSpec U7 where
divider = const 1e21
name = const "kether"