Skip to content

Instantly share code, notes, and snippets.

@m2ym
m2ym / varnumbers.pl
Last active August 29, 2015 14:04
varnumbers/2 in B-Prolog
% unnumber_vars/2 is not working correctly in B-Prolog 8.1. Here is
% an alternative implementation of unnumber_vars/2 named varnumbers/2,
% which is compatible with SWI-Prolog's varnumbers library.
max_varnumber('$VAR'(N), Max) =>
Max = N.
max_varnumber(Term, Max) =>
Term =.. [_ | Args0],
Args @= [Arg : Arg0 in Args0, [Arg], max_varnumber(Arg0, Arg)],
Max is max([-1 | Args]).
@m2ym
m2ym / Huffman.hs
Created January 15, 2014 16:45
Huffman coding in Haskell for learning
import Data.Bits (setBit)
import Data.Word (Word8)
import Data.Tuple (swap)
import Data.Maybe (fromJust)
import qualified Data.Map as M
import qualified Data.Heap as H
import qualified Data.ByteString as B
import Control.Arrow (second, (&&&))
type OccurrenceTable a = M.Map a Int
@m2ym
m2ym / a.hs
Created January 12, 2014 12:44
Data.Heap.MaxPrioHeap can't type fmap
import qualified Data.Heap as H
h :: H.MaxPrioHeap Int Char
h = H.fromList [(1, 'a')]
h' :: H.MaxPrioHeap Int String
h' = fmap (:[]) h
main :: IO ()
main = do
@m2ym
m2ym / mvn-ramdisk.sh
Created October 16, 2013 02:21
Maven Ramdisk
#!/bin/sh
set -ex
DIR="$HOME/var/tmp"
SIZE=1024m
mkdir -p "$DIR"
sudo umount "$DIR"
sudo mount -t tmpfs -o size=$SIZE tmpfs "$DIR"
@m2ym
m2ym / gist:6534131
Created September 12, 2013 07:46
for (...) { var a = ...; f(function() { return a; }); } みたいな危険なキャプチャを検出するルール
dangerous_capture(Ident) :-
for_body(ForBody),
stmt_child(ForBody, stmt, VarStmt),
statement(VarStmt, var, Var, _, _),
var(Var, Decls),
var_decls(Decls, D),
var_decl(D, VarName, _, _, _),
stmt_desc(ForBody, expr, FuncExpr),
@m2ym
m2ym / Map.hx
Created August 27, 2013 10:30
Immutable Map implementation using Red-Black Tree in Haxe
private enum Color { Red; Black; }
private enum TreeT<T> {
Leaf;
Node(color: Color, left: TreeT<T>, label: T, right: TreeT<T>);
}
private class TreeF {
private function new() {}
import Data.Function (on)
import Data.List (sortBy)
import Control.Monad (forM_)
solve :: Int -> Int -> [Int] -> Int
solve e r vs = solve' 0 (sortBy (flip compare `on` snd) (zip [0..] vs)) []
where
solve' gain [] as = gain
solve' gain ((i,v):vs) as = solve' (gain + v * a) vs ((i,a,b):as)
where b = maximum (0:[b' + a - (j-i) * r | (j,a,b') <- as, i < j])
@m2ym
m2ym / dpkg-readme.sh
Last active December 10, 2015 17:28
dpkg-readme helps you to quickly open README.Debian of given package
#!/bin/sh
: ${PAGER:=cat}
package="$1"
readme="$(dpkg-query -L "$package" 2> /dev/null | grep README.Debian | head -n 1)"
if [ -s "$readme" ]; then
case "$readme" in
*.gz) gunzip -qc "$readme" | $PAGER;;
*) $PAGER "$readme";;
@m2ym
m2ym / rb-tree.lisp
Created December 9, 2012 14:56
Red Black Tree using optima in Common Lisp
(defpackage :rb-tree
(:use :cl :optima)
(:export #:rb-empty
#:rb-member
#:rb-insert))
(in-package :rb-tree)
(defstruct (leaf (:constructor leaf)))
(defstruct (node (:constructor node (color left label right)))
color left label right)
@m2ym
m2ym / SplayTree.hs
Created December 7, 2012 10:34
Toy Splay Tree in Haskell
import Data.Maybe (isJust)
data Tree a = Leaf | Node (Tree a) a (Tree a)
replace :: a -> Tree a -> Tree a
replace a Leaf = Node Leaf a Leaf
replace a (Node l _ r) = Node l a r
rotateR :: Tree a -> Tree a
rotateR (Node (Node x a y) b z) = Node x a (Node y b z)