Skip to content

Instantly share code, notes, and snippets.

@harpocrates
harpocrates / Memoize.hs
Created February 26, 2016 04:16
Memoizing (safe use of unsafePerformIO)
module Memoize (memoize) where
import Data.Map as M
import Data.IORef
import System.IO.Unsafe
-- | Memoize a function. The use of unsafePerformIO is fine since referential transparency is maintained.
-- `memoize f` will return a new function which behaves the same as `f` but memoizes its results everytime
-- it is called with an argument it hasn't seen yet.
memoize :: Ord a => (a -> b) -> (a -> b)
module PriorityQueue (
PQ,
size, priority, peek,
singleton, branch, push,
pop
) where
{- Priority queue with ordered keys `k` and values `v`. A branch stores the
minimum key in its subtrees as well as the value associated (for fast peek)
as well as its size (for easily maintaining balance). -}
module ImperativeQuickSort (quicksort) where
import Prelude hiding (take,drop,length,tail,init)
import Data.Vector (modify,Vector)
import Data.Vector.Generic.Mutable hiding (modify)
-- | Imperative quicksort with O(log n) auxilary space (on top of returned vector)
quicksort :: Ord a => Vector a -> Vector a
quicksort = modify qsort'
where
{-# LANGUAGE TypeFamilies #-}
-- Subsitute type `x` for type `y` in type `a`
-- Works only for type constructors having up to 4 type arguments...
type family Substitute x y a where
Substitute x y x = y
Substitute x y (k a b c d) = k (Substitute x y a) (Substitute x y b) (Substitute x y c) (Substitute x y d)
Substitute x y (k a b c) = k (Substitute x y a) (Substitute x y b) (Substitute x y c)
Substitute x y (k a b) = k (Substitute x y a) (Substitute x y b)
Substitute x y (k a) = k (Substitute x y a)
Control.Arrow
=============
"compose/arr" forall f g .
(arr f) . (arr g) = arr (f . g)
"first/arr" forall f .
first (arr f) = arr (first f)
"second/arr" forall f .
second (arr f) = arr (second f)
"product/arr" forall f g .
arr f *** arr g = arr (f *** g)
import scala.language.experimental.macros
import scala.reflect.macros.blackbox.Context
object Macro
// inspect how scala has desugared your code
def traceSugar[T](t: T): T = macro impl
def impl(c: Context)(t: c.Tree): c.Tree = { println(t); t }
@harpocrates
harpocrates / subtype-examples.hs
Last active May 18, 2021 04:57
Build (single) inheritance up from scratch in Haskell
{-# LANGUAGE TypeFamilies, TypeOperators, FlexibleContexts,
TypeSynonymInstances, FlexibleInstances, MultiParamTypeClasses
#-}
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe (maybeToList)
import Data.Ratio (numerator, denominator)
import Data.IORef (IORef)
import SubType
@harpocrates
harpocrates / Undefined.hs
Last active March 23, 2017 04:43
Do the unthinkable: catch errors in pure code
-- Not for the weak at heart.
-- If you use this, you should feel bad about yourself!
import Control.Exception
import System.IO.Unsafe
-- Given a value, check if it has anything undefined in WNHF. If so, return the exception message, else the value
fromError :: a -> Either String a
fromError x = unsafePerformIO $ catch (Right x <$ evaluate x) getMessage
where

In a recent discussion I had with a friend about Haskell and Scala, they brought up the fact that they sometimes miss Scala's partial functions. In Scala, these are a trait of their own somewhat different from what Haskellers usually understand by "partial function". In particular, you can check if a value is in the domain of the partial function before applying it to the function.

Interestingly enough, partial functions are also supported in Haskell - they just happen to be hidden away in some more obscure parts of the base library. What follows is my attempt to make a module that brings this functionality out and makes it more accessible. Since this is meant to be a literate Haskell source, let's start with some preamble.

{-# LANGUAGE TypeOperators, NoImplicitPrelude, GeneralizedNewtypeDeriving #-}

module Data.Function.Partial where

import Prelude hiding (id, (.), ($))
{-# LANGUAGE GADTs, PolyKinds, DataKinds, TypeOperators, FlexibleInstances, FlexibleContexts #-}
import Data.Foldable
import Text.PrettyPrint.HughesPJClass
data Nat = Z | S Nat
type N0 = Z
type N1 = S N0
type N2 = S N1