Skip to content

Instantly share code, notes, and snippets.

@andrewthad
andrewthad / gadt_vs_polymorphic_recursion.hs
Created April 7, 2018 15:46
Replacing polymorphic recursion with a GADT for 2-3 trees
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
module GadtVsPolymorphicRecursion where
import Data.Kind (Type)
-- This example is based on the Tree type given on page 3
@andrewthad
andrewthad / prime.hs
Created March 8, 2018 15:48
AKS Primality Test in GHC Haskell
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
module Prime
( prime
) where
import GHC.Int
import GHC.Exts
prime :: Int -> Bool
@andrewthad
andrewthad / fix_ghc_symlinks
Created February 9, 2018 15:45
Fix GHC Symlinks
@andrewthad
andrewthad / instructions_elasticsearch.markdown
Created February 6, 2018 20:07
ElasticSearch Setup Instructions

Install essential utilities:

sudo apt install vim tmux tree

Install the public signing key:

wget -qO - https://artifacts.elastic.co/GPG-KEY-elasticsearch | sudo apt-key add -

Install apt-transport-https:

@andrewthad
andrewthad / arrow_shrink.hs
Last active January 30, 2018 15:29
Arrow-Like Shrinking
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall #-}
module BugCrush where
@andrewthad
andrewthad / idris_record.idr
Created January 28, 2018 01:34
Records in Idris
module IdrisRecord
import Data.Vect
import Data.List
%default total
data Value : Bool -> Type -> Type where
Present : {t : Type} -> t -> Value True t
Absent : {t : Type} -> Value False t
@andrewthad
andrewthad / dependent_pokemon.idr
Created January 16, 2018 14:39
Prove that a pokemon's types are distinct
module DependentPokemon
data Poketype = Fire | Water | Grass
data Different : Poketype -> Poketype -> Type where
DifferentFireWater : Different Fire Water
DifferentFireGrass : Different Fire Grass
DifferentWaterFire : Different Water Fire
DifferentWaterGrass : Different Water Grass
DifferentGrassFire : Different Grass Fire
@andrewthad
andrewthad / folds.hs
Last active January 3, 2018 16:19
Fold with a monoidal accumulator
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Applicative
import Data.Monoid
import Control.Monad.Trans.State.Lazy (State,runState,get,put)
-- Lazy in the monoidal accumulator. Monoidal accumulation
-- happens from left to right.
foldlMapA :: forall g b a m. (Foldable g, Monoid b, Applicative m) => (a -> m b) -> g a -> m b
foldlMapA f = foldr f' (pure mempty)
@andrewthad
andrewthad / matrix_to_html.hs
Created November 20, 2017 19:23
Matrix to HTML
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
import qualified Data.Matrix as M
import qualified Text.Blaze.Html5 as H
import Text.Blaze.Html (Html,toHtml)
import Text.Blaze.Renderer.Pretty (renderMarkup)
main :: IO ()
main = putStrLn (renderMarkup (matrixToHtml myMatrix))
@andrewthad
andrewthad / unboxed_lambda.hs
Created November 16, 2017 16:39
The potential impact of functions with unboxed arguments
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_GHC -O2 #-}
import Control.Monad
import Data.Primitive
import Control.Monad.ST
import Criterion.Main