Last active
January 5, 2022 22:28
-
-
Save mkohlhaas/bb64df9da5e966771e7245b33815cb20 to your computer and use it in GitHub Desktop.
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 Ch11 where | |
import Prelude (Unit, class Semiring, class Ord, type (~>), discard, flip, negate, otherwise, show, zero, ($), (>), (+), (<>), (<<<)) | |
import Data.Foldable (class Foldable, foldl, foldr, foldMap) | |
import Data.Semigroup.Foldable (class Foldable1, foldl1) | |
import Data.List (List(..), (:), singleton) | |
import Data.List.Types (NonEmptyList(..)) | |
import Data.NonEmpty ((:|)) | |
import Effect (Effect) | |
import Effect.Console (log) | |
data Tree a = Leaf a | Node (Tree a) (Tree a) | |
newtype RFTree a = RFTree (Tree a) -- RightFirstTree; breadth-first search | |
newtype LFTree a = LFTree (Tree a) -- LeftFirstTree; depth-first search | |
class ToList f where | |
toList :: ∀ a. f a -> List a | |
reverse :: List ~> List | |
reverse = foldl (flip (:)) Nil | |
max :: ∀ a. Ord a => a -> a -> a | |
max a1 a2 | a1 > a2 = a1 | |
| otherwise = a2 | |
findMax :: ∀ f a. Ord a => Foldable f => a -> f a -> a | |
findMax default = foldl max default | |
findMaxNE :: ∀ f a. Ord a => Foldable1 f => f a -> a | |
findMaxNE = foldl1 max | |
sum :: ∀ f a. Foldable f => Semiring a => f a -> a | |
sum = foldl (+) zero | |
instance toListTree :: ToList Tree where | |
toList (Leaf n) = singleton n | |
toList (Node left right) = toList left <> toList right | |
instance foldableTree :: Foldable Tree where | |
foldl f i = foldl f i <<< toList | |
foldr f i = foldr f i <<< toList | |
foldMap f = foldMap f <<< toList | |
-- you could also generate a Newtype and use unwrap | |
instance toListRFTree :: ToList RFTree where | |
toList (RFTree (Leaf x)) = singleton x | |
toList (RFTree (Node lt rt)) = toList (RFTree rt) <> toList (RFTree lt) | |
instance toListLFTree :: ToList LFTree where | |
toList (LFTree (Leaf x)) = singleton x | |
toList (LFTree (Node lt rt)) = toList (LFTree lt) <> toList (LFTree rt) | |
instance foldableRFTree :: Foldable RFTree where | |
foldr f acc = foldr f acc <<< toList | |
foldl f acc = foldl f acc <<< toList | |
foldMap f = foldMap f <<< toList | |
instance foldableLFTree :: Foldable LFTree where | |
foldr f acc = foldr f acc <<< toList | |
foldl f acc = foldl f acc <<< toList | |
foldMap f = foldMap f <<< toList | |
----------- Tests --------------------------------------------------------------------------------------------------------------------- | |
test :: Effect Unit | |
test = do | |
log "Chapter 11. Use folds without folding!" | |
log $ show $ reverse (10 : 20 : 30 : Nil) -- (30 : 20 : 10 : Nil) | |
log $ show $ max (-1) 99 -- 99 | |
log $ show $ max "aa" "z" -- "z" | |
log $ show $ findMax 0 (37 : 311 : -1 : 2 : 84 : Nil) -- 311 (0 is default value) | |
log $ show $ findMax "" ("a" : "bbb" : "c" : Nil) -- "c" ("" is default value) | |
log $ show $ findMaxNE (NonEmptyList $ 37 :| (311 : -1 : 2 : 84 : Nil)) -- 311 | |
log $ show $ findMaxNE (NonEmptyList $ "a" :| ("bbb" : "c" : Nil)) -- "c" | |
log $ show $ sum (1 : 2 : 3 : Nil) -- 6 | |
log $ show $ sum (1.0 : 2.0 : 3.0 : Nil) -- 6.0 | |
log $ show $ toList (Node (Node (Leaf 5) (Node (Leaf (-1)) (Leaf 14))) (Leaf 99)) -- (5 : -1 : 14 : 99 : Nil) | |
log $ show $ sum (Node (Node (Leaf 5) (Node (Leaf (-1)) (Leaf 14))) (Leaf 99)) -- 117 | |
log $ show $ toList $ LFTree (Node (Node (Leaf 5) (Node (Leaf (-1)) (Leaf 14))) (Leaf 99)) -- (5 : -1 : 14 : 99 : Nil) | |
log $ show $ sum $ LFTree (Node (Node (Leaf 5) (Node (Leaf (-1)) (Leaf 14))) (Leaf 99)) -- 117 | |
log $ show $ toList $ RFTree (Node (Node (Leaf 5) (Node (Leaf (-1)) (Leaf 14))) (Leaf 99)) -- (99 : 14 : -1 : 5 : Nil) | |
log $ show $ sum $ RFTree (Node (Node (Leaf 5) (Node (Leaf (-1)) (Leaf 14))) (Leaf 99)) -- 117 |
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
{ name = "my-project" | |
, dependencies = [ "console", "effect", "foldable-traversable", "lists", "nonempty", "prelude", "psci-support" ] | |
, 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