Skip to content

Instantly share code, notes, and snippets.

@viviag
viviag / tzupdate.sh
Last active January 7, 2020 15:25
Update system timezone based on IP geolocation, established under Linux Munt 18.3.
#!/bin/bash
# crontab:
# */10 * * * * tzupdate.sh
# @reboot doesn't fit because of network connection delay.
# Get external IP
IP=$(curl ifconfig.me)
# Request to geolocation web service (https://ipgeolocation.io/documentation/timezone-api.html).
@viviag
viviag / power.hs
Created February 15, 2020 12:12
Some liquid-haskell proofs
-- Proof that even powers of integers are natural.
{-@ powEven :: {a:Int | a /= 0} -> {b:Nat | b mod 2 = 0} -> Nat / [b] @-}
powEven :: Int -> Int -> Int
powEven a 0 = 1
powEven a b = a * a * powEven a (b - 2)
{-@ powOdd :: {a:Int | a /= 0} -> {k:Nat | k mod 2 == 1} -> Int / [k] @-}
powOdd :: Int -> Int -> Int
powOdd a 1 = a
powOdd a b = a * a * powOdd a (b - 2)
@viviag
viviag / IPC.hs
Created August 31, 2020 03:46
Server-side IPC emulation
{-# LANGUAGE DataKinds, TypeOperators, TypeApplications #-}
module Main where
import Control.Concurrent (threadDelay, forkIO)
import Control.Monad (when, mapM_)
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.Char8 as BSLC
import Data.HashMap.Strict (HashMap, singleton)
@viviag
viviag / threadcount_naive.hs
Created July 26, 2022 12:35
Count active threads in order to terminate gracefully, minimal version
module Main where
import GHC.Conc (atomically)
import System.Exit (exitSuccess)
import Control.Concurrent.STM.TVar (TVar, readTVarIO, newTVarIO, modifyTVar')
import Control.Concurrent (forkIO, threadDelay)
import Control.Exception (bracket_)
import Control.Monad (void, when, forever)
@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
@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 / 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 / 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-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 / 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