Skip to content

Commit 09ef597

Browse files
committed
Clean up package strucute, exports and documentation
1 parent 15cba27 commit 09ef597

File tree

6 files changed

+119
-55
lines changed

6 files changed

+119
-55
lines changed

package.yaml

Lines changed: 9 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
name: linear-code
2-
version: 0.1.0.0
2+
version: 0.1.0
33
github: "wchresta/linear-code"
4-
license: GPL3
4+
license: GPL-3
55
author: "Wanja Chresta"
66
maintainer: "wanja.hs@chrummibei.ch"
77
copyright: "2018, Wanja Chresta"
@@ -20,17 +20,15 @@ description: Please see the README on GitHub at <https://github.com/wchresta/lin
2020

2121
dependencies:
2222
- base >= 4.7 && < 5
23-
- combinat >= 0.2
24-
- containers >= 0.5
25-
- data-default >= 0.5
26-
- matrix >= 0.3
27-
- HaskellForMaths >= 0.4
28-
- ghc-typelits-natnormalise >= 0.2
29-
- ghc-typelits-knownnat >= 0.4
23+
- combinat
24+
- containers
25+
- data-default
26+
- matrix
27+
- HaskellForMaths
28+
- ghc-typelits-natnormalise
29+
- ghc-typelits-knownnat
3030
- random
3131
- MonadRandom
32-
# - hmatrix
33-
# - polynomial
3432

3533
library:
3634
source-dirs: src

src/Math/Algebra/Code/Linear.hs

Lines changed: 28 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -37,11 +37,11 @@ over arbitrary fields, including finite fields. Goes well with the
3737
@HaskellForMath@ library and its finite field implementations in
3838
@Math.Algebra.Field@. To use extension fields (fields of prime power, i.e.
3939
@F_{p^k}@ with @k>1@), use one of the exported finite fields in
40-
@Math.Algebra.Field.Extension@ like 'F16' and its generator 'a16'.
40+
"Math.Algebra.Field.Extension" like 'F16' and its generator 'a16'.
4141
4242
As theoretical basis, Introduction to Coding Theory by Yehuda Lindell is used.
4343
It can be found at
44-
http://u.cs.biu.ac.il/~lindell/89-662/coding_theory-lecture-notes.pdf
44+
<http://u.cs.biu.ac.il/~lindell/89-662/coding_theory-lecture-notes.pdf>
4545
-}
4646
module Math.Algebra.Code.Linear
4747
( LinearCode (..)
@@ -71,12 +71,12 @@ module Math.Algebra.Code.Linear
7171
, e, e1, e2, e3, e4, e5, e6, e7, e8, e9, e10
7272
, char
7373

74-
-- * Reexported matrix functions
74+
-- * Reexported matrix functions from "Math.Algebra.Matrix"
7575
, matrix, zero, transpose, fromList, fromLists
7676

77-
-- * Reexported finite fields
78-
, FiniteField, F2, F3, F5, F7, F11
79-
, ExtensionField, F4, F8, F16, F9
77+
-- * Reexported finite fields from @Math.Algebra.Field@
78+
, F2, F3, F5, F7, F11
79+
, F4, F8, F16, F9
8080
) where
8181

8282
-- Linear codes from mathematical coding theory, including error correcting
@@ -117,32 +117,37 @@ import Math.Algebra.Matrix
117117
)
118118

119119

120-
-- | A Generator is the generator matrix of a linear code, not necessarily
120+
-- | A 'Generator' is the generator matrix of a linear code, not necessarily
121121
-- in standard form.
122122
type Generator (n :: Nat) (k :: Nat) = Matrix k n
123+
124+
-- | A 'CheckMatrix' or parity matrix is the dual of a 'Generator'. It can
125+
-- be used to check if a word is a valid code word for the code. Also,
126+
-- > ∀v∈F^k: cG * H^T = 0
127+
-- i.e. the code is generated by the kernel of a check matrix.
123128
type CheckMatrix (n :: Nat) (k :: Nat) = Matrix (n-k) n
124129

