Skip to content

Instantly share code, notes, and snippets.

@jtobin
jtobin / local_genesis.json
Created February 29, 2016 06:00
Ethereum genesis block
{
"nonce": "0xcafebabecafebabe",
"timestamp": "0x0",
"parentHash": "0x0000000000000000000000000000000000000000000000000000000000000000",
"extraData": "0x0",
"gasLimit": "0xfffffff",
"difficulty": "0x400",
"mixhash": "0x0000000000000000000000000000000000000000000000000000000000000000",
"coinbase": "0x3333333333333333333333333333333333333333",
"alloc": {
@jtobin
jtobin / foo.hs
Created February 15, 2016 21:39
Independence and Applicativeness
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE LambdaCase #-}
import Control.Applicative.Free
import Control.Monad
import Control.Monad.Free
import Control.Monad.Primitive
import System.Random.MWC.Probability (Prob)
import qualified System.Random.MWC.Probability as MWC
@jtobin
jtobin / histo-futu.hs
Created February 9, 2016 02:21
Time-traveling recursion schemes
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-}
import Control.Comonad.Cofree
import Control.Monad.Free
import Data.Functor.Foldable
oddIndices :: [a] -> [a]
oddIndices = histo $ \case
Nil -> []
@jtobin
jtobin / foo.hs
Created January 31, 2016 05:27
Using recursion-schemes w/non-functor type
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeFamilies #-}
import Data.Functor.Foldable hiding (Foldable, Unfoldable)
import qualified Data.Functor.Foldable as RS (Foldable, Unfoldable)
data Expr =
Num Int
| Sum Expr Expr
@jtobin
jtobin / apo.hs
Created January 19, 2016 04:03
Sorting (Slowly) With Style
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeFamilies #-}
import Data.Functor.Foldable
data ListF a r =
ConsF a r
| NilF
deriving (Show, Functor)
@jtobin
jtobin / cofree.hs
Created December 9, 2015 18:51
A program defined using 'Cofree'
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
data Program f a = Program {
annotation :: a
, running :: f (Program f a)
}
@jtobin
jtobin / free.hs
Created December 9, 2015 18:51
A program defined using 'Free'
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
data Program f a =
Running (f (Program f a))
| Terminated a
deriving instance (Show a, Show (f (Program f a))) => Show (Program f a)
@jtobin
jtobin / fix.hs
Created December 9, 2015 18:50
A program defined using 'Fix'
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
data Program f = Running (f (Program f))
deriving instance (Show (f (Program f))) => Show (Program f)
data Instruction r =
@jtobin
jtobin / fix-free-cofree.hs
Created December 9, 2015 06:13
Fix, Free, and Cofree
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
import Prelude hiding (succ)
newtype Fix f = Fix (f (Fix f))
deriving instance (Show (f (Fix f))) => Show (Fix f)
@jtobin
jtobin / recursion_schemes.hs
Created September 6, 2015 00:58
An illustration of the recursion-schemes library.
{-# LANGUAGE DeriveFunctor #-}
import Data.List.Ordered (merge)
import Data.Functor.Foldable
import Prelude hiding (Foldable, succ)
data NatF r =
ZeroF
| SuccF r
deriving (Show, Functor)