simple-expr-0.2.0.0: Minimalistic toolkit for simple mathematical expression.
Copyright(C) 2025 Alexey Tochin
LicenseBSD3 (see the file LICENSE)
MaintainerAlexey Tochin <Alexey.Tochin@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Debug.SimpleExpr.Utils.Traced

Description

This module provides a Traced type that wraps values with and adds automatic tracing functionality from Trace for debugging purposes. When operations are performed on Traced values, they output trace messages showing what computations are being performed.

Overview

The Traced type is particularly useful for:

  • Debugging complex mathematical computations
  • Understanding the order of operations in lazy evaluation
  • Tracking intermediate values in symbolic computations
  • Educational purposes to visualize computation flow

Basic Usage

>>> import Debug.SimpleExpr.Utils.Traced (traced)
  • Create traced values
>>> x = traced 3
>>> y = traced 4
  • Operations automatically trace
>>> x + y
 <<< TRACING: Calculating (+) of 3 and 4 >>>
7

Integration with NumHask

This module integrates with the numhask hierarchy, providing instances for:

>>> import NumHask (Additive, Subtractive, Multiplicative, Divisive, ExpField, TrigField)
Synopsis

The Traced Type

newtype Traced a Source #

A wrapper type that adds tracing to any value.

When operations are performed on Traced values, they output trace messages to stderr showing what computations are happening.

Examples

Expand

Basic arithmetic with tracing:

>>> x = traced 5
>>> y = traced 3
>>> x * y
 <<< TRACING: Calculating (*) of 5 and 3 >>>
15

Tracing can be nested:

>>> (x + y) * (x - y)
 <<< TRACING: Calculating (+) of 5 and 3 >>>
 <<< TRACING: Calculating (-) of 5 and 3 >>>
 <<< TRACING: Calculating (*) of 8 and 2 >>>
16

Constructors

MkTraced 

Fields

Instances

Instances details
Functor Traced Source # 
Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

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

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

ExtandableMap a b c d => ExtandableMap a b (Traced c) (Traced d) Source #

Traced instance fo ExtandableMaptypecalss.

Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

extendMap :: (a -> b) -> Traced c -> Traced d Source #

(Show b, AlgebraicPower a b) => AlgebraicPower a (Traced b) Source # 
Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

(^^) :: Traced b -> a -> Traced b Source #

(Show b, MultiplicativeAction a b) => MultiplicativeAction a (Traced b) Source # 
Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

(*|) :: a -> Traced b -> Traced b Source #

(Num a, Show a) => Num (Traced a) Source #

Standard Num instance for compatibility with base Haskell.

Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

(+) :: Traced a -> Traced a -> Traced a #

(-) :: Traced a -> Traced a -> Traced a #

(*) :: Traced a -> Traced a -> Traced a #

negate :: Traced a -> Traced a #

abs :: Traced a -> Traced a #

signum :: Traced a -> Traced a #

fromInteger :: Integer -> Traced a #

Show a => Show (Traced a) Source #

Show instance that displays the wrapped value.

Note that this shows the wrapped value, not the Traced constructor.

>>> show (traced 42)
"42"
Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

showsPrec :: Int -> Traced a -> ShowS #

show :: Traced a -> String #

showList :: [Traced a] -> ShowS #

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

Defined in Debug.SimpleExpr.Utils.Traced

Methods

(==) :: Traced a -> Traced a -> Bool #

(/=) :: Traced a -> Traced a -> Bool #

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

Defined in Debug.SimpleExpr.Utils.Traced

Methods

hashWithSalt :: Int -> Traced a -> Int #

hash :: Traced a -> Int #

(Additive a, Show a) => Additive (Traced a) Source #

NumHask Additive instance for addition operations.

Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

(+) :: Traced a -> Traced a -> Traced a #

zero :: Traced a #

(Subtractive a, Show a) => Subtractive (Traced a) Source #

NumHask Subtractive'instance for subtraction operations.

Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

negate :: Traced a -> Traced a #

(-) :: Traced a -> Traced a -> Traced a #

(ExpField a, Show a) => ExpField (Traced a) Source #

NumHask ExpField instance for exponential and logarithmic operations.

>>> import NumHask (exp, log)
>>> exp (traced 1)
 <<< TRACING: Calculating exp of 1.0 >>>
2.718281828459045
>>> log (traced 10)
 <<< TRACING: Calculating log of 10.0 >>>
2.302585092994046
>>> (traced 2) ** (traced 3)
 <<< TRACING: Calculating (**) of 2.0 and 3.0 >>>
8.0
Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

exp :: Traced a -> Traced a #

log :: Traced a -> Traced a #