125-
-- | A [n,k]-Linear code over the field f. The code parameters f,n and k
126-
-- are carried on the type level.
127-
-- A linear code is a subspace C of f generated by the generator matrix.
130+
-- | A @[n,k]@-Linear code over the field @f@. The code parameters @f@,@n@ and
131+
-- @k@ are carried on the type level.
132+
-- A linear code is a subspace @C@ of @f^n@ generated by the generator matrix.
128133
data LinearCode (n :: Nat) (k :: Nat) (f :: *)
129134
= LinearCode { generatorMatrix :: Generator n k f
130135
-- ^ Generator matrix, used for most of the operations
131-
-- , standardFormGenerator :: Maybe (Generator n k f)
132136
, checkMatrix :: CheckMatrix n k f
133137
-- ^ Check matrix which can be automatically calculated
134138
-- from the standard form generator.
135139
, distance :: Maybe Int
136140
-- ^ The minimal distance of the code. This is the parameter
137-
-- d in [n,k,d]_q notation of code parameters. The problem
138-
-- of finding the minimal distance is NP-Hard, thus might
139-
-- not be available.
141+
-- @d@ in @[n,k,d]_q@ notation of code parameters. The
142+
-- problem of finding the minimal distance is NP-Hard, thus
143+
-- might not be available.
140144
, syndromeTable :: SyndromeTable n k f
141145
-- ^ A map of all possible syndromes to their error vector.
142146
-- It is used to use syndrome decoding, a very slow decoding
143147
-- algorithm.
144148
}
145149

150+
-- | Extract an Int from a type level 'KnownNat'.
146151
natToInt :: forall k. KnownNat k => Proxy k -> Int
147152
natToInt = fromInteger . natVal
148153

@@ -154,11 +159,12 @@ instance forall n k f. (Eq f, Fractional f, KnownNat n, KnownNat k, k <= n)
154159
instance forall n k f c.
155160
(KnownNat n, KnownNat k, KnownNat (Characteristic f))
156161
=> Show (LinearCode n k f) where
157-
show LinearCode{} =
158-
'[':show n<>","<>show k<>"]_"<>show c<>"-Code"
162+
show LinearCode{distance=md} =
163+
'[':show n<>","<>show k<>dist<>"]_"<>show c<>"-Code"
159164
where c = char (Proxy :: Proxy f)
160165
n = natToInt @n Proxy
161166
k = natToInt @k Proxy
167+
dist = fromMaybe "" $ fmap (\d -> ',':show d) md
162168

