Add more work
This commit is contained in:
parent
71e4388478
commit
0151948fb9
5 changed files with 574 additions and 0 deletions
428
Assignment2/SolutionPA2.hs
Normal file
428
Assignment2/SolutionPA2.hs
Normal file
|
@ -0,0 +1,428 @@
|
|||
--DO NOT MODIFY--
|
||||
module SolutionPA2 where
|
||||
import Prelude hiding (mod,double,square,sum,reverse)
|
||||
|
||||
-- command to run the test:
|
||||
-- ghc /home/cs/cs420/autograder/PA2/Test.hs -e main
|
||||
|
||||
-- colored printing enabled
|
||||
coloredPrint = True
|
||||
--DO NOT MODIFY--
|
||||
|
||||
--Write your solution below--
|
||||
--Write your solutions after Function Type, the sentence after that is just a placeholder
|
||||
|
||||
-- Part A: Basic Haskell Prelude
|
||||
-- In this part of the assignment you will create your own prelude libraries
|
||||
|
||||
--myMod
|
||||
--Write your own modulus function that is calculate the remainder
|
||||
--
|
||||
-- myMod 12 4
|
||||
-- >>> 0
|
||||
--
|
||||
-- myMod 12 5
|
||||
-- >>> 2
|
||||
--
|
||||
-- myMod 12 12
|
||||
-- >>> 0
|
||||
|
||||
myMod :: Int -> Int -> Int
|
||||
-- Idea: Use integer division, multiply back out, and find the
|
||||
-- difference.
|
||||
myMod x y = x - (y * div x y)
|
||||
|
||||
|
||||
--toDigit
|
||||
--The function is to convert a positive number to a list of number, if it is negative or 0 then return empty list
|
||||
--
|
||||
-- toDigit 13
|
||||
-- >>> [1,3]
|
||||
--
|
||||
-- toDigit 0
|
||||
-- >>> []
|
||||
--
|
||||
-- toDigit (-13)
|
||||
-- >>> []
|
||||
|
||||
toDigit :: Int -> [Int]
|
||||
toDigit n | n <= 0 = []
|
||||
-- Resursive step.
|
||||
-- Call toDigit with the number divided by 10, and append that
|
||||
-- to the list with just the last digit (mod)
|
||||
| otherwise = toDigit (div n 10) ++ [myMod n 10]
|
||||
|
||||
|
||||
--reverseList (10 pts)
|
||||
--The function is used to reverse a list of arbitrary type
|
||||
-- reverseList ['a','b','c']
|
||||
-- >>> "cba"
|
||||
-- reverseList [1,2,3,4]
|
||||
-- >>> [4,3,2,1]
|
||||
-- reverseList "racecar"
|
||||
-- >>> "racecar"
|
||||
|
||||
reverseList :: [a] -> [a]
|
||||
-- Base case.
|
||||
reverseList [] = []
|
||||
-- Recursive step, use pattern matching to get last part of list,
|
||||
-- reverse it, and then append the first element at the end.
|
||||
reverseList (x:xs) = reverseList xs ++ [x]
|
||||
|
||||
--sumList
|
||||
--The function is used to get the sum of a list of number
|
||||
-- sumList [1,2,3,4]
|
||||
-- >>> 10
|
||||
--
|
||||
-- sumList [1,2,3,(-2)]
|
||||
-- >>> 4
|
||||
--
|
||||
-- sumList []
|
||||
-- >>> 0
|
||||
|
||||
sumList :: [Int] -> Int
|
||||
-- Base case.
|
||||
sumList [] = 0
|
||||
-- Recursive step, use pattern matching to split list into first
|
||||
-- element, and add it to the sum of everything else.
|
||||
sumList (x:xs) = sumList xs + x
|
||||
|
||||
|
||||
|
||||
--toDigitRev is used to reverse toDigit list
|
||||
--
|
||||
-- toDigitRev 34
|
||||
-- >>> [4,3]
|
||||
--
|
||||
-- toDigitRev 53
|
||||
-- >>> [3,5]
|
||||
--
|
||||
-- toDigitRev 10
|
||||
-- >>> [0,1]
|
||||
|
||||
toDigitRev :: Int -> [Int]
|
||||
-- Just use reverseList and toDigit.
|
||||
toDigitRev n = reverseList (toDigit n)
|
||||
|
||||
-- Part B: Folding Function
|
||||
-- In this part of the problems, you have to use foldr. Every function will be check for the foldr unless specified otherwise such as doubleEveryOther
|
||||
-- Without using foldr, your function will be mark 0 even if the output is correct
|
||||
|
||||
--myDouble
|
||||
--Write your own double function that is using foldr
|
||||
--without using fold it will be 0 even the output is right
|
||||
--
|
||||
-- myDouble 2
|
||||
-- >>> 4
|
||||
--
|
||||
-- myDouble 4
|
||||
-- >>> 8
|
||||
--
|
||||
-- myDouble 0
|
||||
-- >>> 0
|
||||
|
||||
myDouble :: Int -> Int
|
||||
-- We can sum the list of 2 of the parameter.
|
||||
myDouble n = foldr (+) 0 [n,n]
|
||||
|
||||
|
||||
-- doubleEveryOther will double the value of every other digit from left to right, beginning with the second digit
|
||||
-- NOTE: You do not have to use foldr for this particular function.
|
||||
--
|
||||
-- doubleEveryOther [1,2,3,4]
|
||||
-- >>> [1,4,3,8]
|
||||
--
|
||||
-- doubleEveryOther [1,2,3]
|
||||
-- >>> [1,4,3]
|
||||
|
||||
doubleEveryOther :: [Int] -> [Int]
|
||||
-- I don't like this code. It doesn't feel very Haskell.
|
||||
-- Use list comprehension to get all the indices of xs.
|
||||
-- Then if the index is odd, double the value.
|
||||
-- This will double every other starting with the 2nd digit.
|
||||
doubleEveryOther xs = [if myMod i 2 == 0 then xs !! i else myDouble (xs!!i) | i <- [0..(length xs) - 1]]
|
||||
|
||||
--mySquare
|
||||
--Write your own my square function using foldr
|
||||
--
|
||||
-- mySquare 0
|
||||
-- >>> 0
|
||||
--
|
||||
-- mySquare 1
|
||||
-- >>> 1
|
||||
--
|
||||
-- mySquare (-5)
|
||||
-- >>> 25
|
||||
|
||||
mySquare :: Int -> Int
|
||||
-- Use foldr with a list of [n,n] and *.
|
||||
mySquare n = foldr (*) 1 [n,n]
|
||||
|
||||
|
||||
-- Write sqSum function such that sqSum [x1, ... , xn] should return (x1^2 + ... + xn^2)
|
||||
--
|
||||
-- >>> sqSum []
|
||||
-- 0
|
||||
--
|
||||
-- >>> sqSum [1,2,3,4]
|
||||
-- 30
|
||||
--
|
||||
-- >>> sqSum [(-1), (-2), (-3), (-4)]
|
||||
-- 30
|
||||
|
||||
sqSum :: [Int] -> Int
|
||||
-- We can use foldr and list comprehension to add evertything in a new
|
||||
-- list where mySquare was applied (map).
|
||||
sqSum ns = foldr (+) 0 [mySquare x | x <- ns]
|
||||
|
||||
|
||||
--sumDigits is to add the sum of all the number inside the list that is already turn into single digit (10 pts)
|
||||
--
|
||||
-- sumDigits [1,10,12] which is 1 + 1 + 0 + 1 + 2
|
||||
-- >>> 5
|
||||
--
|
||||
-- sumDigits [23,32,(-45)] which is 2 + 3 + 3 + 2 + 0
|
||||
-- >>> 10
|
||||
|
||||
sumDigits :: [Int] -> Int
|
||||
-- We can use a double list comprehension combined with foldr.
|
||||
-- Take every n from ns.
|
||||
-- Find the digits, and then get every digit x.
|
||||
-- Combine it all into a list and apply foldr.
|
||||
sumDigits ns = foldr (+) 0 [x | n <- ns, x <- toDigit n]
|
||||
|
||||
-- sepConcat will concatenate the defined seperator to a list of string. If the list is empty despite the defined seperator return empty string.
|
||||
--
|
||||
-- sepConcat ", " []
|
||||
-- >>> ""
|
||||
--
|
||||
-- sepConcat ", " ["foo", "bar", "baz"]
|
||||
-- >>> "foo, bar, baz"
|
||||
--
|
||||
-- sepConcat "#" ["a","b","c","d","e"]
|
||||
-- >>> "a#b#c#d#e"
|
||||
|
||||
sepConcat :: String -> [String] -> String
|
||||
-- Base case 1, when the list is empty.
|
||||
sepConcat _ [] = []
|
||||
-- Pattern match a list with only one element.
|
||||
-- When we reach this case, we don't add separator to the end.
|
||||
sepConcat _ (t:[]) = t
|
||||
-- On the recursive case, we patten match the first element and the rest
|
||||
-- of the list. We then concat it with the separator and recurse.
|
||||
sepConcat sep (t:ts) = t ++ sep ++ sepConcat sep ts
|
||||
|
||||
|
||||
-- Part C: Credit Card problem
|
||||
|
||||
-- Using the above written functions, create a validate function will decide if a number is legal to use as credit card using Luhn algorithm
|
||||
-- Luhn algorithm:
|
||||
-- 1) Double the value of every other digit from right to left, beginning with the second to last digit.
|
||||
-- 2) Add the digits of the results of Step 1 to the remaining digits in the credit card number.
|
||||
-- 3) If the result mod 10 is equal to 0, the number is valid. If the result mod 10 is not equal to 0, the validation fails.
|
||||
-- source: https://www.ibm.com/docs/en/order-management-sw/9.3.0?topic=cpms-handling-credit-cards
|
||||
--To validate the credit card using this website
|
||||
--https://dnschecker.org/credit-card-validator.php
|
||||
--To generate using same website above or this
|
||||
--https://www.lambdatest.com/free-online-tools/credit-card-number-generator
|
||||
|
||||
--
|
||||
-- validate 4723304884813
|
||||
-- >>> True
|
||||
--
|
||||
-- validate 4012888888881881
|
||||
-- >>> True
|
||||
--
|
||||
-- validate 4012888888881882
|
||||
-- >>> False
|
||||
|
||||
validate :: Int -> Bool
|
||||
-- Application of all our functions.
|
||||
validate n = myMod (sumDigits (doubleEveryOther (toDigitRev n))) 10 == 0
|
||||
|
||||
|
||||
-- PartD: Sorts algorithms
|
||||
|
||||
-- splitHalf will split a list of number to 2 half
|
||||
--
|
||||
-- splitHalf [1,2,3,4,5]
|
||||
-- >>> ([1,2],[3,4,5])
|
||||
--
|
||||
-- splitHalf [1,2,3,4,5,6]
|
||||
-- >>> ([1,2,3],[4,5,6])
|
||||
|
||||
-- helper function
|
||||
-- Base case.
|
||||
mySplit 0 p = p
|
||||
-- mySplit will collect from the 2nd ordered pair, and move n
|
||||
-- elements into the first list.
|
||||
-- This is done recursively by decrementing n on each call, and moving
|
||||
-- one y into left of the ordered pair.
|
||||
mySplit n (xs,(y:ys)) = mySplit (n-1) (xs++[y], ys)
|
||||
|
||||
splitHalf :: [a] -> ([a], [a])
|
||||
-- splitHalf simply calls mySplit with n = length / 2.
|
||||
splitHalf xs = mySplit (div l 2) ([], xs)
|
||||
where l = length xs
|
||||
|
||||
|
||||
-- mergeList will merge 2 list that is sorted by the key value b
|
||||
--
|
||||
-- mergeList [("dat",1),("scott",5)] [("dan",3),("scott",4)]
|
||||
-- >>> [("dat",1),("dan",3),("scott",4),("scott",5)]
|
||||
--
|
||||
-- mergeList [("danny",35),("scott",5)] [("dan",3),("scott",4)]
|
||||
-- >>> [("dan",3),("scott",4),("danny",35),("scott",5)]
|
||||
|
||||
|
||||
mergeList :: Ord b => [(a, b)] -> [(a, b)] -> [(a, b)]
|
||||
-- Base case.
|
||||
-- If one of the lists is empty, then we can just return one of the
|
||||
-- lists.
|
||||
mergeList [] pys = pys
|
||||
mergeList pxs [] = pxs
|
||||
|
||||
-- Lots of pattern matching.
|
||||
-- axs, ays = "All xs"
|
||||
-- x,y = Sorting value
|
||||
-- ys,xs = "Rest of xs"
|
||||
mergeList axs@( px@(_,x) : xs) ays@( py@(_,y) : ys)
|
||||
-- If x <= y, the first pair ps should go first.
|
||||
-- Then we can merge the rest of xs with all of ays.
|
||||
| x <= y = px : mergeList xs ays
|
||||
-- Otherwise, we can just call mergeList again.
|
||||
| otherwise = py : mergeList axs ys
|
||||
|
||||
|
||||
-- mergeSort will sort using mergeList function
|
||||
--
|
||||
-- mergeSort [("dat",1),("scott",5),("Tim",2)]
|
||||
-- >>> [("dat",1),("Tim",2),("scott",5)]
|
||||
--
|
||||
-- mergeSort [("dat",1),("dan",5),("scott",4),("scottish",3)]
|
||||
-- >>> [("dat",1),("dat2",3),("scott",4),("scott",5)]
|
||||
|
||||
-- Some helper function
|
||||
-- Apply a function that takes 2 params and apply it to an ordered pair
|
||||
-- with the 2 parameters.
|
||||
applyPair :: (a->b->c) -> (a,b) -> c
|
||||
applyPair f (x,y) = f x y
|
||||
|
||||
-- Apply a function to each part of the pair.
|
||||
applyEachPair :: (a->b) -> (a,a) -> (b,b)
|
||||
applyEachPair f (x, y) = (f x, f y)
|
||||
|
||||
mergeSort :: Ord b => [(a,b)] -> [(a,b)]
|
||||
-- Base cases
|
||||
mergeSort [] = []
|
||||
mergeSort [x] = [x]
|
||||
|
||||
-- To merge a list xs,
|
||||
-- we split the list in half, and recursive apply mergeSort to each
|
||||
-- half.
|
||||
-- Then, we mergeList on both of them.
|
||||
mergeSort xs = applyPair mergeList (applyEachPair mergeSort (splitHalf xs))
|
||||
|
||||
|
||||
-- Part E - working with new type
|
||||
-- Note: You should not use fold anywhere in this part of the assignment
|
||||
type BigInt = [Int]
|
||||
--
|
||||
-- You will be writing three helper functions to solve bigAdd, mulByDigit, bigMul
|
||||
|
||||
-- `clone x n` returns a `[x,x,...,x]` containing `n` copies of `x`
|
||||
--
|
||||
-- clone 3 5
|
||||
-- >>> [3,3,3,3,3]
|
||||
--
|
||||
-- clone "foo" 2
|
||||
-- >>> ["foo", "foo"]
|
||||
|
||||
clone :: a -> Int -> [a]
|
||||
-- Base case
|
||||
clone _ 0 = []
|
||||
-- List with just x
|
||||
clone x 1 = x : []
|
||||
-- Create a list with [x], then recursive call function.
|
||||
clone x n = x : clone x (n-1)
|
||||
|
||||
|
||||
-- `padZero l1 l2` returns a pair (l1', l2') which are the input lists,
|
||||
-- padded with extra `0` on the left such that the lengths of `l1'`
|
||||
-- and `l2'` are equal.
|
||||
--
|
||||
-- padZero [9,9] [1,0,0,2]
|
||||
-- >>> ([0,0,9,9], [1,0,0,2])
|
||||
--
|
||||
-- padZero [1,0,0,2] [9,9]
|
||||
-- >>> ([1,0,0,2], [0,0,9,9])
|
||||
|
||||
-- Helper function
|
||||
clonez = clone 0
|
||||
|
||||
padZero :: BigInt -> BigInt -> (BigInt, BigInt)
|
||||
-- If left is longer, clone zeros and prepend to right.
|
||||
-- If right is longer, clone zeros and prepend to left.
|
||||
-- Otherwise, if they're the same, just return them.
|
||||
padZero xs ys | xl > yl = (xs, clonez (xl-yl) ++ ys)
|
||||
| xl < yl = (clonez (yl-xl) ++ xs, ys)
|
||||
| otherwise = (xs,ys)
|
||||
where xl = length xs
|
||||
yl = length ys
|
||||
|
||||
|
||||
-- `removeZero ls` strips out all leading `0` from the left-side of `ls`.
|
||||
--
|
||||
-- removeZero [0,0,0,1,0,0,2]
|
||||
-- >>> [1,0,0,2]
|
||||
--
|
||||
-- removeZero [9,9]
|
||||
-- >>> [9,9]
|
||||
--
|
||||
-- removeZero [0,0,0,0]
|
||||
-- >>> []
|
||||
|
||||
removeZero :: BigInt -> BigInt
|
||||
-- Base case
|
||||
removeZero [] = []
|
||||
-- If we can pattern match a zero, recurse with rest of list.
|
||||
removeZero (0:xs) = removeZero xs
|
||||
-- Otherwise just return it.
|
||||
removeZero xs = xs
|
||||
|
||||
|
||||
-- `bigAdd n1 n2` returns the `BigInt` representing the sum of `n1` and `n2`
|
||||
--
|
||||
-- bigAdd [9, 9] [1, 0, 0, 2]
|
||||
-- >>> [1, 1, 0, 1]
|
||||
--
|
||||
-- bigAdd [9, 9, 9, 9] [9, 9, 9]
|
||||
-- >>> [1, 0, 9, 9, 8]
|
||||
|
||||
--bigAdd :: BigInt -> BigInt -> BigInt
|
||||
bigAdd _ _ = "not implemented"
|
||||
|
||||
|
||||
-- `mulByDigit i n` returns the result of multiplying
|
||||
-- the digit `i` (between 0..9) with `BigInt` `n`.
|
||||
--
|
||||
-- mulByDigit 9 [9,9,9,9]
|
||||
-- >>> [8,9,9,9,1]
|
||||
|
||||
--mulByDigit :: Int -> BigInt -> BigInt
|
||||
mulByDigit _ _ = "not implemented"
|
||||
|
||||
|
||||
-- `bigMul n1 n2` returns the `BigInt` representing the
|
||||
-- product of `n1` and `n2`.
|
||||
--
|
||||
-- bigMul [9,9,9,9] [9,9,9,9]
|
||||
-- >>> [9,9,9,8,0,0,0,1]
|
||||
--
|
||||
-- bigMul [9,9,9,9,9] [9,9,9,9,9]
|
||||
-- >>> [9,9,9,9,8,0,0,0,0,1]
|
||||
|
||||
--bigMul :: BigInt -> BigInt -> BigInt
|
||||
bigMul _ _ = "not implemented"
|
||||
|
||||
|
11
Week6/lecture.hs
Normal file
11
Week6/lecture.hs
Normal file
|
@ -0,0 +1,11 @@
|
|||
-- Types are not required, but useful
|
||||
avg :: [Int] -> Int
|
||||
avg xs = div (sum xs) (length xs)
|
||||
|
||||
-- Factorial is pretty simple to write
|
||||
factorial n = product [1..n]
|
||||
|
||||
-- Can also use infix operator.
|
||||
average xs = sum xs `div` length xs
|
||||
|
||||
|
29
Week6/lecture2.hs
Normal file
29
Week6/lecture2.hs
Normal file
|
@ -0,0 +1,29 @@
|
|||
factors :: Int -> [Int]
|
||||
factors n = [x | x <- [1..n], rem n x == 0]
|
||||
|
||||
prime :: Int -> Bool
|
||||
prime n = factors n == [1,n]
|
||||
|
||||
primes :: Int -> [Int]
|
||||
primes n = [p | p <- [2..n], prime p]
|
||||
|
||||
pairs :: [a] -> [(a,a)]
|
||||
pairs xs = zip xs (tail xs)
|
||||
|
||||
sorted :: Ord a => [a] -> Bool
|
||||
sorted xs = and [x <= y | (x,y) <- pairs xs]
|
||||
|
||||
perfect :: Int -> Bool
|
||||
perfect n = sum (init (factors n)) == n
|
||||
|
||||
perfects :: Int -> [Int]
|
||||
perfects n = [x | x <- [1..n], perfect x]
|
||||
|
||||
scalar :: Num a => [a] -> [a] -> a
|
||||
scalar xs ys = sum [x*y | (x,y) <- zip xs ys]
|
||||
|
||||
pyth (a,b,c) = a^2 + b^2 == c^2
|
||||
|
||||
pyths :: Int -> [(Int,Int,Int)]
|
||||
pyths n = [(a,b,c) | a <- [1..n], b <- [1..n], c <- [1..n], pyth (a,b,c)]
|
||||
|
17
Week6/week6.hs
Normal file
17
Week6/week6.hs
Normal file
|
@ -0,0 +1,17 @@
|
|||
import Data.List( delete, nub, sort )
|
||||
|
||||
-- Remove the first part of xs from ys and then recurse.
|
||||
difference (x:xs) ys = difference xs (delete x ys)
|
||||
-- Once the list is empty we can just use y.
|
||||
difference [] (y:_) = y
|
||||
|
||||
-- Get the count of some element x in xs.
|
||||
count xs x = length [x' | x' <- xs, x' == x]
|
||||
|
||||
-- Return a list of all the frequencies for unique elements of xs.
|
||||
frequencies xs = map (count xs) us where us = nub xs
|
||||
|
||||
-- If the frequency lists have the same elements,
|
||||
-- they can be replaced. i.e., they are isomorphic.
|
||||
isomorphic xs ys = sort (frequencies xs) == sort (frequencies ys)
|
||||
|
89
Week7/lecture.hs
Normal file
89
Week7/lecture.hs
Normal file
|
@ -0,0 +1,89 @@
|
|||
myAnd :: [Bool] -> Bool
|
||||
myAnd [x] = x
|
||||
myAnd (x:xs) = x && (myAnd xs)
|
||||
|
||||
myConcat :: [[a]] -> [a]
|
||||
myConcat [xs] = xs
|
||||
myConcat (xs:xss) = xs ++ myConcat xss
|
||||
|
||||
myReplicate :: Int -> a -> [a]
|
||||
myReplicate 1 v = v : []
|
||||
myReplicate n v = v : myReplicate (n-1) v
|
||||
|
||||
(*!!) :: [a] -> Int -> a
|
||||
(*!!) (x:_) 0 = x
|
||||
(*!!) (x:xs) i = (*!!) xs (i-1)
|
||||
|
||||
myElem :: Eq a => a -> [a] -> Bool
|
||||
myElem x [] = False
|
||||
myElem x (y:xs) | x == y = True
|
||||
| otherwise = myElem x xs
|
||||
|
||||
iSort :: Ord a => [a] -> [a]
|
||||
-- Base cases
|
||||
iSort [] = []
|
||||
iSort [x] = [x]
|
||||
iSort (x:y:[]) | x <= y = [x,y]
|
||||
| otherwise = [y,x]
|
||||
|
||||
-- Split into first and rest of element.
|
||||
-- Then, we sort the remaining list recursive.
|
||||
-- Finally, we use the correct ordering to recurisvely call iSort for
|
||||
-- the rest of the list with y in the correct order.
|
||||
iSort (x:xs) | x <= y = x : iSort (y:l)
|
||||
| otherwise = y : iSort (x:l)
|
||||
where (y:l) = iSort xs
|
||||
|
||||
-- helper function
|
||||
-- Base case.
|
||||
mySplit 0 p = p
|
||||
-- mySplit will collect from the 2nd ordered pair, and move n
|
||||
-- elements into the first list.
|
||||
-- This is done recursively by decrementing n on each call, and moving
|
||||
-- one y into left of the ordered pair.
|
||||
mySplit n (xs,(y:ys)) = mySplit (n-1) (xs++[y], ys)
|
||||
|
||||
splitHalf :: [a] -> ([a], [a])
|
||||
-- splitHalf simply calls mySplit with n = length / 2.
|
||||
splitHalf xs = mySplit (div l 2) ([], xs)
|
||||
where l = length xs
|
||||
|
||||
mergeList :: Ord a => [a] -> [a] -> [a]
|
||||
-- Base case.
|
||||
-- If one of the lists is empty, then we can just return one of the
|
||||
-- lists.
|
||||
mergeList [] ys = ys
|
||||
mergeList xs [] = xs
|
||||
|
||||
-- Lots of pattern matching.
|
||||
-- axs, ays = "All xs"
|
||||
-- x,y = Sorting value
|
||||
-- ys,xs = "Rest of xs"
|
||||
mergeList axs@(x:xs) ays@(y:ys)
|
||||
-- If x <= y, x should go first.
|
||||
-- Then we can merge the rest of xs with all of ays.
|
||||
| x <= y = x : mergeList xs ays
|
||||
-- Otherwise, we can just call mergeList again.
|
||||
| otherwise = y : mergeList axs ys
|
||||
|
||||
-- Some helper function
|
||||
-- Apply a function that takes 2 params and apply it to an ordered pair
|
||||
-- with the 2 parameters.
|
||||
applyPair :: (a->b->c) -> (a,b) -> c
|
||||
applyPair f (x,y) = f x y
|
||||
|
||||
-- Apply a function to each part of the pair.
|
||||
applyEachPair :: (a->b) -> (a,a) -> (b,b)
|
||||
applyEachPair f (x, y) = (f x, f y)
|
||||
|
||||
mergeSort :: Ord a => [a] -> [a]
|
||||
-- Base cases
|
||||
mergeSort [] = []
|
||||
mergeSort [x] = [x]
|
||||
|
||||
-- To merge a list xs,
|
||||
-- we split the list in half, and recursive apply mergeSort to each
|
||||
-- half.
|
||||
-- Then, we mergeList on both of them.
|
||||
mergeSort xs = applyPair mergeList $ applyEachPair mergeSort $ splitHalf xs
|
||||
|
Loading…
Reference in a new issue