Skip to content

Instantly share code, notes, and snippets.

View rampion's full-sized avatar

Noah Luck Easterly rampion

  • Mercury Technologies
View GitHub Profile
@rampion
rampion / FunctorFun.hs
Last active August 29, 2015 14:06
Streams, Lists, and Tries with Fix and Compose
{-# LANGUAGE FlexibleContexts #-} -- {{{
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-} -- }}}
module FunctorFun where
-- {{{
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
module SO25311781 where
import Data.Generics.Uniplate.Direct
data Expression a where
I :: Int -> Expression Int
@rampion
rampion / SO25210743.hs
Created August 10, 2014 03:03
Solution for "Bicategories in Haskell", replacing dependency on `Arr` with dependency on `Composable`
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
@rampion
rampion / SO25210743.hs
Last active August 29, 2015 14:05
Solution for [Bicategories in Haskell](http://stackoverflow.com/questions/25210743/bicategories-in-haskell) on StackOverflow
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
@rampion
rampion / Unique.hs
Last active August 29, 2015 14:02
Indexed Monad for uniquely consumed values
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DeriveFunctor #-}
module Unique (
@rampion
rampion / 0-scenes.md
Last active January 4, 2016 18:39
Gonking One Shot

Scenes:

The City Gate:

  • The caravan gets ready to leave in the square next to the city gate, giving the characters a chance to make themselves known to each other.

  • Criers call out news.

  • It's the 20th anniversary of Dysus's departure for Thurb, and his widow,
@rampion
rampion / DocumentWindow.nib
Last active June 9, 2017 09:33
How to make TextEdit.app fullscreen

Why Are Haskell Package Versions Numbers?

#Semantic Versioning is great.

Let me start by answering a different question. Why do Haskell packages have versions?

  • For support: when users report problems, knowing which version they're using allows the package support team to trace the problem through the package code accurately.
  • For compatibility:
@rampion
rampion / LazyLength.hs
Last active May 24, 2021 12:34
The Lazy Length monoid allows you to compare two lists by length without calculating the full length of both lists (unless they are of equal length). Though `lazyLength :: [a] -> LazyLength` is O(n), two `LazyLength` values for lists of length n and m may be compared in time O(min(log n, log m)).
{-# LANGUAGE BangPatterns #-}
module LazyLength (
LazyLength(),
fromLazyLength,
toLazyLength,
lazyLength,
-- QuickCheck properties
prop_invariant,
prop_invertible,
prop_addition,
module Main where
import Criterion.Main
import qualified Data.List.Ordered as O
import qualified Data.List as L
import qualified Data.Set as S
import qualified Data.IntSet as IS
repeatsTail, orderedIntersect, listIntersect, setIntersect :: [Integer] -> [Integer] -> [Integer] -> [Integer]
intsetIntersect :: [Int] -> [Int] -> [Int] -> [Int]