HaTeX-3.22.3.1: The Haskell LaTeX library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.LaTeX.Base.Math

Description

This module contains the maths-specific part of Text.LaTeX.Base.Commands, i.e. of the commands that are available in LaTeX out of the box without any imports.

Note however that most maths-related documents use the amsmath package, which not only adds some more environments but also improves on rendering details such as symbol spacing. So even if you only need the vanilla-LaTeX commands that this module provides, consider importing Text.LaTeX.Packages.AMSMath instead; it re-exports the entire Text.LaTeX.Base.Math module.

Synopsis

Math Environments

math :: LaTeXC l => l -> l Source #

Inline mathematical expressions.

mathDisplay :: LaTeXC l => l -> l Source #

Displayed mathematical expressions, i.e. in a seperate line / block.

equation :: LaTeXC l => l -> l Source #

A numbered mathematical equation (or otherwise math expression).

equation_ :: LaTeXC l => l -> l Source #

The unnumbered variant of equation.

Referencing

nonumber :: LaTeXC l => l Source #

Prevent an equation from being numbered, where the environment would by default do that.

Symbols and utilities

Brackets / delimiters

autoParens :: LaTeXC l => l -> l Source #

Surround a LaTeX math expression by parentheses whose height automatically matches the expression's. Translates to \left(...\right).

autoSquareBrackets :: LaTeXC l => l -> l Source #

Like autoParens, but with square brackets. Equivalent to autoBrackets"[""]".

autoBraces :: LaTeXC l => l -> l Source #

Like autoParens, but with curly brackets.

autoAngleBrackets :: LaTeXC l => l -> l Source #

Like autoParens, but with angle brackets \(\langle\) ... \(\rangle\). Equivalent to autoBrackets langle rangle.

autoBrackets :: LaTeXC l => LaTeX -> LaTeX -> l -> l Source #

Use custom LaTeX expressions as auto-scaled delimiters to surround math. Suitable delimiters include \(|\ldots|\) (absolute value), \(\|\ldots\|\) (norm, dblPipe), \(\lfloor\ldots\rfloor\) (round-off Gauss brackets, lfloor / rfloor) etc..

langle :: LaTeXC l => l Source #

Left angle bracket, \(\langle\).

rangle :: LaTeXC l => l Source #

Right angle bracket, \(\rangle\).

lfloor :: LaTeXC l => l Source #

Left floor, \(\lfloor\).

rfloor :: LaTeXC l => l Source #

Right floor, \(\rfloor\).

lceil :: LaTeXC l => l Source #

Left ceiling, \(\lceil\).

rceil :: LaTeXC l => l Source #

Right ceiling, \(\rceil\).

dblPipe :: LaTeXC l => l Source #

Double vertical line, used as delimiter for norms \(\| \ldots \|\).

Superscript and subscript

(^:) :: LaTeXC l => l -> l -> l Source #

Superscript.

(!:) :: LaTeXC l => l -> l -> l Source #

Subscript.

(!^) :: LaTeXC l => l -> (l, l) -> l Source #

Sub- and superscript, both stacked.

Function symbols

Some symbols are preceded with t to be distinguished from predefined Haskell entities (like sin and cos).

tsin :: LaTeXC l => l Source #

Sine function symbol.

arcsin :: LaTeXC l => l Source #

Arcsine function symbol.

tcos :: LaTeXC l => l Source #

Cosine function symbol.

arccos :: LaTeXC l => l Source #

Arccosine function symbol.

ttan :: LaTeXC l => l Source #

Tangent function symbol.

arctan :: LaTeXC l => l Source #

Arctangent function symbol.

cot :: LaTeXC l => l Source #

Cotangent function symbol.

arccot :: LaTeXC l => l Source #

Arccotangent function symbol.

tsinh :: LaTeXC l => l Source #

Hyperbolic sine function symbol.

tcosh :: LaTeXC l => l Source #

Hyperbolic cosine function symbol.

ttanh :: LaTeXC l => l Source #

Hyperbolic tangent function symbol.

