Skip to content

Instantly share code, notes, and snippets.

@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:3950460
Created October 25, 2012 04:49
Multiple async HTTP requests by Haskell
{-# LANGUAGE FlexibleContexts #-}
import Data.Conduit
import qualified Data.Conduit.List as CL
import Network.HTTP.Conduit
import Control.Concurrent.Async (mapConcurrently)
import Control.Concurrent.MVar
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Control (MonadBaseControl)
@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:3246709
Created August 3, 2012 11:11
Number of binary trees have N leaves with logging by Writer Monad
import Control.Arrow (first)
import Control.Monad.List
import Control.Monad.Writer
liftList :: (Monad m) => [a] -> ListT m a
liftList = ListT . return
splites :: Int -> [(Int, Int)]
splites n = [ (x, n - x) | x <- [1..n-1] ]
@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
@hyone
hyone / gist:3238199
Created August 2, 2012 16:05
Multiple async HTTP requests by using http.async.client callback API
;; (defproject async-test2 "0.1.0-SNAPSHOT"
;; :description "FIXME: write description"
;; :url "http://example.com/FIXME"
;; :license {:name "Eclipse Public License"
;; :url "http://www.eclipse.org/legal/epl-v10.html"}
;; :dependencies [[org.clojure/clojure "1.4.0"]
;; [http.async.client "0.4.5"]])
(ns async-test2.core
@hyone
hyone / gist:3215897
Created July 31, 2012 10:24
split a list into sublists that have N items
import Control.Monad.State
splitEvery :: Int -> [a] -> [[a]]
splitEvery n = takeWhile (not . null) . evalState (sequence $ repeat (state (splitAt n)))
{-
ghci> splitEvery 5 [1..27]
[[1,2,3,4,5],[6,7,8,9,10],[11,12,13,14,15],[16,17,18,19,20],[21,22,23,24,25],[26,27]]
ghci> splitEvery 5 []
[]