Skip to content

Instantly share code, notes, and snippets.

@ion1
ion1 / google-android-apps.md
Last active February 4, 2016 19:30
Google apps for your non-Nexus phone
@ion1
ion1 / e.md
Last active August 29, 2015 14:27
Trying to derive an equation for e from df(x)/dx = f(x)

Trying to derive an equation for e from df(x)/dx = f(x)

Exists f.

df(x)/dx = f(x)

lim{y→0} (f(x+y) − f(x)) / y = f(x)

lim{y→0} f(x+y) − f(x) − y f(x) = 0

@ion1
ion1 / sample-set-weights
Created August 10, 2015 16:56
Sample an item from an ordered set with the proportional weights 1, 2, 3, …
Sample an item from an ordered set with the proportional weights 1, 2, 3, …:
tri x = (x·(x+1))/2
invtri x = (√(8·x+1)−1)/2
r ← uniform [0,1)
n = number of items
index = floor (invtri (r · tri n))
@ion1
ion1 / passwd-reset
Last active August 29, 2015 14:24
passwd-reset
#!/bin/sh
set -eu
umask 077
for username; do
password="$(pwgen -n 16 1)"
printf '%s:%s\n' "$username" "$password" | chpasswd
chage -E "$(( ($(date '+%s') / 86400) + 2 ))" "$username"
passwd -e "$username"
@ion1
ion1 / MTLSTIO.hs
Last active August 29, 2015 14:23
MonadState and MonadReader instances for ST and IO
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UnboxedTuples #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-- | 'MonadState' and 'MonadReader' instances for 'ST' and 'IO'
module MTLSTIO (State' (..)) where
@ion1
ion1 / LatinSquare.hs
Created June 15, 2015 17:52
Latin squares
import Data.Monoid
import Data.Set (Set, (\\))
import qualified Data.Set as Set
type Square a = [Row a]
type Row a = [a]
main :: IO ()
main = mapM_ (putStrLn . unlines) (genSquare (Set.fromList "abc")) where
@ion1
ion1 / MiniLens.hs
Last active June 16, 2019 06:00
Mini lens
{-# LANGUAGE RankNTypes #-}
import Control.Applicative
import Data.Functor.Identity
import Data.Monoid
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
_1 :: Lens (a,b) (a',b) a a'
@ion1
ion1 / ListOperations.hs
Last active August 29, 2015 14:22
Miscellaneous list operations
import Data.List
-- | What to do when taking the middle of a list where the number of elements
-- around the middle window is odd. Either return the requested number of
-- elements or grow the window by one (making the number of elements on either
-- side of the window the same). The latter is convenient for computing the
-- median of a list (@median = mean . takeMiddle GrowWindow 1@).
data WindowBehavior = KeepWindow -- ^ @splitMiddle KeepWindow 1 "abcd" = ("a", "b", "cd")@
| GrowWindow -- ^ @splitMiddle GrowWindow 1 "abcd" = ("a", "bc", "d")@
deriving (Eq, Ord, Bounded, Show, Read)
@ion1
ion1 / Foo.hs
Created May 13, 2015 22:08
If ($) was left-associative
-- If ($) was left-associative
foo = bar -- an expression worth its own line
$ baz -- ditto, as the first parameter to bar
$ quuz -- ditto, as the second parameter to bar
@ion1
ion1 / BoxMuller.hs
Last active August 29, 2015 14:20
Box-Muller for MonadRandom
module BoxMuller
( getNormal
, getNormal'
, getNormals
, getNormals'
) where
import Control.Monad ((<$!>))
import Control.Monad.Random