Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type Prime = Int
- data FactoryChar
- theFactoryChar :: IORef FactoryChar
- setFactoryChar :: FactoryChar -> IO ()
- mapIntoCF :: FactoryChar -> CF -> CF
- newtype Fp (p :: Nat) = Fp Int
- fpPrime :: KnownNat p => Fp p -> Int
- modp :: (KnownNat p, Integral a) => a -> Fp p
- fpToFF :: KnownNat p => Fp p -> FF p
- newtype FF (p :: Nat) = FF {}
- mkFF :: (KnownNat p, Integral a) => a -> FF p
- ffPrime :: KnownNat p => FF p -> Int
- newtype GF (p :: Nat) (n :: Nat) (x :: Symbol) = GF {}
- mkGF :: (KnownNat p, KnownNat n, KnownSymbol x, Integral a) => a -> GF p n x
- genGF :: (KnownNat p, KnownNat n, KnownSymbol x) => GF p n x
- genPowGF :: (KnownNat p, KnownNat n, KnownSymbol x) => Int -> GF p n x
- powGF :: (KnownNat p, KnownNat n, KnownSymbol x) => GF p n x -> Int -> GF p n x
- gfPrime :: KnownNat p => GF p n x -> Int
- gfExponent :: KnownNat n => GF p n x -> Int
- gfSymbol :: KnownSymbol x => GF p n x -> String
- class (Eq a, Show a, Num a) => BaseDomain a where
- characteristic :: Proxy a -> Int
- charExponent :: Proxy a -> Int
- baseDomainName :: Proxy a -> String
- factoryChar :: Proxy a -> FactoryChar
- baseToCF :: a -> CF
- unsafeCfToBase :: CF -> a
- isZero :: a -> Bool
- isOne :: a -> Bool
- setBaseDomain :: BaseDomain a => Proxy a -> IO ()
- class BaseDomain domain => FiniteDomain domain where
- domainSize :: Proxy domain -> Int
- enumerateDomain :: [domain]
- mkProxy :: a -> Proxy a
- proxyUndef :: Proxy a -> a
The global characteristics
data FactoryChar Source #
Instances
Eq FactoryChar Source # | |
Defined in Math.Singular.Factory.Domains (==) :: FactoryChar -> FactoryChar -> Bool # (/=) :: FactoryChar -> FactoryChar -> Bool # | |
Show FactoryChar Source # | |
Defined in Math.Singular.Factory.Domains showsPrec :: Int -> FactoryChar -> ShowS # show :: FactoryChar -> String # showList :: [FactoryChar] -> ShowS # |
theFactoryChar :: IORef FactoryChar Source #
Unfortunately, Factory maintains a global state...
setFactoryChar :: FactoryChar -> IO () Source #
Prime fields
newtype Fp (p :: Nat) Source #
Haskell prime fields (this is provided only for completeness)
Instances
Eq (Fp p) Source # | |
KnownNat p => Num (Fp p) Source # | |
Show (Fp p) Source # | |
KnownNat p => FiniteDomain (Fp p) Source # | |
Defined in Math.Singular.Factory.Domains domainSize :: Proxy (Fp p) -> Int Source # enumerateDomain :: [Fp p] Source # | |
KnownNat p => BaseDomain (Fp p) Source # | |
Defined in Math.Singular.Factory.Domains |
Finite fields
newtype FF (p :: Nat) Source #
Factory prime fields
Instances
Eq (FF p) Source # | |
KnownNat p => Fractional (FF p) Source # | |
KnownNat p => Num (FF p) Source # | |
Show (FF p) Source # | |
KnownNat p => FiniteDomain (FF p) Source # | |
Defined in Math.Singular.Factory.Domains domainSize :: Proxy (FF p) -> Int Source # enumerateDomain :: [FF p] Source # | |
KnownNat p => BaseDomain (FF p) Source # | |
Defined in Math.Singular.Factory.Domains |
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
Instances
Eq (GF p n x) Source # | |
(KnownNat p, KnownNat n, KnownSymbol x) => Fractional (GF p n x) Source # | |
(KnownNat p, KnownNat n, KnownSymbol x) => Num (GF p n x) Source # | |
(KnownNat p, KnownNat n, KnownSymbol x) => Show (GF p n x) Source # | |
(KnownNat p, KnownNat n, KnownSymbol x) => FiniteDomain (GF p n x) Source # | |
Defined in Math.Singular.Factory.Domains 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 # | |
Defined in Math.Singular.Factory.Domains 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 # |
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
Base domains
class (Eq a, Show a, Num a) => BaseDomain a where Source #
characteristic :: Proxy a -> Int Source #
charExponent :: Proxy a -> Int Source #
baseDomainName :: Proxy a -> String Source #
factoryChar :: Proxy a -> FactoryChar Source #
unsafeCfToBase :: CF -> a Source #
Instances
setBaseDomain :: BaseDomain a => Proxy a -> IO () Source #
Finite domains
class BaseDomain domain => FiniteDomain domain where Source #
domainSize :: Proxy domain -> Int Source #
enumerateDomain :: [domain] Source #
Instances
KnownNat p => FiniteDomain (FF p) Source # | |
Defined in Math.Singular.Factory.Domains domainSize :: Proxy (FF p) -> Int Source # enumerateDomain :: [FF p] Source # | |
KnownNat p => FiniteDomain (Fp p) Source # | |
Defined in Math.Singular.Factory.Domains domainSize :: Proxy (Fp p) -> Int Source # enumerateDomain :: [Fp p] Source # | |
(KnownNat p, KnownNat n, KnownSymbol x) => FiniteDomain (GF p n x) Source # | |
Defined in Math.Singular.Factory.Domains domainSize :: Proxy (GF p n x) -> Int Source # enumerateDomain :: [GF p n x] Source # |
Proxy
proxyUndef :: Proxy a -> a Source #