Difference between revisions of "Foldable Traversable In Prelude"

From HaskellWiki
Jump to navigation Jump to search
Line 161: Line 161:
 
Additionally, toList, elem, sum, product, maximum, and minimum, before given as methods on Foldable items are now optional methods in the Foldable class.
 
Additionally, toList, elem, sum, product, maximum, and minimum, before given as methods on Foldable items are now optional methods in the Foldable class.
   
Finally, note that the addition of "length" and "null" to Foldable are technically a separate proposal but are often discussed in conjunction with the FTP.
+
Finally, note that the addition of "length," "null," "toList," and "elem" to Foldable are technically a separate proposal but are often discussed in conjunction with the FTP. Meanwhile the addition of "sum," "product," "maximum," and "minimum" are considered part of the FTP, as will be discussed below.
   
 
== Wow, that's a lot of changes! ==
 
== Wow, that's a lot of changes! ==
Line 170: Line 170:
   
 
Many people import Control.Monad unqualified. If we continued to export the monomorphic functions from Control.Monad, this would lead to many clashes, and much code would break. Now, all that remaining code still works!
 
Many people import Control.Monad unqualified. If we continued to export the monomorphic functions from Control.Monad, this would lead to many clashes, and much code would break. Now, all that remaining code still works!
  +
  +
We could instead drop those functions from Control.Monad instead of reexporting their more polymorphic versions. But this would cause breakages for those who imported them explicitly or qualified. Now that code still works too!
   
 
== But, why does Data.List also generalize its functions? ==
 
== But, why does Data.List also generalize its functions? ==
   
 
Many people import Data.List unqualified. If we continued to export the monomorphic functions from Data.List, this would lead to many clashes, and much code would break. Now, all that remaining code still works!
 
Many people import Data.List unqualified. If we continued to export the monomorphic functions from Data.List, this would lead to many clashes, and much code would break. Now, all that remaining code still works!
  +
  +
We could instead drop those functions from Data.List instead of reexporting their more polymorphic versions. But this would cause breakages for those who imported them explicitly or qualified. Now that code still works too!
   
 
== OK, but why does the Foldable class have so many methods in it? ==
 
== OK, but why does the Foldable class have so many methods in it? ==
Line 181: Line 185:
 
Other methods in the Foldable class, such as foldl and foldr exist for historical reasons, and to allow the possibility of more efficient implementations. Methods such as sum and product were added because their prelude versions were performed with a foldl, while their general versions with a foldMap. Moving them into the class allowed Prelude behaviour to be preserved in the case of lists without altering behaviour otherwise in the case of other structures.
 
Other methods in the Foldable class, such as foldl and foldr exist for historical reasons, and to allow the possibility of more efficient implementations. Methods such as sum and product were added because their prelude versions were performed with a foldl, while their general versions with a foldMap. Moving them into the class allowed Prelude behaviour to be preserved in the case of lists without altering behaviour otherwise in the case of other structures.
   
Finally, length and null were added because they permit potentially O(1) implementations on many structures, and it seemed desirable to allow users to take advantage of this asymptotically more efficient behaviour.
+
Finally, toList and elem were pulled into the class and length and null were added to both the module and the class because they permit potentially more efficient implementations on many structures (with null and length being sometimes, for example O(1)), and it seemed desirable to allow users to take advantage of this asymptotically more efficient behaviour.

Revision as of 21:06, 28 January 2015

This page is a FAQ for the FTP (Foldable/Traversable in Prelude proposal) otherwise known as the BBP (Burning Bridges Proposal), slated for inclusion in the core libraries of GHC 7.10. While elements of this proposal may still be under discussion, this page is intended to summarize the proposal as it now stands as of 28 January, 2015. It is a work in progress, done as best as possible, but should not be taken as necessarily a full statement by the libraries committee on every aspect of this proposal.

Where did the FTP come from?

The FTP was proposed in the context of a very lengthy "Burning Bridges" thread on the haskell libraries list in the summer of 2013.

Over the course of this thread and subsequent and related discussions it was revealed there was a large appetite in the community to "modernize" the Prelude and bring it into line with the current widespread usage of classes such as Applicative, Foldable, and Traversable. Out of these discussions, a "Core Libraries Committee" was formed to manage and steward such large changes in a way to vet them thoroughly and ensure minimal breakage in carrying them out.

What does the FTP do?

