singular-factory-0.1: Multivariate polynomial factorization via bindings to Singular-factory

Safe HaskellNone
LanguageHaskell2010

Math.Singular.Factory.Domains

Contents

Description

Base domains.

These are the base rings and fields Factory can work with, namely:

  • the ring integers
  • the field of rationals
  • finite fields (prime fields and Galois fields)

Another representation for finite fields are explicit algebraic extensions of prime fields. This has less limitations (does not rely on precomputed tables), but it is not implemented yet.

Note1: non-prime order Galois fields are supported only for small orders! (this is a limitation by singular-factory). Also for them to work, we need to be able to figure out the location of the "gftables" directory first.

Note2: as Factory has the base domain as a global state (...), this whole library is not at all thread safe!

Synopsis

The global characteristics

type Prime = Int Source #

data FactoryChar Source #

Constructors

CharZero

QQ

CharFp !Prime

prime field

CharGF !Prime !Int

Galois field

theFactoryChar :: IORef FactoryChar Source #

Unfortunately, Factory maintains a global state...

Prime fields

newtype Fp (p :: Nat) Source #

Haskell prime fields (this is provided only for completeness)

Constructors

Fp Int 
Instances
Eq (Fp p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(==) :: Fp p -> Fp p -> Bool #

(/=) :: Fp p -> Fp p -> Bool #

KnownNat p => Num (Fp p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(+) :: Fp p -> Fp p -> Fp p #

(-) :: Fp p -> Fp p -> Fp p #

(*) :: Fp p -> Fp p -> Fp p #

negate :: Fp p -> Fp p #

abs :: Fp p -> Fp p #

signum :: Fp p -> Fp p #

fromInteger :: Integer -> Fp p #

Show (Fp p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

showsPrec :: Int -> Fp p -> ShowS #

show :: Fp p -> String #

showList :: [Fp p] -> ShowS #

KnownNat p => FiniteDomain (Fp p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

KnownNat p => BaseDomain (Fp p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

fpPrime :: KnownNat p => Fp p -> Int Source #

modp :: (KnownNat p, Integral a) => a -> Fp p Source #

fpToFF :: KnownNat p => Fp p -> FF p Source #

Finite fields

newtype FF (p :: Nat) Source #

Factory prime fields

Constructors

FF 

Fields

Instances
Eq (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(==) :: FF p -> FF p -> Bool #

(/=) :: FF p -> FF p -> Bool #

KnownNat p => Fractional (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(/) :: FF p -> FF p -> FF p #

recip :: FF p -> FF p #

fromRational :: Rational -> FF p #

KnownNat p => Num (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(+) :: FF p -> FF p -> FF p #

(-) :: FF p -> FF p -> FF p #

(*) :: FF p -> FF p -> FF p #

negate :: FF p -> FF p #

abs :: FF p -> FF p #

signum :: FF p -> FF p #

fromInteger :: Integer -> FF p #

Show (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

showsPrec :: Int -> FF p -> ShowS #

show :: FF p -> String #

showList :: [FF p] -> ShowS #

KnownNat p => FiniteDomain (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

KnownNat p => BaseDomain (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

mkFF :: (KnownNat p, Integral a) => a -> FF p Source #

ffPrime :: KnownNat p => FF p -> Int Source #

Galois fields

newtype GF (p :: Nat) (n :: Nat) (x :: Symbol) Source #

Galois fields GF(p^n).

The (nonzero) elements are represented as powers of the canonical generator.

The symbol is the name of the canonical generator (used for pretty-printing).

Note: because of how Factory is implemented, it is required that n >= 2... (use FF for prime fields).

Also, the sizes are really limited (because they rely on tables, and only small tables are included): p < 256 and p^n < 65536

Constructors

GF 

Fields

Instances
Eq (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(==) :: GF p n x -> GF p n x -> Bool #

(/=) :: GF p n x -> GF p n x -> Bool #

(KnownNat p, KnownNat n, KnownSymbol x) => Fractional (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(/) :: GF p n x -> GF p n x -> GF p n x #

recip :: GF p n x -> GF p n x #

fromRational :: Rational -> GF p n x #

(KnownNat p, KnownNat n, KnownSymbol x) => Num (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

(+) :: GF p n x -> GF p n x -> GF p n x #

(-) :: GF p n x -> GF p n x -> GF p n x #

(*) :: GF p n x -> GF p n x -> GF p n x #

negate :: GF p n x -> GF p n x #

abs :: GF p n x -> GF p n x #

signum :: GF p n x -> GF p n x #

fromInteger :: Integer -> GF p n x #

(KnownNat p, KnownNat n, KnownSymbol x) => Show (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

showsPrec :: Int -> GF p n x -> ShowS #

show :: GF p n x -> String #

showList :: [GF p n x] -> ShowS #

(KnownNat p, KnownNat n, KnownSymbol x) => FiniteDomain (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

domainSize :: Proxy (GF p n x) -> Int Source #

enumerateDomain :: [GF p n x] Source #

(KnownNat p, KnownNat n, KnownSymbol x) => BaseDomain (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

characteristic :: Proxy (GF p n x) -> Int Source #

charExponent :: Proxy (GF p n x) -> Int Source #

baseDomainName :: Proxy (GF p n x) -> String Source #

factoryChar :: Proxy (GF p n x) -> FactoryChar Source #

baseToCF :: GF p n x -> CF Source #

unsafeCfToBase :: CF -> GF p n x Source #

isZero :: GF p n x -> Bool Source #

isOne :: GF p n x -> Bool Source #

mkGF :: (KnownNat p, KnownNat n, KnownSymbol x, Integral a) => a -> GF p n x Source #

Create elements of the prime subfield. For the rest, you can use the powers of the generator.

genGF :: (KnownNat p, KnownNat n, KnownSymbol x) => GF p n x Source #

The canonical generator of the (multiplicative group of the) Galois field

genPowGF :: (KnownNat p, KnownNat n, KnownSymbol x) => Int -> GF p n x Source #

A power of the canonical generator

powGF :: (KnownNat p, KnownNat n, KnownSymbol x) => GF p n x -> Int -> GF p n x Source #

gfPrime :: KnownNat p => GF p n x -> Int Source #

gfExponent :: KnownNat n => GF p n x -> Int Source #

Base domains

class (Eq a, Show a, Num a) => BaseDomain a where Source #

Instances
BaseDomain Integer Source # 
Instance details

Defined in Math.Singular.Factory.Domains

BaseDomain Rational Source # 
Instance details

Defined in Math.Singular.Factory.Domains

KnownNat p => BaseDomain (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

KnownNat p => BaseDomain (Fp p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

(KnownNat p, KnownNat n, KnownSymbol x) => BaseDomain (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

characteristic :: Proxy (GF p n x) -> Int Source #

charExponent :: Proxy (GF p n x) -> Int Source #

baseDomainName :: Proxy (GF p n x) -> String Source #

factoryChar :: Proxy (GF p n x) -> FactoryChar Source #

baseToCF :: GF p n x -> CF Source #

unsafeCfToBase :: CF -> GF p n x Source #

isZero :: GF p n x -> Bool Source #

isOne :: GF p n x -> Bool Source #

Finite domains

class BaseDomain domain => FiniteDomain domain where Source #

Methods

domainSize :: Proxy domain -> Int Source #

enumerateDomain :: [domain] Source #

Instances
KnownNat p => FiniteDomain (FF p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

KnownNat p => FiniteDomain (Fp p) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

(KnownNat p, KnownNat n, KnownSymbol x) => FiniteDomain (GF p n x) Source # 
Instance details

Defined in Math.Singular.Factory.Domains

Methods

domainSize :: Proxy (GF p n x) -> Int Source #

enumerateDomain :: [GF p n x] Source #

Proxy

mkProxy :: a -> Proxy a Source #