Skip to content

Instantly share code, notes, and snippets.

@fatho
fatho / uuprint.sh
Created October 19, 2016 14:19
Script to automatically send files for printing to the UU print service.
#!/bin/bash
STUDENT_ADDRESS="<student>@students.uu.nl"
PRINT_ADDRESS="print@uu.nl"
( printf "From: $STUDENT_ADDRESS\n"
printf "To: $PRINT_ADDRESS\n"
printf "Subject: print job\n\n"
for file in "$@"
do
@fatho
fatho / FalloutHacker.hs
Created November 18, 2015 17:08
An application to quickly determine the right password for RobCo terminals in "Fallout: New Vegas" (and possibly other installments of the series, too).
{-# LANGUAGE LambdaCase #-}
module Main where
import Control.Applicative
import Control.Monad
import Data.Foldable (toList)
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Text.Read
import Text.Printf (printf)
@fatho
fatho / IntExercise.agda
Last active August 29, 2015 14:14
A collection of proof exercises about integers I created and solved for fun.
{- Given the defintion of the natural numbers ℕ from the standard library ... -}
open import Level using () renaming (zero to ℓ₀)
open import Data.Nat using (ℕ) renaming (_+_ to _+ℕ_; suc to nsuc; zero to nzero)
import Relation.Binary as B
import Relation.Binary.Core as B
import Relation.Binary.PropositionalEquality as P
open import Function using (flip)
open P using (_≡_)
@fatho
fatho / RevCompConduit.hs
Created January 27, 2015 18:29
Haskell solution to the reverse-complement (http://benchmarksgame.alioth.debian.org/u32/performance.php?test=revcomp) language game benchmark using conduit.
{-# LANGUAGE LambdaCase, OverloadedStrings, RankNTypes, MultiWayIf, BangPatterns #-}
import Control.Monad
import Control.Monad.IO.Class
import qualified Data.Char as Char
import Data.Word
import Data.Monoid
import qualified Foreign.Storable as S
import Foreign.C.String
import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector.Unboxed.Mutable as VUM
@fatho
fatho / D100.hs
Created December 7, 2014 17:36
Haskell DSL for evaluating the following math problem: You are given a 100 sided die. After you roll once, you can choose to either get paid the dollar amount of that roll OR pay one dollar for one more roll. What is the expected value of the game?(There is no limit on the number of rolls.)
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TemplateHaskell, BangPatterns, EmptyDataDecls #-}
module D100 where
import Control.Applicative
import Control.Arrow
import Control.Lens
import Control.Monad.State
import Control.Monad.Random
import Control.Monad.Free
@fatho
fatho / Maze.hs
Created November 1, 2014 23:20
Lets play a game...
data Path e (i :: Nat) (j :: Nat) where
PNil :: Path e i i
PNext :: e i j -> Path e j k -> Path e i k
infixr 9 ~:
(~:) :: e i j -> Path e j k -> Path e i k
(~:) = PNext
data E (i :: Nat) (j :: Nat) where
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
#!/bin/sh
# set environment for x session
source ~/.zsh.d/environment.zsh
# set wallpaper
~/bin/wallpaperd.sh ~/config-files/wallpaper &
source /etc/X11/xinit/xinitrc.d/30-dbus
@fatho
fatho / Threads.hs
Created September 15, 2014 13:56
Cooperative interleaved threading in haskell.
{-# LANGUAGE DeriveFunctor, TemplateHaskell, GeneralizedNewtypeDeriving, FlexibleContexts #-}
module Threads where
import Control.Applicative
import Control.Arrow
import Control.Monad
import Control.Monad.Except
import Control.Monad.State.Class
import Control.Monad.Trans
import Control.Monad.Trans.Free
@fatho
fatho / ConduitListT.hs
Last active August 29, 2015 14:06
ListT using conduit
import Control.Applicative
import Control.Monad
import Data.Conduit
import qualified Data.Conduit.List as CL
newtype ListT m a = ListT { runListT :: Producer m a }
instance (Monad m) => Functor (ListT m) where
fmap f (ListT l) = ListT (l $= CL.map f)