significant-figures-0.1.0.1: Calculate expressions involving significant figures.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.SigFig.Types

Description

Basic types and convenience functions for constructing your own terms and expression trees.

Synopsis

Documentation

data Term Source #

The basic datatype to represent measurements, constant terms, and evaluation results

Constructors

Measured

A measured value with a finite number of significant figures and an associated value

Constant Rational

A constant value with infinite significant figures

Instances

Instances details
Show Term Source # 
Instance details

Defined in Data.SigFig.Types

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

Eq Term Source # 
Instance details

Defined in Data.SigFig.Types

Methods

(==) :: Term -> Term -> Bool #

(/=) :: Term -> Term -> Bool #

data Op Source #

The types of (infix) operators

Constructors

Add 
Sub 
Mul 
Div 

Instances

Instances details
Show Op Source # 
Instance details

Defined in Data.SigFig.Types

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

Eq Op Source # 
Instance details

Defined in Data.SigFig.Types

Methods

(==) :: Op -> Op -> Bool #

(/=) :: Op -> Op -> Bool #

data Expr Source #

A datatype to represent (not-yet-evaluated) expressions. Use parse to create such an expression from text.

Constructors

Leaf Term

Leaf of an expression

Prec1 [(Op, Expr)]

Operation of "Precedence 1": addition and subtraction

Prec2 [(Op, Expr)]

Operation of "Precedence 2": multiplication and division

Exp Expr Integer

Exponentiation with a constant integer exponent

Apply Function Expr

Application of a function to an expression argument

Instances

Instances details
Show Expr Source # 
Instance details

Defined in Data.SigFig.Types

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Eq Expr Source # 
Instance details

Defined in Data.SigFig.Types

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

data Function Source #

A datatype representing the supported functions.

Constructors

Log10

The function log() in expressions.

Antilog10

The function exp() in expressions.

Instances

Instances details
Show Function Source # 
Instance details

Defined in Data.SigFig.Types

Eq Function Source # 
Instance details

Defined in Data.SigFig.Types

Creating Terms and Expression Trees

measured :: Integer -> Rational -> Term Source #

Create a measured value

constant :: Rational -> Term Source #

Create a constant value

l :: Term -> Expr Source #

Create a leaf node out of a term, like a "singleton".

lMeasured :: Integer -> Rational -> Expr Source #

Create a leaf node and construct the Measured value argument at the same time. Convenience function.

lConstant :: Rational -> Expr Source #

Create a leaf node and construct the Constant value argument at the same time. Convenience function.

Building and Combining Expression Trees

add :: [Expr] -> Expr Source #

Add together a list of Exprs and create a new Expr.

add a b c is similar in idea to a + b + c.

sub :: [Expr] -> Expr Source #

"Subtract together" a list of Exprs and create a new Expr.

sub a b c is similar in idea to a - b - c.

mul :: [Expr] -> Expr Source #

multiply together a list of Exprs and create a new Expr.

mul a b c is similar in idea to a * b * c.

div :: [Expr] -> Expr Source #

"Divide together" a list of Exprs and create a new Expr.

div a b c is similar in idea to a / b / c.

exp :: Expr -> Integer -> Expr Source #

Take an Expr to the power of an integer. Equivalent to Exp.

apply :: Function -> Expr -> Expr Source #

Apply a function to an Expr. Equivalent to Apply.