Skip to content

Instantly share code, notes, and snippets.

View plaidfinch's full-sized avatar

plaidfinch plaidfinch

View GitHub Profile
@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
{-# 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
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
-- How to use fix to implement polymorphic recursion!
module PolymorphicFixedpoints where
import Data.Function ( fix )
-- 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…
@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
@plaidfinch
plaidfinch / Handles.hs
Last active September 8, 2016 17:00
File handles with type-level verification that you use them properly
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE RebindableSyntax #-}
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
> take 7 pascalLists
[[1],
[1, 1],
[1, 2, 1],
[1, 3, 3, 1],
[1, 4, 6, 4, 1],
[1, 5, 10, 10, 5, 1],
[1, 6, 15, 20, 15, 6, 1],
[1, 7, 21, 35, 35, 21, 7, 1]]
pascalLists :: [[Integer]]
pascalLists = map pascalList [0..]
where
pascalList n =
map view .
takeWhile ((>= 0) . row) .
iterate (go $ above & right) .
goto (0,n) $ pascal
pascal :: Z2 Int Int Integer
pascal = evaluate $ sheet (0,0) 0 $
repeat 1 : repeat (1 : pascalRow)
where pascalRow = repeat $ cell above + cell left
pascalLists :: [[Integer]]
pascalLists = map pascalList [0..]
where
pascalList n =
map view .