163169
instance forall n k f.
164170
(KnownNat n, KnownNat k, k <= n, Eq f, FinSet f, Num f, Ord f)
@@ -174,7 +180,9 @@ randomPermMatrix g =
174180
let n = natToInt @n Proxy
175181
delta i j = if i == j then 1 else 0
176182
(perm,g') = _randomPermutation n g
177-
in (fromLists [ [ delta i (perm !! (j-1)) | j <- [1..n] ] | i <- [1..n] ],g')
183+
in (fromLists [ [ delta i (perm !! (j-1))
184+
| j <- [1..n] ]
185+
| i <- [1..n] ],g')
178186

179187
-- | A random code with a generator in standard form. This does not generate
180188
-- all possible codes but only one representant of the equivalence class
@@ -340,7 +348,9 @@ calcSyndromeTable c = M.fromListWith minWt allSyndromes
340348
allSyndromes :: [(Syndrome n k f, Vector n f)]
341349
allSyndromes = [(syndrome c e,e) | e <- lighterWords w]
342350

343-
351+
-- | Replace the 'syndromeTable' of a code with a newly calculated syndrome
352+
-- table for the (current) generator. Useful to get a syndrome table for
353+
-- transformed codes when the table cannot be transformed, too.
344354
recalcSyndromeTable :: forall n k f.
345355
(KnownNat n, KnownNat k, k <= n, Eq f, FinSet f, Num f, Ord f)
346356
=> LinearCode n k f -> LinearCode n k f

src/Math/Algebra/Field/Instances.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,19 @@
1515
You should have received a copy of the GNU General Public License
1616
along with Foobar. If not, see <https://www.gnu.org/licenses/>.
1717
-}
18+
{-|
19+
Module : Math.Algebra.Field.Instances
20+
Description : Missing instnaces for @HaskellForMaths@'s 'Math.Algebra.Field'
21+
Copyright : (c) Wanja Chresta, 2018
22+
License : GPL-3
23+
Maintainer : wanja.hs@chrummibei.ch
24+
Stability : experimental
25+
Portability : POSIX
26+
27+
Some important instances like 'Random' and 'Bounded' are missing from
28+
@HaskellForMath@'s implementation of finite fiels. Here, orphan instances
29+
for these classes are added.
30+
-}
1831

1932
module Math.Algebra.Field.Instances() where
2033

src/Math/Algebra/Field/Static.hs

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,18 @@
2020
You should have received a copy of the GNU General Public License
2121
along with Foobar. If not, see <https://www.gnu.org/licenses/>.
2222
-}
23+
{-|
24+
Module : Math.Algebra.Field.Static
25+
Description : Some type families extracting finite field parameters
26+
Copyright : (c) Wanja Chresta, 2018
27+
License : GPL-3
28+
Maintainer : wanja.hs@chrummibei.ch
29+
Stability : experimental
30+
Portability : POSIX
31+
32+
Some finite field parameters are missing from @HaskellForMaths@ implementation.
33+
Here, we add type classes to add these parameters to the type level.
34+
-}
2335
module Math.Algebra.Field.Static where
2436

2537
import Data.Proxy (Proxy(Proxy))
@@ -57,7 +69,7 @@ type instance Characteristic F.F79 = 79
5769
type instance Characteristic F.F83 = 83
5870
type instance Characteristic F.F89 = 89
5971
type instance Characteristic F.F97 = 97
60-
type instance Characteristic (F.ExtensionField k poly)
72+
type instance Characteristic (F.ExtensionField k poly)
6173
= Characteristic k -- Extension fields have their base fields char
6274

6375

@@ -85,7 +97,7 @@ type instance PolyDegree F.ConwayF32 = 5
8597
-- of a finite field.
8698
type family Size (f :: *) :: Nat
8799
type instance Size (F.Fp p) = Characteristic (F.Fp p)
88-
type instance Size (F.ExtensionField fp poly) =
100+
type instance Size (F.ExtensionField fp poly) =
89101
Characteristic fp ^ PolyDegree poly
90102

91103

src/Math/Algebra/Matrix.hs

Lines changed: 45 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,9 @@ import Data.Maybe (isNothing, listToMaybe)
6767
import qualified Data.Matrix as M
6868
import qualified System.Random as R
6969

70+
71+
-- | A matrix over the type @f@ with @m@ rows and @n@ columns. This just wraps
72+
-- the 'Data.Matrix.Matrix' constructor and adds size information to the type
7073
newtype Matrix (m :: Nat) (n :: Nat) (f :: *) = Matrix (M.Matrix f)
7174
deriving (Eq, Functor, Applicative, Foldable, Traversable, Monoid)
7275

@@ -115,67 +118,87 @@ instance forall m n a. (KnownNat m, KnownNat n, R.Random a)
115118
(^*) :: forall m n a. Num a => a -> Matrix m n a -> Matrix m n a
116119
x ^* (Matrix n) = Matrix $ M.scaleMatrix x n
117120

121+
-- | A row vector (a matrix with one row).
118122
type Vector = Matrix 1
119123

124+
-- | /O(rows*cols)/. Generate a matrix from a generator function.
125+
-- | The elements are 1-indexed, i.e. top-left element is @(1,1)@.
120126
matrix :: forall m n a. (KnownNat m, KnownNat n)
121127
=> ((Int, Int) -> a) -> Matrix (m :: Nat) (n :: Nat) a
122128
matrix = Matrix . M.matrix m' n'
123-
where m' = fromInteger $ natVal (Proxy @m)
124-
n' = fromInteger $ natVal (Proxy @n)
129+
where m' = fromInteger $ natVal @m Proxy
130+
n' = fromInteger $ natVal @n Proxy
125131

132+
-- | /O(rows*cols)/. The transpose of a matrix.
126133
transpose :: forall m n a. Matrix m n a -> Matrix n m a
127134
transpose (Matrix m) = Matrix . M.transpose $ m
128135

136+
-- | Horizontally join two matrices. Visually:
137+
--
138+
-- > ( A ) <|> ( B ) = ( A | B )
129139
(<|>) :: forall m n k a. (KnownNat n, KnownNat k)
130140
=> Matrix m n a -> Matrix m k a -> Matrix m (k+n) a
131141
(Matrix x) <|> (Matrix y) = Matrix $ x M.<|> y
132142

143+
-- | /O(rows*cols)/. Identity matrix
133144
identity :: forall n a. (Num a, KnownNat n) => Matrix n n a
134145
identity = Matrix $ M.identity n'
135-
where n' = fromInteger $ natVal (Proxy @n)
146+
where n' = fromInteger $ natVal @n Proxy
136147

148+
-- | /O(rows*cols)/. The zero matrix
137149
zero :: forall m n a. (Num a, KnownNat n, KnownNat m) => Matrix m n a
138150
zero = Matrix $ M.zero m' n'
139-
where n' = fromInteger $ natVal (Proxy @n)
140-
m' = fromInteger $ natVal (Proxy @m)
151+
where n' = fromInteger $ natVal @n Proxy
152+
m' = fromInteger $ natVal @m Proxy
141153

154+
-- | Create a matrix from a list of elements.
155+
-- The list must have exactly length @n*m@. This is checked or else an
156+
-- exception is thrown.
142157
fromList :: forall m n a. (KnownNat m, KnownNat n) => [a] -> Matrix m n a
143-
fromList as = if length as == n'*m'
144-
then Matrix $ M.fromList m' n' as
158+
fromList as = if length as == n*m
159+
then Matrix $ M.fromList m n as
145160
else error $ "List has wrong dimension: "
146161
<>show (length as)
147162
<>" instead of "
148-
<>show (n'*m')
149-
where n' = fromInteger $ natVal (Proxy @n)
150-
m' = fromInteger $ natVal (Proxy @m)
163+
<>show (n*m)
164+
where n = fromInteger $ natVal @n Proxy
165+
m = fromInteger $ natVal @m Proxy
151166

167+
-- | Create a matrix from a list of rows. The list must have exactly @m@
168+
-- lists of length @n@. An exception is thrown otherwise.
152169
fromLists :: forall m n a. (KnownNat m, KnownNat n) => [[a]] -> Matrix m n a
153-
fromLists as = if length as == m' && length (head as) == n'
170+
fromLists as = if length as == m && all (\row -> length row == n) as
154171
then Matrix $ M.fromLists as
155172
else error $ "List has wrong dimension: "
156173
<>show (length as)<>":"
157174
<>show (length $ head as)
158175
<>" instead of "
159-
<>show m' <>":"<> show n'
160-
where n' = fromInteger $ natVal (Proxy @n)
161-
m' = fromInteger $ natVal (Proxy @m)
162-
176+
<>show m <>":"<> show n
177+
where n = fromInteger $ natVal @n Proxy
178+
m = fromInteger $ natVal @m Proxy
163179

180+
-- | Get the elements of a matrix stored in a list.
164181
toList :: forall m n a. Matrix m n a -> [a]
165182
toList (Matrix m) = M.toList m
166183

167-
184+
-- | Get the elements of a matrix stored in a list of lists,
185+
-- where each list contains the elements of a single row.
168186
toLists :: forall m n a. Matrix m n a -> [[a]]
169187
toLists (Matrix m) = M.toLists m
170188

171189

190+
-- | /O(1)/. Extract a submatrix from the given position. The size of the
191+
-- extract is determined by the types, i.e. the parameters define which
192+
-- element is the top-left element of the extract.
193+
-- CAUTION: It is not checked if an extract is possible. Wrong parameters
194+
-- will cause an exception.
172195
submatrix :: forall m n m' n' a.
173196
(KnownNat m, KnownNat n, KnownNat m', KnownNat n'
174197
, m' <= m, n' <= n)
175198
=> Int -> Int -> Matrix m n a -> Matrix m' n' a
176199
submatrix i j (Matrix mat) = Matrix $ M.submatrix i (i+m'-1) j (j+n'-1) mat
177-
where n' = fromInteger . natVal $ Proxy @n'
178-
m' = fromInteger . natVal $ Proxy @m'
200+
where n' = fromInteger $ natVal @n' Proxy
201+
m' = fromInteger $ natVal @m' Proxy
179202

180203

181204

@@ -212,7 +235,7 @@ rref mat = fromLists $ f m 0 [0 .. rows - 1]
212235
| otherwise = zipWith h newRow row
213236
where h = subtract . (* row !! lead')
214237

215-
replace :: Int -> a -> [a] -> [a]
216-
{- Replaces the element at the given index. -}
217-
replace n e l = a ++ e : b
218-
where (a, _ : b) = splitAt n l
238+
replace :: Int -> b -> [b] -> [b]
239+
{- Replaces the element at the given index. -}
240+
replace n e l = a ++ e : b
241+
where (a, _ : b) = splitAt n l

test/Main.hs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,15 @@ codeTests =
4141
let tc = trivialCode :: BinaryCode 5 3
4242
hamming74 = hamming :: BinaryCode 7 4
4343
in testGroup "Codes"
44-
[ testGroup "Trivial code"
44+
[ testGroup "Instances"
45+
[ testCase "Show works for unknown distance" $
46+
show (trivialCode {distance=Nothing} :: LinearCode 7 4 F.F3)
47+
@?= "[7,4]_3-Code"
48+
, testCase "Show works for known distance" $
49+
show (trivialCode {distance=Just 3} :: LinearCode 7 4 F.F3)
50+
@?= "[7,4,3]_3-Code"
51+
]
52+
, testGroup "Trivial code"
4553
[ testCase "Trivial binary code == codeFromA zero, [5,3]" $
4654
tc @?= codeFromA zero
4755
, testCase "Trivial binary code == codeFromA zero, [3,3]" $
@@ -88,7 +96,7 @@ codeTests =
8896
]
8997

9098
-- SmallCheck Series for GF
91-
instance forall m f. (Monad m, FiniteField f) => S.Serial m f where
99+
instance forall m f. (Monad m, F.FiniteField f) => S.Serial m f where
92100
series = S.generate $ \d -> take (d+1) (F.eltsFq 1 :: [f])
93101

94102
instance forall m n f. (KnownNat m, KnownNat n, Q.Arbitrary f)

0 commit comments

Comments
 (0)