yap-examples-0.1: examples of the algebraic classes in the yap package
Copyright(c) Ross Paterson 2021
LicenseBSD-style (see the file LICENSE)
Maintainer[email protected]
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.YAP.PowerSeries.General

Description

An example instance of the algebraic classes: formal power series generalized to arbitrary exponents.

Synopsis

General power series

data PowerSeries i a Source #

A formal series of the form

\[ \sum_{e \in I} a_e x^e \]

such that the set of indices \(e\) for which \(a_e\) is non-zero is left-finite: for any \(i\), the set of indices \(e < i\) for which \(a_e\) is non-zero is finite.

Addition of indices is required to preserve the ordering.

Instances

Instances details
AdditiveFunctor (PowerSeries i) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

Methods

mapAdditive :: (AdditiveMonoid a, AdditiveMonoid b) => (a -> b) -> PowerSeries i a -> PowerSeries i b #

(Show i, Show a, Eq a, AdditiveMonoid a) => Show (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

Methods

showsPrec :: Int -> PowerSeries i a -> ShowS #

show :: PowerSeries i a -> String #

showList :: [PowerSeries i a] -> ShowS #

(Eq i, Eq a) => Eq (PowerSeries i a) Source #

fails for equal series

Instance details

Defined in Data.YAP.PowerSeries.General

Methods

(==) :: PowerSeries i a -> PowerSeries i a -> Bool #

(/=) :: PowerSeries i a -> PowerSeries i a -> Bool #

(Ord i, Ord a, AdditiveMonoid a) => Ord (PowerSeries i a) Source #

treats the indeterminate as a positive infinitesimal

Instance details

Defined in Data.YAP.PowerSeries.General

Methods

compare :: PowerSeries i a -> PowerSeries i a -> Ordering #

(<) :: PowerSeries i a -> PowerSeries i a -> Bool #

(<=) :: PowerSeries i a -> PowerSeries i a -> Bool #

(>) :: PowerSeries i a -> PowerSeries i a -> Bool #

(>=) :: PowerSeries i a -> PowerSeries i a -> Bool #

max :: PowerSeries i a -> PowerSeries i a -> PowerSeries i a #

min :: PowerSeries i a -> PowerSeries i a -> PowerSeries i a #

(Ord i, Eq a, AbelianGroup a) => AbelianGroup (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

Methods

(-) :: PowerSeries i a -> PowerSeries i a -> PowerSeries i a #

negate :: PowerSeries i a -> PowerSeries i a #

gtimes :: (AbelianGroup b, ToInteger b) => b -> PowerSeries i a -> PowerSeries i a #

(Ord i, Eq a, AdditiveMonoid a) => AdditiveMonoid (PowerSeries i a) Source #

Pointwise addition

Instance details

Defined in Data.YAP.PowerSeries.General

Methods

(+) :: PowerSeries i a -> PowerSeries i a -> PowerSeries i a #

zero :: PowerSeries i a #

atimes :: ToInteger b => b -> PowerSeries i a -> PowerSeries i a #

(Ord i, AbelianGroup i, Eq a, Field a) => DivisionRing (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

(Ord i, AbelianGroup i, Eq a, Field a) => DivisionSemiring (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

Methods

recip :: PowerSeries i a -> PowerSeries i a #

(Ord i, AbelianGroup i, Eq a, Field a) => Field (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

(Ord i, AdditiveMonoid i, Eq a, FromRational a) => FromRational (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

(Ord i, AdditiveMonoid i, Eq a, Ring a) => Ring (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

Methods

fromInteger :: Integer -> PowerSeries i a #

(Ord i, AbelianGroup i, Eq a, Field a) => Semifield (PowerSeries i a) Source # 
Instance details

Defined in Data.YAP.PowerSeries.General

Methods

(/) :: PowerSeries i a -> PowerSeries i a -> PowerSeries i a #

(Ord i, AdditiveMonoid i, Eq a, Semiring a) => Semiring (PowerSeries i a) Source #

Discrete convolution

Instance details

Defined in Data.YAP.PowerSeries.General

Construction

term :: (Eq a, AdditiveMonoid a) => i -> a -> PowerSeries i a Source #

term i a is a series consisting of the term \(a x^i\).

term i a * term j b = term (i+j) (a*b)

constant :: (AdditiveMonoid i, Eq a, AdditiveMonoid a) => a -> PowerSeries i a Source #

Power series representing a constant value \(c\)

constant a = term 0 a

identity :: (Semiring i, Semiring a) => PowerSeries i a Source #

Identity function, i.e. the indeterminate \(x\)

identity = term 1 1

fromTerms :: (Eq a, AdditiveMonoid a) => [(i, a)] -> PowerSeries i a Source #

Construct a power series from a list in ascending order of index

fromTerms ts = sum [term i a | (i, a) <- ts]

fromCoefficients :: (Semiring i, Eq a, AdditiveMonoid a) => [a] -> PowerSeries i a Source #

Power series formed from a list of coefficients of indices 0, 1, ... If the list is finite, the remaining coefficients are zero.

Queries

order :: (Eq a, AdditiveMonoid a) => PowerSeries i a -> i Source #

The smallest exponent with a non-zero coefficient (undefined on zero)

terms :: (Eq a, AdditiveMonoid a) => PowerSeries i a -> [(i, a)] Source #

Indices with non-zero coefficients, in ascending order

Special cases

type LaurentSeries = PowerSeries Integer Source #

A formal power series with integer indices, of which finitely many are negative.

laurentSeries :: (Eq a, AdditiveMonoid a) => Integer -> [a] -> LaurentSeries a Source #

A Laurent series with coefficients starting from the given index

type LeviCivitaField = PowerSeries Rational Source #

The Levi-Civita field.