coth :: LaTeXC l => l Source #

Hyperbolic cotangent function symbol.

sec :: LaTeXC l => l Source #

Secant function symbol.

csc :: LaTeXC l => l Source #

Cosecant function symbol.

texp :: LaTeXC l => l Source #

Exponential function symbol.

tlog :: LaTeXC l => l Source #

Logarithm function symbol.

ln :: LaTeXC l => l Source #

Natural logarithm symbol.

tsqrt :: LaTeXC l => Maybe l -> l -> l Source #

Root notation. Use tsqrt (Just n) x for the nth root of x. When Nothing is supplied, the function will output a square root.

Custom function symbols

operatorname :: LaTeXC l => l -> l Source #

Defines a new function symbol. Note that function symbols defined in this way will not be automatically translated by babel.

Summation / integration / differentiation / relations

tsum :: LaTeXC l => l Source #

Sigma sumation symbol \(\sum\). Use sumFromTo instead if you want to specify the limits of the sum.

sumFromTo Source #

Arguments

:: LaTeXC l 
=> l

Expression below the sigma.

-> l

Expression above the sigma.

-> l 

Sigma sumation symbol with limits, like \[\sum_0^n\].

prod :: LaTeXC l => l Source #

Pi product symbol \(\prod\). Use prodFromTo if you want to specify the limits of the product.

prodFromTo Source #

Arguments

:: LaTeXC l 
=> l

Expression below the pi.

-> l

Expression above the pi.

-> l 

Pi product symbol with limits, like \[\prod_0^n\].

coprod :: LaTeXC l => l Source #

Coproduct symbol \(\coprod\). Use coprodFromTo if you want to specify the limits of the coproduct.

coprodFromTo Source #

Arguments

:: LaTeXC l 
=> l

Expression below.

-> l

Expression above.

-> l 

Coproduct symbol with limits, like \[\coprod_0^n\].

integral :: LaTeXC l => l Source #

Integral symbol. Use integralFromTo if you want to specify the limits of the integral.

integralFromTo Source #

Arguments

:: LaTeXC l 
=> l

Lower limit of integration.

-> l

Upper limit of integration.

-> l 

Integral symbol with limits of integration. \(\int\limits_{-1}^1\)

partial :: LaTeXC l => l Source #

Partial-differentiation symbol \(\partial\)

totald :: LaTeXC l => l Source #

Total-differentiation (or integration-variable) symbol d (non-italic!) To be used as frac (totald) (totald<>"x")\(\frac{\mathrm{d}}{\mathrm{d}x}\).

partialOf :: LaTeXC l => l -> l Source #

Partial-differentiation of variable, e.g. frac (partialOf h) (partialOf t)\(\frac{\partial h}{\partial t}\).

totaldOf :: LaTeXC l => l -> l Source #

Total-differentiation of variable, or integration over variable. To be used as

integralFromTo 0 infty $ totaldOf "x" <> "f(x)"

\[\int\limits_0^\infty\mathrm{d}x f(x),\] or frac (totaldOf"f") (totaldOf"x")\(\frac{\mathrm{d}f}{\mathrm{d}x}\).

bigcup :: LaTeXC l => l Source #

Big union symbol \(\bigcup\). Use bigcupFromTo if you want to specify the limits of the union.

bigcupFromTo Source #

Arguments

:: LaTeXC l 
=> l

Expression below.

-> l

Expression above.

-> l 

Big union symbol with limits, like \[\bigcup_0^n\].

bigcap :: LaTeXC l => l Source #

Big intersection symbol \(\bigcap\). Use bigcapFromTo if you want to specify the limits of the intersection.

bigcapFromTo Source #

Arguments

:: LaTeXC l 
=> l

Expression below.

-> l

Expression above.

-> l 

Big intersection symbol with limits, like \[\bigcap_0^n\].

Operator symbols

Arithmetic

(+-) :: LaTeXC l => l -> l -> l infixl 6 Source #

Plus-or-minus operator \(\pm\). Also available as symbol pm.

