Add missing HW3.
This commit is contained in:
parent
1b885e2197
commit
b2e7ccfeda
195
HW3.fedorind.hs
Normal file
195
HW3.fedorind.hs
Normal file
|
@ -0,0 +1,195 @@
|
||||||
|
module HW3 where
|
||||||
|
|
||||||
|
import Prelude hiding (Enum(..), sum)
|
||||||
|
import Data.List (group)
|
||||||
|
import Data.Bifunctor (Bifunctor(second))
|
||||||
|
|
||||||
|
--
|
||||||
|
-- * Part 1: Run-length lists
|
||||||
|
--
|
||||||
|
|
||||||
|
-- | Convert a regular list into a run-length list.
|
||||||
|
--
|
||||||
|
-- >>> compress [1,1,1,2,3,3,3,1,2,2,2,2]
|
||||||
|
-- [(3,1),(1,2),(3,3),(1,1),(4,2)]
|
||||||
|
--
|
||||||
|
-- >>> compress "Mississippi"
|
||||||
|
-- [(1,'M'),(1,'i'),(2,'s'),(1,'i'),(2,'s'),(1,'i'),(2,'p'),(1,'i')]
|
||||||
|
--
|
||||||
|
compress :: Eq a => [a] -> [(Int,a)]
|
||||||
|
compress = map ((>>=id) $ fmap ((second head) .) (,) . length) . group
|
||||||
|
|
||||||
|
-- Yeah this isn't so good pointfree.
|
||||||
|
-- I don't normally write code like this, believe me.
|
||||||
|
--
|
||||||
|
-- So we have:
|
||||||
|
-- >>= id = join :: m (m a) -> m a = (a -> a -> b) -> a -> b
|
||||||
|
-- temp1 = (,) . length :: [a] -> [a] -> (Int, [a])
|
||||||
|
-- (make a tuple and find the length)
|
||||||
|
-- temp2 = fmap ((second head) .) temp1 :: [a] -> [a] -> (Int, a)
|
||||||
|
-- (transform the tuple's second element into its head)
|
||||||
|
-- temp3 = join temp2 :: [a] -> (Int, a)
|
||||||
|
-- (ensure both parts of the tuple are the same list)
|
||||||
|
|
||||||
|
-- | Convert a run-length list back into a regular list.
|
||||||
|
--
|
||||||
|
-- >>> decompress [(5,'a'),(3,'b'),(4,'c'),(1,'a'),(2,'b')]
|
||||||
|
-- "aaaaabbbccccabb"
|
||||||
|
--
|
||||||
|
decompress :: [(Int,a)] -> [a]
|
||||||
|
decompress = concatMap (uncurry replicate)
|
||||||
|
|
||||||
|
|
||||||
|
--
|
||||||
|
-- * Part 2: Natural numbers
|
||||||
|
--
|
||||||
|
|
||||||
|
-- | The natural numbers.
|
||||||
|
data Nat
|
||||||
|
= Zero
|
||||||
|
| Succ Nat
|
||||||
|
deriving (Eq,Show)
|
||||||
|
|
||||||
|
fold :: a -> (a -> a) -> Nat -> a
|
||||||
|
fold b f Zero = b
|
||||||
|
fold b f (Succ n) = f (fold b f n)
|
||||||
|
|
||||||
|
-- | The number 1.
|
||||||
|
one :: Nat
|
||||||
|
one = Succ Zero
|
||||||
|
|
||||||
|
-- | The number 2.
|
||||||
|
two :: Nat
|
||||||
|
two = Succ one
|
||||||
|
|
||||||
|
-- | The number 3.
|
||||||
|
three :: Nat
|
||||||
|
three = Succ two
|
||||||
|
|
||||||
|
-- | The number 4.
|
||||||
|
four :: Nat
|
||||||
|
four = Succ three
|
||||||
|
|
||||||
|
|
||||||
|
-- | The predecessor of a natural number.
|
||||||
|
--
|
||||||
|
-- >>> pred Zero
|
||||||
|
-- Zero
|
||||||
|
--
|
||||||
|
-- >>> pred three
|
||||||
|
-- Succ (Succ Zero)
|
||||||
|
--
|
||||||
|
pred = snd . fold (id, Zero) ((,) Succ . uncurry ($))
|
||||||
|
|
||||||
|
|
||||||
|
-- | True if the given value is zero.
|
||||||
|
--
|
||||||
|
-- >>> isZero Zero
|
||||||
|
-- True
|
||||||
|
--
|
||||||
|
-- >>> isZero two
|
||||||
|
-- False
|
||||||
|
--
|
||||||
|
isZero = fold True (const False)
|
||||||
|
|
||||||
|
|
||||||
|
-- | Convert a natural number to an integer. NOTE: We use this function in
|
||||||
|
-- tests, but you should not use it in your other definitions!
|
||||||
|
--
|
||||||
|
-- >>> toInt Zero
|
||||||
|
-- 0
|
||||||
|
--
|
||||||
|
-- >>> toInt three
|
||||||
|
-- 3
|
||||||
|
--
|
||||||
|
toInt = fold 0 (+1)
|
||||||
|
|
||||||
|
|
||||||
|
-- | Add two natural numbers.
|
||||||
|
--
|
||||||
|
-- >>> add one two
|
||||||
|
-- Succ (Succ (Succ Zero))
|
||||||
|
--
|
||||||
|
-- >>> add Zero one == one
|
||||||
|
-- True
|
||||||
|
--
|
||||||
|
-- >>> add two two == four
|
||||||
|
-- True
|
||||||
|
--
|
||||||
|
-- >>> add two three == add three two
|
||||||
|
-- True
|
||||||
|
--
|
||||||
|
add = flip fold Succ
|
||||||
|
|
||||||
|
|
||||||
|
-- | Subtract the second natural number from the first. Return zero
|
||||||
|
-- if the second number is bigger.
|
||||||
|
--
|
||||||
|
-- >>> sub two one
|
||||||
|
-- Succ Zero
|
||||||
|
--
|
||||||
|
-- >>> sub three one
|
||||||
|
-- Succ (Succ Zero)
|
||||||
|
--
|
||||||
|
-- >>> sub one one
|
||||||
|
-- Zero
|
||||||
|
--
|
||||||
|
-- >>> sub one three
|
||||||
|
-- Zero
|
||||||
|
--
|
||||||
|
sub = flip $ fold id ((pred.))
|
||||||
|
|
||||||
|
-- | Is the left value greater than the right?
|
||||||
|
--
|
||||||
|
-- >>> gt one two
|
||||||
|
-- False
|
||||||
|
--
|
||||||
|
-- >>> gt two one
|
||||||
|
-- True
|
||||||
|
--
|
||||||
|
-- >>> gt two two
|
||||||
|
-- False
|
||||||
|
--
|
||||||
|
gt = fmap (fmap (not . (==Zero))) sub
|
||||||
|
|
||||||
|
-- | Multiply two natural numbers.
|
||||||
|
--
|
||||||
|
-- >>> mult two Zero
|
||||||
|
-- Zero
|
||||||
|
--
|
||||||
|
-- >>> mult Zero three
|
||||||
|
-- Zero
|
||||||
|
--
|
||||||
|
-- >>> toInt (mult two three)
|
||||||
|
-- 6
|
||||||
|
--
|
||||||
|
-- >>> toInt (mult three three)
|
||||||
|
-- 9
|
||||||
|
--
|
||||||
|
mult = fold Zero . add
|
||||||
|
|
||||||
|
|
||||||
|
-- | Compute the sum of a list of natural numbers.
|
||||||
|
--
|
||||||
|
-- >>> sum []
|
||||||
|
-- Zero
|
||||||
|
--
|
||||||
|
-- >>> sum [one,Zero,two]
|
||||||
|
-- Succ (Succ (Succ Zero))
|
||||||
|
--
|
||||||
|
-- >>> toInt (sum [one,two,three])
|
||||||
|
-- 6
|
||||||
|
--
|
||||||
|
sum :: [Nat] -> Nat -- Monomorphism restriction hits here
|
||||||
|
sum = foldl add Zero
|
||||||
|
|
||||||
|
|
||||||
|
-- | An infinite list of all of the *odd* natural numbers, in order.
|
||||||
|
--
|
||||||
|
-- >>> map toInt (take 5 odds)
|
||||||
|
-- [1,3,5,7,9]
|
||||||
|
--
|
||||||
|
-- >>> toInt (sum (take 100 odds))
|
||||||
|
-- 10000
|
||||||
|
--
|
||||||
|
odds = one : map (Succ . Succ) odds
|
Loading…
Reference in New Issue
Block a user