halg-partial-fraction-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

Algebra.Ring.LinearRecurrentSequence

Synopsis

Documentation

data Power Source #

Constructors

P Natural 
Np 

Instances

Instances details
Eq Power Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(==) :: Power -> Power -> Bool #

(/=) :: Power -> Power -> Bool #

Ord Power Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

compare :: Power -> Power -> Ordering #

(<) :: Power -> Power -> Bool #

(<=) :: Power -> Power -> Bool #

(>) :: Power -> Power -> Bool #

(>=) :: Power -> Power -> Bool #

max :: Power -> Power -> Power #

min :: Power -> Power -> Power #

Show Power Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

showsPrec :: Int -> Power -> ShowS #

show :: Power -> String #

showList :: [Power] -> ShowS #

data GeneralTerm k where Source #

Constructors

Const :: k -> GeneralTerm k 
N :: GeneralTerm k 
(:^) :: GeneralTerm k -> Power -> GeneralTerm k infixr 8 
(:+) :: GeneralTerm k -> GeneralTerm k -> GeneralTerm k infixl 6 
(:*) :: GeneralTerm k -> GeneralTerm k -> GeneralTerm k infixl 7 
(:-) :: GeneralTerm k -> GeneralTerm k -> GeneralTerm k infixl 6 
Lift :: Reifies s (Unipol k) => Proxy s -> GeneralTerm (WrapDecidableUnits (Quotient s (Unipol k))) -> GeneralTerm k 

Instances