(**) :: Traced a -> Traced a -> Traced a #

logBase :: Traced a -> Traced a -> Traced a #

sqrt :: Traced a -> Traced a #

(TrigField a, Show a) => TrigField (Traced a) Source #

NumHask TrigField instance for trigonometric operations.

>>> cos (traced 0)
 <<< TRACING: Calculating cos of 0.0 >>>
1.0
Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

pi :: Traced a #

sin :: Traced a -> Traced a #

cos :: Traced a -> Traced a #

tan :: Traced a -> Traced a #

asin :: Traced a -> Traced a #

acos :: Traced a -> Traced a #

atan :: Traced a -> Traced a #

atan2 :: Traced a -> Traced a -> Traced a #

sinh :: Traced a -> Traced a #

cosh :: Traced a -> Traced a #

tanh :: Traced a -> Traced a #

asinh :: Traced a -> Traced a #

acosh :: Traced a -> Traced a #

atanh :: Traced a -> Traced a #

(Divisive a, Show a) => Divisive (Traced a) Source #

NumHask Divisive instance for division operations.

Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

recip :: Traced a -> Traced a #

(/) :: Traced a -> Traced a -> Traced a #

(Multiplicative a, Show a) => Multiplicative (Traced a) Source #

NumHask Multiplicative instance for multiplication operations.

Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

(*) :: Traced a -> Traced a -> Traced a #

one :: Traced a #

FromInteger a => FromInteger (Traced a) Source # 
Instance details

Defined in Debug.SimpleExpr.Utils.Traced

Methods

fromInteger :: Integer -> Traced a #

Creating Traced Values

traced :: a -> Traced a Source #

Smart constructor for creating traced values.

This is equivalent to using the MkTraced constructor directly, but provides a more descriptive name.

Examples

Expand
>>> traced 42
42

untraced :: Traced a -> a Source #

Extract the underlying value from a Traced wrapper. It is equivalent to using the getTraced.

Examples

Expand
>>> untraced (traced 42)
42

Tracing Combinators

addTraceUnary :: Show a => String -> (a -> b) -> Traced a -> Traced b Source #

Apply a unary function with tracing.

This is the core building block for traced unary operations. It outputs a trace message before applying the function.

Examples

Expand
>>> import GHC.Num (abs)
>>> absoluteTraced = addTraceUnary "abs" abs
>>> absoluteTraced (traced (-5))
 <<< TRACING: Calculating abs of -5 >>>
5

Custom unary operations:

>>> double = addTraceUnary "double" (\x -> x * 2)
>>> double (traced 7)
 <<< TRACING: Calculating double of 7 >>>
14

addTraceBinary :: (Show a, Show b) => String -> (a -> b -> c) -> Traced a -> Traced b -> Traced c Source #

Apply a binary function with tracing.

This is the core building block for traced binary operations. It outputs a trace message before applying the function.

Examples

Expand

Basic binary operation:

>>> two = traced 2
>>> three = traced 3
>>> addTraced = addTraceBinary "(+)" (+)
>>> addTraced two three
 <<< TRACING: Calculating (+) of 2 and 3 >>>
5

With symbolic expressions (assuming SimpleExpr is imported):

>>> import Debug.SimpleExpr (variable)
>>> x = traced $ variable "x"
>>> y = traced $ variable "y"
>>> z = x + y
>>> z ** 2
 <<< TRACING: Calculating (+) of x and y >>>
 <<< TRACING: Calculating (**) of x+y and 2 >>>
(x+y)^2

addTraceTernary :: (Show a, Show b, Show c) => String -> (a -> b -> c -> d) -> Traced a -> Traced b -> Traced c -> Traced d Source #

Apply a ternary function with tracing.

Useful for functions that take three arguments.

Examples

Expand
>>> import Data.Ord (Ord(min, max))
>>> clamp = addTraceTernary "clamp" (\low high x -> max low (min high x))
>>> clamp (traced 0) (traced 10) (traced 15)
 <<< TRACING: Calculating clamp of 0, 10, and 15 >>>
10

Utility Functions

withTrace :: String -> Traced a -> Traced a Source #

Execute a computation with a custom trace message.

This allows you to add custom trace points in your code.

Examples

Expand
>>> withTrace "Starting computation" $ (traced 3) + (traced 4)
 <<< TRACING: Starting computation >>>
 <<< TRACING: Calculating (+) of 3 and 4 >>>
7

traceShow :: Show a => String -> Traced a -> Traced a Source #

Trace the current value with a custom message.

Examples

Expand
>>> x = traced 42
>>> traceShow "Current value" x
 <<< TRACING: Current value: 42 >>>
42