Skip to content

Instantly share code, notes, and snippets.

View tmhedberg's full-sized avatar

Taylor M. Hedberg tmhedberg

View GitHub Profile
@tmhedberg
tmhedberg / wordsplit.hs
Last active December 15, 2015 18:58
Split a string into valid words, if it is possible to do so
import Control.Monad
import Data.Char
import Data.Functor
import Data.List
import Data.Maybe
import Data.Set (Set, fromList, member)
import System.Environment
import System.Exit
@tmhedberg
tmhedberg / parspec.hs
Created March 6, 2013 03:58
Parallel RSpec test runner
#!/usr/bin/runhaskell
import Control.Category ((>>>))
import Data.Function
import Data.Functor
import Data.List
import System.Environment
import System.Info
@tmhedberg
tmhedberg / NiceDebug.hs
Created February 15, 2013 01:05
Template Haskell macro for producing less repetitive debugging statements. Requires the `th-orphans` package.
{-# LANGUAGE TemplateHaskell #-}
module NiceDebug where
import Debug.Trace
import Language.Haskell.TH
import Language.Haskell.TH.Instances
debug :: Name -> Q Exp
@tmhedberg
tmhedberg / pre-commit
Created February 4, 2013 18:26
Git pre-commit hook for running RSpec test suite
#!/bin/bash
bundle exec rspec &
trap '
kill -INT $!
kill -INT $!
wait
echo
' INT
wait
@tmhedberg
tmhedberg / concurrent_sieve.hs
Created November 18, 2012 12:46
Concurrent prime sieve translated from Go (http://play.golang.org/p/9U22NfrXeq)
-- Compile with `ghc -threaded -with-rtsopts=-N concurrent_sieve.hs`
import Control.Concurrent
import Control.Monad
import System.Environment
generate :: MVar Int -> IO ()
generate mOut = mapM_ (putMVar mOut) [2..]
@tmhedberg
tmhedberg / LList.hs
Created November 18, 2012 02:51
A list type with statically determined length encoded in its type
{-# LANGUAGE DataKinds
, GADTs
, KindSignatures
, StandaloneDeriving
, TypeOperators
#-}
-- | A list type with statically determined length encoded in its type
--
-- Requires GHC 7.6.1 or greater.
@tmhedberg
tmhedberg / grammar
Created November 12, 2012 22:17
Procedurally generated quasi-poetry
POEM: <LINE> <LINE> <LINE> <LINE> <LINE>
LINE: <NOUN>|<PREPOSITION>|<PRONOUN> $LINEBREAK
ADJECTIVE: black|white|dark|light|bright|murky|muddy|clear <NOUN>|<ADJECTIVE>|$END
NOUN: heart|sun|moon|thunder|fire|time|wind|sea|river|flavor|wave|willow|rain|tree|flower|field|meadow|pasture|harvest|water|father|mother|brother|sister <VERB>|<PREPOSITION>|$END
PRONOUN: my|your|his|her <NOUN>|<ADJECTIVE>
VERB: runs|walks|stands|climbs|crawls|flows|flies|transcends|ascends|descends|sinks <PREPOSITION>|<PRONOUN>|$END
PREPOSITION: above|across|against|along|among|around|before|behind|beneath|beside|between|beyond|during|inside|onto|outside|under|underneath|upon|with|without|through <NOUN>|<PRONOUN>|<ADJECTIVE>
@tmhedberg
tmhedberg / AOTest.hs
Created May 9, 2012 18:28
Advanced overlapping instance resolution
{-# LANGUAGE FlexibleInstances
, MultiParamTypeClasses
, TemplateHaskell
, TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
import Prelude hiding (print)
import AdvancedOverlap
@tmhedberg
tmhedberg / rep.hs
Created April 7, 2012 23:24
Parallel computation of numbers with no repeated digits in Haskell
{-
- Count how many numbers with no repeated digits lie between 1 and the
- specified maximum (given as a command line argument)
-
- For instance 183957 is counted, while 298387 is not ('8' occurs twice).
-
- On SMP systems, parallelism is exploited to speed up the computation
- significantly. The search space is divided into as many evenly-sized chunks
- as the host system has cores, and worker threads are spawned to run on each
- core. This small program is primarily intended to illustrate the usage of
@tmhedberg
tmhedberg / THOp.hs
Created March 4, 2012 03:51
Using Template Haskell to declare operators
{-# LANGUAGE TemplateHaskell #-}
module THOp (mkOps) where
import Control.Monad
import Language.Haskell.TH
mkOp :: String -> Q [Dec]
mkOp n = [| $(varE a) + $(varE b) + length (filter (=='-') n) |] >>= \body ->