Skip to content

Commit

Permalink
Merge pull request #29 from Bodigrim/master
Browse files Browse the repository at this point in the history
Avoid unsafeCoerce in prime fields
  • Loading branch information
sdiehl committed Apr 8, 2020
2 parents b59ecd8 + e849a32 commit bcd58af
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 94 deletions.
6 changes: 3 additions & 3 deletions galois-field.cabal
Expand Up @@ -67,7 +67,7 @@ library
, integer-gmp >=1.0.2 && <1.1
, mod >=0.1.0 && <0.2
, MonadRandom >=0.5.1 && <0.6
, poly >=0.3.2 && <0.4
, poly >=0.3.2 && <0.5
, protolude >=0.2 && <0.3
, QuickCheck >=2.13 && <2.14
, semirings >=0.5.2 && <0.6
Expand Down Expand Up @@ -115,7 +115,7 @@ test-suite galois-field-tests
, integer-gmp >=1.0.2 && <1.1
, mod >=0.1.0 && <0.2
, MonadRandom >=0.5.1 && <0.6
, poly >=0.3.2 && <0.4
, poly >=0.3.2 && <0.5
, protolude >=0.2 && <0.3
, QuickCheck >=2.13 && <2.14
, semirings >=0.5 && <0.6
Expand Down Expand Up @@ -166,7 +166,7 @@ benchmark galois-field-benchmarks
, integer-gmp >=1.0.2 && <1.1
, mod >=0.1.0 && <0.2
, MonadRandom >=0.5.1 && <0.6
, poly >=0.3.2 && <0.4
, poly >=0.3.2 && <0.5
, protolude >=0.2 && <0.3
, QuickCheck >=2.13 && <2.14
, semirings >=0.5 && <0.6
Expand Down
103 changes: 12 additions & 91 deletions src/Data/Field/Galois/Prime.hs
Expand Up @@ -3,7 +3,6 @@ module Data.Field.Galois.Prime
, PrimeField
, fromP
, toP
, toP'
) where

import Protolude as P hiding (Semiring, natVal, rem)
Expand All @@ -14,11 +13,10 @@ import Data.Field (Field)
import Data.Group (Group(..))
import Data.Mod (Mod, unMod, (^%))
import Data.Semiring (Ring(..), Semiring(..))
import GHC.Natural (Natural, naturalFromInteger, naturalToInteger)
import GHC.Natural (naturalToInteger)
import GHC.TypeNats (natVal)
import Test.QuickCheck (Arbitrary(..), choose)
import Text.PrettyPrint.Leijen.Text (Pretty(..))
import Unsafe.Coerce (unsafeCoerce)

import Data.Field.Galois.Base (GaloisField(..))

Expand All @@ -33,12 +31,15 @@ class GaloisField k => PrimeField k where
fromP :: k -> Integer

-- | Prime field elements.
newtype Prime (p :: Nat) = P Natural
deriving (Bits, Eq, Generic, Hashable, NFData, Ord, Show)
newtype Prime (p :: Nat) = P (Mod p)
deriving (Eq, Ord, Show, Generic, Num, Fractional, Euclidean, Field, GcdDomain, Ring, Semiring, Bounded, Enum, NFData)

instance Hashable (Prime p) where
hashWithSalt s (P x) = hashWithSalt s (unMod x)

-- Prime fields are convertible.
instance KnownNat p => PrimeField (Prime p) where
fromP (P x) = naturalToInteger x
fromP (P x) = naturalToInteger (unMod x)
{-# INLINABLE fromP #-}

-- Prime fields are Galois fields.
Expand All @@ -62,7 +63,7 @@ instance KnownNat p => GaloisField (Prime p) where
instance KnownNat p => Group (Prime p) where
invert = recip
{-# INLINE invert #-}
pow x = P . unMod . (^%) (unsafeCoerce x :: Mod p)
pow (P x) k = P (x ^% k)
{-# INLINE pow #-}

-- Prime fields are multiplicative monoids.
Expand All @@ -77,90 +78,15 @@ instance KnownNat p => Semigroup (Prime p) where
stimes = flip pow
{-# INLINE stimes #-}

-------------------------------------------------------------------------------
-- Numeric instances
-------------------------------------------------------------------------------

-- Prime fields are fractional.
instance KnownNat p => Fractional (Prime p) where
recip x = P $ unMod $ recip $ (unsafeCoerce x :: Mod p)
{-# INLINE recip #-}
fromRational (x:%y) = fromInteger x / fromInteger y
{-# INLINABLE fromRational #-}

-- Prime fields are numeric.
instance KnownNat p => Num (Prime p) where
x + y = P $ unMod $ (unsafeCoerce x + unsafeCoerce y :: Mod p)
{-# INLINE (+) #-}
x * y = P $ unMod $ (unsafeCoerce x * unsafeCoerce y :: Mod p)
{-# INLINE (*) #-}
x - y = P $ unMod $ (unsafeCoerce x - unsafeCoerce y :: Mod p)
{-# INLINE (-) #-}
negate x = P $ unMod $ P.negate $ (unsafeCoerce x :: Mod p)
{-# INLINE negate #-}
fromInteger x = P $ unMod $ (fromIntegral x :: Mod p)
{-# INLINABLE fromInteger #-}
abs = panic "Prime.abs: not implemented."
signum = panic "Prime.signum: not implemented."

-------------------------------------------------------------------------------
-- Semiring instances
-------------------------------------------------------------------------------

-- Prime fields are Euclidean domains.
instance KnownNat p => Euclidean (Prime p) where
degree = panic "Prime.degree: not implemented."
quotRem = (flip (,) 0 .) . (/)
{-# INLINE quotRem #-}

-- Prime fields are fields.
instance KnownNat p => Field (Prime p)

-- Prime fields are GCD domains.
instance KnownNat p => GcdDomain (Prime p)

-- Prime fields are rings.
instance KnownNat p => Ring (Prime p) where
negate = P.negate
{-# INLINE negate #-}

-- Prime fields are semirings.
instance KnownNat p => Semiring (Prime p) where
fromNatural = fromIntegral
{-# INLINABLE fromNatural #-}
one = P 1
{-# INLINE one #-}
plus = (+)
{-# INLINE plus #-}
times = (*)
{-# INLINE times #-}
zero = P 0
{-# INLINE zero #-}

-------------------------------------------------------------------------------
-- Other instances
-------------------------------------------------------------------------------

-- Prime fields are arbitrary.
instance KnownNat p => Arbitrary (Prime p) where
arbitrary = P . naturalFromInteger <$>
choose (0, naturalToInteger $ natVal (witness :: Prime p) - 1)
arbitrary = choose (minBound, maxBound)
{-# INLINABLE arbitrary #-}

-- Prime fields are bounded.
instance KnownNat p => Bounded (Prime p) where
maxBound = P $ natVal (witness :: Prime p) - 1
{-# INLINE maxBound #-}
minBound = P 0
{-# INLINE minBound #-}

-- Prime fields are enumerable.
instance KnownNat p => Enum (Prime p) where
fromEnum = fromIntegral
{-# INLINABLE fromEnum #-}
toEnum = fromIntegral
{-# INLINABLE toEnum #-}

-- Prime fields are integral.
instance KnownNat p => Integral (Prime p) where
quotRem = S.quotRem
Expand All @@ -170,13 +96,13 @@ instance KnownNat p => Integral (Prime p) where

-- Prime fields are pretty.
instance KnownNat p => Pretty (Prime p) where
pretty (P x) = pretty $ naturalToInteger x
pretty (P x) = pretty $ naturalToInteger $ unMod x

-- Prime fields are random.
instance KnownNat p => Random (Prime p) where
random = randomR (P 0, P $ natVal (witness :: Prime p) - 1)
random = randomR (minBound, maxBound)
{-# INLINABLE random #-}
randomR (a, b) = first (P . naturalFromInteger) . randomR (fromP a, fromP b)
randomR (a, b) = first fromInteger . randomR (fromP a, fromP b)
{-# INLINABLE randomR #-}

-- Prime fields are real.
Expand All @@ -192,8 +118,3 @@ instance KnownNat p => Real (Prime p) where
toP :: KnownNat p => Integer -> Prime p
toP = fromInteger
{-# INLINABLE toP #-}

-- | Unsafe convert from @Z@ to @GF(p)@.
toP' :: KnownNat p => Integer -> Prime p
toP' = P . naturalFromInteger
{-# INLINABLE toP' #-}

0 comments on commit bcd58af

Please sign in to comment.