(-+) :: LaTeXC l => l -> l -> l infixl 6 Source #

Minus-or-plus operator \(\mp\). Also available as symbol mp.

cdot :: LaTeXC l => l -> l -> l Source #

Centered-dot operator \(\cdot\).

times :: LaTeXC l => l -> l -> l Source #

"x-cross" multiplication operator \(\times\).

div_ :: LaTeXC l => l -> l -> l Source #

Division operator \(\div\).

frac :: LaTeXC l => l -> l -> l Source #

Fraction operator, like frac 1 2\(\frac12\).

(*:) :: LaTeXC l => l -> l -> l infixl 7 Source #

Asterisk operator \(\ast\).

infixl 7 *:

star :: LaTeXC l => l -> l -> l Source #

Star operator \(\star\).

circ :: LaTeXC l => l -> l -> l Source #

Ring operator \(\circ\).

bullet :: LaTeXC l => l -> l -> l Source #

Bullet operator \(\bullet\).

Comparison

(=:) :: LaTeXC l => l -> l -> l infixr 4 Source #

Simple equals sign \(=\).

infixr 4 =:

(/=:) :: LaTeXC l => l -> l -> l infixr 4 Source #

Not equal \(\neq\).

infixr 4 /=:

(<:) :: LaTeXC l => l -> l -> l Source #

Lesser \(<\).

(<=:) :: LaTeXC l => l -> l -> l Source #

Lesser or equal \(\leq\).

(>:) :: LaTeXC l => l -> l -> l Source #

Greater \(>\).

(>=:) :: LaTeXC l => l -> l -> l Source #

Greater or equal \(\geq\).

ll :: LaTeXC l => l -> l -> l Source #

Much less \(\ll\).

gg :: LaTeXC l => l -> l -> l Source #

Much greater \(\gg\).

equiv :: LaTeXC l => l -> l -> l Source #

Identical / defined-as / equivalent \(\equiv\).

propto :: LaTeXC l => l -> l -> l Source #

Proportional-to \(\propto\).

parallel :: LaTeXC l => l -> l -> l Source #

Parallel \(\parallel\).

perp :: LaTeXC l => l -> l -> l Source #

Perpendicular \(\perp\). This is the infix version of bot.

approx :: LaTeXC l => l -> l -> l Source #

Approximate equality \(\approx\)

sim :: LaTeXC l => l -> l -> l Source #

Generic equivalence relation \(\sim\).

simeq :: LaTeXC l => l -> l -> l Source #

Equivalence relation \(\simeq\). Sometimes used for approximate equality or isomorphism.

cong :: LaTeXC l => l -> l -> l Source #

Congruence \(\cong\).

Sets

in_ :: LaTeXC l => l -> l -> l Source #

Element-of \(\in\).

ni :: LaTeXC l => l -> l -> l Source #

Mirrored element-of \(\ni\).

notin :: LaTeXC l => l -> l -> l Source #

Not element of \(\notin\).

subset :: LaTeXC l => l -> l -> l Source #

Subset-of \(\subset\).

supset :: LaTeXC l => l -> l -> l Source #

Superset-of \(\supset\).

subseteq :: LaTeXC l => l -> l -> l Source #

Subset-of-or-equal \(\subseteq\).

supseteq :: LaTeXC l => l -> l -> l Source #

Superset-of-or-equal \(\supseteq\).

cap :: LaTeXC l => l -> l -> l Source #

Set intersection \(\cap\).

cup :: LaTeXC l => l -> l -> l Source #

Set union \(\cup\).

setminus :: LaTeXC l => l -> l -> l Source #

Set minus \(\setminus\).

Misc operators

vee :: LaTeXC l => l -> l -> l Source #

Angle pointing downwards \(\vee\).

wedge :: LaTeXC l => l -> l -> l Source #

Angle pointing upwards \(\wedge\).

oplus :: LaTeXC l => l -> l -> l Source #

Circled plus operator \(\oplus\).

ominus :: LaTeXC l => l -> l -> l Source #

Circled minus operator \(\ominus\).

otimes :: LaTeXC l => l -> l -> l Source #

Circled multiplication cross \(\otimes\).

oslash :: LaTeXC l => l -> l -> l Source #

Circled slash \(\oslash\).

odot :: LaTeXC l => l -> l -> l Source #

Circled dot operator \(\odot\).

uplus :: LaTeXC l => l -> l -> l Source #

Disjoint sum operator \(\uplus\).

Accents

hat :: LaTeXC l => l -> l Source #

Add a hat accent above a symbol, like \(\hat{x}\).

tilde :: LaTeXC l => l -> l Source #

Add a tilde accent above a symbol, like \(\tilde{y}\).

bar :: LaTeXC l => l -> l Source #

Add a bar accent above a symbol, like \(\bar{z}\).

vec :: LaTeXC l => l -> l Source #

Add a vector arrow accent above a symbol, like \(\vec{v}\).

widehat :: LaTeXC l => l -> l Source #

Add a wide hat accent above a symbol, like \(\widehat{w}\).

widetilde :: LaTeXC l => l -> l Source #

Add a wide tilde accent above a symbol, like \(\widetilde{u}\).

dot :: LaTeXC l => l -> l Source #

Add a dot accent above a symbol, as used to denote a derivative, like \(\dot{x}\).

overline :: LaTeXC l => l -> l Source #

Add a wide line accent above a symbol, like \(\overline{abc}\).

Greek alphabet

Functions of greek alphabet symbols.

Uppercase versions are suffixed with u. Variants are prefixed with var. The function pi_ is ended by an underscore symbol to distinguish it from the pi Prelude function.

alpha :: LaTeXC l => l Source #

\(\alpha\) symbol.

beta :: LaTeXC l => l Source #

\(\beta\) symbol.

gamma :: LaTeXC l => l Source #

\(\gamma\) symbol.

gammau :: LaTeXC l => l Source #

\(\Gamma\) symbol.

delta :: LaTeXC l => l Source #

\(\delta\) symbol.

deltau :: LaTeXC l => l Source #

\(\Delta\) symbol.

epsilon :: LaTeXC l => l Source #

\(\epsilon\) symbol.

varepsilon :: LaTeXC l => l Source #

\(\varepsilon\) symbol.

zeta :: LaTeXC l => l Source #

\(\zeta\) symbol.

eta :: LaTeXC l => l Source #

\(\eta\) symbol.

theta :: LaTeXC l => l Source #

\(\theta\) symbol.

vartheta :: LaTeXC l => l Source #

\(\vartheta\) symbol.

thetau :: LaTeXC l => l Source #

\(\Theta\) symbol.

iota :: LaTeXC l => l Source #

\(\iota\) symbol.

kappa :: LaTeXC l => l Source #

\(\kappa\) symbol.

lambda :: LaTeXC l => l Source #

\(\lambda\) symbol.

lambdau :: LaTeXC l => l Source #

\(\Lambda\) symbol.

mu :: LaTeXC l => l Source #

\(\mu\) symbol.

nu :: LaTeXC l => l Source #

\(\nu\) symbol.

xi :: LaTeXC l => l Source #

\(\xi\) symbol.

xiu :: LaTeXC l => l Source #

\(\Xi\) symbol.

pi_ :: LaTeXC l => l Source #

\(\pi\) symbol.

varpi :: LaTeXC l => l Source #

\(\varpi\) symbol.

piu :: LaTeXC l => l Source #

\(\Pi\) symbol.

rho :: LaTeXC l => l Source #

\(\rho\) symbol.

varrho :: LaTeXC l => l Source #

\(\varrho\) symbol.

sigma :: LaTeXC l => l Source #

\(\sigma\) symbol.

varsigma :: LaTeXC l => l Source #

\(\varsigma\) symbol.

sigmau :: LaTeXC l => l Source #

\(\Sigma\) symbol.

tau :: LaTeXC l => l Source #

\(\tau\) symbol.

upsilon :: LaTeXC l => l Source #

