Skip to content

Instantly share code, notes, and snippets.

View snowleopard's full-sized avatar

Andrey Mokhov snowleopard

View GitHub Profile
@snowleopard
snowleopard / unfoldr.hs
Created May 17, 2021 18:38
Generalised unfoldr
-- See http://www.staff.city.ac.uk/~ross/papers/FingerTree.html
class Monoid m => Measured a m where
measure :: a -> m
instance Measured a [a] where
measure a = [a]
-- Generalised to any resulting monoid from `unfoldr :: (b -> Maybe (a, b)) -> b -> [a]`
unfoldr :: Measured a m => (b -> Maybe (a, b)) -> b -> m
unfoldr f b = case f b of
@snowleopard
snowleopard / sigma-pi-monad.ml
Created February 24, 2020 18:13
Sigma Pi monad
(* See https://github.com/snowleopard/selective/blob/master/src/Control/Selective/Multi.hs *)
module Sigma (T : sig
type 'a t
end) =
struct
type t = Sigma : 'a T.t * 'a -> t
end
module type T = sig
@snowleopard
snowleopard / CCC.hs
Last active September 30, 2019 22:01
Connected components, concurrently
{-# LANGUAGE GADTs, ScopedTypeVariables, TypeOperators #-}
module CCC where
import Algebra.Graph.Undirected
import Prelude hiding ((.), id, repeat, round)
import Control.Category
import Control.Monad.Writer
import Data.List.Extra hiding (repeat)
import Data.Map.Strict (Map)
import Data.Void
@snowleopard
snowleopard / typed-constant-folding.hs
Last active August 28, 2018 10:37
Typed constant folding
{-# LANGUAGE GADTs, DataKinds, TypeOperators #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
-- This is an attempt to find a safer implementation for GHC constant folding algorithm
-- See https://ghc.haskell.org/trac/ghc/ticket/15569
-- Shapes of expression trees: L stands for a literal, V for a variable
data Shape = L | V | Shape :+: Shape | Shape :*: Shape
-- Arithmetic expressions with shape annotations