{-# LANGUAGE ImportQualifiedPost #-}
module Data.SigFig.Types
( Term (..),
Op (..),
Expr (..),
Function (..),
measured,
constant,
l,
lMeasured,
lConstant,
add,
sub,
mul,
div,
exp,
apply,
)
where
import Data.BigDecimal (BigDecimal (..))
import Data.BigDecimal qualified as BD
import Prelude hiding (div, exp)
data Term
=
Measured {Term -> Integer
numSigFigs :: Integer, Term -> BigDecimal
value :: BigDecimal}
|
Constant Rational
deriving (Int -> Term -> ShowS
[Term] -> ShowS
Term -> String
(Int -> Term -> ShowS)
-> (Term -> String) -> ([Term] -> ShowS) -> Show Term
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Term] -> ShowS
$cshowList :: [Term] -> ShowS
show :: Term -> String
$cshow :: Term -> String
showsPrec :: Int -> Term -> ShowS
$cshowsPrec :: Int -> Term -> ShowS
Show, Term -> Term -> Bool
(Term -> Term -> Bool) -> (Term -> Term -> Bool) -> Eq Term
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Term -> Term -> Bool
$c/= :: Term -> Term -> Bool
== :: Term -> Term -> Bool
$c== :: Term -> Term -> Bool
Eq)
measured :: Integer -> Rational -> Term
measured :: Integer -> Rational -> Term
measured Integer
sf = Integer -> BigDecimal -> Term
Measured Integer
sf (BigDecimal -> Term)
-> (Rational -> BigDecimal) -> Rational -> Term
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> BigDecimal
forall a. Fractional a => Rational -> a
fromRational
constant :: Rational -> Term
constant :: Rational -> Term
constant = Rational -> Term
Constant
data Op
= Add
| Sub
| Mul
| Div
deriving (Int -> Op -> ShowS
[Op] -> ShowS
Op -> String
(Int -> Op -> ShowS)
-> (Op -> String) -> ([Op] -> ShowS) -> Show Op
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Op] -> ShowS
$cshowList :: [Op] -> ShowS
show :: Op -> String
$cshow :: Op -> String
showsPrec :: Int -> Op -> ShowS
$cshowsPrec :: Int -> Op -> ShowS
Show, Op -> Op -> Bool
(Op -> Op -> Bool) -> (Op -> Op -> Bool) -> Eq Op
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Op -> Op -> Bool
$c/= :: Op -> Op -> Bool
== :: Op -> Op -> Bool
$c== :: Op -> Op -> Bool
Eq)
l :: Term -> Expr
l :: Term -> Expr
l = Term -> Expr
Leaf
lMeasured :: Integer -> Rational -> Expr
lMeasured :: Integer -> Rational -> Expr
lMeasured = (Term -> Expr
l (Term -> Expr) -> (Rational -> Term) -> Rational -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Rational -> Term) -> Rational -> Expr)
-> (Integer -> Rational -> Term) -> Integer -> Rational -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Rational -> Term
measured
lConstant :: Rational -> Expr
lConstant :: Rational -> Expr
lConstant = Term -> Expr
l (Term -> Expr) -> (Rational -> Term) -> Rational -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Term
constant
add :: [Expr] -> Expr
add :: [Expr] -> Expr
add = [(Op, Expr)] -> Expr
Prec1 ([(Op, Expr)] -> Expr)
-> ([Expr] -> [(Op, Expr)]) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Op] -> [Expr] -> [(Op, Expr)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Op -> [Op]
forall a. a -> [a]
repeat Op
Add)
sub :: [Expr] -> Expr
sub :: [Expr] -> Expr
sub [] = [(Op, Expr)] -> Expr
Prec1 []
sub (Expr
x : [Expr]
xs) = [(Op, Expr)] -> Expr
Prec1 ([(Op, Expr)] -> Expr) -> [(Op, Expr)] -> Expr
forall a b. (a -> b) -> a -> b
$ (Op
Add, Expr
x) (Op, Expr) -> [(Op, Expr)] -> [(Op, Expr)]
forall a. a -> [a] -> [a]
: [Op] -> [Expr] -> [(Op, Expr)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Op -> [Op]
forall a. a -> [a]
repeat Op
Sub) [Expr]
xs
mul :: [Expr] -> Expr
mul :: [Expr] -> Expr
mul = [(Op, Expr)] -> Expr
Prec2 ([(Op, Expr)] -> Expr)
-> ([Expr] -> [(Op, Expr)]) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Op] -> [Expr] -> [(Op, Expr)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Op -> [Op]
forall a. a -> [a]
repeat Op
Mul)
div :: [Expr] -> Expr
div :: [Expr] -> Expr
div [] = [(Op, Expr)] -> Expr
Prec2 []
div (Expr
x : [Expr]
xs) = [(Op, Expr)] -> Expr
Prec2 ([(Op, Expr)] -> Expr) -> [(Op, Expr)] -> Expr
forall a b. (a -> b) -> a -> b
$ (Op
Mul, Expr
x) (Op, Expr) -> [(Op, Expr)] -> [(Op, Expr)]
forall a. a -> [a] -> [a]
: [Op] -> [Expr] -> [(Op, Expr)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Op -> [Op]
forall a. a -> [a]
repeat Op
Div) [Expr]
xs
exp :: Expr -> Integer -> Expr
exp :: Expr -> Integer -> Expr
exp = Expr -> Integer -> Expr
Exp
apply :: Function -> Expr -> Expr
apply :: Function -> Expr -> Expr
apply = Function -> Expr -> Expr
Apply
data Function
=
Log10
|
Antilog10
deriving (Int -> Function -> ShowS
[Function] -> ShowS
Function -> String
(Int -> Function -> ShowS)
-> (Function -> String) -> ([Function] -> ShowS) -> Show Function
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Function] -> ShowS
$cshowList :: [Function] -> ShowS
show :: Function -> String
$cshow :: Function -> String
showsPrec :: Int -> Function -> ShowS
$cshowsPrec :: Int -> Function -> ShowS
Show, Function -> Function -> Bool
(Function -> Function -> Bool)
-> (Function -> Function -> Bool) -> Eq Function
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Function -> Function -> Bool
$c/= :: Function -> Function -> Bool
== :: Function -> Function -> Bool
$c== :: Function -> Function -> Bool
Eq)
data Expr
=
Leaf Term
|
Prec1 [(Op, Expr)]
|
Prec2 [(Op, Expr)]
|
Exp Expr Integer
|
Apply Function Expr
deriving (Int -> Expr -> ShowS
[Expr] -> ShowS
Expr -> String
(Int -> Expr -> ShowS)
-> (Expr -> String) -> ([Expr] -> ShowS) -> Show Expr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Expr] -> ShowS
$cshowList :: [Expr] -> ShowS
show :: Expr -> String
$cshow :: Expr -> String
showsPrec :: Int -> Expr -> ShowS
$cshowsPrec :: Int -> Expr -> ShowS
Show, Expr -> Expr -> Bool
(Expr -> Expr -> Bool) -> (Expr -> Expr -> Bool) -> Eq Expr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Expr -> Expr -> Bool
$c/= :: Expr -> Expr -> Bool
== :: Expr -> Expr -> Bool
$c== :: Expr -> Expr -> Bool
Eq)