Instances details
Ring k => RightModule Integer (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(*.) :: GeneralTerm k -> Integer -> GeneralTerm k #

Rig k => RightModule Natural (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(*.) :: GeneralTerm k -> Natural -> GeneralTerm k #

Semiring k => RightModule k (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(*.) :: GeneralTerm k -> k -> GeneralTerm k #

Ring k => LeftModule Integer (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(.*) :: Integer -> GeneralTerm k -> GeneralTerm k #

Rig k => LeftModule Natural (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(.*) :: Natural -> GeneralTerm k -> GeneralTerm k #

Semiring k => LeftModule k (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(.*) :: k -> GeneralTerm k -> GeneralTerm k #

(Show k, Field k, CoeffRing k, PrettyCoeff k) => Show (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Additive k => Semigroup (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Rig k => Monoid (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Ring k => Ring (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Ring k => Rig (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Unital k => Unital (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

one :: GeneralTerm k #

pow :: GeneralTerm k -> Natural -> GeneralTerm k #

productWith :: Foldable f => (a -> GeneralTerm k) -> f a -> GeneralTerm k #

Ring k => Semiring (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Multiplicative (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(*) :: GeneralTerm k -> GeneralTerm k -> GeneralTerm k #

pow1p :: GeneralTerm k -> Natural -> GeneralTerm k #

productWith1 :: Foldable1 f => (a -> GeneralTerm k) -> f a -> GeneralTerm k #

Rig k => Monoidal (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

zero :: GeneralTerm k #

sinnum :: Natural -> GeneralTerm k -> GeneralTerm k #

sumWith :: Foldable f => (a -> GeneralTerm k) -> f a -> GeneralTerm k #

Ring k => Group (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Additive (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(+) :: GeneralTerm k -> GeneralTerm k -> GeneralTerm k #

sinnum1p :: Natural -> GeneralTerm k -> GeneralTerm k #

sumWith1 :: Foldable1 f => (a -> GeneralTerm k) -> f a -> GeneralTerm k #

Abelian k => Abelian (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Semiring k => RightModule (Scalar k) (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(*.) :: GeneralTerm k -> Scalar k -> GeneralTerm k #

Semiring k => LeftModule (Scalar k) (GeneralTerm k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Methods

(.*) :: Scalar k -> GeneralTerm k -> GeneralTerm k #

showsGTWith :: (CoeffRing k, Field k) => (Int -> k -> ShowSCoeff) -> Int -> GeneralTerm k -> ShowS Source #

data Recurrence a where Source #

Constructors

Recurrence 

Fields

generatingFunction :: forall k. (Field k, CoeffRing k) => Recurrence k -> Fraction (Unipol k) Source #

Generating function for the sequence defined by the n-ary linear recurrence formula: [ a_{n + k} = c_0 a_n + c_1 a_1 + cdots + c_{k - 1} a_{n + k - 1}. ] Where initial values \(a_0, \ldots, a_{k - 1}\) are given.

Fibonacci \(a0 = 0, a1 = 1, a(n+2) = an + a(n+1)\):

>>> generatingFunction $ Recurrence (1 :< 1 :< Nil) (0 :< (1 :: Rational) :< Nil) 0
-x / x^2 + x - 1

Tribonacci:

>>> generatingFunction $ Recurrence (1 :< 1 :< 1 :< Nil) (0 :< 1 :< (1 :: Rational) :< Nil) 0
-x / x^3 + x^2 + x - 1

solveTernaryRecurrence Source #

Arguments

:: MonadRandom m 
=> Sized 2 Rational

Recurrence coefficients

-> Sized 2 Rational

Initial values

-> Rational

Constant term

-> m (GeneralTerm Rational) 

Solves ternary linear recurrent sequence (e.g. Fibonacci).

  • Example: Fibonacci sequence
>>> fib <- evalRandIO $ solveTernaryRecurrence (1 :< 1 :< Nil) (0 :< 1 :< Nil) 0
>>> fib
((2 / 5)*Root(x^2 + x - 1) + (1 / 5)) * (Root(x^2 + x - 1) + 1) ^ n + (-(2 / 5)*Root(x^2 + x - 1) - (1 / 5)) * (-Root(x^2 + x - 1)) ^ n
>>> map (evalGeneralTerm fib) [0..12]
[0,1,1,2,3,5,8,13,21,34,55,89,144]

solveRationalRecurrence Source #

Arguments

:: MonadRandom m 
=> Recurrence Rational

Recurrence coefficients

-> m (GeneralTerm Rational) 

Solves general (n+1)-ary linear recurrent sequence.

  • * Example1: Tribonacci sequence defined by: T_{n+3} = T_n + T_{n+1} + T_{n+2} T_0 = 0, T_1 = 0, T_2 = 1
>>> trib <- evalRandIO $ solveRationalRecurrence $ Recurrence (1 :< 1 :< 1 :< Nil) (0 :< 0 :< 1 :< Nil) 0
>>> trib
((5 / 22)*Root(x^3 + x^2 + x - 1)^2 + (1 / 22)*Root(x^3 + x^2 + x - 1) + (1 / 11)) * (Root(x^3 + x^2 + x - 1)^2 + Root(x^3 + x^2 + x - 1) + 1) ^ n + (-(5 / 22)*Root(x^3 + x^2 + x - 1) - (2 / 11)*Root(1*x^2 + Root(x^3 + x^2 + x - 1) + 1*x + Root(x^3 + x^2 + x - 1)^2 + Root(x^3 + x^2 + x - 1) + 1) + -(5 / 22)*Root(x^3 + x^2 + x - 1)^2 - (5 / 22)*Root(x^3 + x^2 + x - 1) - (3 / 22)) * (-Root(x^3 + x^2 + x - 1)*Root(1*x^2 + Root(x^3 + x^2 + x - 1) + 1*x + Root(x^3 + x^2 + x - 1)^2 + Root(x^3 + x^2 + x - 1) + 1) + -Root(x^3 + x^2 + x - 1)^2 - Root(x^3 + x^2 + x - 1)) ^ n + ((5 / 22)*Root(x^3 + x^2 + x - 1) + (2 / 11)*Root(1*x^2 + Root(x^3 + x^2 + x - 1) + 1*x + Root(x^3 + x^2 + x - 1)^2 + Root(x^3 + x^2 + x - 1) + 1) + (2 / 11)*Root(x^3 + x^2 + x - 1) + (1 / 22)) * (Root(x^3 + x^2 + x - 1)*Root(1*x^2 + Root(x^3 + x^2 + x - 1) + 1*x + Root(x^3 + x^2 + x - 1)^2 + Root(x^3 + x^2 + x - 1) + 1)) ^ n
>>> map (evalGeneralTerm trib) [0..12]
[0,0,1,1,2,4,7,13,24,44,81,149,274]
  • * Example2: Tetrabonacci sequence defined by: T_{n+4} = T_n + T_{n+1} + T_{n+2} + T_{n+3} T_0 = 0, T_1 = 0, T_2 = 0, T_3 = 1
>>> tet <- evalRandIO $ solveRationalRecurrence $ Recurrence (1 :< 1 :< 1 :< 1 :< Nil) (0 :< 0 :< 0 :< 1 :< Nil) 0
>>> tet
>>> map (evalGeneralTerm tet) [0..12]
[0,0,0,1,1,2,4,8,15,29,56,108,208]

solveFiniteFieldRecurrence Source #

Arguments

:: (MonadRandom m, CoeffRing k, FiniteField k, Random k) 
=> Recurrence k

Recurrence coefficients

-> m (GeneralTerm k) 

Solves linear recurrent sequence over finite fields.

  • * Example1: Fibonacci sequence over F_{17}. >>> import Numeric.Field.Prime >>> :set -XDataKinds >>> fibF17 <- evalRandIO $ solveFiniteFieldRecurrence $ Recurrence (1 :< 1 :< Nil) (0 :< (1 :: F 17) :< Nil) 0 >>> fibF17 (14*Root(x^2 + x + 16) + 7) * (Root(x^2 + x + 16) + 1) ^ n + (3*Root(x^2 + x + 16) + 10) * (16*Root(x^2 + x + 16)) ^ n
>>> map (evalGeneralTerm  fibF17) [0..20]
[0,1,1,2,3,5,8,13,4,0,4,4,8,12,3,15,1,16,0,16,16]
  • * Example2: Tetrabonacci over F_{17} >>> tetF17 <- evalRandIO $ solveFiniteFieldRecurrence $ Recurrence ((1 :: F 17) :< 1 :< 1 :< 1 :< Nil) (0 :< 0 :< 0 :< 1 :< Nil) 0 >>> map (evalGeneralTerm tetF17) [0..20] [0,0,0,1,1,2,4,8,15,12,5,6,4,10,8,11,16,11,12,16,4]
  • * Example3: Twekaed tribonacci over GF_{5^3}

T_{n+3} = T_n + T_{n+1} + T_{n+2} T_0 = 1, T_1 = ξ, T_2 = ξ^2, where ξ is a primitive element of GF_{5^3}.

>>> triGF53 <- evalRandIO $ solveFiniteFieldRecurrence $ Recurrence (1 :< (1 :: GF 5 3) :< 1 :< Nil) ( 1 :< primitive :< (primitive ^ 2) :< Nil) 0
>>> triGF53
<ξ^2 + ξ + 1> * <3*ξ + 2> ^ n + <ξ^2 + ξ + 1> * <4*ξ^2> ^ n + <3*ξ^2 + 3*ξ + 4> * <ξ^2 + 2*ξ + 4> ^ n
>>> map (evalGeneralTerm  triGF53) [0..20]
[1,<ξ>,<ξ^2>,<ξ^2 + ξ + 1>,<2*ξ^2 + 2*ξ + 1>,<4*ξ^2 + 3*ξ + 2>,<2*ξ^2 + ξ + 4>,<3*ξ^2 + ξ + 2>,<4*ξ^2 + 3>,<4*ξ^2 + 2*ξ + 4>,<ξ^2 + 3*ξ + 4>,<4*ξ^2 + 1>,<4*ξ^2 + 4>,<4*ξ^2 + 3*ξ + 4>,<2*ξ^2 + 3*ξ + 4>,<ξ + 2>,<ξ^2 + 2*ξ>,<3*ξ^2 + ξ + 1>,<4*ξ^2 + 4*ξ + 3>,<3*ξ^2 + 2*ξ + 4>,<2*ξ + 3>]

solveRecurrenceWith Source #

Arguments

:: (Functor m, CoeffRing k, Field k) 
=> (Unipol k -> m (k, NonEmpty (Unipol k, Natural)))

Factorisation function; must return content and monic square-free factorisation over k.

-> Recurrence k

Recurrence coefficients

-> m (GeneralTerm k) 

newtype WrapDecidableUnits k Source #

Unsafe wrapper to treat DecidableUnits as if it is a field.

Constructors

WrapDecidableUnits 

Instances

Instances details
RightModule c k => RightModule c (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

LeftModule c k => LeftModule c (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Eq k => Eq (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Ord k => Ord (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Show k => Show (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(DecidableAssociates k, Ring k, DecidableZero k, DecidableUnits k) => UFD (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(DecidableAssociates k, Ring k, DecidableZero k, DecidableUnits k) => PID (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(DecidableAssociates k, Ring k, DecidableZero k, DecidableUnits k) => GCDDomain (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(DecidableAssociates k, Ring k, DecidableZero k, DecidableUnits k) => IntegralDomain (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(DecidableAssociates k, Ring k, DecidableZero k, DecidableUnits k) => Euclidean (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(Monoidal k, Multiplicative k) => ZeroProductSemiring (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(DecidableAssociates k, Ring k, DecidableZero k, DecidableUnits k) => UnitNormalForm (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Ring k => Ring (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Rig k => Rig (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

DecidableZero k => DecidableZero (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

DecidableUnits k => DecidableUnits (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

DecidableAssociates k => DecidableAssociates (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Unital k => Unital (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

DecidableUnits k => Division (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Multiplicative k => Commutative (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

(Additive k, Multiplicative k) => Semiring (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Multiplicative k => Multiplicative (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Monoidal k => Monoidal (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Group k => Group (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Additive k => Additive (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Additive k => Abelian (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

Hashable k => Hashable (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

PrettyCoeff k => PrettyCoeff (WrapDecidableUnits k) Source # 
Instance details

Defined in Algebra.Ring.LinearRecurrentSequence

unliftQuadInverse Source #

Arguments

:: forall k. (CoeffRing k, Field k) 
=> Natural

Multiplicity

-> Fraction (Unipol k)

Formal fraction with square-free denominator of degree >= 2.

-> GeneralTerm k 

linearInverse Source #

Arguments

:: (CoeffRing k, Field k) 
=> k

alpha for X - alpha

-> Natural

power

-> k

coefficient

-> GeneralTerm k 

fixedPoint :: (a -> Rewriter a) -> a -> a Source #