Many functions can be generalised

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

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"
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_changes_over_the_entire/cp6vpb4/ [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

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

On Sun, 27 Nov 2016, amindfv@gmail.com wrote:
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.
And you lose type inference in more cases.
maybeToList :: Foldable f => f a -> [a] maybeToList = toList
Why should we have two names for Foldable.toList, where maybeToList even is no longer special to Maybe?
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)
cycle :: Foldable f => f a -> [a] cycle = toListOf (cycled folded)
I'd prefer an extension to Monoid, i.e. take :: (??? m) => Int -> m -> m drop :: (??? m) => Int -> m -> m cycle :: (Semigroup m) => m -> m Yet, I do not propose to replace Prelude functions by this generalisations.

(I meant FTP, not AMP) Fine points, the proposal wasn't a smashing hit but the response has been jolly good. What about functions that aren't expected to preserve structure like ‘lookup’ and (new) suggestions
lookup :: Eq a => k -> Foldable f => f (k, v) -> Maybe v lookup = lookupOf folded
elemIndex :: Eq a => a -> Foldable f => f a -> Maybe Int elemIndex = elemIndexOf folded
elemIndices :: Eq a => a -> Foldable f => f a -> Maybe Int elemIndices = elemIndicesOf folded
findIndex :: (a -> Bool) -> Foldable f => f a -> Maybe Int findIndex = findIndexOf folded
findIndices :: (a -> Bool) -> Foldable f => f a -> [Int] findIndices = findIndicesOf folded
and the few that do fit that pattern such as ‘scanl1’, ‘scanr1’, possibly ‘transpose’ as well. P.s. At least I did not propose ↓ yet :)
shuffleM :: (Foldable f, MonadRandom m) => f a -> m (f a)
class ... => Sort f where sort :: Ord a => f a -> f a sort = over (partsOf traverse) Data.List.sort default sort :: Ord a => Traversable f => f a -> f a
2016-11-27 7:53 GMT+00:00 David Feuer
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_changes_over_the_entire/cp6vpb4/ [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

`lookup`, and the rest of the association list nonsense, are the wrong
shape to generalize altogether. Please don't try. I wish they weren't in
there at all. Some other things you mention might work; I'll have to look
more closely.
On Nov 30, 2016 4:08 AM, "Baldur Blöndal"
(I meant FTP, not AMP)
Fine points, the proposal wasn't a smashing hit but the response has been jolly good.
What about functions that aren't expected to preserve structure like ‘lookup’ and (new) suggestions
lookup :: Eq a => k -> Foldable f => f (k, v) -> Maybe v lookup = lookupOf folded
elemIndex :: Eq a => a -> Foldable f => f a -> Maybe Int elemIndex = elemIndexOf folded
elemIndices :: Eq a => a -> Foldable f => f a -> Maybe Int elemIndices = elemIndicesOf folded
findIndex :: (a -> Bool) -> Foldable f => f a -> Maybe Int findIndex = findIndexOf folded
findIndices :: (a -> Bool) -> Foldable f => f a -> [Int] findIndices = findIndicesOf folded
and the few that do fit that pattern such as ‘scanl1’, ‘scanr1’, possibly ‘transpose’ as well.
P.s. At least I did not propose ↓ yet :)
shuffleM :: (Foldable f, MonadRandom m) => f a -> m (f a)
class ... => Sort f where sort :: Ord a => f a -> f a sort = over (partsOf traverse) Data.List.sort default sort :: Ord a => Traversable f => f a -> f a
2016-11-27 7:53 GMT+00:00 David Feuer
: 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_ft p_propagate_changes_over_the_entire/cp6vpb4/ [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

On 09:08 Wed 30 Nov , Baldur Blöndal wrote:
P.s. At least I did not propose ↓ yet :)
shuffleM :: (Foldable f, MonadRandom m) => f a -> m (f a)
This would be an utter nonsense, given that many if not most foldables either don't have an order like Set or must have very specific order like different kinds of trees and therefore cannot be shuffled.

This was probably supposed to be a Traversable constraint. I still suspect
it would be unwise, because there may be data structures that can be
shuffled more efficiently than this type would allow.
On Nov 30, 2016 6:22 PM, "Lana Black"
On 09:08 Wed 30 Nov , Baldur Blöndal wrote:
P.s. At least I did not propose ↓ yet :)
shuffleM :: (Foldable f, MonadRandom m) => f a -> m (f a)
This would be an utter nonsense, given that many if not most foldables either don't have an order like Set or must have very specific order like different kinds of trees and therefore cannot be shuffled. _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On 2016-11-30 04:08 AM, Baldur Blöndal wrote:
What about functions that aren't expected to preserve structure like ‘lookup’ and (new) suggestions
lookup :: Eq a => k -> Foldable f => f (k, v) -> Maybe v lookup = lookupOf folded
-1. It needs to die.
elemIndex :: Eq a => a -> Foldable f => f a -> Maybe Int elemIndex = elemIndexOf folded
elemIndices :: Eq a => a -> Foldable f => f a -> Maybe Int elemIndices = elemIndicesOf folded
findIndex :: (a -> Bool) -> Foldable f => f a -> Maybe Int findIndex = findIndexOf folded
findIndices :: (a -> Bool) -> Foldable f => f a -> [Int] findIndices = findIndicesOf folded
I'm +0.5 on these but only if they come in together with the (!!) operator, which should then be added as a Foldable class method to allow for optimizations. Without (!!) there'd be no way to express the laws these operations need to satisfy.

