Skip to content

Instantly share code, notes, and snippets.

@jiamo
Last active May 27, 2018 17:31
Show Gist options
  • Save jiamo/682fc4168791869b23439787a2aeaaab to your computer and use it in GitHub Desktop.
Save jiamo/682fc4168791869b23439787a2aeaaab to your computer and use it in GitHub Desktop.
high order function transform simple 2
module Cartesian_product2 where
import Prelude hiding(product)
-- introduce mapa
map' :: (b->a) -> [b] -> [a]
map' g l = foldr' f [] l where
f x y = (g x) : y
foldr' :: (a -> b -> b) -> b -> [a] -> b
foldr' f z [] = z
foldr' f z (a:as) = f a (foldr' f z as)
mapa :: (b -> a) -> [a] -> [b] -> [a]
mapa g z l = (map g l) ++ z
mapa' :: (b -> a) -> [a] -> [b] -> [a]
mapa' g z l = foldr f z l where
f x y = (g x):y
-- introduce mapa finish
--- Where the
cartProdN1 :: [[a]] -> [[a]]
cartProdN1 [] = [[]]
cartProdN1 (xs:yss) = [ x:ys | x <- xs, ys <- cartProdN1 yss ]
--- Can we see a foldr strunct? we need a help function
cartProdN1' :: [[a]] -> [[a]]
cartProdN1' xss =
h xss where
h [] = [[]]
h (xs:yss) = [ x:ys | x <- xs, ys <- h yss ]
-- we can take (h yss) as yss
cartProdN1'' :: [[a]] -> [[a]]
cartProdN1'' xss =
h xss where
h [] = [[]]
h (xs:yss) = g xs (h yss) where
g xs yss = [x:ys | x <- xs, ys <- yss]
-- now we have pattern struct like foldr g is the runtime f in foldr
-- just foldr it
cartProdN2 :: [[a]] -> [[a]]
cartProdN2 xss =
foldr h [[]] xss where
h xs yss = [x:ys | x <- xs, ys <- yss]
cartProdN3 :: [[a]] -> [[a]]
cartProdN3 xss =
foldr h [[]] xss where
h [] yss = []
h xs yss = [x:ys | x <- xs, ys <- yss]
cartProdN4 :: [[a]] -> [[a]]
cartProdN4 xss =
foldr h [[]] xss where
h [] yss = []
h (x:xs) yss =
map (x:) yss ++ [x:ys| x <- xs, ys <- yss]
-- what the list comprehension does is h itself.
cartProdN5 :: [[a]] -> [[a]]
cartProdN5 xss =
foldr h [[]] xss where
h [] yss = []
h (x:xs) yss = (map (x:) yss) ++ (h xs yss)
cartProdN6 :: [[a]] -> [[a]]
cartProdN6 xss =
foldr h [[]] xss where
h [] yss = []
h (x:xs) yss = mapa (x:) (h xs yss) yss
cartProdN7 :: [[a]] -> [[a]]
cartProdN7 xss =
foldr h [[]] xss where
h [] yss = []
h (x:xs) yss = foldr f (h xs yss) yss where
f xs yss = (x:xs):yss
-- here x: is g in mapa'
-- xs yss in f is scope in f not h
cartProdN8 :: [[a]] -> [[a]]
cartProdN8 xss =
foldr h [[]] xss where
h xs yss = h' xs
where
h' [] = []
h' (x:xs) = foldr f (h' xs) yss where
f xs yss = (x:xs):yss
-- why h' here should understand recurisve
-- (h xs yss) in cartProdN7
-- (h' xs) cartProdN8 then are recurisve sturct
-- we can think (h' xs) is the work just have done
-- is the same as (h xs yss) in cartProdN7
-- introduce a helper g
-- https://stackoverflow.com/questions/50447596/it-is-hard-to-understand-to-a-transform-foldr-in-cartesian-product
cartProdN9 :: [[a]] -> [[a]]
cartProdN9 xss =
foldr h1 [[]] xss where
h1 xs yss = h' xs
where
h' [] = []
h' (x:xs) = g x (h' xs)
g x zss = foldr f zss yss
where
f xs yss = (x:xs):yss
--- here g is f in foldr as runtime args pass to h'
cartProdN10 :: [[a]] -> [[a]]
cartProdN10 xss =
foldr h1 [[]] xss where
h1 xs yss = foldr g [] xs where
g x zss = foldr f zss yss where
f xs yss = (x:xs):yss
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment