SlideShare a Scribd company logo
{-
Do not change the skeleton code! The point of this
assignment is to figure out how the functions can
be written this way (using fold). You may only
replace the `error "TBD:..."` parts.
For this assignment, you may use the following library functions:
map
foldl'
foldr
length
append (or ++)
zip
-}
module Warmup where
import Prelude hiding (replicate, sum, reverse)
import Data.List (foldl')
foldLeft :: (a -> b -> a) -> a -> [b] -> a
foldLeft = foldl'
foldRight :: (b -> a -> a) -> a -> [b] -> a
foldRight = foldr
-- | Sum the elements of a list
--
-- >>> sumList [1, 2, 3, 4]
-- 10
--
-- >>> sumList [1, -2, 3, 5]
-- 7
--
-- >>> sumList [1, 3, 5, 7, 9, 11]
-- 36
sumList :: [Int] -> Int
sumList xs = error "TBD:sumList"
-- | `digitsOfInt n` should return `[]` if `n` is not positive,
-- and otherwise returns the list of digits of `n` in the
-- order in which they appear in `n`.
--
-- >>> digitsOfInt 3124
-- [3, 1, 2, 4]
--
-- >>> digitsOfInt 352663
-- [3, 5, 2, 6, 6, 3]
digitsOfInt :: Int -> [Int]
digitsOfInt 0 = []
digitsOfInt n = error "TBD:digitsOfInt"
-- | `digits n` retruns the list of digits of `n`
--
-- >>> digits 31243
-- [3,1,2,4,3]
--
-- digits (-23422)
-- [2, 3, 4, 2, 2]
digits :: Int -> [Int]
digits n = digitsOfInt (abs n)
-- | From http://mathworld.wolfram.com/AdditivePersistence.html
-- Consider the process of taking a number, adding its digits,
-- then adding the digits of the number derived from it, etc.,
-- until the remaining number has only one digit.
-- The number of additions required to obtain a single digit
-- from a number n is called the additive persistence of n,
-- and the digit obtained is called the digital root of n.
-- For example, the sequence obtained from the starting number
-- 9876 is (9876, 30, 3), so 9876 has
-- an additive persistence of 2 and
-- a digital root of 3.
--
-- NOTE: assume additivePersistence & digitalRoot are only called with positive numbers
-- >>> additivePersistence 9876
-- 2
additivePersistence :: Int -> Int
additivePersistence n = error "TBD"
-- | digitalRoot n is the digit obtained at the end of the sequence
-- computing the additivePersistence
--
-- >>> digitalRoot 9876
-- 3
digitalRoot :: Int -> Int
digitalRoot n = error "TBD"
-- | listReverse [x1,x2,...,xn] returns [xn,...,x2,x1]
--
-- >>> listReverse []
-- []
--
-- >>> listReverse [1,2,3,4]
-- [4,3,2,1]
--
-- >>> listReverse ["i", "want", "to", "ride", "my", "bicycle"]
-- ["bicycle", "my", "ride", "to", "want", "i"]
listReverse :: [a] -> [a]
listReverse xs = error "TBD"
-- | In Haskell, a `String` is a simply a list of `Char`, that is:
--
-- >>> ['h', 'a', 's', 'k', 'e', 'l', 'l']
-- "haskell"
--
-- >>> palindrome "malayalam"
-- True
--
-- >>> palindrome "myxomatosis"
-- False
palindrome :: String -> Bool
palindrome w = error "TBD"
-- | 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
sqSum xs = foldLeft f base xs
where
f a x = error "TBD: sqSum f"
base = error "TBD: sqSum base"
-- | `pipe [f1,...,fn] x` should return `f1(f2(...(fn x)))`
--
-- >>> pipe [] 3
-- 3
--
-- >>> pipe [(x -> x+x), (x -> x + 3)] 3
-- 12
--
-- >>> pipe [(x -> x * 4), (x -> x + x)] 3
-- 24
pipe :: [(a -> a)] -> (a -> a)
pipe fs = foldLeft f base fs
where
f a x = error "TBD"
base = error "TBD"
-- | `sepConcat sep [s1,...,sn]` returns `s1 ++ sep ++ s2 ++ ... ++ sep ++ sn`
--
-- >>> sepConcat "---" []
-- ""
--
-- >>> sepConcat ", " ["foo", "bar", "baz"]
-- "foo, bar, baz"
--
-- >>> sepConcat "#" ["a","b","c","d","e"]
-- "a#b#c#d#e"
sepConcat :: String -> [String] -> String
sepConcat sep [] = ""
sepConcat sep (h:t) = foldLeft f base l
where
f a x = error "TBD"
base = error "TBD"
l = error "TBD"
intString :: Int -> String
intString = show
-- | `stringOfList pp [x1,...,xn]` uses the element-wise printer `pp` to
-- convert the element-list into a string:
--
-- >>> stringOfList intString [1, 2, 3, 4, 5, 6]
-- "[1, 2, 3, 4, 5, 6]"
--
-- >>> stringOfList (x -> x) ["foo"]
-- "[foo]"
--
-- >>> stringOfList (stringOfList show) [[1, 2, 3], [4, 5], [6], []]
-- "[[1, 2, 3], [4, 5], [6], []]"
stringOfList :: (a -> String) -> [a] -> String
stringOfList f xs = error "TBD"
-- | `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]
clone x n = error "TBD"
type BigInt = [Int]
-- | `padZero l1 l2` returns a pair (l1', l2') which are just 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]
padZero :: BigInt -> BigInt -> (BigInt, BigInt)
padZero l1 l2 = error "TBD"
-- | `removeZero ds` strips out all leading `0` from the left-side of `ds`.
--
-- >>> 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
removeZero ds = error "TBD"
-- | `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 l1 l2 = removeZero res
where
(l1', l2') = padZero l1 l2
(_ , res) = foldRight f base args
f (x1, x2) (carry, sum) = error "TBD"
base = error "TBD"
args = error "TBD"
-- | `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 i l = error "TBD"
-- | `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 l1 l2 = res
where
(_, res) = foldRight f base args
f x (z, p) = error "TBD"
base = error "TBD"
args = error "TBD"

More Related Content

Similar to {- Do not change the skeleton code! The point of this assign.pdf

Python data structures
Python data structuresPython data structures
Python data structures
Tony Nguyen
 
Python data structures
Python data structuresPython data structures
Python data structures
Luis Goldster
 
Python data structures
Python data structuresPython data structures
Python data structures
James Wong
 
Python data structures
Python data structuresPython data structures
Python data structures
Young Alista
 
Python data structures
Python data structuresPython data structures
Python data structures
Fraboni Ec
 
Python data structures
Python data structuresPython data structures
Python data structures
Harry Potter
 
Finish the program below that does several bit-wise manipulations of.pdf
Finish the program below that does several bit-wise manipulations of.pdfFinish the program below that does several bit-wise manipulations of.pdf
Finish the program below that does several bit-wise manipulations of.pdf
fasttrackcomputersol
 

Similar to {- Do not change the skeleton code! The point of this assign.pdf (20)

Python From Scratch (1).pdf
Python From Scratch  (1).pdfPython From Scratch  (1).pdf
Python From Scratch (1).pdf
 
Pandas
PandasPandas
Pandas
 
An overview of Python 2.7
An overview of Python 2.7An overview of Python 2.7
An overview of Python 2.7
 
A tour of Python
A tour of PythonA tour of Python
A tour of Python
 
Haskellで学ぶ関数型言語
Haskellで学ぶ関数型言語Haskellで学ぶ関数型言語
Haskellで学ぶ関数型言語
 
Python data structures
Python data structuresPython data structures
Python data structures
 
Python data structures
Python data structuresPython data structures
Python data structures
 
Python data structures
Python data structuresPython data structures
Python data structures
 
Python data structures
Python data structuresPython data structures
Python data structures
 
Python data structures
Python data structuresPython data structures
Python data structures
 
Python data structures
Python data structuresPython data structures
Python data structures
 
KScope19 - SQL Features
KScope19 - SQL FeaturesKScope19 - SQL Features
KScope19 - SQL Features
 
Finish the program below that does several bit-wise manipulations of.pdf
Finish the program below that does several bit-wise manipulations of.pdfFinish the program below that does several bit-wise manipulations of.pdf
Finish the program below that does several bit-wise manipulations of.pdf
 
C PROGRAMS - SARASWATHI RAMALINGAM
C PROGRAMS - SARASWATHI RAMALINGAMC PROGRAMS - SARASWATHI RAMALINGAM
C PROGRAMS - SARASWATHI RAMALINGAM
 
C++ ARRAY WITH EXAMPLES
C++ ARRAY WITH EXAMPLESC++ ARRAY WITH EXAMPLES
C++ ARRAY WITH EXAMPLES
 
Артём Акуляков - F# for Data Analysis
Артём Акуляков - F# for Data AnalysisАртём Акуляков - F# for Data Analysis
Артём Акуляков - F# for Data Analysis
 
codecentric AG: Using Cassandra and Clojure for Data Crunching backends
codecentric AG: Using Cassandra and Clojure for Data Crunching backendscodecentric AG: Using Cassandra and Clojure for Data Crunching backends
codecentric AG: Using Cassandra and Clojure for Data Crunching backends
 
Computer Programming- Lecture 9
Computer Programming- Lecture 9Computer Programming- Lecture 9
Computer Programming- Lecture 9
 
Mysql 4.0 casual
Mysql 4.0 casualMysql 4.0 casual
Mysql 4.0 casual
 
CLUSTERGRAM
CLUSTERGRAMCLUSTERGRAM
CLUSTERGRAM
 

More from atul2867

More from atul2867 (12)

{0r1s-0r-s} over {0-1} is not regular-.pdf
{0r1s-0r-s} over {0-1} is not regular-.pdf{0r1s-0r-s} over {0-1} is not regular-.pdf
{0r1s-0r-s} over {0-1} is not regular-.pdf
 
Z is the standard normal distribution- Find the indicated probability-.pdf
Z is the standard normal distribution- Find the indicated probability-.pdfZ is the standard normal distribution- Find the indicated probability-.pdf
Z is the standard normal distribution- Find the indicated probability-.pdf
 
Your task is as follows- Create 2D- 3D- and 4D programs implementing (.pdf
Your task is as follows- Create 2D- 3D- and 4D programs implementing (.pdfYour task is as follows- Create 2D- 3D- and 4D programs implementing (.pdf
Your task is as follows- Create 2D- 3D- and 4D programs implementing (.pdf
 
Your Task Consider the following table- displaying three binary input.pdf
Your Task Consider the following table- displaying three binary input.pdfYour Task Consider the following table- displaying three binary input.pdf
Your Task Consider the following table- displaying three binary input.pdf
 
Your patient has been transported to the emergency department by EMS a.pdf
Your patient has been transported to the emergency department by EMS a.pdfYour patient has been transported to the emergency department by EMS a.pdf
Your patient has been transported to the emergency department by EMS a.pdf
 
Your instructor is playing 5 rounds of fetch with his dog Ruby- About.pdf
Your instructor is playing 5 rounds of fetch with his dog Ruby- About.pdfYour instructor is playing 5 rounds of fetch with his dog Ruby- About.pdf
Your instructor is playing 5 rounds of fetch with his dog Ruby- About.pdf
 
Your first discussion this week focuses on ethnicity- If you live in t.pdf
Your first discussion this week focuses on ethnicity- If you live in t.pdfYour first discussion this week focuses on ethnicity- If you live in t.pdf
Your first discussion this week focuses on ethnicity- If you live in t.pdf
 
Your friend states that viruses are NOT living organisms- Based on wha.pdf
Your friend states that viruses are NOT living organisms- Based on wha.pdfYour friend states that viruses are NOT living organisms- Based on wha.pdf
Your friend states that viruses are NOT living organisms- Based on wha.pdf
 
Your Grandfather who has been healthy and does not take any medication.pdf
Your Grandfather who has been healthy and does not take any medication.pdfYour Grandfather who has been healthy and does not take any medication.pdf
Your Grandfather who has been healthy and does not take any medication.pdf
 
You work for a corporate office in HIM providing services to customers.pdf
You work for a corporate office in HIM providing services to customers.pdfYou work for a corporate office in HIM providing services to customers.pdf
You work for a corporate office in HIM providing services to customers.pdf
 
You want to invest $100-000 for five years- Which of the following opp.pdf
You want to invest $100-000 for five years- Which of the following opp.pdfYou want to invest $100-000 for five years- Which of the following opp.pdf
You want to invest $100-000 for five years- Which of the following opp.pdf
 
You want to extend the annual display of summer color in your landscap.pdf
You want to extend the annual display of summer color in your landscap.pdfYou want to extend the annual display of summer color in your landscap.pdf
You want to extend the annual display of summer color in your landscap.pdf
 

Recently uploaded

plant breeding methods in asexually or clonally propagated crops
plant breeding methods in asexually or clonally propagated cropsplant breeding methods in asexually or clonally propagated crops
plant breeding methods in asexually or clonally propagated crops
parmarsneha2
 

Recently uploaded (20)

Palestine last event orientationfvgnh .pptx
Palestine last event orientationfvgnh .pptxPalestine last event orientationfvgnh .pptx
Palestine last event orientationfvgnh .pptx
 
Solid waste management & Types of Basic civil Engineering notes by DJ Sir.pptx
Solid waste management & Types of Basic civil Engineering notes by DJ Sir.pptxSolid waste management & Types of Basic civil Engineering notes by DJ Sir.pptx
Solid waste management & Types of Basic civil Engineering notes by DJ Sir.pptx
 
Unit 8 - Information and Communication Technology (Paper I).pdf
Unit 8 - Information and Communication Technology (Paper I).pdfUnit 8 - Information and Communication Technology (Paper I).pdf
Unit 8 - Information and Communication Technology (Paper I).pdf
 
Jose-Rizal-and-Philippine-Nationalism-National-Symbol-2.pptx
Jose-Rizal-and-Philippine-Nationalism-National-Symbol-2.pptxJose-Rizal-and-Philippine-Nationalism-National-Symbol-2.pptx
Jose-Rizal-and-Philippine-Nationalism-National-Symbol-2.pptx
 
Basic_QTL_Marker-assisted_Selection_Sourabh.ppt
Basic_QTL_Marker-assisted_Selection_Sourabh.pptBasic_QTL_Marker-assisted_Selection_Sourabh.ppt
Basic_QTL_Marker-assisted_Selection_Sourabh.ppt
 
Instructions for Submissions thorugh G- Classroom.pptx
Instructions for Submissions thorugh G- Classroom.pptxInstructions for Submissions thorugh G- Classroom.pptx
Instructions for Submissions thorugh G- Classroom.pptx
 
Phrasal Verbs.XXXXXXXXXXXXXXXXXXXXXXXXXX
Phrasal Verbs.XXXXXXXXXXXXXXXXXXXXXXXXXXPhrasal Verbs.XXXXXXXXXXXXXXXXXXXXXXXXXX
Phrasal Verbs.XXXXXXXXXXXXXXXXXXXXXXXXXX
 
The approach at University of Liverpool.pptx
The approach at University of Liverpool.pptxThe approach at University of Liverpool.pptx
The approach at University of Liverpool.pptx
 
Fish and Chips - have they had their chips
Fish and Chips - have they had their chipsFish and Chips - have they had their chips
Fish and Chips - have they had their chips
 
Digital Tools and AI for Teaching Learning and Research
Digital Tools and AI for Teaching Learning and ResearchDigital Tools and AI for Teaching Learning and Research
Digital Tools and AI for Teaching Learning and Research
 
plant breeding methods in asexually or clonally propagated crops
plant breeding methods in asexually or clonally propagated cropsplant breeding methods in asexually or clonally propagated crops
plant breeding methods in asexually or clonally propagated crops
 
How libraries can support authors with open access requirements for UKRI fund...
How libraries can support authors with open access requirements for UKRI fund...How libraries can support authors with open access requirements for UKRI fund...
How libraries can support authors with open access requirements for UKRI fund...
 
NLC-2024-Orientation-for-RO-SDO (1).pptx
NLC-2024-Orientation-for-RO-SDO (1).pptxNLC-2024-Orientation-for-RO-SDO (1).pptx
NLC-2024-Orientation-for-RO-SDO (1).pptx
 
The Challenger.pdf DNHS Official Publication
The Challenger.pdf DNHS Official PublicationThe Challenger.pdf DNHS Official Publication
The Challenger.pdf DNHS Official Publication
 
Basic phrases for greeting and assisting costumers
Basic phrases for greeting and assisting costumersBasic phrases for greeting and assisting costumers
Basic phrases for greeting and assisting costumers
 
2024.06.01 Introducing a competency framework for languag learning materials ...
2024.06.01 Introducing a competency framework for languag learning materials ...2024.06.01 Introducing a competency framework for languag learning materials ...
2024.06.01 Introducing a competency framework for languag learning materials ...
 
50 ĐỀ LUYỆN THI IOE LỚP 9 - NĂM HỌC 2022-2023 (CÓ LINK HÌNH, FILE AUDIO VÀ ĐÁ...
50 ĐỀ LUYỆN THI IOE LỚP 9 - NĂM HỌC 2022-2023 (CÓ LINK HÌNH, FILE AUDIO VÀ ĐÁ...50 ĐỀ LUYỆN THI IOE LỚP 9 - NĂM HỌC 2022-2023 (CÓ LINK HÌNH, FILE AUDIO VÀ ĐÁ...
50 ĐỀ LUYỆN THI IOE LỚP 9 - NĂM HỌC 2022-2023 (CÓ LINK HÌNH, FILE AUDIO VÀ ĐÁ...
 
Supporting (UKRI) OA monographs at Salford.pptx
Supporting (UKRI) OA monographs at Salford.pptxSupporting (UKRI) OA monographs at Salford.pptx
Supporting (UKRI) OA monographs at Salford.pptx
 
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa
 
PART A. Introduction to Costumer Service
PART A. Introduction to Costumer ServicePART A. Introduction to Costumer Service
PART A. Introduction to Costumer Service
 

{- Do not change the skeleton code! The point of this assign.pdf

  • 1. {- Do not change the skeleton code! The point of this assignment is to figure out how the functions can be written this way (using fold). You may only replace the `error "TBD:..."` parts. For this assignment, you may use the following library functions: map foldl' foldr length append (or ++) zip -} module Warmup where import Prelude hiding (replicate, sum, reverse) import Data.List (foldl') foldLeft :: (a -> b -> a) -> a -> [b] -> a foldLeft = foldl' foldRight :: (b -> a -> a) -> a -> [b] -> a foldRight = foldr -- | Sum the elements of a list --
  • 2. -- >>> sumList [1, 2, 3, 4] -- 10 -- -- >>> sumList [1, -2, 3, 5] -- 7 -- -- >>> sumList [1, 3, 5, 7, 9, 11] -- 36 sumList :: [Int] -> Int sumList xs = error "TBD:sumList" -- | `digitsOfInt n` should return `[]` if `n` is not positive, -- and otherwise returns the list of digits of `n` in the -- order in which they appear in `n`. -- -- >>> digitsOfInt 3124 -- [3, 1, 2, 4] -- -- >>> digitsOfInt 352663 -- [3, 5, 2, 6, 6, 3] digitsOfInt :: Int -> [Int] digitsOfInt 0 = [] digitsOfInt n = error "TBD:digitsOfInt"
  • 3. -- | `digits n` retruns the list of digits of `n` -- -- >>> digits 31243 -- [3,1,2,4,3] -- -- digits (-23422) -- [2, 3, 4, 2, 2] digits :: Int -> [Int] digits n = digitsOfInt (abs n) -- | From http://mathworld.wolfram.com/AdditivePersistence.html -- Consider the process of taking a number, adding its digits, -- then adding the digits of the number derived from it, etc., -- until the remaining number has only one digit. -- The number of additions required to obtain a single digit -- from a number n is called the additive persistence of n, -- and the digit obtained is called the digital root of n. -- For example, the sequence obtained from the starting number -- 9876 is (9876, 30, 3), so 9876 has -- an additive persistence of 2 and -- a digital root of 3. --
  • 4. -- NOTE: assume additivePersistence & digitalRoot are only called with positive numbers -- >>> additivePersistence 9876 -- 2 additivePersistence :: Int -> Int additivePersistence n = error "TBD" -- | digitalRoot n is the digit obtained at the end of the sequence -- computing the additivePersistence -- -- >>> digitalRoot 9876 -- 3 digitalRoot :: Int -> Int digitalRoot n = error "TBD" -- | listReverse [x1,x2,...,xn] returns [xn,...,x2,x1] -- -- >>> listReverse [] -- [] -- -- >>> listReverse [1,2,3,4] -- [4,3,2,1] -- -- >>> listReverse ["i", "want", "to", "ride", "my", "bicycle"] -- ["bicycle", "my", "ride", "to", "want", "i"]
  • 5. listReverse :: [a] -> [a] listReverse xs = error "TBD" -- | In Haskell, a `String` is a simply a list of `Char`, that is: -- -- >>> ['h', 'a', 's', 'k', 'e', 'l', 'l'] -- "haskell" -- -- >>> palindrome "malayalam" -- True -- -- >>> palindrome "myxomatosis" -- False palindrome :: String -> Bool palindrome w = error "TBD" -- | sqSum [x1, ... , xn] should return (x1^2 + ... + xn^2) -- -- >>> sqSum [] -- 0 -- -- >>> sqSum [1,2,3,4] -- 30 --
  • 6. -- >>> sqSum [(-1), (-2), (-3), (-4)] -- 30 sqSum :: [Int] -> Int sqSum xs = foldLeft f base xs where f a x = error "TBD: sqSum f" base = error "TBD: sqSum base" -- | `pipe [f1,...,fn] x` should return `f1(f2(...(fn x)))` -- -- >>> pipe [] 3 -- 3 -- -- >>> pipe [(x -> x+x), (x -> x + 3)] 3 -- 12 -- -- >>> pipe [(x -> x * 4), (x -> x + x)] 3 -- 24 pipe :: [(a -> a)] -> (a -> a) pipe fs = foldLeft f base fs where f a x = error "TBD" base = error "TBD"
  • 7. -- | `sepConcat sep [s1,...,sn]` returns `s1 ++ sep ++ s2 ++ ... ++ sep ++ sn` -- -- >>> sepConcat "---" [] -- "" -- -- >>> sepConcat ", " ["foo", "bar", "baz"] -- "foo, bar, baz" -- -- >>> sepConcat "#" ["a","b","c","d","e"] -- "a#b#c#d#e" sepConcat :: String -> [String] -> String sepConcat sep [] = "" sepConcat sep (h:t) = foldLeft f base l where f a x = error "TBD" base = error "TBD" l = error "TBD" intString :: Int -> String intString = show -- | `stringOfList pp [x1,...,xn]` uses the element-wise printer `pp` to -- convert the element-list into a string: --
  • 8. -- >>> stringOfList intString [1, 2, 3, 4, 5, 6] -- "[1, 2, 3, 4, 5, 6]" -- -- >>> stringOfList (x -> x) ["foo"] -- "[foo]" -- -- >>> stringOfList (stringOfList show) [[1, 2, 3], [4, 5], [6], []] -- "[[1, 2, 3], [4, 5], [6], []]" stringOfList :: (a -> String) -> [a] -> String stringOfList f xs = error "TBD" -- | `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] clone x n = error "TBD" type BigInt = [Int] -- | `padZero l1 l2` returns a pair (l1', l2') which are just the input lists, -- padded with extra `0` on the left such that the lengths of `l1'` and `l2'` -- are equal.
  • 9. -- -- >>> 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] padZero :: BigInt -> BigInt -> (BigInt, BigInt) padZero l1 l2 = error "TBD" -- | `removeZero ds` strips out all leading `0` from the left-side of `ds`. -- -- >>> 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 removeZero ds = error "TBD" -- | `bigAdd n1 n2` returns the `BigInt` representing the sum of `n1` and `n2`. --
  • 10. -- >>> 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 l1 l2 = removeZero res where (l1', l2') = padZero l1 l2 (_ , res) = foldRight f base args f (x1, x2) (carry, sum) = error "TBD" base = error "TBD" args = error "TBD" -- | `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 i l = error "TBD" -- | `bigMul n1 n2` returns the `BigInt` representing the product of `n1` and `n2`. --
  • 11. -- >>> 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 l1 l2 = res where (_, res) = foldRight f base args f x (z, p) = error "TBD" base = error "TBD" args = error "TBD"