Skip to content

Instantly share code, notes, and snippets.

View plaidfinch's full-sized avatar

finch plaidfinch

View GitHub Profile
module MultiFilters where
import Control.Applicative ((<$>))
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
a .: b = (a .) . b
juxt :: [a -> b] -> a -> [b]
juxt = sequence
@plaidfinch
plaidfinch / Truffula.hs
Created July 12, 2014 19:08
Binary-tree zippers with type witnesses of position in tree
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
module Truffula where
data Path = LeftOf Path | RightOf Path | Root
data Tree (p :: Path) a where
Tree :: { value :: a
-- a Wrapper is a pair of *something*, and if that something is an Int, an additional boolean
data Wrapper a =
Wrapper { get :: a
, test :: (a ~ Int) => Bool }
-- We can construct a Wrapper from something of any type
makeWrapper :: a -> Wrapper a
makeWrapper x = Wrapper x (x == 0) -- Whoa! We're comparing it to zero even if it might not be an Int!
-- We can construct a Wrapper, as noted above, at various type indices…
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
-- How to use fix to implement polymorphic recursion!
module PolymorphicFixedpoints where
import Data.Function ( fix )
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UnicodeSyntax #-}
module DeMorganCPS where
-- Products and sums with prettier type notation
data a ∧ b = Pair a b
data a ∨ b = InL a | InR b
@plaidfinch
plaidfinch / Dicts.hs
Last active August 29, 2015 14:12
List of Dicts?
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import Data.Constraint
import Data.Proxy
@plaidfinch
plaidfinch / FunWithDictionaries.hs
Last active August 29, 2015 14:12
Playing with Data.Constraint for great fun
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Constraint
import Data.Proxy
@plaidfinch
plaidfinch / SOP.hs
Last active August 29, 2015 14:12
Playing with sums of products
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
@plaidfinch
plaidfinch / Spiral.hs
Created February 5, 2015 05:18
The `spiral` function: a perplexing piece of coinduction
module Spiral where
-- Based on <pigworker.wordpress.com/2015/01/02/coinduction>
data Tree x = Leaf x
| Branch x (Tree x) (Tree x)
deriving ( Show )
data Stream x = x :> Stream x
deriving ( Show )
@plaidfinch
plaidfinch / Cooperational.hs
Created February 7, 2015 22:20
The Coöperational Comonad
{-# LANGUAGE GADTs #-}
module Cooperational where
import Control.Monad
import Control.Applicative
import Control.Comonad
data Oper f a =
Return a