@@ -101,9 +101,11 @@ module Math.Algebra.Code.Linear
101
101
102
102
-- * Code-Vectors and codewords
103
103
, Vector , encode , isCodeword , hasError , weight , codewords
104
+ , allVectors , fullVectors , hammingWords , lighterWords
104
105
105
106
-- * Decoding
106
- , syndrome , decode , syndromeDecode , calcSyndromeTable
107
+ , syndrome , decode , syndromeDecode , calcSyndromeTable , recalcSyndromeTable
108
+ , SyndromeTable
107
109
108
110
-- * Code transformers
109
111
, dualCode , permuteCode
@@ -117,7 +119,7 @@ module Math.Algebra.Code.Linear
117
119
, codeLength
118
120
, rank
119
121
120
- , e , e1 , e2 , e3 , e4 , e5 , e6 , e7 , e8 , e9 , e10
122
+ , eVec , e1 , e2 , e3 , e4 , e5 , e6 , e7 , e8 , e9 , e10
121
123
, char
122
124
123
125
-- * Reexported matrix functions from "Math.Algebra.Matrix"
@@ -130,36 +132,26 @@ module Math.Algebra.Code.Linear
130
132
131
133
-- Linear codes from mathematical coding theory, including error correcting
132
134
-- codes
133
- import Prelude hiding (CVector )
134
135
import GHC.TypeLits
135
136
( Nat , KnownNat , natVal
136
137
, type (<= ), type (+ ), type (- ), type (^ )
137
138
)
138
139
139
- import Control.Monad.Random.Class (MonadRandom , getRandoms )
140
140
import Data.Bifunctor (first )
141
- import Data.Either (fromRight )
142
141
import Data.Monoid ((<>) )
143
142
import Data.Maybe (fromMaybe )
144
143
import Data.List (permutations )
145
144
import qualified Data.Map.Strict as M
146
145
import Data.Proxy (Proxy (.. ))
147
- import System.Random ( Random , RandomGen
148
- , random , randomR , randoms , randomRs , split )
146
+ import System.Random (Random , RandomGen , random , randomR )
149
147
150
148
import Math.Core.Utils (FinSet , elts )
151
149
import Math.Combinat.Permutations (_randomPermutation )
152
- import Math.Common.IntegerAsType (IntegerAsType , value )
153
- import Math.Algebra.Field.Base
154
- ( FiniteField , eltsFq , basisFq , Fp (Fp )
155
- , F2 , F3 , F5 , F7 , F11
156
- )
157
- import Math.Algebra.Field.Static (Size , Characteristic , PolyDegree , char )
158
- import Math.Algebra.Field.Extension
159
- ( ExtensionField (Ext ), x , embed , pvalue
160
- , F4 , F8 , F16 , F9
161
- )
162
- import Math.Algebra.Field.Instances -- import Random instances for Fields
150
+ import Math.Common.IntegerAsType (IntegerAsType )
151
+ import Math.Algebra.Field.Base (Fp , F2 , F3 , F5 , F7 , F11 )
152
+ import Math.Algebra.Field.Static (Size , Characteristic , char )
153
+ import Math.Algebra.Field.Extension (F4 , F8 , F16 , F9 )
154
+ import Math.Algebra.Field.Instances () -- import Random instances for Fields
163
155
import Math.Algebra.Matrix
164
156
( Matrix , matrix , transpose , (<|>) , (.*)
165
157
, identity , zero , fromList , fromLists , Vector , rref , submatrix
@@ -205,7 +197,7 @@ instance forall n k f. (Eq f, Fractional f, KnownNat n, KnownNat k, k <= n)
205
197
c == d = standardFormGenerator c == standardFormGenerator d
206
198
207
199
-- We do not show d since it might be expensive to calculate
208
- instance forall n k f c .
200
+ instance forall n k f .
209
201
(KnownNat n , KnownNat k , KnownNat (Characteristic f ))
210
202
=> Show (LinearCode n k f ) where
211
203
show LinearCode {distance= md} =
@@ -253,8 +245,7 @@ instance forall n k f.
253
245
random g = uncurry shuffleCode $ randomStandardFormCode g
254
246
255
247
randomR (hc,lc) g =
256
- let k = fromInteger . natVal $ Proxy @ k
257
- n = fromInteger . natVal $ Proxy @ n
248
+ let k = natToInt @ k Proxy
258
249
extractA = submatrix 1 k . generatorMatrix
259
250
(rmat,g2) = randomR (extractA hc, extractA lc) g
260
251
rcode = codeFromA rmat
@@ -287,7 +278,7 @@ rank :: forall n k f. KnownNat k => LinearCode n k f -> Int
287
278
rank _ = natToInt @ k Proxy
288
279
289
280
-- | The hamming weight of a Vector is an 'Int' between 0 and n
290
- weight :: forall n f m . (Eq f , Num f , Functor m , Foldable m ) => m f -> Int
281
+ weight :: forall f m . (Eq f , Num f , Functor m , Foldable m ) => m f -> Int
291
282
weight = sum . fmap (\ x -> if x== 0 then 0 else 1 )
292
283
293
284
-- | Generate a linear [n,k]_q-Code over the field a with the generator in
@@ -342,7 +333,8 @@ hammingWords w = fromList <$> shuffledVecs
342
333
shuffledVecs :: [[f ]]
343
334
shuffledVecs = orderedVecs >>= permutations
344
335
345
- -- | List of all words with hamming weight smaller than a given boundary
336
+ -- | List of all words with (non-zero) hamming weight smaller than a given
337
+ -- boundary
346
338
lighterWords :: forall n f . (KnownNat n , FinSet f , Num f , Eq f )
347
339
=> Int -> [Vector n f ]
348
340
lighterWords w = concat [ hammingWords l | l <- [1 .. w] ]
@@ -378,6 +370,12 @@ decode = syndromeDecode
378
370
379
371
-- | Pairs of (e,S(e)) where e is an error vector and S(e) is its syndrome.
380
372
type Syndrome n k f = Vector (n - k ) f
373
+
374
+ -- | A syndrome table is a map from syndromes to their minimal weight
375
+ -- representative. Every vector @v@ has a syndrome \( S(v) \). This table
376
+ -- reverses the syndrome function @S@ and chooses the vector with the smallest
377
+ -- hamming weight from it's image. This is a lookup table for syndrome
378
+ -- decoding.
381
379
type SyndromeTable n k f = M. Map (Syndrome n k f ) (Vector n f )
382
380
383
381
-- | Return a syndrome table for the given linear code. If the distance is not
@@ -480,9 +478,7 @@ simplex :: forall k p s.
480
478
simplex = codeFromA . transpose $ fromLists nonUnit
481
479
where
482
480
k = natToInt @ k Proxy
483
- allVectors :: Size (Fp p ) ~ s => [[Fp p ]]
484
- allVectors = fmap reverse . tail $ iterate ([(0 : ),(1 : )] <*> ) [[] ] !! k
485
- nonUnit = filter ((> 1 ) . weight) allVectors
481
+ nonUnit = filter ((> 1 ) . weight) $ allVectorsI k
486
482
487
483
-- | The /Hamming(7,4)/-code. It is a [7,4,3]_2 code
488
484
hamming :: (KnownNat m , 2 <= m , m <= 2 ^ m , 1 + m <= 2 ^ m )
@@ -493,41 +489,41 @@ hamming = dualCode simplex { distance = Just 3 }
493
489
-- * Helper functions
494
490
495
491
-- | Standard base vector [0..0,1,0..0] for any field. Parameter must be >=1
496
- e :: forall n f . (KnownNat n , Num f ) => Int -> Vector n f
497
- e i = fromList $ replicate (i- 1 ) 0 ++ 1 : replicate (n- i) 0
498
- where
499
- n = natToInt @ n Proxy
492
+ eVec :: forall n f . (KnownNat n , Num f ) => Int -> Vector n f
493
+ eVec i = fromList $ replicate (i- 1 ) 0 ++ 1 : replicate (n- i) 0
494
+ where
495
+ n = natToInt @ n Proxy
500
496
501
497
-- | First base vector [1,0..0]
502
498
e1 :: forall n f . (KnownNat n , Num f ) => Vector n f
503
- e1 = e 1
499
+ e1 = eVec 1
504
500
505
501
-- | Second base vector [0,1,0..0]
506
502
e2 :: forall n f . (KnownNat n , Num f ) => Vector n f
507
- e2 = e 2
503
+ e2 = eVec 2
508
504
509
505
e3 :: forall n f . (KnownNat n , Num f ) => Vector n f
510
- e3 = e 3
506
+ e3 = eVec 3
511
507
512
508
e4 :: forall n f . (KnownNat n , Num f ) => Vector n f
513
- e4 = e 4
509
+ e4 = eVec 4
514
510
515
511
e5 :: forall n f . (KnownNat n , Num f ) => Vector n f
516
- e5 = e 5
512
+ e5 = eVec 5
517
513
518
514
e6 :: forall n f . (KnownNat n , Num f ) => Vector n f
519
- e6 = e 6
515
+ e6 = eVec 6
520
516
521
517
e7 :: forall n f . (KnownNat n , Num f ) => Vector n f
522
- e7 = e 7
518
+ e7 = eVec 7
523
519
524
520
e8 :: forall n f . (KnownNat n , Num f ) => Vector n f
525
- e8 = e 8
521
+ e8 = eVec 8
526
522
527
523
e9 :: forall n f . (KnownNat n , Num f ) => Vector n f
528
- e9 = e 9
524
+ e9 = eVec 9
529
525
530
526
e10 :: forall n f . (KnownNat n , Num f ) => Vector n f
531
- e10 = e 10
527
+ e10 = eVec 10
532
528
533
529
-- vim : set colorcolumn=80
0 commit comments