Haskell/Solutions/Foldable
1.
-- We start from:
foldMap g = mconcat . fmap g
foldMap g = foldr mappend mempty . fmap g -- mconcat definition
-- Which can be simplified to:
foldMap f = foldr (mappend . f) mempty
-- Or, more pointfully:
foldMap f xs = foldr (\x z -> f x <> z) mempty xs
-- Alternatively (via the definition of foldr):
foldMap _ [] = mempty
foldMap g (x:xs) = g x <> foldMap g xs
1.
答案的總結。微妙的問題在下面的筆記中解釋。
| 摺疊 | mempty
|
mappend
|
初步 函式 |
newtype 來自Data.Monoid |
筆記 |
|---|---|---|---|---|---|
product |
1 |
(*) |
乘積 |
||
concat |
[] |
(++) |
|||
concatMap f |
[] |
(++) |
f |
||
all p |
True |
(&&) |
p |
All |
|
elem x |
False |
(||) |
(== x) |
Any |
|
length |
0 |
(+) |
const 1 |
Sum |
|
traverse_ f |
pure () |
(*>) |
void . f |
參見 [i] | |
mapM_ f |
return () |
(>>) |
void . f |
參見 [i] | |
safeMaximum |
Nothing |
max' Nothing m = m max' m Nothing = m max' (Just x) (Just y) = Just (max x y) |
參見 [ii] | ||
find p |
Nothing |
最左邊的 Just |
\x -> if p x then Just x else Nothing |
First |
參見 [iii] |
composeL f |
id |
flip (.) |
flip f |
Dual . Endo |
參見 [iv] |
筆記
[i]: 這裡的 monoid 的型別為 Applicative f => f ()。函式 void(在 Data.Functor 中定義為 fmap (const ()))用於將操作的內部值轉換為 (),從而丟棄內部值。這種轉換在基於 foldr 的實現中是不需要的(就像實際的實現一樣);然而,對於不是使用 Endo 的通用 foldMap,我們需要要麼使用 void 丟棄結果(如上所示),要麼建立一個忘記結果型別的包裝器。後一種技巧(實際上是一種相當高階的技巧)使用了一個叫做 存在量化 的功能,可能看起來像這樣
{-# LANGUAGE ExistentialQuantification #-} -- First line of the source file.
-- forall a. causes the type to be forgotten.
data NoResults f = forall a. NoResults (f a)
runNoResults :: Applicative f => NoResults f -> f ()
runNoResults (NoResults u) = const () <$> u
instance Applicative f => Monoid (NoResults f) where
mempty = NoResults (pure ())
NoResults u `mappend` NoResults v = NoResults (u *> v)
雖然這是一個時尚的解決方案,但它會產生很多問題 - 我們不能使用 newtype 或者記錄,並且仍然需要一個 fmap (const ()) 來提取最終的操作。所以把這種方法僅僅當作一個好奇心來看待吧。
在更合理的情況下,mapM_ 只是在型別簽名上與 traverse_ 不同,因為 return = pure 以及 (>>) = (*>)。這也意味著上述觀察也適用於它。
[ii]: max :: Ord a => a -> a -> a 計算出兩個引數中的較大值,而 max' :: Ord a => Maybe a -> Maybe a -> Maybe a 類似,但涉及 Maybe。這裡使用 Maybe 只是一個技巧,為型別 a 新增一個額外的 Nothing 值,以便 max' 可以成為合法的 mappend。Nothing 作為 mempty,是 max' 的單位元,因此充當一個小於或等於 a 中所有值的值(例如,對於整數來說,就像負無窮大一樣)。這個 monoid 可以用包裝器 Max 實現如下(事實上,類似的東西被用於 Data.Foldable 中 maximum 的預設實現中)。
newtype Max a = Max { unMax :: Maybe a }
instance Ord a => Monoid (Max a) where
mempty = Max Nothing
Max Nothing `mappend` x = x
x `mappend` Max Nothing = x
Max (Just x) `mappend` Max (Just y) = Max $ Just $ max x y
-- safeMaximum can then be written
safeMaximum = unMax . foldMap (Max . Just)
注意,liftA2 max 不能用作 mappend,因為 liftA2 max Nothing x = Nothing,因此 Nothing 不是 liftA2 max 的單位元,如 monoid 法則要求的那樣。
[iii]: “最左邊的 Just” 意味著
Just x `mappendFirst` _ = Just x
_ `mappendFirst` Just y = Just y
_ `mappendFirst` _ = Nothing
映象的替代方案是
_ `mappendLast` Just y = Just y
Just x `mappendLast` _ = Just x
_ `mappendLast` _ = Nothing
它們分別透過 Data.Monoid 中的 First 和 Last newtype 包裝器實現。
[iv]: 這是 高階函式 中 foldl 練習解決方案的簡化版本。Dual 是一個 Data.Monoid 包裝器,它會 flip 包裝的 Monoid 的 mappend。
1a.
instance Foldable Tree where
foldMap f t = case t of
Leaf x -> f x
Branch tl tr -> foldMap f tl <> foldMap f tr
1b.
-- Using the catamorphism
-- treeFold :: (b -> b -> b) -> (a -> b) -> Tree a -> b
treeDepth :: Tree a -> Int
treeDepth = treeFold (\dl dr -> 1 + max dl dr) (const 0)
不可能使用 Foldable 來實現 treeDepth。像列表一樣摺疊樹會破壞分支結構的資訊。這可以透過找到一對結構不同但被 toList 轉換為相同列表的樹來清楚地顯示。
1a.
instance (Monoid a, Monoid b) => Monoid (a,b) where
mempty = (mempty, mempty)
(x1, y1) `mappend` (x2, y2) = (x1 `mappend` x2, y1 `mappend` y2)
1b.
-- For given a and b
-- f :: (Monoid a, Monoid b) => a -> b
-- If f is a monoid homomorphism, then
-- f mempty = mempty
-- f (x <> y) = f x <> f y
fst (mempty, mempty) = mempty -- Target
fst (mempty, mempty) -- LHS
mempty -- Q.E.D
fst ((x1, y1) <> (x2, y2)) = fst (x1, y1) <> fst (x2, y2)
fst (x1 <> x2, y1 <> y2) = x1 <> x2
x1 <> x2 = x1 <> x2 -- Q.E.D
1c.
foldMap f &&& foldMap g = foldMap (f &&& g) -- Target
-- f &&& g = \x -> (f x, g x)
(\x -> (foldMap f x, foldMap g x)) = foldMap (\x -> (f x, g x)) -- Target 2
-- Target 2 holds if the following hold:
fst . (\x -> (foldMap f x, foldMap g x)) = fst . foldMap (\x -> (f x, g x)) -- Target 3a
snd . (\x -> (foldMap f x, foldMap g x)) = snd . foldMap (\x -> (f x, g x)) -- Target 3b
-- From Target 3a, using the monoid homomorphism property:
fst . (\x -> (foldMap f x, foldMap g x)) = foldMap (fst . (\x -> (f x, g x)))
foldMap f = foldMap f -- OK
-- From Target 3b, using the monoid homomorphism property:
snd . (\x -> (foldMap f x, foldMap g x)) = foldMap (snd . (\x -> (f x, g x)))
foldMap g = foldMap g -- OK
-- Q.E.D (both Target 3a and Target 3b hold.)