Skip to content

Instantly share code, notes, and snippets.

@fmap
fmap / gist:ece133d4452b10add990
Last active August 29, 2015 14:04
Construct vectors of length LEQ some bound.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE Rank2Types #-}
-- Construct vectors of length LEQ some bound. :-)
data Natural where
Zero :: Natural
Succ :: Natural -> Natural
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH (ExpQ, Exp(LamE, VarE, TupE), Pat(VarP), newName)
tuple :: Int -> ExpQ
tuple n = do
x <- newName "x"
return $ LamE [VarP x] (TupE . replicate n $ VarE x)
-- $(tuple 3) "fnord" == ("fnord","fnord","fnord")
import Control.Monad (liftM2)
import Control.Arrow (Arrow((&&&)), (>>>), (<<<))
(>>|) :: Arrow a => a b c -> a c d -> a b (c,d)
(>>|) = liftM2 (<<<) (&&&) (>>>)
allOf :: Enum a => Bounded a => [a]
allOf = [minBound..maxBound]
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RankNTypes #-}
data N = Z | S N
data Vector :: * -> N -> * where
Nil :: Vector a 'Z
import Prelude hiding (foldr, filter)
import Data.Maybe (fromJust, isJust)
import Data.Foldable (Foldable(foldr))
import Data.HashMap.Lazy (HashMap, singleton, unionWith, foldrWithKey)
import Data.Hashable (Hashable(..))
import Data.Monoid (Monoid(mappend, mempty))
import Data.Vector (Vector, find, cons, filter)
-- sniEquivalence describes a surjective but non-injective relation between
-- {b, a}.
---
Four Postures of Death
Sidney Keyes
August 1941
---
I
DEATH AND THE MAIDEN
#!/usr/bin/env runhaskell
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
-- # [Task:](http://functionaljobs.com/jobs/8678-haskell-developer-at-zalora)
a (m,n) | m==0 = n+1
| m>0 && n==0 = a(m-1,1)
| m>0 && n>0 = a(m-1,a(m,n-1))
k c n d | n == 0 = c*d
| n == 1 = c^d
| d == 0 = 1
| otherwise = k c (n-1) $ k c n (d-1)
g = (!!63) $ iterate (\ n -> k 3 n 3) 4
DATE="$1"
yymmdd() {
date -d"$DATE" '+%Y%m%d'
};
cat <<EOF | sed 's/^ *//'
BEGIN:VCALENDAR
VERSION:2.0
PRODID:-//Hack and Tell//NONSGML v1.0//EN
BEGIN:VEVENT