Skip to content

Instantly share code, notes, and snippets.

View tmhedberg's full-sized avatar

Taylor M. Hedberg tmhedberg

View GitHub Profile
@tmhedberg
tmhedberg / Variadic.hs
Created October 23, 2013 00:12
Turn any function of type `a -> a -> a` into a variadic function
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module Data.Function.Variadic where
class Variadic a r where variadic :: (a -> a -> a) -> a -> r
instance Variadic a a where variadic _ = id
instance Variadic a r => Variadic a (a -> r) where
variadic f x = variadic f . f x
@tmhedberg
tmhedberg / tcp-tty.hs
Last active December 21, 2015 18:29
RS-232 terminal tunneled over TCP
#!/usr/bin/runhaskell
import Control.Concurrent
import Control.Monad
import qualified Data.ByteString.Lazy as BSL
import Network
import System.IO
@tmhedberg
tmhedberg / Generator.hs
Last active December 21, 2015 10:08
A monad transformer for generator coroutines
-- | A monad transformer for generator coroutines
module Control.Monad.Generator where
import Control.Applicative
import Control.Monad
import Control.Monad.Trans
-- | The type of generators yielding intermediate results of type @t@ in base
-- monad @m@, with a final result of type @r@
data Generator t m r = Generator {runGen :: m (GeneratorState t m r)}
@tmhedberg
tmhedberg / LList.hs
Created August 8, 2013 02:32
Lists with type-encoded length
{-# LANGUAGE DataKinds, GADTs, KindSignatures, TemplateHaskell #-}
-- | Lists with type-encoded length
--
-- Includes TH macros for concise usage of Peano naturals at type and term
-- level.
--
-- Examples:
--
-- >>> :t Nil
@tmhedberg
tmhedberg / Assert.hs
Last active December 18, 2015 20:39
Assertions with an optional descriptive message, with both monadic and non-monadic variants
{-# LANGUAGE DeriveDataTypeable, FlexibleInstances, OverlappingInstances #-}
module Assert where
import Control.Exception
import Data.Typeable
data AssertionFailure = AssertionFailure (Maybe String) deriving Typeable
@tmhedberg
tmhedberg / Gray.hs
Last active December 18, 2015 17:29
Polymorphic Gray code generator
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Gray where
import Control.Applicative
class Binary b where zero :: b
one :: b
instance Binary Bool where zero = False
@tmhedberg
tmhedberg / Chance.hs
Last active December 18, 2015 07:29
Mini-EDSL for RPG-style die roll specifiers
-- | Mini-EDSL for RPG-style die roll specifiers
--
-- Examples:
--
-- > Chance> let c = 3 + 2 `d` 20
-- > Chance> roll c
-- > 17
-- > Chance> roll c
-- > 21
-- > Chance> roll c
@tmhedberg
tmhedberg / Counter.hs
Last active December 17, 2015 11:49
Self-incrementing counters based on mutable references
{-# LANGUAGE FunctionalDependencies #-}
-- | Self-incrementing counters based on mutable references
module Counter where
import Control.Monad.ST
import Data.IORef
import Data.STRef
@tmhedberg
tmhedberg / commodities.hs
Last active December 17, 2015 08:19
Convert PMA commodity/variety spreadsheet from CSV to JSON
#!/usr/bin/runhaskell
{-
- Convert PMA commodity/variety spreadsheet from CSV to JSON
-
- Requires HP + aeson, cassava, utf8-string
-}
import Control.Applicative
@tmhedberg
tmhedberg / Modular.hs
Created April 21, 2013 20:11
Modular addition with statically inferred modulus
{-# LANGUAGE DataKinds
, GeneralizedNewtypeDeriving
, KindSignatures
, ScopedTypeVariables
#-}
-- | Modular addition with statically inferred modulus
--
-- Usage example (with @DataKinds@ extension enabled):
--