significant-figures-0.1.0.0: Calculate expressions involving significant figures.
LicenseGPL-3.0-or-later (see the LICENSE file)
Maintainermichaellan202@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.SigFig

Description

This module exports everything you need to work with significant figures, including parsing and evaluation.

Synopsis

Types

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
Eq Term Source # 
Instance details

Defined in Data.SigFig.Types

Methods

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

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

Show Term Source # 
Instance details

Defined in Data.SigFig.Types

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

data Op Source #

The types of (infix) operators

Constructors

Add 
Sub 
Mul 
Div 

Instances

Instances details
Eq Op Source # 
Instance details

Defined in Data.SigFig.Types

Methods

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

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

Show Op Source # 
Instance details

Defined in Data.SigFig.Types

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

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
Eq Expr Source # 
Instance details

Defined in Data.SigFig.Types

Methods

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

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

Show Expr Source # 
Instance details

Defined in Data.SigFig.Types

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

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
Eq Function Source # 
Instance details

Defined in Data.SigFig.Types

Show Function Source # 
Instance details

Defined in Data.SigFig.Types

High-Level Functions

parseEval :: Text -> Either Text Term Source #

Takes an expression in text and returns either an error message or an evaluated term.

parse :: Text -> Either Text Expr Source #

Parse text into either an error message or an expression.

parse' :: Text -> Expr Source #

Like parse, but assume the result is a valid expression and crash otherwise.

evaluate :: Expr -> Either Text Term Source #

Given an expression tree, evaluate it and return either an error or result.

evaluate' :: Expr -> Term Source #

Like evaluate, but assume the result is a valid term and crash otherwise.

display :: Term -> Text Source #

Given a term, display it in the most convenient way possible. This means, if the normal representation of the number accurately represents how many significant figures it has, then display it normally. Adds trailing zeroes if necessary to floats and opts for scientific notation if necessary.

Examples

Expand
>>> display $ measured 3 200
"200."
>>> display $ measured 3 4
"4.00"
>>> display $ measured 2 400
"4.0 x 10^2"
>>> display $ measured 2 430
"430"
>>> display $ measured 1 1
"1"
>>> display $ constant (3 % 8)
"0.375"
>>> display $ constant (4 % 9)
"4/9"
>>> display $ measured 2 4.3
"4.3"

displayInformational :: Term -> (Text, Text) Source #

Given a term, return a tuple where the first element is the output of display and the second is an annotation of the type of value. Used in the API.

Examples

Expand
>>> displayInformational $ constant 3
("3","constant value")
>>> displayInformational $ measured 2 3.4
("3.4","2 significant figures")
>>> displayInformational $ measured 3 3400
("3.40 x 10^3","3 significant figures")

displayFull :: Term -> Text Source #

Used in the CLI. Not super pretty but gets the job done in terms of displaying enough information.

Examples

Expand
>>> displayFull (constant 3.45)
"3.45 (const)"
>>> displayFull (measured 3 8500)
"8.50 x 10^3 (3 s.f.)"

processExpression :: Text -> Text Source #

A convenience function for use in REPLs (used in the CLI). Returns text that can either signify a result or error.

Creating and Manipulating Terms and Expressions

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.

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.