{-# LANGUAGE TypeSynonymInstances #-} module Algebra.Z ( Z , Ring(..) ) where import Test.QuickCheck import Algebra.Structures.IntegralDomain import Algebra.Structures.EuclideanDomain import Algebra.Structures.StronglyDiscrete import Algebra.Structures.BezoutDomain import Algebra.Structures.PruferDomain import Algebra.Structures.Coherent import Algebra.Ideal import Algebra.Matrix import Algebra.PLM -- | Type synonym for integers. type Z = Integer instance Ring Z where (<*>) = (*) (<+>) = (+) neg = negate one = 1 zero = 0 instance CommutativeRing Z instance IntegralDomain Z propIntegralDomainZ :: Z -> Z -> Z -> Property propIntegralDomainZ = propIntegralDomain instance EuclideanDomain Z where d = abs quotientRemainder = quotRem propEuclideanDomainZ :: Z -> Z -> Z -> Property propEuclideanDomainZ = propEuclideanDomain -- Euclidean domain -> Bezout domain propBezoutDomainZ :: Ideal Z -> Z -> Z -> Z -> Property propBezoutDomainZ = propBezoutDomain -- Bezout domain -> Strongly discrete propStronglyDiscreteZ :: Z -> Ideal Z -> Bool propStronglyDiscreteZ = propStronglyDiscrete -- Bezout domain -> Coherent instance Coherent Z where solve = solveB propCoherentZ :: Vector Z -> Bool propCoherentZ = propCoherent propSolveMxNZ :: Matrix Z -> Bool propSolveMxNZ = propSolveMxN propSolveGeneralEquationZ :: Vector Z -> Z -> Bool propSolveGeneralEquationZ = propSolveGeneralEquation -- Not working perfectly... propSolveGeneralZ :: Matrix Z -> Vector Z -> Property propSolveGeneralZ = propSolveGeneral -- PLM propPLMZ :: Ideal Z -> Bool propPLMZ id = propPLM id (computePLM_B id) -- Prufer domain propPruferDomainZ :: Z -> Z -> Z -> Property propPruferDomainZ = propPruferDomain propIsSameIdealPruferDomain :: Ideal Z -> Ideal Z -> Bool propIsSameIdealPruferDomain = isSameIdeal intersectionPDWitness