\(\upsilon\) symbol.

upsilonu :: LaTeXC l => l Source #

\(\Upsilon\) symbol.

phi :: LaTeXC l => l Source #

\(\phi\) symbol.

varphi :: LaTeXC l => l Source #

\(\varphi\) symbol.

phiu :: LaTeXC l => l Source #

\(\Phi\) symbol.

chi :: LaTeXC l => l Source #

\(\chi\) symbol.

psi :: LaTeXC l => l Source #

\(\psi\) symbol.

psiu :: LaTeXC l => l Source #

\(\Psi\) symbol.

omega :: LaTeXC l => l Source #

\(\omega\) symbol.

omegau :: LaTeXC l => l Source #

\(\Omega\) symbol.

Arrows

uparrow :: LaTeXC l => l Source #

\(\uparrow\) symbol

downarrow :: LaTeXC l => l Source #

\(\downarrow\) symbol

uparrow2 :: LaTeXC l => l Source #

\(\Uparrow\) symbol

downarrow2 :: LaTeXC l => l Source #

\(\Downarrow\) symbol

updownarrow :: LaTeXC l => l Source #

\(\updownarrow\) symbol

updownarrow2 :: LaTeXC l => l Source #

\(\Updownarrow\) symbol

leftarrow :: LaTeXC l => l Source #

\(\leftarrow\) symbol

rightarrow :: LaTeXC l => l Source #

\(\rightarrow\) symbol

leftrightarrow :: LaTeXC l => l Source #

\(\leftrightarrow\) symbol

leftrightarrow2 :: LaTeXC l => l Source #

\(\Leftrightarrow\) symbol

leftarrow2 :: LaTeXC l => l Source #

\(\Leftarrow\) symbol

rightarrow2 :: LaTeXC l => l Source #

\(\Rightarrow\) symbol

longleftarrow :: LaTeXC l => l Source #

\(\longleftarrow\) symbol

longrightarrow :: LaTeXC l => l Source #

\(\longrightarrow\) symbol

longleftarrow2 :: LaTeXC l => l Source #

\(\Longleftarrow\) symbol

longrightarrow2 :: LaTeXC l => l Source #

\(\Longrightarrow\) symbol

longleftrightarrow :: LaTeXC l => l Source #

\(\longleftrightarrow\) symbol

longleftrightarrow2 :: LaTeXC l => l Source #

\(\Longleftrightarrow\) symbol

nwarrow :: LaTeXC l => l Source #

\(\nwarrow\) symbol

nearrow :: LaTeXC l => l Source #

\(\nearrow\) symbol

swarrow :: LaTeXC l => l Source #

\(\swarrow\) symbol

searrow :: LaTeXC l => l Source #

\(\searrow\) symbol

to :: LaTeXC l => l Source #

A right-arrow, \(\to\).

mapsto :: LaTeXC l => l Source #

A right-arrow for function definitions, \(\mapsto\).

longmapsto :: LaTeXC l => l Source #

\(\longmapsto\) symbol

hookleftarrow :: LaTeXC l => l Source #

\(\hookleftarrow\) symbol

hookrightarrow :: LaTeXC l => l Source #

\(\hookrightarrow\) symbol

leftharpoonup :: LaTeXC l => l Source #

\(\leftharpoonup\) symbol

rightharpoonup :: LaTeXC l => l Source #

\(\rightharpoonup\) symbol

leftharpoondown :: LaTeXC l => l Source #

\(\leftharpoondown\) symbol

rightharpoondown :: LaTeXC l => l Source #

\(\rightharpoondown\) symbol

Other symbols

pm :: LaTeXC l => l Source #

Plus-or-minus symbol \(\pm\). Also available as infix +-.

mp :: LaTeXC l => l Source #

Minus-or-plus symbol \(\mp\).

implies :: LaTeXC l => l Source #

An implication arrow, \(\implies\).

forall :: LaTeXC l => l Source #

For all symbol, \(\forall\).

exists :: LaTeXC l => l Source #

Exists symbol, \(\exists\).

dagger :: LaTeXC l => l Source #

Dagger symbol, \(\dagger\).

ddagger :: LaTeXC l => l Source #

Double dagger symbol, \(\ddagger\).

infty :: LaTeXC l => l Source #

Infinity symbol, \(\infty\).

imath :: LaTeXC l => l Source #

Dotless letter i, \(\imath\).

jmath :: LaTeXC l => l Source #

Dotless letter j, \(\jmath\).

bot :: LaTeXC l => l Source #

Bottom symbol, \(\bot\). For the infix version see perp.

Fonts

mathdefault :: LaTeXC l => l -> l Source #

Default math symbol font.

mathbf :: LaTeXC l => l -> l Source #

Bold face, like \(\mathbf{Abc}\).

mathrm :: LaTeXC l => l -> l Source #

Roman, i.e. not-italic math, \(\mathrm{deF}\)

mathcal :: LaTeXC l => l -> l Source #

Calligraphic math symbols. Only works (reliably) with uppercase letters, like \(\mathcal{LMN}\).

mathsf :: LaTeXC l => l -> l Source #

Sans-serif math, \(\mathsf{xyz}\).

mathtt :: LaTeXC l => l -> l Source #

Typewriter font, \(\mathtt{ijk}\).

mathit :: LaTeXC l => l -> l Source #

Italic math. Uses the same glyphs as mathdefault, but with spacings intended for multi-character symbols rather than juxtaposition of single-character symbols.

Orphan instances

Floating LaTeX Source #

The asinh, atanh and acosh methods use custom operatornames and will not be automatically translated by babel. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Fractional LaTeX Source #

Division uses the LaTeX frac command. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Num LaTeX Source #

The signum method uses a custom operatorname and will not be automatically translated by babel. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

(Monad m, a ~ ()) => Floating (LaTeXT m a) Source #

Undefined methods: asinh, atanh and acosh. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Methods

pi :: LaTeXT m a #

exp :: LaTeXT m a -> LaTeXT m a #

log :: LaTeXT m a -> LaTeXT m a #

sqrt :: LaTeXT m a -> LaTeXT m a #

(**) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

logBase :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

sin :: LaTeXT m a -> LaTeXT m a #

cos :: LaTeXT m a -> LaTeXT m a #

tan :: LaTeXT m a -> LaTeXT m a #

asin :: LaTeXT m a -> LaTeXT m a #

acos :: LaTeXT m a -> LaTeXT m a #

atan :: LaTeXT m a -> LaTeXT m a #

sinh :: LaTeXT m a -> LaTeXT m a #

cosh :: LaTeXT m a -> LaTeXT m a #

tanh :: LaTeXT m a -> LaTeXT m a #

asinh :: LaTeXT m a -> LaTeXT m a #

acosh :: LaTeXT m a -> LaTeXT m a #

atanh :: LaTeXT m a -> LaTeXT m a #

log1p :: LaTeXT m a -> LaTeXT m a #

expm1 :: LaTeXT m a -> LaTeXT m a #

log1pexp :: LaTeXT m a -> LaTeXT m a #

log1mexp :: LaTeXT m a -> LaTeXT m a #

(Monad m, a ~ ()) => Fractional (LaTeXT m a) Source #

Division uses the LaTeX frac command. This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Methods

(/) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

recip :: LaTeXT m a -> LaTeXT m a #

fromRational :: Rational -> LaTeXT m a #

(Monad m, a ~ ()) => Num (LaTeXT m a) Source #

Careful! Method signum is undefined. Don't use it! This instance is defined in the Text.LaTeX.Packages.AMSMath module.

Instance details

Methods

(+) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

(-) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

(*) :: LaTeXT m a -> LaTeXT m a -> LaTeXT m a #

negate :: LaTeXT m a -> LaTeXT m a #

abs :: LaTeXT m a -> LaTeXT m a #

signum :: LaTeXT m a -> LaTeXT m a #

fromInteger :: Integer -> LaTeXT m a #