Skip to content

Commit 8712ae4

Browse files
committed
Hackage release 0.1.0, resolve all -Wall warnings
1 parent db4d9a4 commit 8712ae4

File tree

6 files changed

+60
-58
lines changed

6 files changed

+60
-58
lines changed

ChangeLog.md

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
0.1.0
2+
-----
3+
4+
* Initial release
5+
- Includes trivial, hamming and random codes
6+
- Implements syndrome decoding
7+

README.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ Library to handle linear codes from coding theory.
44
The library is designed to carry the most important bits of information in the
55
type system while still keeping the types sane.
66

7-
This library is based roughly on [/Introduction to Coding Theory/ by /Yehuda Lindell/](http://u.cs.biu.ac.il/~lindell/89-662/coding_theory-lecture-notes.pdf)
7+
This library is based roughly on [_Introduction to Coding Theory_ by _Yehuda Lindell_](http://u.cs.biu.ac.il/~lindell/89-662/coding_theory-lecture-notes.pdf)
88

99
# Usage example
1010
## Working with random codes

package.yaml

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,11 +7,12 @@ maintainer: "wanja.hs@chrummibei.ch"
77
copyright: "2018, Wanja Chresta"
88

99
extra-source-files:
10+
- ChangeLog.md
1011
- README.md
1112

1213
# Metadata used when publishing your package
1314
synopsis: A simple library for linear codes (coding theory, error correction)
14-
category: Mathematics
15+
category: Math
1516

1617
# To avoid duplicated efforts in documentation and dealing with the
1718
# complications of embedding Haddock markup inside cabal files, it is
@@ -28,7 +29,6 @@ dependencies:
2829
- ghc-typelits-natnormalise
2930
- ghc-typelits-knownnat
3031
- random
31-
- MonadRandom
3232

3333
library:
3434
source-dirs: src
@@ -37,6 +37,8 @@ library:
3737
- Math.Algebra.Field.Instances
3838
- Math.Algebra.Field.Static
3939
- Math.Algebra.Matrix
40+
ghc-options:
41+
- -Wall
4042

4143
tests:
4244
linear-code-test:

src/Math/Algebra/Code/Linear.hs

Lines changed: 36 additions & 40 deletions
Original file line numberDiff line numberDiff line change
@@ -101,9 +101,11 @@ module Math.Algebra.Code.Linear
101101

102102
-- * Code-Vectors and codewords
103103
, Vector, encode, isCodeword, hasError, weight, codewords
104+
, allVectors, fullVectors, hammingWords, lighterWords
104105

105106
-- * Decoding
106-
, syndrome, decode, syndromeDecode, calcSyndromeTable
107+
, syndrome, decode, syndromeDecode, calcSyndromeTable, recalcSyndromeTable
108+
, SyndromeTable
107109

108110
-- * Code transformers
109111
, dualCode, permuteCode
@@ -117,7 +119,7 @@ module Math.Algebra.Code.Linear
117119
, codeLength
118120
, rank
119121

120-
, e, e1, e2, e3, e4, e5, e6, e7, e8, e9, e10
122+
, eVec, e1, e2, e3, e4, e5, e6, e7, e8, e9, e10
121123
, char
122124

123125
-- * Reexported matrix functions from "Math.Algebra.Matrix"
@@ -130,36 +132,26 @@ module Math.Algebra.Code.Linear
130132

131133
-- Linear codes from mathematical coding theory, including error correcting
132134
-- codes
133-
import Prelude hiding (CVector)
134135
import GHC.TypeLits
135136
( Nat, KnownNat, natVal
136137
, type (<=), type (+), type (-), type (^)
137138
)
138139

139-
import Control.Monad.Random.Class (MonadRandom, getRandoms)
140140
import Data.Bifunctor (first)
141-
import Data.Either (fromRight)
142141
import Data.Monoid ((<>))
143142
import Data.Maybe (fromMaybe)
144143
import Data.List (permutations)
145144
import qualified Data.Map.Strict as M
146145
import Data.Proxy (Proxy (..))
147-
import System.Random ( Random, RandomGen
148-
, random, randomR, randoms, randomRs, split)
146+
import System.Random (Random, RandomGen, random, randomR)
149147

150148
import Math.Core.Utils (FinSet, elts)
151149
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
163155
import Math.Algebra.Matrix
164156
( Matrix, matrix, transpose, (<|>), (.*)
165157
, 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)
205197
c == d = standardFormGenerator c == standardFormGenerator d
206198

207199
-- 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.
209201
(KnownNat n, KnownNat k, KnownNat (Characteristic f))
210202
=> Show (LinearCode n k f) where
211203
show LinearCode{distance=md} =
@@ -253,8 +245,7 @@ instance forall n k f.
253245
random g = uncurry shuffleCode $ randomStandardFormCode g
254246

255247
randomR (hc,lc) g =
256-
let k = fromInteger . natVal $ Proxy @k
257-
n = fromInteger . natVal $ Proxy @n
248+
let k = natToInt @k Proxy
258249
extractA = submatrix 1 k . generatorMatrix
259250
(rmat,g2) = randomR (extractA hc, extractA lc) g
260251
rcode = codeFromA rmat
@@ -287,7 +278,7 @@ rank :: forall n k f. KnownNat k => LinearCode n k f -> Int
287278
rank _ = natToInt @k Proxy
288279

289280
-- | 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
291282
weight = sum . fmap (\x -> if x==0 then 0 else 1)
292283

293284
-- | Generate a linear [n,k]_q-Code over the field a with the generator in
@@ -342,7 +333,8 @@ hammingWords w = fromList <$> shuffledVecs
342333
shuffledVecs :: [[f]]
343334
shuffledVecs = orderedVecs >>= permutations
344335

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
346338
lighterWords :: forall n f. (KnownNat n, FinSet f, Num f, Eq f)
347339
=> Int -> [Vector n f]
348340
lighterWords w = concat [ hammingWords l | l <- [1..w] ]
@@ -378,6 +370,12 @@ decode = syndromeDecode
378370

379371
-- | Pairs of (e,S(e)) where e is an error vector and S(e) is its syndrome.
380372
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.
381379
type SyndromeTable n k f = M.Map (Syndrome n k f) (Vector n f)
382380

383381
-- | Return a syndrome table for the given linear code. If the distance is not
@@ -480,9 +478,7 @@ simplex :: forall k p s.
480478
simplex = codeFromA . transpose $ fromLists nonUnit
481479
where
482480
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
486482

487483
-- | The /Hamming(7,4)/-code. It is a [7,4,3]_2 code
488484
hamming :: (KnownNat m, 2 <= m, m <= 2^m, 1+m <= 2^m)
@@ -493,41 +489,41 @@ hamming = dualCode simplex { distance = Just 3 }
493489
-- * Helper functions
494490

495491
-- | 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
500496

501497
-- | First base vector [1,0..0]
502498
e1 :: forall n f. (KnownNat n, Num f) => Vector n f
503-
e1 = e 1
499+
e1 = eVec 1
504500

505501
-- | Second base vector [0,1,0..0]
506502
e2 :: forall n f. (KnownNat n, Num f) => Vector n f
507-
e2 = e 2
503+
e2 = eVec 2
508504

509505
e3 :: forall n f. (KnownNat n, Num f) => Vector n f
510-
e3 = e 3
506+
e3 = eVec 3
511507

512508
e4 :: forall n f. (KnownNat n, Num f) => Vector n f
513-
e4 = e 4
509+
e4 = eVec 4
514510

515511
e5 :: forall n f. (KnownNat n, Num f) => Vector n f
516-
e5 = e 5
512+
e5 = eVec 5
517513

518514
e6 :: forall n f. (KnownNat n, Num f) => Vector n f
519-
e6 = e 6
515+
e6 = eVec 6
520516

521517
e7 :: forall n f. (KnownNat n, Num f) => Vector n f
522-
e7 = e 7
518+
e7 = eVec 7
523519

524520
e8 :: forall n f. (KnownNat n, Num f) => Vector n f
525-
e8 = e 8
521+
e8 = eVec 8
526522

527523
e9 :: forall n f. (KnownNat n, Num f) => Vector n f
528-
e9 = e 9
524+
e9 = eVec 9
529525

530526
e10 :: forall n f. (KnownNat n, Num f) => Vector n f
531-
e10 = e 10
527+
e10 = eVec 10
532528

533529
-- vim : set colorcolumn=80

src/Math/Algebra/Field/Instances.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE ScopedTypeVariables #-}
2+
{-# OPTIONS_GHC -fno-warn-orphans #-}
23
{-
34
This file is part of linear-codes.
45

src/Math/Algebra/Matrix.hs

Lines changed: 11 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -56,13 +56,11 @@ module Math.Algebra.Matrix
5656
, submatrix
5757
) where
5858

59-
import GHC.TypeLits (Nat, KnownNat, natVal, type (+), type (-), type (<=))
60-
import GHC.Generics (Generic)
59+
import GHC.TypeLits (Nat, KnownNat, natVal, type (+), type (<=))
6160
import Data.List (find)
6261
import Data.Proxy (Proxy(..))
63-
import Data.Semigroup (Semigroup, (<>))
64-
import Data.Monoid (mappend)
65-
import Data.Maybe (isNothing, listToMaybe)
62+
import Data.Semigroup ((<>))
63+
import Data.Maybe (isNothing)
6664

6765
import qualified Data.Matrix as M
6866
import qualified System.Random as R
@@ -99,9 +97,7 @@ instance forall m n a. (KnownNat m, KnownNat n, R.Random a)
9997
randomR (lm,hm) g =
10098
-- lm and hm are matrices. We zip the elements and use these as
10199
-- hi/lo bounds for the random generator
102-
let m = fromInteger . natVal $ Proxy @m
103-
n = fromInteger . natVal $ Proxy @n
104-
zipEls :: [(a,a)]
100+
let zipEls :: [(a,a)]
105101
zipEls = zip (toList lm) (toList hm)
106102
rmatStep :: R.RandomGen g => (a,a) -> ([a],g) -> ([a],g)
107103
rmatStep hilo (as,g1) = let (a,g2) = R.randomR hilo g1
@@ -207,13 +203,13 @@ submatrix i j (Matrix mat) = Matrix $ M.submatrix i (i+m'-1) j (j+n'-1) mat
207203
-- https://rosettacode.org/wiki/Reduced_row_echelon_form#Haskell
208204
rref :: forall m n a. (KnownNat m, KnownNat n, m <= n, Fractional a, Eq a)
209205
=> Matrix m n a -> Matrix m n a
210-
rref mat = fromLists $ f m 0 [0 .. rows - 1]
206+
rref mat = fromLists $ f matM 0 [0 .. rows - 1]
211207
where
212-
m = toLists mat
213-
rows = length m
214-
cols = length $ head m
208+
matM = toLists mat
209+
rows = length matM
210+
cols = length $ head matM
215211

216-
f m _ [] = m
212+
f m _ [] = m
217213
f m lead (r : rs)
218214
| isNothing indices = m
219215
| otherwise = f m' (lead' + 1) rs
@@ -237,5 +233,5 @@ rref mat = fromLists $ f m 0 [0 .. rows - 1]
237233

238234
replace :: Int -> b -> [b] -> [b]
239235
{- Replaces the element at the given index. -}
240-
replace n e l = a ++ e : b
241-
where (a, _ : b) = splitAt n l
236+
replace n e t = a ++ e : b
237+
where (a, _ : b) = splitAt n t

0 commit comments

Comments
 (0)