th-cas: Compile-time CAS(Computer Algebra System)

[ library, math, mit, numeric ] [ Propose Tags ] [ Report a vulnerability ]

th-cas is a Computer Algebra System (CAS) for Haskell that performs symbolic mathematics operations at compile-time using Template Haskell. It provides both interactive usage (similar to Mathematica) and compile-time optimization for mathematical computations with zero runtime overhead. . Features include: . * Symbolic differentiation with automatic simplification . * Symbolic integration using the Risch-Norman heuristic algorithm . * Linear and polynomial equation solvers . * Gröbner basis computation for multivariate polynomial systems . * Pattern matching and coefficient extraction . * Compile-time code generation via Template Haskell . The library supports polynomial operations (GCD, LCM, factorization), trigonometric and exponential functions, and advanced algorithms including Hermite reduction for rational functions and the Extended Euclidean algorithm. . With 150+ test cases, th-cas provides reliable symbolic computation for both runtime and compile-time mathematical operations in Haskell.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0, 0.2.0
Change log ChangeLog.md
Dependencies base (>=4.7 && <5), containers (>=0.6 && <1), template-haskell (>=2.20.0 && <2.23), text (>=2.0 && <3) [details]
License MIT
Author Junji Hashimoto
Maintainer junji.hashimoto@gmail.com
Category Math, Numeric
Home page https://github.com/junjihashimoto/th-cas
Bug tracker https://github.com/junjihashimoto/th-cas/issues
Source repo head: git clone https://github.com/junjihashimoto/th-cas
Uploaded by junjihashimoto at 2025-12-16T21:42:31Z
Distributions NixOS:0.1.0
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 1014 total (4 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2025-12-16 [all 1 reports]

Readme for th-cas-0.2.0

[back to package description]

th-cas : Compile-time CAS (Computer Algebra System)

Hackage version Build Status

th-cas is a Computer Algebra System (CAS) for Haskell that performs symbolic mathematics operations at compile-time using Template Haskell. It provides both interactive usage (like Mathematica) and compile-time optimization for mathematical computations.

Table of Contents

Features

  • Symbolic Differentiation: Automatic differentiation of algebraic expressions
  • Symbolic Integration: Integration using the Risch-Norman heuristic algorithm
  • Equation Solving: Linear and polynomial equation solvers
  • Gröbner Basis: Computation for multivariate polynomial systems
  • Formula Simplification: Automatic algebraic simplification
  • Pattern Matching: Match and extract coefficients from expressions
  • Compile-time Optimization: Zero runtime overhead using Template Haskell

Installation

Add th-cas to your project dependencies:

cabal install th-cas
# or with stack
stack install th-cas

Interactive Usage

th-cas supports interactive usage similar to Mathematica. Start the REPL with:

stack ghci
# or
cabal repl

Variables are defined using the V data constructor or with OverloadedStrings:

Basic Algebra

*Algebra.CAS> :set -XOverloadedStrings
*Algebra.CAS> let x = "x" :: Formula
*Algebra.CAS> let y = "y" :: Formula

-- Automatic simplification
*Algebra.CAS> x^2 + 2*x + x^2
2*x + 2*(x^2)

-- Expansion
*Algebra.CAS> expand $ (x + 1) * (x + 2)
2 + 3*x + x^2

Differentiation

-- Basic differentiation
*Algebra.CAS> diff (x^2 + 2*x + x^2) x
2 + 4*x

-- Chain rule
*Algebra.CAS> diff (sin(x^2)) x
2*x*cos(x^2)

-- Substitution
*Algebra.CAS> subst [(x,1)] $ diff (x^2 + 2*x + x^2) x
6

Integration

-- Polynomial integration
*Algebra.CAS> integrate (x^2) x
(x^3)/3

-- Exponential integration
*Algebra.CAS> integrate (x * exp(x)) x
(-1)*e(x) + x*e(x)

-- Trigonometric integration
*Algebra.CAS> integrate (sin(x) * cos(x)) x
(sin(x)^2)/2

Equation Solving

-- Linear system
*Algebra.CAS> linsolve [x+y=:2, x-y=:3]
Just [(x,5/2),(y,(-1)/2)]

-- Polynomial equations
*Algebra.CAS> solve (x^2 - 5*x + 6) x
[2,3]

Gröbner Basis

-- Compute Gröbner basis for polynomial ideal
*Algebra.CAS> let f1 = x^2 + y
*Algebra.CAS> let f2 = x*y + 1
*Algebra.CAS> grobnerBasis [f1, f2]
[-- basis polynomials --]

-- Polynomial reduction
*Algebra.CAS> reductions (x^2 + x*y) [x + y]
(-1)*(x^2) + x

Compile-time Usage with Template Haskell

th-cas can perform CAS operations at compile-time using Template Haskell, generating optimized code with zero runtime overhead.

Compile-time Differentiation

{-# LANGUAGE TemplateHaskell #-}
import Algebra.CAS.TH

-- This function
myfunc :: Int -> Int
myfunc x = $(diff [|x*x + 2*x + 1|] [|x|])

-- Is compiled to this optimized code at compile-time:
-- myfunc x = 2*x + 2

The differentiation happens during compilation, so there's no symbolic math overhead at runtime.

Pattern Matching

Extract coefficients from expressions:

*Algebra.CAS> match [a*x^2 + b*x + c] [x^2 + 3*x + 4]
Just [(a,1),(b,3),(c,4)]

API Overview

Core Functions

Function Description Example
diff f x Differentiate f with respect to x diff (x^2) x2*x
diffn n f x nth derivative diffn 2 (x^3) x6*x
integrate f x Integrate f with respect to x integrate (x^2) xx^3/3
expand f Expand expression expand ((x+1)^2)1 + 2*x + x^2
simplify f Simplify expression simplify (x/x)1
subst env f Substitute variables subst [(x,2)] (x^2)4
solve f x Solve equation solve (x^2-1) x[-1,1]
linsolve eqs Solve linear system linsolve [x+y=:1]Just [...]
grobnerBasis fs Compute Gröbner basis grobnerBasis [x^2+y, x*y]
degree f Polynomial degree degree (x^3)3
gcdPolynomial f g Polynomial GCD gcdPolynomial (x^2-1) (x-1)x-1

Advanced Examples

Solving Systems of Equations

-- Three equations, three unknowns
*Algebra.CAS> let eqs = [x + y + z =: 6, 2*x + y - z =: 1, x - y + z =: 2]
*Algebra.CAS> linsolve eqs
Just [(x,1),(y,2),(z,3)]

Polynomial Division and GCD

-- Greatest Common Divisor
*Algebra.CAS> gcdPolynomial (x^2 - 1) (x^3 - 1)
(-1) + x

-- LCM
*Algebra.CAS> lcmPolynomial (x^2 - 1) (x^3 - 1)
1 + x + x^2 + (-1)*(x^3) + (-1)*(x^4) + (-1)*(x^5)

Complex Integration

-- Integration by parts (handled automatically)
*Algebra.CAS> integrate (x^2 * exp(x)) x
2*e(x) + (-2)*x*e(x) + (x^2)*e(x)

-- Verify by differentiation
*Algebra.CAS> diff (integrate (x^2 * exp(x)) x) x
(x^2)*e(x)

Supported Operations

Arithmetic

  • Addition, subtraction, multiplication, division
  • Integer and rational exponents
  • Automatic simplification

Functions

  • Trigonometric: sin, cos, tan
  • Exponential: exp, log
  • Power: sqrt, **

Special Features

  • Risch-Norman Integration: Heuristic algorithm for symbolic integration
  • Hermite Reduction: Rational function integration
  • Square-free Factorization: Polynomial factorization (Yun's algorithm)
  • Extended Euclidean Algorithm: For polynomial GCD

Development

Running Tests

cabal test

The project includes comprehensive test coverage:

  • 150+ test cases
  • Property-based tests
  • Integration verification tests

Contributing

Contributions are welcome! Please feel free to submit pull requests or open issues.

License

See LICENSE file for details.

References

  • Risch-Norman Algorithm for symbolic integration
  • Buchberger's Algorithm for Gröbner basis computation