Skip to content

Instantly share code, notes, and snippets.

@cheecheeo
cheecheeo / markovFun.hs
Created July 12, 2014 00:28
Fun with Markov Chains in Haskell.
import NLP.Tokenize
import Data.MarkovChain
import System.Random
text = "The protagonist of Hamlet is Prince Hamlet of Denmark, son of the recently deceased King Hamlet, and nephew of King Claudius, his father's brother and successor. Claudius hastily married King Hamlet's widow, Gertrude, Hamlet's mother. Denmark has a long-standing feud with neighbouring Norway, and an invasion led by the Norwegian prince, Fortinbras, is expected.\nThe play opens on a cold winter midnight on \"platform before the castle\" of Elsinore, the Danish royal castle. The sentry Francisco is keeping trusty guard when two figures appear in the darkness. Bernardo, a sentry come to replace Francisco, calls out, \"Who's there?\" Francisco replies, \"Nay, answer me. Stand and unfold yourself.\" Friendly identity proven, Francisco retires to bed. En route, Francisco encounters Horatio and Marcellus who are coming to visit Bernardo. Bernardo and Marcellus discuss the recent appearance of a curious intruder which they describe as a \"dread
module Roll where
{--
Okay, shoot! Fell asleep while composing a problem; sorry for the delay!
So, this one is an easy one. We get a little Forth'y'. This is from P19
of the P99 problem-set.
--}
module Data.Deque where
{--
The following sets of problems over the next few days get their inspiration
from some of the problems from the P99, or Ninety-Nine Prolog Problems
published by Werner Hett.
Create a traversable data type, let’s call it Deque a (‘Deque’ meaning:
‘double-ended queue’) such that the operation
@cheecheeo
cheecheeo / downloads.ini
Created July 2, 2014 01:57
Share Anything
(************************************)
(* Never edit options files when *)
(* the daemon is running *)
(************************************)
(* SECTION : Main *)
(* Main options *)
(************************************)
@cheecheeo
cheecheeo / search.hs
Created June 25, 2014 23:28
Queens, Sudoku, List monad
import Control.Monad
import Data.List.HT
import Data.List
import System.Random.Shuffle
import Control.Monad.Random.Class
import qualified Data.Set as S
bitStringsN1s :: Int -> Int -> [[Int]]
bitStringsN1s n maxLength = do
bitString <- replicateM maxLength [0, 1]
module MatchingSub where
import Data.List
-- | Submit these to MissingH
dropWhilePrefixList :: ([a] -> Bool) -> [a] -> [a]
dropWhilePrefixList = go []
where go :: [a] -> ([a] -> Bool) -> [a] -> [a]
go _ _ [] = []
go acc p rest@(x : xs) = if (not . p) acc then rest else go (acc ++ [x]) p xs
module NGrams where
import Data.Char
import Data.List
-- | Given a String, compute all the n letters n-grams of its words (excluding all non alphanums characters).
-- Word separations matter.
--
-- Example:
--
-- >>> lettersNGrams 3 "Hello, world!"
@cheecheeo
cheecheeo / maybe.rb
Last active August 29, 2015 14:02
Maybe in Ruby
nothing = lambda {|default, junk| default}
just = lambda {|x| lambda{|junk, f| f[x]}}
maybe = lambda {|default, f, m| m[default, f]}
show_maybe = lambda {|m| maybe['nothing', lambda {|x| "just[#{x}]"}, m]}
plus_2 = lambda {|x| maybe[nothing, lambda {|x| just[x + 2]}, x]}
# >>> x = nothing
# >>> y = just[5]
# >>> maybe[false, lambda {|x| true}, y]
# true
# >>> maybe[false, lambda {|x| true}, x]
@cheecheeo
cheecheeo / either.py
Created June 4, 2014 21:11
Either in Python
"""
Either in Python.
"""
def left(x):
"""
Haskell: Left 5
Python: left(5)
"""
swap (x,y) = (y,x)
alternate xs ys = Prelude.concat (zipWith (\x y -> [x, y]) xs ys)
-- | Swap then interleave the swapped elements
-- >>> interleaveSwapped [(1,2),(2,3)]
-- [(1,2),(2,1),(2,3),(3,2)]
interleaveSwapped = alternate <*> map swap