Skip to content

Instantly share code, notes, and snippets.

@MiniXC
Created October 21, 2017 09:33
Show Gist options
  • Save MiniXC/1d4ee9119825e1791fe51cbe863c199a to your computer and use it in GitHub Desktop.
Save MiniXC/1d4ee9119825e1791fe51cbe863c199a to your computer and use it in GitHub Desktop.
-- Informatics 1 - Functional Programming
-- Tutorial 3
--
-- Week 5 - Due: 19-20 Oct.
module Tutorial3 where
import Data.Char
import Test.QuickCheck
-- 1. Map
-- a.
uppers :: String -> String
uppers = map toUpper
-- b.
doubles :: [Int] -> [Int]
doubles = map (*2)
-- c.
penceToPounds :: [Int] -> [Float]
penceToPounds = map ((/100) . realToFrac)
-- d.
uppersComp :: String -> String
uppersComp str = [toUpper c | c <- str]
prop_uppers :: String -> Bool
prop_uppers str = uppers str == uppersComp str
-- 2. Filter
-- a.
alphas :: String -> String
alphas = filter isAlpha
-- b.
rmChar :: Char -> String -> String
rmChar c = filter (/= c)
-- c.
above :: Int -> [Int] -> [Int]
above i = filter (> i)
-- d.
unequals :: [(Int,Int)] -> [(Int,Int)]
unequals = filter (uncurry (/=))
-- e.
rmCharComp :: Char -> String -> String
rmCharComp c str = [x | x <- str, x /= c]
prop_rmChar :: Char -> String -> Bool
prop_rmChar c str = rmChar c str == rmCharComp c str
-- 3. Comprehensions vs. map & filter
-- a.
upperChars :: String -> String
upperChars s = map toUpper (filter isAlpha s)
upperCharsComp :: String -> String
upperCharsComp s = [toUpper c | c <- s, isAlpha c]
prop_upperChars :: String -> Bool
prop_upperChars s = upperChars s == upperCharsComp s
-- b.
largeDoubles :: [Int] -> [Int]
largeDoubles xs = map (*2) (filter (>3) xs)
largeDoublesComp :: [Int] -> [Int]
largeDoublesComp xs = [2 * x | x <- xs, x > 3]
prop_largeDoubles :: [Int] -> Bool
prop_largeDoubles xs = largeDoubles xs == largeDoublesComp xs
-- c.
reverseEven :: [String] -> [String]
reverseEven strs = map reverse (filter (even . length) strs)
reverseEvenComp :: [String] -> [String]
reverseEvenComp strs = [reverse s | s <- strs, even (length s)]
prop_reverseEven :: [String] -> Bool
prop_reverseEven strs = reverseEven strs == reverseEvenComp strs
-- 4. Foldr
-- a.
productRec :: [Int] -> Int
productRec [] = 1
productRec (x:xs) = x * productRec xs
productFold :: [Int] -> Int
productFold = foldr (*) 1
prop_product :: [Int] -> Bool
prop_product xs = productRec xs == productFold xs
-- b.
andRec :: [Bool] -> Bool
andRec [] = True
andRec (x:xs) = x && andRec xs
andAll xs = all(==True) xs
andFold :: [Bool] -> Bool
andFold = foldr (&&) True
prop_and :: [Bool] -> Bool
prop_and xs = andRec xs == andFold xs
-- c.
concatRec :: [[a]] -> [a]
concatRec [] = []
concatRec (x:xs) = x ++ concatRec xs
concatFold :: [[a]] -> [a]
concatFold = foldr (++) []
prop_concat :: [String] -> Bool
prop_concat strs = concatRec strs == concatFold strs
-- d.
rmCharsRec :: String -> String -> String
rmCharsRec [] ys = ys
rmCharsRec (x:xs) ys = rmCharsRec xs (rmChar x ys)
rmCharsFold :: String -> String -> String
rmCharsFold xs ys = foldr rmChar ys xs
prop_rmChars :: String -> String -> Bool
prop_rmChars chars str = rmCharsRec chars str == rmCharsFold chars str
type Matrix = [[Int]]
-- 5
-- a.
uniform :: [Int] -> Bool
uniform [] = False
uniform xs = all(==head xs) xs
-- b.
valid :: Matrix -> Bool
valid xs = uniform (map length xs) && not (null (head xs))
-- 6.
-- a
-- 18
-- b
zipWithComp f xs ys = [ f x y | (x, y) <- zip xs ys]
-- c
zipWithOrd f xs ys = map (uncurry f) (zip xs ys)
-- 7.
addM :: Matrix -> Matrix -> Matrix
addM m n = zipWith (zipWith (+)) m n
-- 8.
dot :: [Int] -> [Int] -> Int
dot u v = zipWith (*) u v
--timesM :: Matrix -> Matrix -> Matrix
--timesM m n = zipWith (zipWith dot) (transpose m) n
-- Optional material
-- 9.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment