Safe Haskell | None |
---|---|
Language | Haskell2010 |
Low-level bindings to singular-factory
Synopsis
- data Variable
- data CanonicalForm
- data Factor
- data FactorList
- type Var = ForeignPtr Variable
- type CF = ForeignPtr CanonicalForm
- type Fac = ForeignPtr Factor
- type FacList = ForeignPtr FactorList
- c_level_trans :: CInt
- c_level_base :: CInt
- c_level_quot :: CInt
- c_level_expr :: CInt
- c_get_factory_version :: Ptr CChar -> Int -> IO ()
- c_get_package_version :: Ptr CChar -> Int -> IO ()
- getFactoryVersion :: IO String
- getPackageVersion :: IO String
- c_have_FLINT :: IO CInt
- c_have_NTL :: IO CInt
- c_have_GMP :: IO CInt
- c_set_default_switches :: IO ()
- setDefaultSwitches :: IO ()
- varFinalizerPtr :: FunPtr (Ptr Variable -> IO ())
- cfFinalizerPtr :: FunPtr (Ptr CanonicalForm -> IO ())
- facFinalizerPtr :: FunPtr (Ptr Factor -> IO ())
- faclistFinalizerPtr :: FunPtr (Ptr FactorList -> IO ())
- makeVar :: Ptr Variable -> IO Var
- makeCF :: Ptr CanonicalForm -> IO CF
- makeFac :: Ptr Factor -> IO Fac
- makeFacList :: Ptr FactorList -> IO FacList
- c_new_var_level :: CInt -> IO (Ptr Variable)
- c_new_var_name :: CChar -> IO (Ptr Variable)
- c_new_var_level_name :: CInt -> CChar -> IO (Ptr Variable)
- newVarL :: Int -> IO Var
- newVarN :: Char -> IO Var
- newVarLN :: Int -> Char -> IO Var
- newTransVar :: IO Var
- c_root_of :: Ptr CanonicalForm -> IO (Ptr Variable)
- newRootOf :: CF -> IO Var
- c_get_var_level :: Ptr Variable -> IO CInt
- c_get_var_name :: Ptr Variable -> IO CChar
- getVarLevel :: Var -> IO Int
- getVarName :: Var -> IO Char
- c_has_mipo :: Ptr Variable -> IO CInt
- c_get_mipo :: Ptr Variable -> Ptr Variable -> IO (Ptr CanonicalForm)
- c_set_mipo :: Ptr Variable -> Ptr CanonicalForm -> IO ()
- c_set_reduce :: Ptr Variable -> CInt -> IO ()
- hasMinimalPoly :: Var -> IO Bool
- getMinimalPoly :: Var -> Var -> IO CF
- setReduceFlag :: Var -> Bool -> IO ()
- c_get_factor :: Ptr Factor -> IO (Ptr CanonicalForm)
- getFactorCF :: Fac -> IO CF
- c_get_fac_expo :: Ptr Factor -> IO CInt
- getFactorExpo :: Fac -> IO Int
- unpackFactor :: Fac -> IO (CF, Int)
- c_get_list_length :: Ptr FactorList -> IO CInt
- getListLength :: FacList -> IO Int
- c_flatten_faclist :: Ptr FactorList -> Ptr (Ptr Factor) -> IO ()
- flattenFactorList :: FacList -> IO [Fac]
- unpackFactorList :: FacList -> IO [(CF, Int)]
- c_hs_factorize :: Ptr CanonicalForm -> IO (Ptr FactorList)
- factorizeIO' :: CF -> IO FacList
- factorizeIO :: CF -> IO [(CF, Int)]
- c_empty_cf :: IO (Ptr CanonicalForm)
- newEmptyCF :: IO CF
- c_const_cf :: CInt -> IO (Ptr CanonicalForm)
- newSmallConstCF :: Int -> IO CF
- c_var_cf :: Ptr Variable -> IO (Ptr CanonicalForm)
- c_var_pow_cf :: Ptr Variable -> Int -> IO (Ptr CanonicalForm)
- varIO :: Var -> IO CF
- varPowIO :: Var -> Int -> IO CF
- bool2cint :: Bool -> CInt
- cint2bool :: CInt -> Bool
- liftBool :: IO CInt -> IO Bool
- c_is_zero :: Ptr CanonicalForm -> IO CInt
- c_is_one :: Ptr CanonicalForm -> IO CInt
- isZeroIO :: CF -> IO Bool
- isOneIO :: CF -> IO Bool
- c_is_imm :: Ptr CanonicalForm -> IO CInt
- c_is_univariate :: Ptr CanonicalForm -> IO CInt
- isImmediateIO :: CF -> IO Bool
- isUnivariateIO :: CF -> IO Bool
- c_in_ZZ :: Ptr CanonicalForm -> IO CInt
- c_in_QQ :: Ptr CanonicalForm -> IO CInt
- c_in_GF :: Ptr CanonicalForm -> IO CInt
- c_in_FF :: Ptr CanonicalForm -> IO CInt
- isInZZ_IO :: CF -> IO Bool
- isInQQ_IO :: CF -> IO Bool
- isInGF_IO :: CF -> IO Bool
- isInFF_IO :: CF -> IO Bool
- c_in_BaseDomain :: Ptr CanonicalForm -> IO CInt
- c_in_CoeffDomain :: Ptr CanonicalForm -> IO CInt
- c_in_PolyDomain :: Ptr CanonicalForm -> IO CInt
- c_in_Extension :: Ptr CanonicalForm -> IO CInt
- c_in_QuotDomain :: Ptr CanonicalForm -> IO CInt
- isInBaseDomainIO :: CF -> IO Bool
- isInCoeffDomainIO :: CF -> IO Bool
- isInPolyDomainIO :: CF -> IO Bool
- isInExtensionIO :: CF -> IO Bool
- isInQuotDomainIO :: CF -> IO Bool
- c_degree_of :: Ptr CanonicalForm -> IO CInt
- c_level_of :: Ptr CanonicalForm -> IO CInt
- c_mvar_of :: Ptr CanonicalForm -> IO (Ptr Variable)
- getDegree :: CF -> IO Int
- getLevel :: CF -> IO Int
- getMainVar :: CF -> IO Var
- c_smallint_value :: Ptr CanonicalForm -> IO CLong
- getSmallIntValue :: CF -> IO Int
- c_numer :: Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_denom :: Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- getNumer :: CF -> IO CF
- getDenom :: CF -> IO CF
- c_index_poly :: Ptr CanonicalForm -> Int -> IO (Ptr CanonicalForm)
- c_map_into :: Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_substitute :: Ptr CanonicalForm -> Ptr Variable -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- getCfAtIndex :: CF -> Int -> IO CF
- mapIntoIO :: CF -> IO CF
- substituteIO :: Var -> CF -> CF -> IO CF
- c_is_equal :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO CInt
- isEqualIO :: CF -> CF -> IO Bool
- c_plus_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_minus_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_times_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_pow_cf :: Ptr CanonicalForm -> CInt -> IO (Ptr CanonicalForm)
- c_div_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_mod_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_gcd_poly_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- c_reduce_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm)
- plusIO :: CF -> CF -> IO CF
- minusIO :: CF -> CF -> IO CF
- timesIO :: CF -> CF -> IO CF
- powIO :: CF -> Int -> IO CF
- divIO :: CF -> CF -> IO CF
- modIO :: CF -> CF -> IO CF
- gcdPolyIO :: CF -> CF -> IO CF
- reduceIO :: CF -> CF -> IO CF
- c_get_gmp_numerator :: Ptr CanonicalForm -> Ptr MPZ -> IO ()
- c_get_gmp_denominator :: Ptr CanonicalForm -> Ptr MPZ -> IO ()
- getGmpNumerator :: CF -> IO Integer
- getGmpDenominator :: CF -> IO Integer
- c_make_ZZ_from_gmp :: Ptr MPZ -> IO (Ptr CanonicalForm)
- c_make_QQ_from_gmp :: Ptr MPZ -> Ptr MPZ -> CInt -> IO (Ptr CanonicalForm)
- makeIntegerCF :: Integer -> IO CF
- makeRationalCF :: Rational -> IO CF
- c_get_characteristic :: IO CInt
- c_set_characteristic1 :: CInt -> IO ()
- c_set_characteristic3 :: CInt -> CInt -> CChar -> IO ()
- getCharacteristic :: IO Int
- setCharacteristic1 :: Int -> IO ()
- setCharacteristic3 :: Int -> Int -> Char -> IO ()
- c_get_gf_value :: Ptr CanonicalForm -> IO CInt
- c_is_FF_in_GF :: Ptr CanonicalForm -> IO CInt
- c_get_GF_degree :: IO CInt
- c_get_GF_generator :: IO (Ptr CanonicalForm)
- getGFValue :: CF -> IO Int
- isFFinGF_IO :: CF -> IO Bool
- getGFDegree :: IO Int
- getGFGenerator :: IO CF
types
data CanonicalForm Source #
data FactorList Source #
type Var = ForeignPtr Variable Source #
type CF = ForeignPtr CanonicalForm Source #
type Fac = ForeignPtr Factor Source #
type FacList = ForeignPtr FactorList Source #
constants
c_level_trans :: CInt Source #
c_level_base :: CInt Source #
c_level_quot :: CInt Source #
c_level_expr :: CInt Source #
versions
c_have_FLINT :: IO CInt Source #
c_have_NTL :: IO CInt Source #
c_have_GMP :: IO CInt Source #
config
c_set_default_switches :: IO () Source #
setDefaultSwitches :: IO () Source #
memory management
cfFinalizerPtr :: FunPtr (Ptr CanonicalForm -> IO ()) Source #
faclistFinalizerPtr :: FunPtr (Ptr FactorList -> IO ()) Source #
makeFacList :: Ptr FactorList -> IO FacList Source #
variables
newTransVar :: IO Var Source #
c_get_mipo :: Ptr Variable -> Ptr Variable -> IO (Ptr CanonicalForm) Source #
c_set_mipo :: Ptr Variable -> Ptr CanonicalForm -> IO () Source #
factors
c_get_factor :: Ptr Factor -> IO (Ptr CanonicalForm) Source #
lists
c_get_list_length :: Ptr FactorList -> IO CInt Source #
factorization
c_flatten_faclist :: Ptr FactorList -> Ptr (Ptr Factor) -> IO () Source #
c_hs_factorize :: Ptr CanonicalForm -> IO (Ptr FactorList) Source #
basic CFs
c_empty_cf :: IO (Ptr CanonicalForm) Source #
newEmptyCF :: IO CF Source #
c_const_cf :: CInt -> IO (Ptr CanonicalForm) Source #
c_var_pow_cf :: Ptr Variable -> Int -> IO (Ptr CanonicalForm) Source #
basic CF predicates
c_is_univariate :: Ptr CanonicalForm -> IO CInt Source #
c_in_BaseDomain :: Ptr CanonicalForm -> IO CInt Source #
c_in_CoeffDomain :: Ptr CanonicalForm -> IO CInt Source #
c_in_PolyDomain :: Ptr CanonicalForm -> IO CInt Source #
c_in_Extension :: Ptr CanonicalForm -> IO CInt Source #
c_in_QuotDomain :: Ptr CanonicalForm -> IO CInt Source #
basic properties
c_degree_of :: Ptr CanonicalForm -> IO CInt Source #
c_level_of :: Ptr CanonicalForm -> IO CInt Source #
small values
c_smallint_value :: Ptr CanonicalForm -> IO CLong Source #
c_numer :: Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_denom :: Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_index_poly :: Ptr CanonicalForm -> Int -> IO (Ptr CanonicalForm) Source #
c_map_into :: Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_substitute :: Ptr CanonicalForm -> Ptr Variable -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
Polynomial operations
Binary operations
c_is_equal :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO CInt Source #
c_plus_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_minus_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_times_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_pow_cf :: Ptr CanonicalForm -> CInt -> IO (Ptr CanonicalForm) Source #
c_div_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_mod_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_gcd_poly_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
c_reduce_cf :: Ptr CanonicalForm -> Ptr CanonicalForm -> IO (Ptr CanonicalForm) Source #
GMP compatibility layer
c_get_gmp_numerator :: Ptr CanonicalForm -> Ptr MPZ -> IO () Source #
c_get_gmp_denominator :: Ptr CanonicalForm -> Ptr MPZ -> IO () Source #
c_make_ZZ_from_gmp :: Ptr MPZ -> IO (Ptr CanonicalForm) Source #
c_make_QQ_from_gmp :: Ptr MPZ -> Ptr MPZ -> CInt -> IO (Ptr CanonicalForm) Source #
Base domain characteristic
c_set_characteristic1 :: CInt -> IO () Source #
setCharacteristic1 :: Int -> IO () Source #
prime fields and QQ
c_get_gf_value :: Ptr CanonicalForm -> IO CInt Source #
c_is_FF_in_GF :: Ptr CanonicalForm -> IO CInt Source #
c_get_GF_degree :: IO CInt Source #
getGFValue :: CF -> IO Int Source #
This returns the exponent of the canonical generator. If the input is zero, it appears to return the order of the field, q, but don't rely on this...
getGFDegree :: IO Int Source #
Returns the degree of the Galois field (degree of extension over the prime field)
getGFGenerator :: IO CF Source #
Returns the generator of the Galois field