Skip to content

Instantly share code, notes, and snippets.

@hyone
hyone / gist:8205717
Created January 1, 2014 06:46
ruby koans: about_scoring_project.rb
# Greed is a dice game where you roll up to five dice to accumulate
# points. The following "score" function will be used to calculate the
# score of a single roll of the dice.
#
# A greed roll is scored as follows:
#
# * A set of three ones is 1000 points
#
# * A set of three numbers (other than ones) is worth 100 times the
# number. (e.g. three fives is 500 points).
@hyone
hyone / gist:6128565
Last active December 20, 2015 12:09
Number of binary trees have N leaves with logging by Writer Monad #2 ( see: http://hyone.hatenablog.com/entry/20120803/1343996582 )
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.List
import Control.Monad.Trans (lift)
import Control.Monad.Writer
splites :: Int -> [(Int, Int)]
splites n = [ (x, n - x) | x <- [1..n-1] ]
liftList :: Monad m => [a] -> ListT m a
@hyone
hyone / HList.hs
Last active December 10, 2015 04:08
Typed Heterogeneous Lists with DataKinds language extension
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module HList where
@hyone
hyone / gist:3994646
Created November 1, 2012 16:10
Example code to implement instances for Singlton types
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- | Example code to implement instances for Singlton types introduced GHC 7.6.1
@hyone
hyone / IndexedMatrixAndIFunctor.hs
Last active October 12, 2015 07:18
Length Indexed Matrix and Indexed Functor
-- Run on GHC 7.6.1
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
@hyone
hyone / gist:3973701
Created October 29, 2012 13:56
Don't match type level arithmetic result with same literal value on GHC 7.6.1
-- $ ghci
-- GHCi, version 7.6.1: http://www.haskell.org/ghc/ :? for help
ghci> import GHC.TypeLits
ghci> :set -XDataKinds
ghci> :set -XPolyKinds
ghci> :set -XGADTs
ghci> data EqRefl a b where { Refl :: EqRefl a a }
ghci> :t Refl :: EqRefl 1 1
Refl :: EqRefl 1 1 :: EqRefl Nat 1 1
@hyone
hyone / gist:3799190
Created September 28, 2012 11:00
FizzBuzz on Type Level
-- Run on GHC 7.4.2
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
@hyone
hyone / gist:3629254
Created September 5, 2012 02:16
Define function that accepts only a specific data constructor on a type
{-# LANGUAGE GADTs #-}
data Nil
data Cons
data StrongList x tag where
Nil :: StrongList a Nil
Cons :: a -> StrongList a b -> StrongList a Cons
safeHead :: StrongList x Cons -> x
@hyone
hyone / gist:3615967
Created September 4, 2012 02:44
Define function that accepts only specific multi data constructors on a type
{-# LANGUAGE GADTs #-}
data MyString
data MyInt
data MyNil
data MyData tag where
MyString :: String -> MyData MyString
MyInt :: Int -> MyData MyInt
MyNil :: MyData MyNil
@hyone
hyone / gist:3246701
Created August 3, 2012 11:09
Number of binary trees have N leaves
splites :: Int -> [(Int, Int)]
splites n = [ (x, n - x) | x <- [1..n-1] ]
count :: Int -> Int
count 1 = 1
count n = sum $ do
(i, j) <- splites n
return $ count i * count j