On 07:10 Sun 27 Nov , Baldur Blöndal wrote:
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)
These two as well as 'filter' are generalized in witherable[1]. [1]: https://hackage.haskell.org/package/witherable/

On Sun, Nov 27, 2016 at 9:08 AM, Lana Black
On 07:10 Sun 27 Nov , Baldur Blöndal wrote:
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)
These two as well as 'filter' are generalized in witherable[1].
I'm also -1 to the OP. If we want to do these sorts of generalizations, then we should use something like witherable and get that API to where everyone agrees it captures the right concept. Just because we *can* go polymorphic as above doesn't mean those are the proper generalizations. Anything sequential can be made into lists, but that doesn't mean lists are appropriate; lists lose a lot of information. I'd much rather see the above functions as: mapMaybes :: Foo f => (a -> Maybe b) -> f a -> f b catMaybes :: Foo f => f (Maybe a) -> f a Note how the f-structure is retained, rather than being needlessly converted to a list. The above signatures capture the idea that f is "sparse" and can absorb missing values, which is a coherent concept that should have some nice laws we can exploit to clean up our code. Indeed, the Witherable class takes this approach (though it has an unfortunate Traversable dependency I don't think is always appropriate). -- Live well, ~wren

On Mon, Nov 28, 2016 at 4:41 PM, wren romano
I'd much rather see the above functions as:
mapMaybes :: Foo f => (a -> Maybe b) -> f a -> f b catMaybes :: Foo f => f (Maybe a) -> f a
A while back, I found myself deriving this class:
class Functor f => Siftable f where
siftWith :: (a -> Maybe b) -> f a -> f b
sift :: (a -> Bool) -> f a -> f a
sift f = siftWith (\a -> if f a then Just a else Nothing)
which is essentially Witherable minus Traversable. It has the nice property
that it’s a functor from the Kleisli category for Maybe to Hask, so the
laws are intuitive and easily expressed. You can even express wither using
siftWith and traverse
wither :: (Siftable t, Traversable t, Applicative f) => (a -> f (Maybe
b)) -> t a -> f (t b)
wither f = fmap (siftWith id) . traverse f
But it turns out that there aren’t many instances of Siftable that aren’t
also Traversable. The most obvious would be infinite streams, but even they
have a traversal if you restrict yourself to lazy applicatives.
--
Dave Menendez

On Dec 2, 2016 6:14 PM, "David Menendez"

On Sat, Dec 3, 2016 at 12:50 AM, David Feuer
On Dec 2, 2016 6:14 PM, "David Menendez"
wrote: A while back, I found myself deriving this class:
class Functor f => Siftable f where siftWith :: (a -> Maybe b) -> f a -> f b sift :: (a -> Bool) -> f a -> f a sift f = siftWith (\a -> if f a then Just a else Nothing)
I would expect several classes, corresponding to different methods of Witherable:
class Siftable a m | m -> a where sift :: (a -> Bool) -> m -> m default sift :: SiftWithable f => (a -> Bool) -> f a -> f a sift p = siftWith (\x -> x <$ guard (p x))
class Functor f => SiftWithable f where siftWith :: (a -> Maybe b) -> f a -> f b
class Siftable a m => SiftableA a m where siftA :: Applicative g => (a -> g Bool) -> m -> g m default siftA :: (SiftWithAAble f, Applicative g) => (a -> g Bool) -> f a -> g (f a) siftA p = siftWithA (\x -> (x <$) . guard <$> p x)
class (Traversable f, SiftWithAble f) => SiftWithAAble f where siftWithA :: Applicative g => (a -> g (Maybe b)) -> f a -> g (f a)
Yes, sift is more general than siftWith (which I should have called
siftMap, in hindsight). But, so far as I know, the only things you can
define sift for but not siftWith are sets and set-like things.
At the time, I had also rejected sift by itself because I couldn’t think of
any laws, but now that I look at it again, I guess they would be:
sift (const True) = id
sift (\x -> p x && q x) = sift q . sift p
I think those would make sift a monoid homomorphism.
These still allow some weird instances, like sift _ = id, or something like
this:
newtype Weird a = Map a Bool
instance Ord a => Siftable a (Weird a) where
sift p (Weird m) = Weird (Map.union (Map.updateMin (const False)
yes) no)
where
(yes, no) = Map.partitionWithKey (const . p) m
I imagine it isn’t worth making the laws tighter to forbid this.
--
Dave Menendez

You can also sift monomorphic containers using my class, which should
probably be called MonoSiftable.
data IntList = Cons !Int IntList | Nil
instance Siftable Int IntList where
sift _ Nil = Nil
sift p (Cons x xs)
| p x = Cons x (sift p xs)
| otherwise = sift p xs
On Dec 3, 2016 2:17 PM, "David Menendez"
On Sat, Dec 3, 2016 at 12:50 AM, David Feuer
wrote: On Dec 2, 2016 6:14 PM, "David Menendez"
wrote: A while back, I found myself deriving this class:
class Functor f => Siftable f where siftWith :: (a -> Maybe b) -> f a -> f b sift :: (a -> Bool) -> f a -> f a sift f = siftWith (\a -> if f a then Just a else Nothing)
I would expect several classes, corresponding to different methods of Witherable:
class Siftable a m | m -> a where sift :: (a -> Bool) -> m -> m default sift :: SiftWithable f => (a -> Bool) -> f a -> f a sift p = siftWith (\x -> x <$ guard (p x))
class Functor f => SiftWithable f where siftWith :: (a -> Maybe b) -> f a -> f b
class Siftable a m => SiftableA a m where siftA :: Applicative g => (a -> g Bool) -> m -> g m default siftA :: (SiftWithAAble f, Applicative g) => (a -> g Bool) -> f a -> g (f a) siftA p = siftWithA (\x -> (x <$) . guard <$> p x)
class (Traversable f, SiftWithAble f) => SiftWithAAble f where siftWithA :: Applicative g => (a -> g (Maybe b)) -> f a -> g (f a)
Yes, sift is more general than siftWith (which I should have called siftMap, in hindsight). But, so far as I know, the only things you can define sift for but not siftWith are sets and set-like things.
At the time, I had also rejected sift by itself because I couldn’t think of any laws, but now that I look at it again, I guess they would be:
sift (const True) = id sift (\x -> p x && q x) = sift q . sift p
I think those would make sift a monoid homomorphism.
These still allow some weird instances, like sift _ = id, or something like this:
newtype Weird a = Map a Bool
instance Ord a => Siftable a (Weird a) where sift p (Weird m) = Weird (Map.union (Map.updateMin (const False) yes) no) where (yes, no) = Map.partitionWithKey (const . p) m
I imagine it isn’t worth making the laws tighter to forbid this.
-- Dave Menendez
http://www.eyrie.org/~zednenem/

On Sat, Dec 3, 2016 at 2:32 PM, David Feuer
You can also sift monomorphic containers using my class, which should probably be called MonoSiftable.
data IntList = Cons !Int IntList | Nil
instance Siftable Int IntList where sift _ Nil = Nil sift p (Cons x xs) | p x = Cons x (sift p xs) | otherwise = sift p xs
You can also use it with contra-variant or invariant type constructors,
e.g.,
instance Siftable a (a -> Bool) where
sift f g = \x -> f x && g x
--
Dave Menendez

On Dec 4, 2016 12:22 AM, "David Menendez"

On Sun, Dec 4, 2016 at 12:44 AM, David Feuer
On Dec 4, 2016 12:22 AM, "David Menendez"
wrote: You can also use it with contra-variant or invariant type constructors, e.g.,
instance Siftable a (a -> Bool) where sift f g = \x -> f x && g x
That looks backwards for your composition law, but I'm a bit tired so I wouldn't swear to it.
You’re right. Of course, they’re all the same if we assume total functions. Surely you can do the same with the constructor class.
newtype Ab a = Ab (a -> Bool) instance Siftable Ab where siftAway _ = Ab (const False) sift p (Ab g) = Ab ...
Ab is contravariant, so you would need something like siftContraMap :: (a -> Maybe b) -> f b -> f a
I'm not sure if my siftAway excludes anything it shouldn't....
I’m not sure it’s possible to define siftAway so that it isn’t equal to
sift (const Nothing).
--
Dave Menendez

On Sun, Dec 4, 2016 at 6:45 PM, David Menendez
Surely you can do the same with the constructor class.
newtype Ab a = Ab (a -> Bool) instance Siftable Ab where siftAway _ = Ab (const False) sift p (Ab g) = Ab ...
Ab is contravariant, so you would need something like
siftContraMap :: (a -> Maybe b) -> f b -> f a
That's the Functor version, which entirely excludes contravariant things. For the plain sift :: (a -> Bool) -> f a -> f a version, you can use instance Siftable Ab where sift f (Ab g) = Ab (\x -> g x && f x) siftAway (Ab g) = Ab (const False)
I'm not sure if my siftAway excludes anything it shouldn't....
I’m not sure it’s possible to define siftAway so that it isn’t equal to sift (const Nothing).
As you pointed out, your laws for the plain Siftable don't exclude sift _ = id for an arbitrary Siftable. Adding siftAway with that law ensures that sift (const Nothing) actually "empties" the container. I doubt it actually makes sense to add it to the API, though. As for names, I think for consistency with the rest of the world, the method names that make the most sense are filter, mapMaybe, filterM, and traverseMaybe. The filterM name is a bit unfortunate, since it only needs an Applicative constraint, but that seems to be what people like. The monad-extras package uses the name mapMaybeM, but that strikes me as a terrible name because it's really much more like traverse than like map. David
participants (8)
-
amindfv@gmail.com
-
Baldur Blöndal
-
David Feuer
-
David Menendez
-
Henning Thielemann
-
Lana Black
-
Mario Blažević
-
wren romano