The FTP does what it says. It brings Foldable and Traversable into the Prelude. Along with this, it replaces Prelude functions that clash with Foldable and Traversable with their more polymorphic versions as drawn from those two classes and their associated methods. One goal here is that people should be able to use methods from these modules without the need of a qualified import -- i.e. to prevent clash in the namespace, by resolving such in favor of the more generalized versions. Additionally, there are some new methods added to the Foldable class because it seems to be the "right" thing. This proposal is semi-independent from the rest of FTP, but the changes tend to have been discussed under the same general umbrella.

Does the FTP change any behaviour?

No. By design, any code that compiles under these changes should operate exactly as prior to these changes. If you believe you have found an area where these changes cause a semantic difference, it is a bug and should be reported.

So does the FTP break any code?

As little as possible. Many of the seemingly "odd" aspects of FTP come from engineering choices made specifically so as to minimize code breakage. In particular, a few packages may be broken by new exports from the prelude such as mconcat and foldMap. A few more may be broken by the export of new additions to the Foldable class. And finally, there are a few packages that may be broken by the new generalized signature in the prelude not being sufficient to pin down some otherwise already polymorphic code (particularly in the case of using -XOverloadedStrings).

On the other hand, 569 packages in Stackage, including the core of it, build without problems. According to Edward Kmett, "of the 50-100 that remain, most are awaiting author feedback on already-filed issues / fixes or are broken by a small change downstream."

What are the concrete changes in the FTP?

Here is a diff of the relevant changes. Note that there are other changes, not listed here, notably those introduced by the "AMP", which makes Applicative a superclass of Monad.

 Control.Monad
- foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a
+ foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m ()
+ foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- forM :: Monad m => [a] -> (a -> m b) -> m [b]
+ forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- forM_ :: Monad m => [a] -> (a -> m b) -> m ()
+ forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- mapM :: Monad m => (a -> m b) -> [a] -> m [b]
+ mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
+ mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- msum :: MonadPlus m => [m a] -> m a
+ msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- sequence :: Monad m => [m a] -> m [a]
+ sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- sequence_ :: Monad m => [m a] -> m ()
+ sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()

Data.List
- all :: (a -> Bool) -> [a] -> Bool
+ all :: Foldable t => (a -> Bool) -> t a -> Bool
- and :: [Bool] -> Bool
+ and :: Foldable t => t Bool -> Bool
- any :: (a -> Bool) -> [a] -> Bool
+ any :: Foldable t => (a -> Bool) -> t a -> Bool
- concat :: [[a]] -> [a]
+ concat :: Foldable t => t [a] -> [a]
- concatMap :: (a -> [b]) -> [a] -> [b]
+ concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- elem :: Eq a => a -> [a] -> Bool
+ elem :: (Foldable t, Eq a) => a -> t a -> Bool
- find :: (a -> Bool) -> [a] -> Maybe a
+ find :: Foldable t => (a -> Bool) -> t a -> Maybe a
- foldl :: (b -> a -> b) -> b -> [a] -> b
+ foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl' :: (b -> a -> b) -> b -> [a] -> b
+ foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl1 :: (a -> a -> a) -> [a] -> a
+ foldl1 :: Foldable t => (a -> a -> a) -> t a -> a
- foldr :: (a -> b -> b) -> b -> [a] -> b
+ foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- foldr1 :: (a -> a -> a) -> [a] -> a
+ foldr1 :: Foldable t => (a -> a -> a) -> t a -> a
+ isSubsequenceOf :: (Eq a) => [a] -> [a] -> Bool
- length :: [a] -> Int
+ length :: Foldable t => t a -> Int
- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
+ mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
+ mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
- maximum :: Ord a => [a] -> a
+ maximum :: (Foldable t, Ord a) => t a -> a
- maximumBy :: (a -> a -> Ordering) -> [a] -> a
+ maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- minimum :: Ord a => [a] -> a
+ minimum :: (Foldable t, Ord a) => t a -> a
- minimumBy :: (a -> a -> Ordering) -> [a] -> a
+ minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a
- notElem :: Eq a => a -> [a] -> Bool
+ notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- null :: [a] -> Bool
+ null :: Foldable t => t a -> Bool
- or :: [Bool] -> Bool
+ or :: Foldable t => t Bool -> Bool
- product :: Num a => [a] -> a
+ product :: (Foldable t, Num a) => t a -> a
+ scanl' :: (b -> a -> b) -> b -> [a] -> [b]
+ sortOn :: Ord b => (a -> b) -> [a] -> [a]
- sum :: Num a => [a] -> a
+ sum :: (Foldable t, Num a) => t a -> a
+ uncons :: [a] -> Maybe (a, [a])

