Skip to content

Instantly share code, notes, and snippets.

@andrewthad
andrewthad / quantified_mptc.hs
Created September 20, 2018 23:42
Quantified Constraints with a Multi-Param Type Class
{-# language QuantifiedConstraints #-}
{-# language MultiParamTypeClasses #-}
{-# language UndecidableInstances #-}
module QuantifiedMptc where
import Data.Functor.Identity
import Data.Char
class Bar x where
@andrewthad
andrewthad / persisted_allocator.txt
Created September 18, 2018 14:26
Haskell Persisted Allocator Thoughts
Borrow ideas from LMDB. LMDB starts with two pages at the very beginning of the memory-mapped file.
Writing to either page indicates that a transaction has completed. In LMDB, each of these pages
has pointers to two b-trees. One of those trees is a free page list (there is no garbage collection).
The other is the root page of the database.
In building a database with haskell, my first goal is to implement this approach to transactions.
It should be its own library. The interface is:
-- A wrapper around int, just an increasing id.
data Transaction
@andrewthad
andrewthad / unlifted_sneakiness.hs
Last active August 17, 2018 12:52
Using unlifted types where lifted types are expected
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeInType #-}
import Data.Primitive
import Data.Primitive.UnliftedArray
import GHC.Types
import GHC.Exts
main :: IO ()
@andrewthad
andrewthad / Fancy.hs
Created June 24, 2018 20:53
Optimized Fixed-Length Vectors
{-# language BangPatterns #-}
{-# language KindSignatures #-}
{-# language LambdaCase #-}
{-# language DataKinds #-}
{-# language TypeFamilies #-}
{-# language GADTs #-}
{-# language ScopedTypeVariables #-}
module Fancy
( Vec(..)
@andrewthad
andrewthad / typeclass_method_equality.hs
Last active June 11, 2018 13:20
Typeclass dictionary equality test
{-# language BangPatterns #-}
{-# language UnboxedTuples #-}
{-# language TypeInType #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# language TypeApplications #-}
{-# language MagicHash #-}
import Data.Primitive
import GHC.Exts
import Data.Int
@andrewthad
andrewthad / strict_fold_map.hs
Last active June 8, 2018 13:12
Strict foldMap benchmark
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -O2 #-}
import Gauge
import Data.Foldable
import qualified Data.Set as S
foldMap' :: (Monoid m, Foldable f) => (a -> m) -> f a -> m
foldMap' f = foldl' (\ !acc a -> acc <> f a) mempty
data Nat = Z | S Nat
data TwoGt :: Nat -> Nat -> Type
TwoGtNil :: Gt ('S ('S n)) 'Z
TwoGtStep :: Gt n m -> Gt (S n) (S m)
data Diet :: Nat -> Type where
DietNil :: Diet 'Z
DietCons :: forall n m. Gte n m -> TwoGt m p -> Diet p -> Diet n
@andrewthad
andrewthad / unordered_containers_bench.csv
Created April 22, 2018 00:04
Unordered Containers Benchmark Status Quo against Primitive Array
We can make this file beautiful and searchable if this error is corrected: It looks like row 5 should actually have 14 columns, instead of 7. in line 4.
Name,Delta Mean,Old Mean,Old MeanLB,Old MeanUB,Old Stddev,Old StddevLB,Old StddevUB,Prim Mean,Prim MeanLB,Prim MeanUB,Prim Stddev,Prim StddevLB,Prim StddevUB
Map/lookup/String,-4.01192348635389E-05,0.001107993,0.0011069501,0.0011114222,5.47692473171267E-06,1.72855719234861E-06,1.12967788815314E-05,0.0011481122,0.0011473614,0.0011493945,3.32637535250392E-06,2.21407833355931E-06,5.44070448461763E-06
Map/lookup/ByteString,-1.52147821814251E-05,0.0008407479,0.0008324034,0.0008518746,3.30073523385299E-05,2.45527477038763E-05,4.01806140048334E-05,0.0008559627,0.0008541067,0.0008595795,9.03425130781163E-06,3.37468012405672E-06,1.54984235507102E-05
Map/lookup-miss/String,-1.14117550992136E-05,0.0012808972,0.0012799409,0.0012838897,5.38377062979146E-06,1.99408700405153E-06,1.06894875663886E-05,0.001292309,0.0012898045,0.0012998284,1.48660575328273E-05,2.44746115033326E-06,2.85817455067306E-05
Map/lookup-miss/ByteString,-1.05578692152534E-05,0.0010407583,0.0010352113,0.0010526097,2.71087156628233E-05,1.51385029747848E-
@andrewthad
andrewthad / constraint_backpack.bkp
Created April 16, 2018 20:04
Constraint Backpack
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
unit example where
@andrewthad
andrewthad / finger_tree_gadt.hs
Created April 7, 2018 18:37
Finger trees without polymorphic recursion
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
module FingerTree where
import Data.Kind (Type)
data Nat = Z | S Nat
data Digit n a