This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-- 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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
(* 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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# 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 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# 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 |