Skip to content

Instantly share code, notes, and snippets.

@mkohlhaas
Last active January 5, 2022 10:51
Show Gist options
  • Save mkohlhaas/972b0efdb0af3a02bea1b90abd5acc43 to your computer and use it in GitHub Desktop.
Save mkohlhaas/972b0efdb0af3a02bea1b90abd5acc43 to your computer and use it in GitHub Desktop.
module Ch05 where
import Prelude (Unit, type(~>), discard, negate, show, otherwise, (+), (-), (<), (>), (<=), (>=), (==), (/=), (<<<))
import Data.List (List(..))
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..), snd)
import Effect (Effect)
import Effect.Console (log)
flip :: ∀ a b c. (a -> b -> c) -> b -> a -> c
flip f b a = f a b
const :: ∀ a b. a -> b -> a
const a _ = a
apply :: ∀ a b. (a -> b) -> a -> b
apply f = f
infixr 0 apply as $
applyFlipped :: ∀ a b. a -> (a -> b) -> b
applyFlipped = flip apply
infixl 1 applyFlipped as #
singleton :: ∀ a. a -> List a
singleton a = a : Nil
infixr 6 Cons as :
null :: ∀ a. List a -> Boolean
null Nil = true
null _ = false
snoc :: ∀ a. List a -> a -> List a
snoc Nil a = singleton a
snoc (x : xs) a = x : (snoc xs a)
-- tail-recursive
length :: ∀ a. List a -> Int
length = go 0 where
go acc Nil = acc
go acc (_ : as) = go (acc + 1) as
head :: List ~> Maybe
head Nil = Nothing
head (a : _) = Just a
tail :: ∀ a. List a -> Maybe (List a)
tail Nil = Nothing
tail (_ : as) = Just as
last :: List ~> Maybe
last Nil = Nothing
last (a : Nil) = Just a
last (_ : as) = last as
init :: ∀ a. List a -> Maybe (List a)
init Nil = Nothing
init l = Just $ go l where
go Nil = Nil
go (_ : Nil) = Nil
go (x : xs) = x : (go xs)
uncons :: ∀ a. List a -> Maybe { head :: a, tail :: List a }
uncons Nil = Nothing
uncons (a : as) = Just {head: a, tail: as}
index :: ∀ a. List a -> Int -> Maybe a
index Nil _ = Nothing
index (a : as) count | count < 0 = Nothing
| count == 0 = Just a
| otherwise = index as (count - 1)
infixl 8 index as !!
findIndex :: ∀ a. (a -> Boolean) -> List a -> Maybe Int
findIndex p = go 0 where
go _ Nil = Nothing
go acc (a : as) | p a = Just acc
| otherwise = go (acc + 1) as
findLastIndex :: ∀ a. (a -> Boolean) -> List a -> Maybe Int
findLastIndex p = go Nothing 0 where
go Nothing _ Nil = Nothing
go m_index _ Nil = m_index
go m_index c_index (a : as) | p a = go (Just c_index) (c_index + 1) as
| otherwise = go m_index (c_index + 1) as
reverse :: List ~> List
reverse = go Nil where
go l Nil = l
go l (a : as) = go (a : l) as
concat :: ∀ a. List (List a) -> List a
concat Nil = Nil
concat (Nil : ass) = concat ass
concat ((a : as) : ass) = a : concat (as : ass)
-- NOT tail-recursive
filter :: ∀ a. (a -> Boolean) -> List a -> List a
filter _ Nil = Nil
filter p (a : as) | p a = a : filter p as
| otherwise = filter p as
catMaybes :: ∀ a. List (Maybe a) -> List a
catMaybes Nil = Nil
catMaybes (Nothing : as) = catMaybes as
catMaybes ((Just a) : as) = a : catMaybes as
range :: Int -> Int -> List Int
range a b | a == b = singleton a
range a b | a < b = a : range (a + 1) b
range a b | a > b = a : range (a - 1) b
range _ _ = Nil
infix 8 range as ..
-- NOT tail-recursive
take :: ∀ a. Int -> List a -> List a
take _ Nil = Nil
take count (a : as) | count <= 0 = Nil
| otherwise = a : (take (count - 1) as)
drop :: ∀ a. Int -> List a -> List a
drop _ Nil = Nil
drop count l@(_ : as) | count == 0 = l
| count < 0 = Nil
| otherwise = drop (count - 1) as
-- NOT tail-recursive
takeWhile :: ∀ a. (a -> Boolean) -> List a -> List a
takeWhile _ Nil = Nil
takeWhile p (a : as) | p a = a : takeWhile p as
| otherwise = Nil
dropWhile :: ∀ a. (a -> Boolean) -> List a -> List a
dropWhile _ Nil = Nil
dropWhile p l@(a : as) | p a = dropWhile p as
| otherwise = l
genericEnd :: ∀ a. (Int -> Int -> Boolean) -> Int -> List a -> List a
genericEnd p n = snd <<< go where
go Nil = Tuple 0 Nil
go (a : as) = case go as of
Tuple idx lst | idx `p` n -> Tuple (idx + 1) (a : lst)
| otherwise -> Tuple (idx + 1) lst
dropEnd :: ∀ a. Int -> List a -> List a
dropEnd = genericEnd (>=)
takeEnd :: ∀ a. Int -> List a -> List a
takeEnd = genericEnd (<)
zip :: ∀ a b. List a -> List b -> List (Tuple a b)
zip _ Nil = Nil
zip Nil _ = Nil
zip (a : as) (b : bs) = (Tuple a b) : zip as bs
unzip :: ∀ a b. List (Tuple a b) -> Tuple (List a) (List b)
unzip Nil = Tuple Nil Nil
unzip (Tuple a b : ts) = case unzip ts of
Tuple as bs -> Tuple (a : as) (b : bs)
test :: Effect Unit
test = do
log "Uncomment lines step by step. Implement/import missing functions and all the rest ..."
log (show ((flip const 1 2) == 2))
log $ show $ (flip const 1 2) == 2
(flip const 1 2) == 2 # show # log
log $ show $ (singleton "xyz") == ("xyz" : Nil)
log $ show $ (null Nil) == true
log $ show $ (null ("abc" : Nil)) == false
log $ show $ (snoc (1 : 2 : Nil) 3) == (1 : 2 : 3 : Nil)
log $ show $ (length $ 1 : 2 : 3 : Nil) == 3
log $ show $ (head ("abc" : "123" : Nil)) == (Just "abc")
log $ show $ (head (Nil :: List Unit)) == Nothing
log $ show $ (tail (Nil :: List Unit)) == Nothing
log $ show $ (tail ("abc" : "123" : Nil)) == (Just ("123" : Nil))
log $ show $ ((last Nil :: Maybe Unit)) == Nothing
log $ show $ (last ("a" : "b" : "c" : Nil)) == (Just "c")
log $ show $ (last $ "a" : "b" : "c" : Nil) == (Just "c")
log $ show $ (init (Nil :: List Unit)) == Nothing
log $ show $ (init (1 : Nil)) == (Just Nil)
log $ show $ (init (1 : 2 : Nil)) == (Just (1 : Nil))
log $ show $ (init (1 : 2 : 3 : Nil)) == (Just (1 : 2 : Nil))
log $ show $ (uncons (1 : 2 : 3 : Nil)) == (Just { head: 1, tail: (2 : 3 : Nil) })
log $ show $ (uncons (Nil :: List Unit)) == Nothing
log $ show $ (index (1 : Nil) 4) == Nothing
log $ show $ (index (1 : 2 : 3 : Nil) 1) == (Just 2)
log $ show $ (index (Nil :: List Unit) 0) == Nothing
log $ show $ ((1 : 2 : 3 : Nil) !! 1) == (Just 2)
log $ show $ (findIndex (_ >= 2) (1 : 2 : 3 : Nil)) == (Just 1)
log $ show $ (findIndex (_ >= 99) (1 : 2 : 3 : Nil)) == Nothing
log $ show $ (findIndex (10 /= _) (Nil :: List Int)) == Nothing
log $ show $ (findLastIndex (_ == 10) (Nil :: List Int)) == Nothing
log $ show $ (findLastIndex (_ == 10) (10 : 5 : 10 : -1 : 2 : 10 : Nil)) == (Just 5)
log $ show $ (findLastIndex (_ == 10) (11 : 12 : Nil)) == Nothing
log $ show $ (reverse (10 : 20 : 30 : Nil)) == (30 : 20 : 10 : Nil)
log $ show $ (concat ((1 : 2 : 3 : Nil) : (4 : 5 : Nil) : (6 : Nil) : (Nil) : Nil)) == (1 : 2 : 3 : 4 : 5 : 6 : Nil)
log $ show $ (filter (4 > _) $ (1 : 2 : 3 : 4 : 5 : 6 : Nil)) == (1 : 2 : 3 : Nil)
log $ show $ (catMaybes (Just 1 : Nothing : Just 2 : Nothing : Nothing : Just 5 : Nil)) == (1 : 2 : 5 : Nil)
log $ show $ (range 1 10) == (1 : 2 : 3 : 4 : 5 : 6 : 7 : 8 : 9 : 10 : Nil)
log $ show $ (range 3 ( -3)) == (3 : 2 : 1 : 0 : -1 : -2 : -3 : Nil)
log $ show $ (1 .. 10) == (1 : 2 : 3 : 4 : 5 : 6 : 7 : 8 : 9 : 10 : Nil)
log $ show $ (3 .. ( -3)) == (3 : 2 : 1 : 0 : -1 : -2 : -3 : Nil)
log $ show $ (take 5 (12 : 13 : 14 : Nil)) == (12 : 13 : 14 : Nil)
log $ show $ (take 5 ( -7 : 9 : 0 : 12 : -13 : 45 : 976 : -19 : Nil)) == (-7 : 9 : 0 : 12 : -13 : Nil)
log $ show $ (drop 2 (1 : 2 : 3 : 4 : 5 : 6 : 7 : Nil)) == (3 : 4 : 5 : 6 : 7 : Nil)
log $ show $ (drop 10 (Nil :: List Unit)) == Nil
log $ show $ (takeWhile (_ > 3) (5 : 4 : 3 : 99 : 101 : Nil)) == (5 : 4 : Nil)
log $ show $ (takeWhile (_ == -17) (1 : 2 : 3 : Nil)) == Nil
log $ show $ (dropWhile (_ > 3) (5 : 4 : 3 : 99 : 101 : Nil)) == (3 : 99 : 101 : Nil)
log $ show $ (dropWhile (_ == -17) (1 : 2 : 3 : Nil)) == (1 : 2 : 3 : Nil)
log $ show $ (takeEnd 3 (1 : 2 : 3 : 4 : 5 : 6 : Nil)) == (4 : 5 : 6 : Nil)
log $ show $ (takeEnd 10 (1 : Nil)) == (1 : Nil)
log $ show $ (dropEnd 3 (1 : 2 : 3 : 4 : 5 : 6 : Nil)) == (1 : 2 : 3 : Nil)
log $ show $ (dropEnd 10 (1 : Nil)) == Nil
log $ show $ (zip (1 : 2 : 3 : Nil) ("a" : "b" : "c" : "d" : "e" : Nil)) == ((Tuple 1 "a") : (Tuple 2 "b") : (Tuple 3 "c") : Nil)
log $ show $ (zip ("a" : "b" : "c" : "d" : "e" : Nil) (1 : 2 : 3 : Nil)) == ((Tuple "a" 1) : (Tuple "b" 2) : (Tuple "c" 3) : Nil)
log $ show $ (zip (Nil :: List Unit) (1 : 2 : Nil)) == Nil
log $ show $ (unzip (Tuple 1 "a" : Tuple 2 "b" : Tuple 3 "c" : Nil)) == (Tuple (1 : 2 : 3 : Nil) ("a" : "b" : "c" : Nil))
log $ show $ (unzip (Tuple "a" 1 : Tuple "b" 2 : Tuple "c" 3 : Nil)) == (Tuple ("a" : "b" : "c" : Nil) (1 : 2 : 3 : Nil))
log $ show $ (unzip (Nil :: List (Tuple Unit Unit))) == (Tuple Nil Nil)
{ name = "my-project"
, dependencies = [ "console", "effect", "prelude", "psci-support", "lists", "maybe", "tuples" ]
, packages = ./packages.dhall
, sources = [ "src//*.purs", "test//*.purs" ]
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment