-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathBase.hs
60 lines (52 loc) · 1.49 KB
/
Base.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
module Data.Field.Galois.Base
( module Data.Field.Galois.Base,
)
where
import Control.Monad.Random (Random)
import Data.Field (Field)
import Data.Group qualified as G (Group (..))
import Data.Propagator (PropagatedNum)
import GHC.Natural (Natural)
import Protolude hiding (one, quot, (-))
import Test.QuickCheck (Arbitrary)
import Text.PrettyPrint.Leijen.Text (Pretty)
-------------------------------------------------------------------------------
-- Classes
-------------------------------------------------------------------------------
-- | Galois fields @GF(p^q)@ for @p@ prime and @q@ non-negative.
class
( Arbitrary k,
Field k,
Fractional k,
Generic k,
G.Group k,
Ord k,
Pretty k,
Random k,
Show k,
NFData k,
PropagatedNum k
) =>
GaloisField k
where
{-# MINIMAL char, deg, frob #-}
-- | Characteristic @p@ of field and order of prime subfield.
char :: k -> Natural
-- | Degree @q@ of field as extension field over prime subfield.
deg :: k -> Word
-- | Frobenius endomorphism @x -> x^p@ of prime subfield.
frob :: k -> k
-- | Order @p^q@ of field.
order :: k -> Natural
order = (^) <$> char <*> deg
{-# INLINEABLE order #-}
-- | Exponentiation of field element to integer.
pow :: (GaloisField k, Integral n) => k -> n -> k
pow = G.pow
{-# INLINEABLE pow #-}
{-# SPECIALIZE pow ::
(GaloisField k) => k -> Int -> k,
(GaloisField k) => k -> Integer -> k,
(GaloisField k) => k -> Natural -> k,
(GaloisField k) => k -> Word -> k
#-}