unique-logic-tf-0.5.1: Solve simple simultaneous equations

Safe HaskellSafe
LanguageHaskell98

UniqueLogic.ST.TF.Expression

Contents

Synopsis

Documentation

data T w s a Source #

An expression is defined by a set of equations and the variable at the top-level. The value of the expression equals the value of the top variable.

Instances
(C w, Value w a, C a, C s) => Fractional (T w s a) Source # 
Instance details

Defined in UniqueLogic.ST.TF.Expression

Methods

(/) :: T w s a -> T w s a -> T w s a #

recip :: T w s a -> T w s a #

fromRational :: Rational -> T w s a #

(C w, Value w a, C a, C s) => Num (T w s a) Source # 
Instance details

Defined in UniqueLogic.ST.TF.Expression

Methods

(+) :: T w s a -> T w s a -> T w s a #

(-) :: T w s a -> T w s a -> T w s a #

(*) :: T w s a -> T w s a -> T w s a #

negate :: T w s a -> T w s a #

abs :: T w s a -> T w s a #

signum :: T w s a -> T w s a #

fromInteger :: Integer -> T w s a #

Construct primitive expressions

constant :: (C w, Value w a, C s) => a -> T w s a Source #

Make a constant expression of a simple numeric value.

fromVariable :: C s => Variable w s a -> T w s a Source #

Operators from rules with small numbers of arguments

fromRule1 :: (C w, Value w a, C s) => (Variable w s a -> T w s ()) -> T w s a Source #

fromRule2 :: (C w, Value w b, C s) => (Variable w s a -> Variable w s b -> T w s ()) -> T w s a -> T w s b Source #

fromRule3 :: (C w, Value w c, C s) => (Variable w s a -> Variable w s b -> Variable w s c -> T w s ()) -> T w s a -> T w s b -> T w s c Source #

Operators from rules with any number of arguments

data Apply w s f Source #

Instances
C s => Functor (Apply w s) Source # 
Instance details

Defined in UniqueLogic.ST.TF.Expression

Methods

fmap :: (a -> b) -> Apply w s a -> Apply w s b #

(<$) :: a -> Apply w s b -> Apply w s a #

C s => Applicative (Apply w s) Source # 
Instance details

Defined in UniqueLogic.ST.TF.Expression

Methods

pure :: a -> Apply w s a #

(<*>) :: Apply w s (a -> b) -> Apply w s a -> Apply w s b #

liftA2 :: (a -> b -> c) -> Apply w s a -> Apply w s b -> Apply w s c #

(*>) :: Apply w s a -> Apply w s b -> Apply w s b #

(<*) :: Apply w s a -> Apply w s b -> Apply w s a #

arg :: T w s a -> Apply w s (Variable w s a) Source #

This function allows to generalize fromRule2 and fromRule3 to more arguments using Applicative combinators.

Example:

fromRule3 rule x y
   = runApply $ liftA2 rule (arg x) (arg y)
   = runApply $ pure rule <*> arg x <*> arg y

Building rules with arg provides more granularity than using auxiliary pair rules!

runApply :: (C w, Value w a, C s) => Apply w s (Variable w s a -> T w s ()) -> T w s a Source #

Predicates on expressions

(=:=) :: (C w, C s) => T w s a -> T w s a -> T w s () infix 0 Source #

Common operators (see also Num and Fractional instances)

(=!=) :: (C w, C s) => T w s a -> T w s a -> T w s a infixl 4 Source #

sqr :: (C w, Value w a, Floating a, C s) => T w s a -> T w s a Source #

sqrt :: (C w, Value w a, Floating a, C s) => T w s a -> T w s a Source #

max :: (C w, Ord a, Value w a, C s) => T w s a -> T w s a -> T w s a Source #

We are not able to implement a full Ord instance including Eq superclass and comparisons, but we need to compute maxima.

maximum :: (C w, Ord a, Value w a, C s) => [T w s a] -> T w s a Source #

pair :: (C w, Value w a, Value w b, Value w (a, b), C s) => T w s a -> T w s b -> T w s (a, b) Source #

Construct or decompose a pair.