
I'd also be -1. Function generalization sometimes has a cost in comprehensability, and there aren't enough benefits to make it worth it to me. Tom
El 27 nov 2016, a las 01:53, David Feuer
escribió: I disagree with many of these. For example, I think of takeWhile as having a type shaped like
takeWhile :: (a -> Bool) -> f a -> f a
Implementations are available for, e.g., sequences, sets, and maps. I don't really want some silly list producer. If I want takeWhile.toList, I know where to get it. Similarly, if I want distribute (which I haven't yet), I know where to get it. Some of these proposals also have substantial performance penalties, such as the sort generalization (which also can't be written in an "obviously total" manner, unfortunately).
On Nov 27, 2016 2:10 AM, "Baldur Blöndal"
wrote: A year ago Edwardk Kmett pointed out some possible generalizations of functions [1], I made a ticket about them that led me here [2]. In addition to the functions mentioned maybeToList :: Foldable f => f a -> [a] maybeToList = toList
catMaybes :: (Foldable f) => f (Maybe a) -> [a] catMaybes :: (Foldable f, Foldable g) => f (g a) -> [a] catMaybes = foldMap toList
mapMaybes :: (a -> Maybe b) -> (forall f. Foldable f => f a -> [b]) mapMaybes :: Foldable m => (a -> m b) -> (forall f. Foldable f => f a -> [b]) mapMaybes f = foldMap (toList . f)
we also have *many* other functions (I do not propose generalising all these function ((especially when the name stops making sense)), but I will include them) that I will define in the vocabulary of ‘lens’. Some generalise to ‘Foldable’
take :: Int -> (forall f a. Foldable f => f a -> [a]) take n = toListOf (taking n folded)
drop :: Int -> (forall f a. Foldable f => f a -> [a]) drop n = toListOf (dropping n folded)
takeWhile :: (a -> Bool) -> (forall f. Foldable f => f a -> [a]) takeWhile p = toListOf (takingWhile p folded)
dropWhile :: (a -> Bool) -> (forall f. Foldable f => f a -> [a]) dropWhile p = toListOf (droppingWhile p folded)
-- Same as ‘Control.Lens.Indexed.None’ filter :: (a -> Bool) -> (forall f. Foldable f => f a -> [a]) filter p = toListOf (folded.filtered p)
cycle :: Foldable f => f a -> [a] cycle = toListOf (cycled folded)
lookup :: Eq k => k -> (forall f. Foldable f => f (k, v) -> Maybe v) lookup = lookupOf folded
listToMaybe :: Foldable f => f a -> Maybe a listToMaybe = firstOf folded
while others — to ‘Traversable’
transpose :: Traversable f => f [b] -> [f b] transpose = transposeOf traverse
scanl1 :: (a -> a -> a) -> (forall f. Traversable f => f a -> f a) scanl1 = scanl1Of traverse
scanr1_ :: (a -> a -> a) -> (forall f. Traversable f => f a -> f a) scanr1_ = scanr1Of traverse
More radical suggestions (pay no heed to the hacky ‘partsOf’, assume better implementation [3]) would allow us to sort a ‘data V2 a = V2 a a deriving (…, Traversable)’ if it contains ordered values:
sort :: (Traversable t, Ord a) => t a -> t a sort = over (partsOf traverse) Data.List.sort
sortBy :: (a -> a -> Ordering) -> ([a] -> [a]) sortBy = over (partsOf traverse) . Data.List.sortBy
sortOn :: Ord b => (a -> b) -> ([a] -> [a]) sortOn = over (partsOf traverse) . Data.List.sortOn
reverse :: Traversable t => t a -> t a reverse = over (partsOf traverse) Data.List.reverse
-- Based on ‘Control.Lens.??’ flip :: Functor f => f (a -> b) -> a -> f b flip f x = fmap ($ x) f
or
flip :: (Functor f, Distributive g) => f (g a) -> g (f a) flip = Data.Distributive.distribute
AMP happened some years ago, does this go too far or not far enough? ;) share your thoughts
P.s. I understand those skeptical of the ‘partsOf’ solutions but they do feel magical and uses crop up in odd places, especially in compound structures (I don't have better examples):
ghci> peopleList = Pair ["Bob", "Eve"] (Just "Alice") ghci> data Product f g a = Pair (f a) (g a) deriving (Show, Functor, Foldable, Traversable) ghci> sort peopleList Pair ["Alice","Bob"] (Just "Eve") ghci> reverse peopleList Pair ["Alice","Eve"] (Just "Bob")
ghci> peopleMap = fromList [(1,"Bob"),(2,"Eve"),(3,"Alice")] ghci> sort peopleMap fromList [(1,"Alice"),(2,"Bob"),(3,"Eve")] ghci> reverse peopleMap fromList [(1,"Alice"),(2,"Eve"),(3,"Bob")]
[1] https://www.reddit.com/r/haskell/comments/2y2pe5/shouldnt_ftp_propagate_chan... [2] https://ghc.haskell.org/trac/ghc/ticket/12828 [3] http://stackoverflow.com/a/33320155/165806
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries