numeric-prelude-0.2: An experimental alternative hierarchy of numeric type classes

Portabilityportable
Stabilityprovisional
Maintainernumericprelude@henning-thielemann.de

MathObj.PartialFraction

Contents

Description

Implementation of partial fractions. Useful e.g. for fractions of integers and fractions of polynomials.

For the considered ring the prime factorization must be unique.

Synopsis

Documentation

data T a Source

Cons z (indexMapFromList [(x0,[y00,y01]), (x1,[y10]), (x2,[y20,y21,y22])]) represents the partial fraction z + y00x0 + y01x0^2 + y10x1 + y20x2 + y21x2^2 + y22x2^3 The denominators x0, x1, x2, ... must be irreducible, but we can't check this in general. It is also not enough to have relatively prime denominators, because when adding two partial fraction representations there might concur denominators that have non-trivial common divisors.

Constructors

Cons a (Map (ToOrd a) [a]) 

Instances

Eq a => Eq (T a) 
Show a => Show (T a) 
(C a, C a, C a) => C (T a) 
(C a, C a) => C (T a) 

fromFractionSum :: C a => a -> [(a, [a])] -> T aSource

Unchecked construction.

toFractionSum :: C a => T a -> (a, [(a, [a])])Source

toFraction :: C a => T a -> T aSource

toFactoredFraction :: C a => T a -> ([a], a)Source

PrincipalIdealDomain.C is not really necessary here and only due to invokation of toFraction.

multiToFraction :: C a => a -> [a] -> T aSource

PrincipalIdealDomain.C is not really necessary here and only due to invokation of %.

hornerRev :: C a => a -> [a] -> aSource

fromFactoredFraction :: (C a, C a) => [a] -> a -> T aSource

fromFactoredFraction x y computes the partial fraction representation of y % product x, where the elements of x must be irreducible. The function transforms the factors into their standard form with respect to unit factors.

There are more direct methods for special cases like polynomials over rational numbers where the denominators are linear factors.

fromFactoredFractionAlt :: (C a, C a) => [a] -> a -> T aSource

multiFromFraction :: C a => [a] -> a -> (a, [a])Source

The list of denominators must contain equal elements. Sorry for this hack.

fromValue :: a -> T aSource

reduceHeads :: C a => T a -> T aSource

A normalization step which separates the integer part from the leading fraction of each sub-list.

carryRipple :: C a => a -> [a] -> (a, [a])Source

Cf. Number.Positional

normalizeModulo :: C a => T a -> T aSource

A normalization step which reduces all elements in sub-lists modulo their denominators. Zeros might be the result, that must be remove with removeZeros.

removeZeros :: (C a, C a) => T a -> T aSource

Remove trailing zeros in sub-lists because if lists are converted to fractions by multiToFraction we must be sure that the denominator of the (cancelled) fraction is indeed the stored power of the irreducible denominator. Otherwise mulFrac leads to wrong results.

zipWith :: C a => (a -> a -> a) -> ([a] -> [a] -> [a]) -> T a -> T a -> T aSource

mulFrac :: C a => T a -> T a -> (a, a)Source

Transforms a product of two partial fractions into a sum of two fractions. The denominators must be at least relatively prime. Since T requires irreducible denominators, these are also relatively prime.

Example: mulFrac (1%6) (1%4) fails because of the common divisor 2.

mulFrac' :: C a => T a -> T a -> (T a, T a)Source

mulFracStupid :: C a => T a -> T a -> ((T a, T a), T a)Source

Works always but simply puts the product into the last fraction.

mulFracOverlap :: C a => T a -> T a -> ((T a, T a), T a)Source

Also works if the operands share a non-trivial divisor. However the results are quite arbitrary.

scaleFrac :: (C a, C a) => T a -> T a -> T aSource

Expects an irreducible denominator as associate in standard form.

scaleInt :: (C a, C a) => a -> T a -> T aSource

mul :: (C a, C a) => T a -> T a -> T aSource

mulFast :: (C a, C a) => T a -> T a -> T aSource

Helper functions for work with Maps with Indexable keys

indexMapMapWithKey :: (a -> b -> c) -> Map (ToOrd a) b -> Map (ToOrd a) cSource

indexMapToList :: Map (ToOrd a) b -> [(a, b)]Source

indexMapFromList :: C a => [(a, b)] -> Map (ToOrd a) bSource

mapApplySplit :: Ord a => a -> (c -> c -> c) -> (b -> c) -> (Map a b -> Map a c) -> Map a b -> Map a cSource

Apply a function on a specific element if it exists, and another function to the rest of the map.