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

Debug.SimpleExpr.Expr

Description

Simple expressions base types and manipulations.

Synopsis

Expression manipulation

number :: Natural -> 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

simplifyExpr :: 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"
>>> simplifyExpr $ (x + 0) * 1 - x * (3 - 2)
0

simplifyStep :: (SimpleExpr -> SimpleExpr) -> SimpleExpr -> SimpleExpr Source #

Minimalistic simplification step.

Examples of usage

Expand
>>> import Prelude (($), id)
>>> import NumHask ((+), (*), (**))
>>> simplifyStep id (0 + (0 + (0 + 10)))
0+(0+10)
>>> simplifyStep id (1 * (0 + (10 ** 1)))
0+(10^1)

simplify :: ExtandableMap SimpleExpr SimpleExpr a a => a -> a Source #

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

Base types

data SimpleExprF a Source #

Expression F-algebra functional.

Instances

Instances details
Eq1 SimpleExprF Source #

Equality comparison for SimpleExprF lifted over its parameter.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

liftEq :: (a -> b -> Bool) -> SimpleExprF a -> SimpleExprF b -> Bool #

Functor SimpleExprF Source # 
Instance details

Defined in Debug.SimpleExpr.Expr

Methods

fmap :: (a -> b) -> SimpleExprF a -> SimpleExprF b #

(<$) :: a -> SimpleExprF b -> SimpleExprF a #

Num SimpleExpr Source #

Numeric typeclass instance for SimpleExpr.

This instance enables standard numeric operations on symbolic expressions, allowing for more natural mathematical notation in symbolic computations.

Examples of usage

Expand
>>> import GHC.Num ((+))

The primary benefit of this instance is enabling direct use of numeric literals in symbolic expressions without explicit conversion. This allows you to write natural mathematical expressions:

>>> x = variable "x"
>>> x + 1
x+1

This concise notation is equivalent to the more verbose explicit form:

>>> x + (number 1)
x+1
Instance details

Defined in Debug.SimpleExpr.Expr

Show SimpleExpr Source #

SimpleExpr instance of Show typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

Hashable1 SimpleExprF Source # 
Instance details

Defined in Debug.SimpleExpr.Expr

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> SimpleExprF a -> Int #

Additive SimpleExpr Source #

SimpleExpr instance of Additive typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

Subtractive SimpleExpr Source #

SimpleExpr instance of Subtractive typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

ExpField SimpleExpr Source #

SimpleExpr instance of ExpField typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

TrigField SimpleExpr Source #

SimpleExpr instance of TrigField typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

Divisive SimpleExpr Source #

SimpleExpr instance of Divisive typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

Multiplicative SimpleExpr Source #

SimpleExpr instance of Multiplicative typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

FromInteger SimpleExpr Source #

SimpleExpr instance of FromInteger typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

Generic1 SimpleExprF Source # 
Instance details

Defined in Debug.SimpleExpr.Expr

FromIntegral Natural n => FromIntegral SimpleExpr n Source #

SimpleExpr instance of FromIntegral typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

fromIntegral :: n -> SimpleExpr #

AlgebraicPower Integer SimpleExpr Source #

AlgebraicPower instance for raising SimpleExpr values to Integer exponents.

Instance details

Defined in Debug.SimpleExpr.Utils.Algebra

Integral a => MultiplicativeAction a SimpleExpr Source #

SimpleExpr instance of MultiplicativeAction a.

Instance details

Defined in Debug.SimpleExpr.Utils.Algebra

Methods

(*|) :: a -> SimpleExpr -> SimpleExpr Source #

Eq a => Eq (SimpleExprF a) Source # 
Instance details

Defined in Debug.SimpleExpr.Expr

Hashable a => Hashable (SimpleExprF a) Source # 
Instance details

Defined in Debug.SimpleExpr.Expr

Methods

hashWithSalt :: Int -> SimpleExprF a -> Int #

hash :: SimpleExprF a -> Int #

FromIntegral Natural n => FromIntegral (SimpleExprF a) n Source #

SimpleExprF instance of FromIntegral typeclass.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

fromIntegral :: n -> SimpleExprF a #

type Rep1 SimpleExprF Source # 
Instance details

Defined in Debug.SimpleExpr.Expr

type SimpleExpr = Fix SimpleExprF Source #

Simple expression type, see tutorial

type SE = SimpleExpr Source #

Short type alias for SimpleExpr.

type Expr = ListOf SimpleExpr Source #

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

Auxiliary functions

class ListOf inner outer Source #

Entity that is representable as a list of in general other entities. In particular, X is a list of single [X], see the example below.

Examples of usage

Expand
>>> data Atom = Atom String deriving Show
>>> type Particle = ListOf Atom
>>> content (Atom "He") :: [Atom]
[Atom "He"]
>>> content (Atom "H", Atom "H") :: [Atom]
[Atom "H",Atom "H"]
>>> content [Atom "H", Atom "O", Atom "H"] :: [Atom]
[Atom "H",Atom "O",Atom "H"]

Minimal complete definition

content

Instances

Instances details
ListOf inner () Source #

Base case instance of ListOf.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

content :: () -> [inner] Source #

ListOf inner inner Source #

Identity instance of ListOf.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

content :: inner -> [inner] Source #

ListOf inner outer => ListOf inner [outer] Source #

List `[]` instance of ListOf.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

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

(ListOf inner outer1, ListOf inner outer2) => ListOf inner (outer1, outer2) Source #

Tuple instance of ListOf.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

content :: (outer1, outer2) -> [inner] Source #

(ListOf inner outer1, ListOf inner outer2, ListOf inner outer3) => ListOf inner (outer1, outer2, outer3) Source #

Triple instance of ListOf.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

content :: (outer1, outer2, outer3) -> [inner] Source #

(ListOf inner outer1, ListOf inner outer2, ListOf inner outer3, ListOf inner outer4) => ListOf inner (outer1, outer2, outer3, outer4) Source #

4-tuple instance of ListOf.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

content :: (outer1, outer2, outer3, outer4) -> [inner] Source #

(ListOf inner outer1, ListOf inner outer2, ListOf inner outer3, ListOf inner outer4, ListOf inner outer5) => ListOf inner (outer1, outer2, outer3, outer4, outer5) Source #

5-tuple instance of ListOf.

Instance details

Defined in Debug.SimpleExpr.Expr

Methods

content :: (outer1, outer2, outer3, outer4, outer5) -> [inner] Source #

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

Returns a list of entities the argument consists of.

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]

showWithBrackets :: SimpleExpr -> String Source #

Shows expression adding brackets if it is needed for a context.