-
Notifications
You must be signed in to change notification settings - Fork 0
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
Wouter Willaert
committed
Nov 16, 2014
0 parents
commit d0c5883
Showing
9 changed files
with
578 additions
and
0 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,38 @@ | ||
module caesar where | ||
|
||
let2int :: Char -> Int | ||
let2int c = ord c - ord 'a' | ||
|
||
int2let :: Int -> Char | ||
int2let n = chr (ord 'a' + n) | ||
|
||
shift :: Int -> Char -> Char | ||
shift n c | isLower c = int2let ((let2int c + n) `mod` 26) | ||
| otherwise = c | ||
|
||
encode :: Int -> String -> String | ||
encode n xs = [shift n x | x <- xs] | ||
|
||
table :: [Float] | ||
table = [ 8.2, 1.5, 2.8, 4.3, 12.7, 2.2, 2.0, 6.1, 7.0, 0.2, 0.8, 4.0, 2.4, | ||
6.7, 7.5, 1.9, 0.1, 6.0, 6.3, 9.1, 2.8, 1.0, 2.4, 0.2, 2.0, 0.1 ] | ||
|
||
percent :: Int -> Int -> Float | ||
percent n m = (fromInt n / fromInt m) * 100 | ||
|
||
freqs :: String -> [Float] | ||
freqs xs = [percent (count x xs) n | x <- ['a'..'z']] | ||
where n = lowers xs | ||
|
||
chisqr :: [Float] -> [Float] -> Float | ||
chisqroses = sum [((o − e) ^ 2) / e | (o, e) <- ziposes] | ||
|
||
rotate :: Int -> [a] -> [a] | ||
rotate n xs = drop n xs ++ take n xs | ||
|
||
crack :: String → String | ||
crack xs = encode (-factor) xs | ||
where | ||
factor = head (positions (minimum chitable) chitable) | ||
chitable = [chisqr (rotate n table') table | n <- [0..25]] | ||
table' = freqs xs |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,10 @@ | ||
type Church = (a -> a) -> a -> a | ||
|
||
curchToInteger x = x (+1) 0 | ||
curchToInteger two = (\s z -> s (s z)) (+1) 0 | ||
|
||
curchToString x = x ('*':) "" | ||
curchToString two = (\s z -> s (s z)) ('*':) "" | ||
|
||
add x y = \s z -> x s (y s z) | ||
mul x y = \s z -> x (y s) z |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,76 @@ | ||
-- e1 | ||
|
||
-- safetail xs = if null xs then [] else tail xs | ||
|
||
-- safetail [] = [] | ||
-- safetail (_ : xs) = xs | ||
|
||
-- safetail xs | ||
-- | null xs = [] | ||
-- | otherwise = tail xs | ||
|
||
-- safetail [] = [] | ||
-- safetail xs = tail xs | ||
|
||
safetail | ||
= \ xs -> | ||
case xs of | ||
[] -> [] | ||
(_ : xs) -> xs | ||
|
||
-- e2 | ||
|
||
-- import Prelude hiding ((||)) | ||
|
||
-- False || False = False | ||
-- _ || _ = True | ||
|
||
-- False || b = b | ||
-- True || _ = True | ||
|
||
-- b || c | ||
-- | b == c = b | ||
-- | otherwise = True | ||
|
||
-- b || False = b | ||
-- _ || True = True | ||
|
||
-- b || c | ||
-- | b == c = c | ||
-- | otherwise = True | ||
|
||
-- b || True = b | ||
-- _ || True = True | ||
|
||
False || False = False | ||
False || True = True | ||
True || False = True | ||
True || True = True | ||
|
||
-- e3 | ||
|
||
-- import Prelude hiding ((&&)) | ||
|
||
-- True && True = True | ||
-- _ && _ = False | ||
|
||
-- a && b = if a then if b then True else False else False | ||
-- a && b = if a then b else False | ||
-- a && b = if b then a else False | ||
|
||
-- a && b = if not (a) then not (b) else True | ||
-- a && b = if a then b | ||
-- a && b = if a then if b then False else True else False | ||
|
||
|
||
-- e4 | ||
|
||
-- mult x y z = \ x -> (\ y -> (\ z -> x * y * z)) | ||
-- mult = \ x -> (\ y -> (\ z -> x * y * x)) | ||
-- mult = \ x -> (x * \ y -> (y * \ z -> z)) | ||
-- mult = ((((\x -> \y) -> \z) -> x * y) * z) | ||
|
||
-- e8 | ||
|
||
funct :: Int -> [a] -> [a] | ||
funct x xs = take (x + 1) xs ++ drop x xs |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,64 @@ | ||
import Data.Char (ord, chr) | ||
import Data.Ix (inRange) | ||
|
||
-- e1 | ||
|
||
rep n a = [a | _ <- [1..n]] | ||
|
||
-- e2 | ||
|
||
pyths n | ||
= [(x, y, z) | x <- [1..n], y <- [1..n], z <- [1..n], | ||
x ^ 2 + y ^ 2 == z ^ 2] | ||
|
||
-- e3 | ||
|
||
factors n = | ||
[x | x <- [1..n], n `mod` x == 0] | ||
|
||
perfects n = [x | x <- [1..n], isPerfect x] | ||
where isPerfect num = sum (init (factors num)) == num | ||
|
||
-- e4 | ||
|
||
-- [(x, y) | x <- [1, 2, 3], y <- [4, 5, 6]] | ||
|
||
-- concat [[(x,y) | y <- [4,5,6]] | x <- [1,2,3]] | ||
|
||
-- e5 | ||
|
||
find k t = [v | (k', v) <- t, k == k'] | ||
-- find 1 (zip [1,2,3] [0..3]) | ||
|
||
positions x xs = find x (zip xs [0..n]) | ||
where n = length xs - 1 | ||
|
||
-- e6 | ||
|
||
scalarproduct xs ys = sum [x * y | (x, y) <- xs `zip` ys] | ||
|
||
-- e7 | ||
|
||
let2int :: Char -> Char -> Int | ||
let2int base char = ord char - ord base | ||
|
||
int2let :: Char -> Int -> Char | ||
int2let base int = chr (ord base + int) | ||
|
||
shift :: Int -> Char -> Char | ||
shift n c | ||
| inRange ('a', 'z') c = int2let 'a' (((let2int 'a' c) + n) `mod` 26) | ||
| inRange ('A', 'Z') c = int2let 'A' (((let2int 'A' c) + n) `mod` 26) | ||
| otherwise = c | ||
|
||
encode :: Int -> String -> String | ||
encode n xs = [shift n x | x <- xs] | ||
|
||
-- e12 | ||
|
||
riffle xs ys = concat [[x, y] | (x, y) <- xs `zip` ys] | ||
|
||
-- e13 | ||
|
||
divides x y = x `mod` y == 0 | ||
divisors x = [d | d <- [1..x], x `divides` d] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,75 @@ | ||
-- import Prelude hiding (and) | ||
-- import Prelude hiding (concat) | ||
-- import Prelude hiding (replicate) | ||
-- import Prelude hiding (elem) | ||
|
||
-- e0 | ||
|
||
-- m # 0 = 1 | ||
-- m # n = m * m # (n - 1) | ||
|
||
-- m # 0 = 1 | ||
-- m # n = m * (#) m (n - 1) | ||
|
||
-- e4 | ||
|
||
-- and [] = True | ||
-- and (b : bs) = b && and bs | ||
|
||
-- and [] = True | ||
-- and (b : bs) | ||
-- | b = and bs | ||
-- | otherwise = False | ||
|
||
-- and [] = True | ||
-- and (b : bs) | ||
-- | b == False = False | ||
-- | otherwise = and bs | ||
|
||
-- and [] = True | ||
-- and (b : bs) = and bs && b | ||
|
||
-- e5 | ||
|
||
-- concat :: [[a]] -> [a] | ||
-- concat [] = [] | ||
-- concat (xs : xss) = xs ++ concat xss | ||
|
||
-- e6 | ||
|
||
-- replicate :: Int -> a -> [a] | ||
-- replicate 0 _ = [] | ||
-- replicate n x = x : replicate (n - 1) x | ||
|
||
-- e7 | ||
|
||
-- (#) :: [a] -> Int -> a | ||
-- (x : _) # 0 = x | ||
-- (_ : xs) # n = xs # (n - 1) | ||
|
||
-- e8 | ||
|
||
-- elem :: Eq a => a -> [a] -> Bool | ||
-- elem _ [] = False | ||
-- elem x (y : ys) | ||
-- | x == y = True | ||
-- | otherwise = elem x ys | ||
|
||
-- e9 | ||
|
||
merge :: Ord a => [a] -> [a] -> [a] | ||
merge [] ys = ys | ||
merge xs [] = xs | ||
merge (x : xs) (y : ys) | ||
= if x <= y then x : merge xs (y : ys) else y : merge (x : xs) ys | ||
|
||
-- e10 | ||
|
||
halve :: [a] -> ([a], [a]) | ||
halve xs = splitAt (length xs `div` 2) xs | ||
|
||
msort :: Ord a => [a] -> [a] | ||
msort [] = [] | ||
msort [x] = [x] | ||
msort xs = merge (msort ys) (msort zs) | ||
where (ys, zs) = halve xs |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,102 @@ | ||
-- import Prelude hiding (all) | ||
-- import Prelude hiding (any) | ||
-- import Prelude hiding (takeWhile) | ||
-- import Prelude hiding (dropWhile) | ||
-- import Prelude hiding (map) | ||
|
||
-- e1 | ||
|
||
-- all :: (a -> Bool) -> [a] -> Bool | ||
-- all p xs = and (map p xs) | ||
-- all p = and . map p | ||
-- all p = not . any (not . p) | ||
-- all p xs = foldl (&&) True (map p xs) | ||
-- all p = foldr (&&) True . map p | ||
|
||
-- e2 | ||
|
||
-- any :: (a -> Bool) -> [a] -> Bool | ||
-- any p = or . map p | ||
-- any p xs = length (filter p xs) > 0 | ||
-- any p = not . null . dropWhile (not . p) | ||
-- any p xs = not (all (\x -> not (p x)) xs) | ||
-- any p xs = foldr (\x acc -> (p x) || acc) False xs | ||
-- any p xs = foldr (||) True (map p xs) | ||
|
||
-- e3 | ||
|
||
-- takeWhile :: (a -> Bool) -> [a] -> [a] | ||
-- takeWhile _ [] = [] | ||
-- takeWhile p (x : xs) | ||
-- | p x = x : takeWhile p xs | ||
-- | otherwise = [] | ||
|
||
-- e4 | ||
|
||
-- dropWhile :: (a -> Bool) -> [a] -> [a] | ||
-- dropWhile _ [] = [] | ||
-- dropWhile p (x : xs) | ||
-- | p x = dropWhile p xs | ||
-- | otherwise = x : xs | ||
|
||
-- e5 | ||
|
||
-- map :: (a -> b) -> [a] -> [b] | ||
-- map f = foldl (\ xs x -> xs ++ [f x]) [] | ||
|
||
-- e6 | ||
|
||
-- filter :: (a -> Bool) -> [a] -> [a] | ||
-- filter p = foldr (\ x xs -> if p x then x : xs else xs) [] | ||
|
||
-- e7 | ||
|
||
dec2int :: [Integer] -> Integer | ||
dec2int = foldl (\ x y -> 10 * x + y) 0 | ||
|
||
-- e8 | ||
|
||
-- compose :: [a -> a] -> (a -> a) | ||
-- compose = foldr (.) id | ||
-- sumsqreven = compose [sum, map (^ 2), filter even] | ||
|
||
-- e9 | ||
|
||
-- curry :: ((a, b) -> c) -> a -> b -> c | ||
-- curry f = \ x y -> f (x, y) | ||
|
||
-- e10 | ||
|
||
-- uncurry :: (a -> b -> c) -> (a, b) -> c | ||
-- uncurry f = \ (x, y) -> f x y | ||
|
||
-- e11 | ||
|
||
unfold :: (b -> Bool) -> (b -> a) -> (b -> b) -> b -> [a] | ||
unfold p h t x | ||
| p x = [] | ||
| otherwise = h x : unfold p h t (t x) | ||
|
||
type Bit = Int | ||
|
||
int2bin :: Int -> [Bit] | ||
-- int2bin 0 = [] | ||
-- int2bin n = n `mod` 2 : int2bin (n `div` 2) | ||
int2bin = unfold (== 0) (`mod` 2) (`div` 2) | ||
|
||
chop8 :: [Bit] -> [[Bit]] | ||
-- chop8 [] = [] | ||
-- chop8 bits = take 8 bits : chop8 (drop 8 bits) | ||
chop8 = unfold null (take 8) (drop 8) | ||
|
||
-- e12 | ||
|
||
-- map :: (a -> b) -> [a] -> [b] | ||
-- map f = unfold null (f . head) tail | ||
|
||
-- map (+1) [1,2,3] | ||
|
||
-- e13 | ||
|
||
-- iterate :: (a -> a) -> a -> [a] | ||
-- iterate f = unfold (const False) id f |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,15 @@ | ||
e10 (x, y) = [x, y] | ||
|
||
-- e11 :: (Char, Bool) | ||
e11 = ('\a', True) | ||
|
||
-- e12 :: [(Char, Int)] | ||
e12 = [('a', 1)] | ||
|
||
-- e13 :: Int -> Int -> Int | ||
e13 x y = x + y * y | ||
|
||
-- e14 :: ([Char], [Float]) | ||
|
||
-- e15 :: [a] -> [b] -> (a, b) | ||
e15 xs ys = (head xs, head ys) |
Oops, something went wrong.