Prelude
- all :: (a -> Bool) -> [a] -> Bool
+ all :: Foldable t => (a -> Bool) -> t a -> Bool
- and :: [Bool] -> Bool
+ and :: Foldable t => t Bool -> Bool
- any :: (a -> Bool) -> [a] -> Bool
+ any :: Foldable t => (a -> Bool) -> t a -> Bool
+ class Monoid a
+ class Foldable t
+ class (Functor t, Foldable t) => Traversable t
- concat :: [[a]] -> [a]
+ concat :: Foldable t => t [a] -> [a]
- concatMap :: (a -> [b]) -> [a] -> [b]
+ concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- elem :: Eq a => a -> [a] -> Bool
+ elem :: (Foldable t, Eq a) => a -> t a -> Bool
+ foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m
- foldl :: (b -> a -> b) -> b -> [a] -> b
+ foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl1 :: (a -> a -> a) -> [a] -> a
+ foldl1 :: Foldable t => (a -> a -> a) -> t a -> a
- foldr :: (a -> b -> b) -> b -> [a] -> b
+ foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- foldr1 :: (a -> a -> a) -> [a] -> a
+ foldr1 :: Foldable t => (a -> a -> a) -> t a -> a
- length :: [a] -> Int
+ length :: Foldable t => t a -> Int
- mapM :: Monad m => (a -> m b) -> [a] -> m [b]
+ mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- mapM_ :: Monad m => (a -> m b) -> [a] -> m ()
+ mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
+ mappend :: Monoid a => a -> a -> a
- maximum :: Ord a => [a] -> a
+ maximum :: (Foldable t, Ord a) => t a -> a
+ mconcat :: Monoid a => [a] -> a
+ mempty :: Monoid a => a
- minimum :: Ord a => [a] -> a
+ minimum :: (Foldable t, Ord a) => t a -> a
- notElem :: Eq a => a -> [a] -> Bool
+ notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- null :: [a] -> Bool
+ null :: Foldable t => t a -> Bool
- or :: [Bool] -> Bool
+ or :: Foldable t => t Bool -> Bool
- product :: Num a => [a] -> a
+ product :: (Foldable t, Num a) => t a -> a
- sequence :: Monad m => [m a] -> m [a]
+ sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
+ sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a)
- sequence_ :: Monad m => [m a] -> m ()
+ sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- sum :: Num a => [a] -> a
+ sum :: (Foldable t, Num a) => t a -> a
+ traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)

Data.Foldable
+ length :: Foldable t => t a -> Int
+ null :: Foldable t => t a -> Bool

Additionally, toList, elem, sum, product, maximum, and minimum, before given as methods on Foldable items are now optional methods in the Foldable class.

Finally, note that the addition of "length," "null," "toList," and "elem" to Foldable are technically a separate proposal but are often discussed in conjunction with the FTP. Meanwhile the addition of "sum," "product," "maximum," and "minimum" are considered part of the FTP, as will be discussed below.

Wow, that's a lot of changes!

Well, yes and no. As you can see, these changes are all essentially strict generalizations of existing functions, which was indeed the goal.

But, why does Control.Monad also generalize its functions?

Many people import Control.Monad unqualified. If we continued to export the monomorphic functions from Control.Monad, this would lead to many clashes, and much code would break. Now, all that remaining code still works!

We could instead drop those functions from Control.Monad instead of reexporting their more polymorphic versions. But this would cause breakages for those who imported them explicitly or qualified. Now that code still works too!

But, why does Data.List also generalize its functions?

Many people import Data.List unqualified. If we continued to export the monomorphic functions from Data.List, this would lead to many clashes, and much code would break. Now, all that remaining code still works!

We could instead drop those functions from Data.List instead of reexporting their more polymorphic versions. But this would cause breakages for those who imported them explicitly or qualified. Now that code still works too!

OK, but why does the Foldable class have so many methods in it?

Well, Foldable cannot just be given by toList, much as we might think of it as such. foldMap lets us fold over not only potentially right-infinite structures as with foldr, but potentially left-infinite ones (as with foldl) and even "both-infinite" ones such as rooted but infinitely branching trees!

Other methods in the Foldable class, such as foldl and foldr exist for historical reasons, and to allow the possibility of more efficient implementations. Methods such as sum and product were added because their prelude versions were performed with a foldl, while their general versions with a foldMap. Moving them into the class allowed Prelude behaviour to be preserved in the case of lists without altering behaviour otherwise in the case of other structures.

Finally, toList and elem were pulled into the class and length and null were added to both the module and the class because they permit potentially more efficient implementations on many structures (with null and length being sometimes, for example O(1)), and it seemed desirable to allow users to take advantage of this asymptotically more efficient behaviour.