simple-expr-0.1.1.0: Minimalistic toolkit for simple mathematical expression.
Copyright(C) 2023 Alexey Tochin
LicenseBSD3 (see the file LICENSE)
MaintainerAlexey Tochin <Alexey.Tochin@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • ConstraintKinds
  • InstanceSigs
  • DeriveFunctor
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • RankNTypes
  • ExplicitForAll

Debug.SimpleExpr

Description

Minimalistic toolkit for simple mathematical expression developed for debug purposes. See Tutorial for a quick introduction.

Synopsis

Expression manipulation

number :: Integer -> SimpleExpr Source #

Initializes a single integer number expression.

Examples of usage

Expand
>>> a = number 42
>>> a
42
>>> :t a
a :: SimpleExpr

variable :: String -> SimpleExpr Source #

Initializes a single symbolic variable expression.

Examples of usage

Expand
>>> x = variable "x"
>>> x
x
>>> :t x
x :: SimpleExpr

unaryFunc :: String -> SimpleExpr -> SimpleExpr Source #

Inituialize unarry function

Examples of usage

Expand
>>> x = variable "x"
>>> f = unaryFunc "f"
>>> f x
f(x)
>>> :t x
x :: SimpleExpr
>>> :t f
f :: SimpleExpr -> SimpleExpr

binaryFunc :: String -> SimpleExpr -> SimpleExpr -> SimpleExpr Source #

Inituialize unarry function

Examples of usage

Expand
>>> x = variable "x"
>>> y = variable "y"
>>> (-*-) = binaryFunc "-*-"
>>> x -*- y
x-*-y
>>> :t x
x :: SimpleExpr
>>> :t (-*-)
(-*-) :: SimpleExpr -> SimpleExpr -> SimpleExpr
>>> :t x-*-y
x-*-y :: SimpleExpr

simplify :: SimpleExpr -> SimpleExpr Source #

Simplify expression using some primitive rules like '0 * x -> 0' specified in simplifyStep implementation.

Examples of usage

Expand
>>> import Prelude (($))
>>> import Debug.SimpleExpr (variable, simplify)
>>> import NumHask ((+), (-), (*))
>>> x = variable "x"
>>> simplify $ (x + 0) * 1 - x * (3 - 2)
0

Base types

type SimpleExpr = Fix SimpleExprF Source #

Simple expression type, see tutorial

type Expr = ListOf SimpleExpr Source #

Expression typeclass. It includes SimpleExpr as well as list and tuples of SimpleExpr etc.

Visualisation

plotExpr :: Expr d => d -> IO ThreadId Source #

Visualizes an expression.

Examples of usage

Expand
>>> import Debug.SimpleExpr (number, variable)
>>> import NumHask ((+), (-))
>>> import Data.Graph.VisualizeAlternative (plotDGraphPng)
>>> plotExpr (number 1 + variable "x")

>>> x = variable "x"
>>> y = variable "y"
>>> plotExpr [x + y, x - y]

exprToGraph :: Expr d => d -> DGraph String () Source #

Transforms an expression to graph.

Examples of usage

Expand
>>> import Debug.SimpleExpr (variable)
>>> import NumHask ((+), (-))
>>> x = variable "x"
>>> y = variable "y"
>>> exprToGraph [x + y, x - y]
...

We expect something like fromList [("y",[("x-y",()),("x+y",())]),("x-y",[]),("x",[("x-y",()),("x+y",())]),("x+y",[])] depending on the packages version version.

plotDGraph :: (Hashable v, Ord v, PrintDot v, Show v, Show e) => DGraph v e -> IO ThreadId Source #

A copy of plotDGraph method from Visualize but the parameter Sfdp is replaced by Dot.

plotDGraphPng :: (Hashable v, Ord v, PrintDot v, Show v, Show e) => DGraph v e -> FilePath -> IO FilePath Source #

A copy of toDirectedDot method from Visualize but the parameter Sfdp is replaced by Dot.

Auxiliary functions

dependencies :: SimpleExpr -> [SimpleExpr] Source #

Returns the list of head dependencies of an expression.

Examples of usage

Expand
>>> import Prelude (($), id)
>>> import NumHask ((+), (*))
>>> dependencies (variable "x" + (variable "y" * variable "z"))
[x,y·z]

content :: ListOf inner outer => outer -> [inner] Source #

Returns a list of entities the argument consists of.