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" <baldurpet@gmail.com> wrote:> -- Same as ‘Control.Lens.Indexed.None’> take n = toListOf (taking n folded)> take :: Int -> (forall f a. Foldable f => f a -> [a])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’> catMaybes = foldMap toList> catMaybes :: (Foldable f) => f (Maybe a) -> [a]> maybeToList = toListA 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]
> catMaybes :: (Foldable f, Foldable g) => f (g a) -> [a]
> 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)
> 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)> 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 foldedwhile 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 traverseMore 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) for> flip :: (Functor f, Distributive g) => f (g a) -> g (f a)
> flip = Data.Distributive.distributeAMP happened some years ago, does this go too far or not far enough? ;) share your thoughtsP.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")]
_______________________________________________
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