Skip to content

Instantly share code, notes, and snippets.

@viviag
Last active December 15, 2022 13:31
Show Gist options
  • Save viviag/fcd540145d914c09d9c5edf3df288885 to your computer and use it in GitHub Desktop.
Save viviag/fcd540145d914c09d9c5edf3df288885 to your computer and use it in GitHub Desktop.
Efficient version of https://gist.github.com/viviag/4961e87e7db567f0d2fd86bc664388ae. Runs about 6 times faster.
-- To prevent overflows
{-# LANGUAGE Strict #-}
module Main where
{-
ghc -O2 weigth.hs # Was not tested with default level.
./weight.hs 2> progress-bar.txt
-}
import Control.DeepSeq
import Debug.Trace
import Data.Bits
import Data.Word (Word64)
infixl 7 *.
infixl 7 %.
infixl 6 +.
type N = Int
{-
Over F2 we can use the same logic as in old extract function and model polynomials as integers.
Or as sequence of bits.
Probably it would be better to write in in C. But let's continue as we started.
-}
type Poly = Word64
-- In Word64 type 1 has the only latest bit set. Hence order of is as in natural languages and ends at degree zero.
degree :: Poly -> Int
degree p = (finiteBitSize p) - (countLeadingZeros p) - 1
-- Monomial of degree n.
-- shift n is a multiplication by x^n.
mono :: Int -> Poly
mono n = shift 1 n
-- Sum of two vectors over F2 is naturally their logical symmetric sum.
(+.) :: Poly -> Poly -> Poly
(+.) = xor
-- Multiplication.
-- We iterate through second operand and accumulate values a*k_m*x^m for each position m below degree of second operand.
(*.) :: Poly -> Poly -> Poly
(*.) a b = force $ foldr (\n acc -> acc +. if b .&. mono n == 0 then 0 else shiftL a n) 0 [0..degree b]
-- FIXME: Implement division.
-- Modulo by polynomial.
-- If degree of monomial if less than of object on the right we accumulate monomial itself.
-- If equal (and equal to n) -- add x^n + b to accumulator.
-- If above following equation holds: x^n/f = x^{k*deg f}x^r/f = (f+x^{deg f})^k*x^r (r < deg f).
-- Hence we can multiply the results and take modulo again. Degree will decrease by deg n on each step.
(%.) :: Poly -> Poly -> Poly
(%.) a b = force $ foldr ( \n acc -> acc +. if a .&. mono n == 0 then 0 else case compare n (degree b) of
LT -> mono n
EQ -> b +. mono n
GT -> ((b +. mono (degree b)) *. (mono (n - degree b) %. b)) %. (b)
) 0 [0..degree a]
-- \sum_{i=0}^{n-1} x^i
phi :: N -> Poly
phi n = complement $ shift (complement zeroBits) n
-- x^{n}-1
modulus :: N -> Poly
modulus n = 0 `setBit` 0 `setBit` n
-- x^n. All words below in lexicographic order are polynomials of acceptable degrees.
boundPoly :: N -> Poly
boundPoly n = 0 `setBit` n
-- Actually compute minimal distance of the code.
-- Alternative implementation works without filter - we multiply each element by generator and take modulo to get to code.
minimalDistance :: N -> Poly -> Int
minimalDistance n gen =
foldr ( \a m -> force $ min m (if a == 0 then m else a)
) n ( map popCount (filter (\p -> traceShowId p %. gen == 0) [0..boundPoly n])
)
-- Construct polynomial from more friendly input.
buildPoly :: [Int] -> Poly
buildPoly = foldr (flip setBit) 0
-- Build reciprocal polynomial.
rev :: Poly -> Poly
rev a = foldr ( \n step -> if testBit a (degree a - n)
then setBit step n
else clearBit step n
) a [0..degree a]
main :: IO ()
main = do
putStrLn "Insert modulus (1 <= n <= 64): "
-- Bigger values will cause overflows. Or, hopefully, errors.
n <- read <$> getLine
putStrLn "Insert list of degrees of generating polynomial (format [a,b,c]): "
a' <- read <$> getLine
putStrLn "Minimal distance of the code (is being computed): "
print $ minimalDistance n (buildPoly a')
--putStrLn "Minimal distance of dual code (is being computed): "
--print $ minimalDistance n (rev . (/.) (modulus n) $ buildPoly a')
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment