Last active
December 11, 2015 01:48
-
-
Save jameshfisher/4525636 to your computer and use it in GitHub Desktop.
initial
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module NinetyNine where | |
import Data.List (foldl') | |
-- Problem 1: Find the last element of a list. | |
myLast :: [a] -> a | |
myLast [] = error "myLast []" | |
myLast (x:xs) = foldl' (flip const) x xs | |
-- Problem 2: Find the last but one element of a list. | |
myButLast :: [a] -> a | |
myButLast (x1:x2:xs) = fst $ foldl' (\(x1,x2) x3 -> (x2,x3)) (x1,x2) xs | |
myButLast [x] = error "myButLast [x]" | |
myButLast [] = error "myButLast []" | |
-- Problem 3: Find the K'th element of a list. The first element in the list is number 1. | |
elementAt :: (Integral i, Show i) => [a] -> i -> a | |
elementAt [] i = error $ "elementAt [] " ++ (show i) | |
elementAt (x:xs) 1 = x | |
elementAt (x:xs) n = elementAt xs (n-1) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Test where | |
import NinetyNine | |
import Test.QuickCheck | |
import Test.QuickCheck.Poly (A, B, C) | |
import Test.QuickCheck.Modifiers | |
newtype SmallInt = SmallInt Int deriving (Show) | |
instance Arbitrary SmallInt where | |
arbitrary = do | |
large <- arbitrary | |
return $ SmallInt $ large `mod` 10 | |
-- n <=. l === n <= (length l) | |
-- but also works for infinite lists | |
(<=.) :: Integral i => i -> [a] -> Bool | |
len <=. l = case l of | |
[] -> len <= 0 | |
x:xs -> (len-1) <=. xs | |
prop_myLast_is_head_reverse :: NonEmptyList [A] -> Bool | |
prop_myLast_is_head_reverse (NonEmpty l) = myLast l == head (reverse l) | |
prop_myButLast_is_snd_reverse :: [A] -> Property | |
prop_myButLast_is_snd_reverse l = | |
(length l >= 2) ==> | |
myButLast l == (reverse l) !! 1 | |
prop_elementAt_is_1_index :: [A] -> SmallInt -> Property | |
prop_elementAt_is_1_index l (SmallInt i) = | |
(1 <= i && i <=. l) ==> | |
elementAt l i == l !! (i-1) | |
main = do | |
quickCheck $ prop_myLast_is_head_reverse | |
quickCheck $ prop_myButLast_is_snd_reverse | |
quickCheck $ prop_elementAt_is_1_index |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment