diff --git a/caesar-cipher.hs b/caesar-cipher.hs new file mode 100644 index 0000000..dfda531 --- /dev/null +++ b/caesar-cipher.hs @@ -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 diff --git a/church-numerals.hs b/church-numerals.hs new file mode 100644 index 0000000..59633da --- /dev/null +++ b/church-numerals.hs @@ -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 diff --git a/hw3.hs b/hw3.hs new file mode 100644 index 0000000..82d2b1b --- /dev/null +++ b/hw3.hs @@ -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 diff --git a/hw4.hs b/hw4.hs new file mode 100644 index 0000000..b55908a --- /dev/null +++ b/hw4.hs @@ -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] diff --git a/hw5.hs b/hw5.hs new file mode 100644 index 0000000..c337aca --- /dev/null +++ b/hw5.hs @@ -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 diff --git a/hw6.hs b/hw6.hs new file mode 100644 index 0000000..fc59f1e --- /dev/null +++ b/hw6.hs @@ -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 diff --git a/lab1.hs b/lab1.hs new file mode 100644 index 0000000..57c19fe --- /dev/null +++ b/lab1.hs @@ -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) diff --git a/lab2.hs b/lab2.hs new file mode 100644 index 0000000..2e20a40 --- /dev/null +++ b/lab2.hs @@ -0,0 +1,194 @@ +module Lab2 where + +------------------------------------------------------------------------------------------------------------------------------ +-- Lab 2: Validating Credit Card Numbers +------------------------------------------------------------------------------------------------------------------------------ + +-- =================================== +-- Ex. 0 +-- =================================== + +toDigits :: Integer -> [Integer] +toDigits 0 = [0] +toDigits x = toDigits (x `div` 10) ++ [x `mod` 10] + +-- toDigits n +-- | n < 0 = error "less than zero" +-- | n < 10 = [n] +-- | otherwise = toDigits (n `div` 10) ++ [n `mod` 10] + +-- =================================== +-- Ex. 1 +-- =================================== + +toDigitsRev :: Integer -> [Integer] +toDigitsRev x = reverse (toDigits x) + +-- toDigitsRev n = reverse . toDigits $ n + +-- =================================== +-- Ex. 2 +-- =================================== + +doubleSecond :: [Integer] -> [Integer] +doubleSecond (x:y:xs) = x : (y * 2) : doubleSecond (xs) +doubleSecond a = a + +-- doubleSecond [] = [] +-- doubleSecond (x:xs) = x : (2 * head xs) : doubleSecond (tail xs) + +-- doubleSecond xs = zipWith ($) (cycle [id,(*2)]) + +-- doubleSecond ns = zipWith (\x y -> if even x then y * 2 else y) [1 .. length ns + 1] ns + +-- =================================== +-- Ex. 3 +-- =================================== + +sumDigits :: [Integer] -> Integer +sumDigits [] = 0 +sumDigits (x:xs) = sum (toDigits x) + sumDigits xs + +-- sumDigits ns = foldr (\x y -> y + (sum . toDigits $ x)) 0 ns + +-- =================================== +-- Ex. 4 +-- =================================== + +isValid :: Integer -> Bool +isValid 0 = False +isValid x = 0 == (sumDigits (doubleSecond (toDigitsRev x)) `mod` 10) + +-- isValid n = (sumDigits . doubleSecond . toDigitsRev $ n) `mod` 10 == 0 + +-- =================================== +-- Ex. 5 +-- =================================== + +numValid :: [Integer] -> Integer +numValid xs = sum . map (\_ -> 1) $ filter isValid xs + + +creditcards :: [Integer] +creditcards = [ 4716347184862961, + 4532899082537349, + 4485429517622493, + 4320635998241421, + 4929778869082405, + 5256283618614517, + 5507514403575522, + 5191806267524120, + 5396452857080331, + 5567798501168013, + 6011798764103720, + 6011970953092861, + 6011486447384806, + 6011337752144550, + 6011442159205994, + 4916188093226163, + 4916699537435624, + 4024607115319476, + 4556945538735693, + 4532818294886666, + 5349308918130507, + 5156469512589415, + 5210896944802939, + 5442782486960998, + 5385907818416901, + 6011920409800508, + 6011978316213975, + 6011221666280064, + 6011285399268094, + 6011111757787451, + 4024007106747875, + 4916148692391990, + 4916918116659358, + 4024007109091313, + 4716815014741522, + 5370975221279675, + 5586822747605880, + 5446122675080587, + 5361718970369004, + 5543878863367027, + 6011996932510178, + 6011475323876084, + 6011358905586117, + 6011672107152563, + 6011660634944997, + 4532917110736356, + 4485548499291791, + 4532098581822262, + 4018626753711468, + 4454290525773941, + 5593710059099297, + 5275213041261476, + 5244162726358685, + 5583726743957726, + 5108718020905086, + 6011887079002610, + 6011119104045333, + 6011296087222376, + 6011183539053619, + 6011067418196187, + 4532462702719400, + 4420029044272063, + 4716494048062261, + 4916853817750471, + 4327554795485824, + 5138477489321723, + 5452898762612993, + 5246310677063212, + 5211257116158320, + 5230793016257272, + 6011265295282522, + 6011034443437754, + 6011582769987164, + 6011821695998586, + 6011420220198992, + 4716625186530516, + 4485290399115271, + 4556449305907296, + 4532036228186543, + 4916950537496300, + 5188481717181072, + 5535021441100707, + 5331217916806887, + 5212754109160056, + 5580039541241472, + 6011450326200252, + 6011141461689343, + 6011886911067144, + 6011835735645726, + 6011063209139742, + 379517444387209, + 377250784667541, + 347171902952673, + 379852678889749, + 345449316207827, + 349968440887576, + 347727987370269, + 370147776002793, + 374465794689268, + 340860752032008, + 349569393937707, + 379610201376008, + 346590844560212, + 376638943222680, + 378753384029375, + 348159548355291, + 345714137642682, + 347556554119626, + 370919740116903, + 375059255910682, + 373129538038460, + 346734548488728, + 370697814213115, + 377968192654740, + 379127496780069, + 375213257576161, + 379055805946370, + 345835454524671, + 377851536227201, + 345763240913232 + ] + diff --git a/qsort.hs b/qsort.hs new file mode 100644 index 0000000..96e3303 --- /dev/null +++ b/qsort.hs @@ -0,0 +1,4 @@ +qsort = [] +qsort (x : xs) = qsort smaller ++ [x] ++ qsort larger + where smaller [a | a <- xs, a <= x] + larger [b | b <- xs, b > a]