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

Safe HaskellNone

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, Fractional a) => Fractional (T w s a) 
(C w, Value w a, Fractional a) => Num (T w s a) 

Construct primitive expressions

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

Make a constant expression of a simple numeric value.

fromVariable :: Variable w s a -> T w s aSource

Operators from rules with small numbers of arguments

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

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

fromRule3 :: (C w, Value w c) => (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 cSource

Operators from rules with any number of arguments

data Apply w s f Source

Instances

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) => Apply w s (Variable w s a -> T w s ()) -> T w s aSource

Predicates on expressions

(=:=) :: C w => T w s a -> T w s a -> T w s ()Source

Common operators (see also Num and Fractional instances)

(=!=) :: C w => T w s a -> T w s a -> T w s aSource

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

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

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

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) => [T w s a] -> T w s aSource

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

Construct or decompose a pair.