Skip to content

Commit

Permalink
first checking
Browse files Browse the repository at this point in the history
  • Loading branch information
mzero committed Sep 29, 2011
0 parents commit fe5ef0b
Show file tree
Hide file tree
Showing 11 changed files with 1,500 additions and 0 deletions.
7 changes: 7 additions & 0 deletions Makefile
@@ -0,0 +1,7 @@
all: slides.html

slides.html: slides.md
pandoc --offline -s -t slidy -i -o $@ $<

clean:
-rm -f slides.html
104 changes: 104 additions & 0 deletions Part1.hs
@@ -0,0 +1,104 @@
{- To explore this file:
Run ghci from the shell:
& ghci
GHCi, version 7.0.2: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude>
Load up this file:
Prelude> :load Part1.hs
[1 of 1] Compiling Part1 ( Part1.hs, interpreted )
Ok, modules loaded: Part1.
*Part1>
Try stuff:
*Part1> 2 + 2
4
*Part1> putStr $ poem
occasional clouds
one gets a rest
from moon-viewing
*Part1> main
from moon-viewing
occasional clouds
one gets a rest
-}

module Part1 where

import Data.Char (toUpper)
import Data.List (sort)

main = readFile "poem" >>= putStr . process

process t = unlines (sort (lines t))

process' t = (unlines . sort . lines) t
process'' = unlines . sort . lines


poem = "breakfast apple pie\n\
\lunch banana yoghurt for\n\
\dinner cantaloupe\n"

-- show the poem in ghci with:
-- > putStr $ poem

sortLines = unlines . sort . lines
reverseLines = unlines . reverse . lines
firstTwoLines = unlines . take 2 . lines

-- try applying these to the poem in ghci:
-- > putStr $ sortLines poem
-- > putStr $ reverseLines poem

byLines f = unlines . f . lines

sortLines' = byLines sort
reverseLines' = byLines reverse
firstTwoLines' = byLines (take 2)


indent :: String -> String
indent s = " " ++ s

-- This is commented out, because it won't compile:
-- indentLines = byLines indent

indentEachLine :: String -> String
indentEachLine = byLines (map indent)

eachLine :: (String -> String) -> String -> String
eachLine f = unlines . map f . lines

indentEachLine' :: String -> String
indentEachLine' = eachLine indent


yell :: String -> String
yell s = map toUpper s ++ "!!!"

yellEachLine :: String -> String
yellEachLine = eachLine yell


eachWord :: (String -> String) -> String -> String
eachWord f = unwords . map f . words

yellEachWord :: String -> String
yellEachWord = eachWord yell

eachWordOnEachLine :: (String -> String) -> String -> String
eachWordOnEachLine f = eachLine (eachWord f)

yellEachWordOnEachLine :: String -> String
yellEachWordOnEachLine = eachWordOnEachLine yell
30 changes: 30 additions & 0 deletions Part2a.hs
@@ -0,0 +1,30 @@
module Part2a where

data List α = Nil
| Cons α (List α)
deriving Show -- makes printing out results possible

empty = Nil
oneWord = Cons "apple" Nil
twoWords = Cons "banana" (Cons "cantaloupe" Nil)

mystery1 = Cons "pear" empty
mystery2 = Cons "peach" oneWord
mystery3 = Cons "pineapple" mystery3
-- mystery4 = Cons 42 (Cons "apple" Nil) -- won't compile

dropOne :: List a -> List a
dropOne (Cons first rest) = rest
dropOne Nil = Nil

justOne :: List a -> List a
justOne (Cons a _) = Cons a Nil
justOne Nil = Nil

firstOne :: List a -> a
firstOne (Cons a _) = a
firstOne Nil = error "O Noes!"

maybeFirstOne :: a -> List a -> a
maybeFirstOne def (Cons first rest) = first
maybeFirstOne def Nil = def
29 changes: 29 additions & 0 deletions Part2b.hs
@@ -0,0 +1,29 @@
module Part2b where

-- data [a] = [] | a : [a] -- already built in
-- infixr 5 : -- already built in

empty = []
oneWord = "apple" : []
twoWords = "banana" : "cantaloupe" : []

mystery1 = "pear" : empty
mystery2 = "peach" : oneWord
mystery3 = "pineapple" : mystery3
-- mystery4 = 42 : "apple" : [] -- won't compile

dropOne :: [a] -> [a]
dropOne (first:rest) = rest
dropOne [] = []

justOne :: [a] -> [a]
justOne (a:_) = a:[]
justOne [] = []

firstOne :: [a] -> a
firstOne (a:_) = a
firstOne [] = error "O Noes!"

maybeFirstOne :: a -> [a] -> a
maybeFirstOne def (first:rest) = first
maybeFirstOne def [] = def
33 changes: 33 additions & 0 deletions Part2c.hs
@@ -0,0 +1,33 @@
module Part2c where

-- data [a] = [] | a : [a] -- already built in
-- infixr 5 : -- already built in

empty = []
oneWord = ["apple"] -- syntatic sugar
twoWords = ["banana", "cantaloupe"] -- two teaspoons full

mystery1 = "pear" : empty
mystery2 = "peach" : oneWord
mystery3 = "pineapple" : mystery3
-- mystery4 = [42, "apple"] -- sweet, but still won't compile

dropOne :: [a] -> [a]
dropOne (first:rest) = rest
dropOne [] = []

justOne :: [a] -> [a] -- don't confuse these "[a]"s
justOne (a:_) = [a] -- with this "[a]"
justOne [] = []

firstOne :: [a] -> a -- normally called 'head'
firstOne (a:_) = a
firstOne [] = error "O Noes!"

maybeFirstOne :: a -> [a] -> a
maybeFirstOne def (first:rest) = first
maybeFirstOne def [] = def

firstOne' :: [a] -> Maybe a
firstOne' (a:_) = Just a
firstOne' [] = Nothing
24 changes: 24 additions & 0 deletions Part2d.hs
@@ -0,0 +1,24 @@
module Part2d where


findAfterStar :: String -> Maybe Char
findAfterStar (c:d:r) =
if c == '*' then Just d
else findAfterStar (d:r)
findAfterStar _ = Nothing



findAfterChar :: Char -> String -> Maybe Char
findAfterChar m (c:d:r) =
if c == m then Just d
else findAfterChar m (d:r)
findAfterChar _ _ = Nothing



findAfterElem :: Eq a => a -> [a] -> Maybe a
findAfterElem m (c:d:r) =
if c == m then Just d
else findAfterElem m (d:r)
findAfterElem _ _ = Nothing
25 changes: 25 additions & 0 deletions Part3.hs
@@ -0,0 +1,25 @@
module Part3 where

runLengthEncode :: Eq a => [a] -> [(a, Int)]
runLengthEncode [] = []
runLengthEncode (x:xs) = nextGroup x 1 xs
where
nextGroup e n [] = [(e, n)]
nextGroup e n (y:ys)
| e == y = nextGroup e (n + 1) ys
| otherwise = (e, n) : nextGroup y 1 ys


rlePropLengthPreserved :: [Int] -> Bool
rlePropLengthPreserved as = length as == (sum $ map snd $ runLengthEncode as)

rlePropDupesCollapsed :: Int -> Bool
rlePropDupesCollapsed n
| m == 0 = runLengthEncode "" == []
| otherwise = runLengthEncode (replicate m 'x') == [('x', m)]
where m = n `mod` 100

rlePropRoundTrip :: [Int] -> Bool
rlePropRoundTrip ns = runLengthEncode xs == is
where is = zip ['a'..] $ map (\n -> n `mod` 100 + 1) ns
xs = concatMap (\(i,n) -> replicate n i) is
3 changes: 3 additions & 0 deletions poem
@@ -0,0 +1,3 @@
occasional clouds
one gets a rest
from moon-viewing
24 changes: 24 additions & 0 deletions rle.cpp
@@ -0,0 +1,24 @@
#include <list>
#include <utility>
using namespace std;

template<typename T>
list<pair<T,int> > runLengthEncode(const list<T>& as) {
list<pair<T, int> > runs;
if (!empty(as)) {
list<T>::const_iterator it = as.begin();
T elem = *it;
int count = 0;

for (; it != as.end(); it++) {
if (elem != *it) {
runs.push_back(make_pair(elem, count));
elem = *it;
count = 0;
}
count += 1;
}
runs.push_back(make_pair(elem, count));
}
return runs;
}

0 comments on commit fe5ef0b

Please sign in to comment.