Skip to content

Instantly share code, notes, and snippets.

Sjoerds-iMac:~ sjoerd$ brew install -vd ncursesw
==> Build Environment
CC: /usr/bin/cc => /usr/bin/gcc-4.2
CXX: /usr/bin/c++ => /usr/bin/c++-4.2
LD: /usr/bin/cc => /usr/bin/gcc-4.2
CFLAGS: -O3 -march=core2 -msse4 -w -pipe
CXXFLAGS: -O3 -march=core2 -msse4 -w -pipe
MAKEFLAGS: -j8
PKG_CONFIG_PATH: /usr/lib/pkgconfig:/usr/local/lib/pkgconfig:/opt/local/lib/pkgconfig:
==> Downloading http://ftp.gnu.org/pub/gnu/ncurses/ncurses-5.7.tar.gz
@sjoerdvisscher
sjoerdvisscher / Expr.hs
Created November 11, 2010 12:26
An expression parser and printer.
{-# LANGUAGE TypeOperators #-}
import Web.Zwaluw
import Prelude hiding (id, (.))
import Control.Category
import Data.Char
data Expr
= Variable String
@sjoerdvisscher
sjoerdvisscher / Label.hs
Created November 12, 2010 17:04
Playing with lenses
{-# LANGUAGE TypeOperators, RankNTypes, TupleSections #-}
import Prelude hiding ((^))
import Control.Monad
import Lens
-- Like fclabels, but with failure in get to allow for labels on sum types.
type Label f a = forall r. Lens Maybe Id f f r (a :- r)
@sjoerdvisscher
sjoerdvisscher / multiplate.hs
Created November 20, 2010 15:18
Using Multiplate with a plate containing a field for each constructor.
import Control.Applicative
import Data.Generics.Multiplate
import Data.Functor.Constant
import Data.Functor.Identity
data Expr = Con Int
| Add Expr Expr
| Mul Expr Expr
@sjoerdvisscher
sjoerdvisscher / json.hs
Created December 16, 2010 22:06
A JSON parser and serializer using Zwaluw
{-# LANGUAGE TypeOperators, OverloadedStrings, TemplateHaskell #-}
import Web.Zwaluw
import Web.Zwaluw.TH
import Prelude hiding (id, (.))
import Control.Category
import Data.Char
import Data.Foldable (foldMap)
@sjoerdvisscher
sjoerdvisscher / litorn.hs
Created December 22, 2010 16:16
Generic programming with indexed types (ala Conor McBride)
{-# LANGUAGE TypeOperators, TypeFamilies, GADTs, UndecidableInstances, RankNTypes, MultiParamTypeClasses, TypeSynonymInstances #-}
data End i
data Arg s r
data Rec i r
type family Apply f a :: *
data Univ desc is r i where
@sjoerdvisscher
sjoerdvisscher / mirror.hs
Created December 23, 2010 13:42
Mirror operation on trees with correctness proof.
{-# LANGUAGE TypeFamilies, GADTs, RankNTypes #-}
data Tip
data Node x y z
data Tree a where
Tip :: Tree Tip
Node :: Tree x -> y -> Tree z -> Tree (Node x y z)
type family Mirror a :: *
@sjoerdvisscher
sjoerdvisscher / W-types.hs
Created January 3, 2011 12:14
W-types, following the Agde code here: http://www.e-pig.org/epilogue/?p=324
{-# LANGUAGE TypeOperators, TypeFamilies, GADTs, UndecidableInstances #-}
-- Type level functions
type family Apply f a :: *
data f :.: g -- function composition
type instance Apply (f :.: g) a = Apply f (Apply g a)
data Fst
type instance Apply Fst (a, b) = a
data Snd
type instance Apply Snd (a, b) = b
@sjoerdvisscher
sjoerdvisscher / distance.hs
Created February 2, 2011 21:02
Edit distance monoid
import Data.Monoid
import Data.Function
class (Ord m, Monoid m) => Metric m where
ins :: Int -> m
del :: Int -> m
delta :: Int -> Int -> m
distance :: Metric m => [Int] -> [Int] -> m
distance [] [] = mempty
@sjoerdvisscher
sjoerdvisscher / RepresentableVec.hs
Created March 9, 2011 21:33
Lists are not representable, but vectors are.
{-# LANGUAGE GADTs, KindSignatures, TypeFamilies, FlexibleInstances, FlexibleContexts, MultiParamTypeClasses, UndecidableInstances, StandaloneDeriving #-}
import Control.Applicative
import Control.Arrow
import Data.Key
import Data.Distributive
import Data.Functor.Bind
import Data.Functor.Representable
import Data.Functor.Adjunction