Skip to content

Instantly share code, notes, and snippets.

@viviag
viviag / symb.hs
Last active September 18, 2023 19:35
Differentiation
-- Specification follows corresponding cata on codewars
{-
To run online I recommend to follow https://paiza.io/en/projects/new?language=haskell
, paste the code instead of the template, run and click on output tab.
This is a demo for the specific task, so it bypasses problem with negative logarithm argument optimistically.
Hence it yields arbitrary numbers if called on a value out of domain.
-}
module Main where
@viviag
viviag / weight-basis.hs
Created December 14, 2022 12:31
Compute minimal weight of cyclic code using only linear structure. Fast on low-dimensional codes.
{-# LANGUAGE Strict #-}
module Main where
{-
ghc -O2 weigth-basis.hs # Was not tested with default level.
./weight-basis.hs
-}
import Control.DeepSeq
@viviag
viviag / weight.hs
Last active December 15, 2022 13:31
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
@viviag
viviag / brute-distance.hs
Last active December 12, 2022 16:34
Brutal straightforward computation of minimal distance between words in binary cyclic code. It usually should not be run.
{-# LANGUAGE BangPatterns #-}
import Data.List ((\\), union, sort)
import Data.Foldable
import Debug.Trace
type N = Int
type Mono = Int
type IndexCode = Int
multMonomials :: Mono -> Mono -> Mono
@viviag
viviag / polyalg_f2.hs
Last active December 10, 2022 05:56
gcd of polynomials over F2 and necessities
import Data.List ((\\), union, sort)
type Mono = Int
multMonomials :: Mono -> Mono -> Mono
multMonomials = (+)
divMonomial :: Mono -> Mono -> Mono
divMonomial a b = if a > b
then a - b
@viviag
viviag / orbits-any.hs
Last active December 11, 2022 15:12
Generalization of https://gist.github.com/viviag/decc9a306e2765b2acf4276dca1fc112 to arbitrary prime fields of characteristic p and any modulus such that (n,p)=1
import Data.List (sort, nub)
type Power = Int
type IndexCode = Int
type Flag = Int
type Orbit = [Power]
type Roots = [Power]
type P = Int
type N = Int
@viviag
viviag / orders0.hs
Last active December 8, 2022 18:13
Brute force analogue of computation in orders.hs (https://gist.github.com/viviag/cfe9b791d57e208a97369919baf968cb)
type Order = Integer
type Element = Integer
order :: Order -> Element -> Order
order p elem = order' p elem elem 1
where
order' _ 1 _ ord = ord
order' p power elem ord = order' p (power*elem `mod` p) elem (ord+1)
elemsOfOrder :: Order -> Order -> [Element]
@viviag
viviag / orbits.hs
Last active December 8, 2022 18:18
Compute BCH-bounds for all cyclic codes of length 31 over F2
import Data.List (sort, nub)
type Power = Int
type IndexCode = Int
type Flag = Int
type Orbit = [Power]
type Roots = [Power]
type P = Int
type N = Int
@viviag
viviag / orders.hs
Last active December 6, 2022 07:15
Roughly programmed search of elements with given order in multiplicative group of ring of integers modulo prime p. First semester algebra exercise.
type Order = Integer
type Element = Integer
order :: Order -> Element -> Order
order p elem = order' p elem elem 1
where
order' _ 1 _ ord = ord
order' p power elem ord = order' p (power*elem `mod` p) elem (ord+1)
-- Searching any generator of cyclic subgroup of order d.
@viviag
viviag / hom_covariant.hs
Created August 15, 2022 15:48
Playing around Hom(X,_) in Hask
module Main where
import Control.Monad
-- Directly composing morphisms as if we were not in End_{Hask}.
regular :: (->) Int Int
regular = (+) 1 . (+) 1 . (+) 1 . (+) 1
-- Actually the same, but explicitly using action of Hom-functor on arrows.
functorial :: (->) Int Int