{-# LANGUAGE TypeSynonymInstances #-} -- | Representation of rational numbers as the field of fractions of Z. module Algebra.Q ( Q , toQ, toZ ) where import Test.QuickCheck -- import qualified Math.Algebra.Field.Base as A (Q(..)) -- import Data.Ratio import Algebra.Structures.Field import Algebra.Structures.FieldOfFractions import Algebra.Z ------------------------------------------------------------------------------- -- | Q is the field of fractions of Z. type Q = FieldOfFractions Z instance Num Q where (+) = (<+>) (*) = (<*>) abs (F (a,b)) = F (abs a, b) signum (F (a,_)) = F (signum a,one) fromInteger = toQ instance Fractional Q where (/) = () fromRational = undefined -- fromRational (a :% b) = reduce $ F (a,b) toQ :: Z -> Q toQ = toFieldOfFractions toZ :: Q -> Z toZ = fromFieldOfFractions