
I'm looking for a class abstracting Data.List. I mean something that enable the use of say head, map, take and so on into different kind of types. Is there already something like that? Giacomo

Hi, I'm very new to Haskell and I don't know about head, take, etc. but I
think the `Functor` class (and its `fmap` function) provides the
abstraction for `map` (which, in my understanding, can be considered the
list-specific `fmap`).
2013/5/31 Giacomo Tesio
I'm looking for a class abstracting Data.List. I mean something that enable the use of say head, map, take and so on into different kind of types.
Is there already something like that?
Giacomo
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Nadir

fmap is a much more general concept.. I just want to be able to use map (or
another term, like project) over "enhanced" lists. Such "enhanced" lists
aren't Monads, btw, because I can't write a meaningful return/unit
function: to put the list in context, I always need a context to be
provided.
Giacomo
On Fri, May 31, 2013 at 11:34 AM, Nadir Sampaoli
Hi, I'm very new to Haskell and I don't know about head, take, etc. but I think the `Functor` class (and its `fmap` function) provides the abstraction for `map` (which, in my understanding, can be considered the list-specific `fmap`).
2013/5/31 Giacomo Tesio
I'm looking for a class abstracting Data.List. I mean something that enable the use of say head, map, take and so on into different kind of types.
Is there already something like that?
Giacomo
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Nadir
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Giacomo,
Data.List can be abstracted using Foldable and Traversable but
unfortunately I could not find the functions corresponding to head, take.
Prelude Data.Traversable Data.Foldable> :t Data.Foldable.
Data.Foldable.Foldable Data.Foldable.concatMap
Data.Foldable.foldl' Data.Foldable.foldrM
Data.Foldable.minimum Data.Foldable.sequenceA_
Data.Foldable.all Data.Foldable.elem
Data.Foldable.foldl1 Data.Foldable.forM_
Data.Foldable.minimumBy Data.Foldable.sequence_
Data.Foldable.and Data.Foldable.find
Data.Foldable.foldlM Data.Foldable.for_
Data.Foldable.msum Data.Foldable.sum
Data.Foldable.any Data.Foldable.fold
Data.Foldable.foldr Data.Foldable.mapM_
Data.Foldable.notElem Data.Foldable.toList
Data.Foldable.asum Data.Foldable.foldMap
Data.Foldable.foldr' Data.Foldable.maximum
Data.Foldable.or Data.Foldable.traverse_
Data.Foldable.concat Data.Foldable.foldl
Data.Foldable.foldr1 Data.Foldable.maximumBy Data.Foldable.product
Prelude Data.Traversable Data.Foldable> :t Data.Traversable.
Data.Traversable.Traversable Data.Traversable.for
Data.Traversable.mapAccumR Data.Traversable.sequenceA
Data.Traversable.fmapDefault Data.Traversable.forM
Data.Traversable.mapM Data.Traversable.traverse
Data.Traversable.foldMapDefault Data.Traversable.mapAccumL
Data.Traversable.sequence
Prelude Data.Traversable Data.Foldable> :i Foldable
class Foldable t where
fold :: Data.Monoid.Monoid m => t m -> m
foldMap :: Data.Monoid.Monoid m => (a -> m) -> t a -> m
Data.Foldable.foldr :: (a -> b -> b) -> b -> t a -> b
foldr' :: (a -> b -> b) -> b -> t a -> b
Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a
foldl' :: (a -> b -> a) -> a -> t b -> a
Data.Foldable.foldr1 :: (a -> a -> a) -> t a -> a
Data.Foldable.foldl1 :: (a -> a -> a) -> t a -> a
-- Defined in `Data.Foldable'
instance Foldable [] -- Defined in `Data.Foldable'
instance Foldable Maybe -- Defined in `Data.Foldable'
Prelude Data.Traversable Data.Foldable> :i Tr
Traversable True
Prelude Data.Traversable Data.Foldable> :i Traversable
class (Functor t, Foldable t) => Traversable t where
traverse ::
Control.Applicative.Applicative f => (a -> f b) -> t a -> f (t b)
sequenceA ::
Control.Applicative.Applicative f => t (f a) -> f (t a)
Data.Traversable.mapM :: Monad m => (a -> m b) -> t a -> m (t b)
Data.Traversable.sequence :: Monad m => t (m a) -> m (t a)
-- Defined in `Data.Traversable'
instance Traversable [] -- Defined in `Data.Traversable'
instance Traversable Maybe -- Defined in `Data.Traversable'
Prelude Data.Traversable Data.Foldable> :t foldMap
foldMap
:: (Foldable t, Data.Monoid.Monoid m) => (a -> m) -> t a -> m
-Mukesh
On Fri, May 31, 2013 at 2:26 PM, Giacomo Tesio
I'm looking for a class abstracting Data.List. I mean something that enable the use of say head, map, take and so on into different kind of types.
Is there already something like that?
Giacomo
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

http://hackage.haskell.org/packages/archive/ListLike/3.1.4/doc/html/Data-Lis...
Peter
On 31 May 2013 11:16, mukesh tiwari
Hi Giacomo, Data.List can be abstracted using Foldable and Traversable but unfortunately I could not find the functions corresponding to head, take.
Prelude Data.Traversable Data.Foldable> :t Data.Foldable. Data.Foldable.Foldable Data.Foldable.concatMap Data.Foldable.foldl' Data.Foldable.foldrM Data.Foldable.minimum Data.Foldable.sequenceA_ Data.Foldable.all Data.Foldable.elem Data.Foldable.foldl1 Data.Foldable.forM_ Data.Foldable.minimumBy Data.Foldable.sequence_ Data.Foldable.and Data.Foldable.find Data.Foldable.foldlM Data.Foldable.for_ Data.Foldable.msum Data.Foldable.sum Data.Foldable.any Data.Foldable.fold Data.Foldable.foldr Data.Foldable.mapM_ Data.Foldable.notElem Data.Foldable.toList Data.Foldable.asum Data.Foldable.foldMap Data.Foldable.foldr' Data.Foldable.maximum Data.Foldable.or Data.Foldable.traverse_ Data.Foldable.concat Data.Foldable.foldl Data.Foldable.foldr1 Data.Foldable.maximumBy Data.Foldable.product Prelude Data.Traversable Data.Foldable> :t Data.Traversable. Data.Traversable.Traversable Data.Traversable.for Data.Traversable.mapAccumR Data.Traversable.sequenceA Data.Traversable.fmapDefault Data.Traversable.forM Data.Traversable.mapM Data.Traversable.traverse Data.Traversable.foldMapDefault Data.Traversable.mapAccumL Data.Traversable.sequence Prelude Data.Traversable Data.Foldable> :i Foldable class Foldable t where fold :: Data.Monoid.Monoid m => t m -> m foldMap :: Data.Monoid.Monoid m => (a -> m) -> t a -> m Data.Foldable.foldr :: (a -> b -> b) -> b -> t a -> b foldr' :: (a -> b -> b) -> b -> t a -> b Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a foldl' :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldr1 :: (a -> a -> a) -> t a -> a Data.Foldable.foldl1 :: (a -> a -> a) -> t a -> a -- Defined in `Data.Foldable' instance Foldable [] -- Defined in `Data.Foldable' instance Foldable Maybe -- Defined in `Data.Foldable' Prelude Data.Traversable Data.Foldable> :i Tr Traversable True Prelude Data.Traversable Data.Foldable> :i Traversable class (Functor t, Foldable t) => Traversable t where traverse :: Control.Applicative.Applicative f => (a -> f b) -> t a -> f (t b) sequenceA :: Control.Applicative.Applicative f => t (f a) -> f (t a) Data.Traversable.mapM :: Monad m => (a -> m b) -> t a -> m (t b) Data.Traversable.sequence :: Monad m => t (m a) -> m (t a) -- Defined in `Data.Traversable' instance Traversable [] -- Defined in `Data.Traversable' instance Traversable Maybe -- Defined in `Data.Traversable' Prelude Data.Traversable Data.Foldable> :t foldMap foldMap :: (Foldable t, Data.Monoid.Monoid m) => (a -> m) -> t a -> m
-Mukesh
On Fri, May 31, 2013 at 2:26 PM, Giacomo Tesio
wrote: I'm looking for a class abstracting Data.List. I mean something that enable the use of say head, map, take and so on into different kind of types.
Is there already something like that?
Giacomo
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Exactly what I Was looking for!
Thanks! :-D
Giacomo
On Fri, May 31, 2013 at 12:44 PM, Peter Hall
http://hackage.haskell.org/packages/archive/ListLike/3.1.4/doc/html/Data-Lis...
Peter
On 31 May 2013 11:16, mukesh tiwari
wrote: Hi Giacomo, Data.List can be abstracted using Foldable and Traversable but unfortunately I could not find the functions corresponding to head, take.
Prelude Data.Traversable Data.Foldable> :t Data.Foldable. Data.Foldable.Foldable Data.Foldable.concatMap Data.Foldable.foldl' Data.Foldable.foldrM Data.Foldable.minimum Data.Foldable.sequenceA_ Data.Foldable.all Data.Foldable.elem Data.Foldable.foldl1 Data.Foldable.forM_ Data.Foldable.minimumBy Data.Foldable.sequence_ Data.Foldable.and Data.Foldable.find Data.Foldable.foldlM Data.Foldable.for_ Data.Foldable.msum Data.Foldable.sum Data.Foldable.any Data.Foldable.fold Data.Foldable.foldr Data.Foldable.mapM_ Data.Foldable.notElem Data.Foldable.toList Data.Foldable.asum Data.Foldable.foldMap Data.Foldable.foldr' Data.Foldable.maximum Data.Foldable.or Data.Foldable.traverse_ Data.Foldable.concat Data.Foldable.foldl Data.Foldable.foldr1 Data.Foldable.maximumBy Data.Foldable.product Prelude Data.Traversable Data.Foldable> :t Data.Traversable. Data.Traversable.Traversable Data.Traversable.for Data.Traversable.mapAccumR Data.Traversable.sequenceA Data.Traversable.fmapDefault Data.Traversable.forM Data.Traversable.mapM Data.Traversable.traverse Data.Traversable.foldMapDefault Data.Traversable.mapAccumL Data.Traversable.sequence Prelude Data.Traversable Data.Foldable> :i Foldable class Foldable t where fold :: Data.Monoid.Monoid m => t m -> m foldMap :: Data.Monoid.Monoid m => (a -> m) -> t a -> m Data.Foldable.foldr :: (a -> b -> b) -> b -> t a -> b foldr' :: (a -> b -> b) -> b -> t a -> b Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a foldl' :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldr1 :: (a -> a -> a) -> t a -> a Data.Foldable.foldl1 :: (a -> a -> a) -> t a -> a -- Defined in `Data.Foldable' instance Foldable [] -- Defined in `Data.Foldable' instance Foldable Maybe -- Defined in `Data.Foldable' Prelude Data.Traversable Data.Foldable> :i Tr Traversable True Prelude Data.Traversable Data.Foldable> :i Traversable class (Functor t, Foldable t) => Traversable t where traverse :: Control.Applicative.Applicative f => (a -> f b) -> t a -> f (t b) sequenceA :: Control.Applicative.Applicative f => t (f a) -> f (t a) Data.Traversable.mapM :: Monad m => (a -> m b) -> t a -> m (t b) Data.Traversable.sequence :: Monad m => t (m a) -> m (t a) -- Defined in `Data.Traversable' instance Traversable [] -- Defined in `Data.Traversable' instance Traversable Maybe -- Defined in `Data.Traversable' Prelude Data.Traversable Data.Foldable> :t foldMap foldMap :: (Foldable t, Data.Monoid.Monoid m) => (a -> m) -> t a -> m
-Mukesh
On Fri, May 31, 2013 at 2:26 PM, Giacomo Tesio
wrote: I'm looking for a class abstracting Data.List. I mean something that enable the use of say head, map, take and so on into different kind of types.
Is there already something like that?
Giacomo
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thanks, that's a good starting point. What would be the proper name for such an abstraction in Haskell? In C# it would be Enumerable (and indeed the static class Enumerable<T> contains such kind of functions applicable to anything implementing IEnumerable<T>). What would be the idiomatic name of such a *class* in Haskell? - List ? - Listable ? - Enumerable ? - ListWithContext ? Giacomo On Fri, May 31, 2013 at 12:16 PM, mukesh tiwari < mukeshtiwari.iiitm@gmail.com> wrote:
Hi Giacomo, Data.List can be abstracted using Foldable and Traversable but unfortunately I could not find the functions corresponding to head, take.
Prelude Data.Traversable Data.Foldable> :t Data.Foldable. Data.Foldable.Foldable Data.Foldable.concatMap Data.Foldable.foldl' Data.Foldable.foldrM Data.Foldable.minimum Data.Foldable.sequenceA_ Data.Foldable.all Data.Foldable.elem Data.Foldable.foldl1 Data.Foldable.forM_ Data.Foldable.minimumBy Data.Foldable.sequence_ Data.Foldable.and Data.Foldable.find Data.Foldable.foldlM Data.Foldable.for_ Data.Foldable.msum Data.Foldable.sum Data.Foldable.any Data.Foldable.fold Data.Foldable.foldr Data.Foldable.mapM_ Data.Foldable.notElem Data.Foldable.toList Data.Foldable.asum Data.Foldable.foldMap Data.Foldable.foldr' Data.Foldable.maximum Data.Foldable.or Data.Foldable.traverse_ Data.Foldable.concat Data.Foldable.foldl Data.Foldable.foldr1 Data.Foldable.maximumBy Data.Foldable.product Prelude Data.Traversable Data.Foldable> :t Data.Traversable. Data.Traversable.Traversable Data.Traversable.for Data.Traversable.mapAccumR Data.Traversable.sequenceA Data.Traversable.fmapDefault Data.Traversable.forM Data.Traversable.mapM Data.Traversable.traverse Data.Traversable.foldMapDefault Data.Traversable.mapAccumL Data.Traversable.sequence Prelude Data.Traversable Data.Foldable> :i Foldable class Foldable t where fold :: Data.Monoid.Monoid m => t m -> m foldMap :: Data.Monoid.Monoid m => (a -> m) -> t a -> m Data.Foldable.foldr :: (a -> b -> b) -> b -> t a -> b foldr' :: (a -> b -> b) -> b -> t a -> b Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a foldl' :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldr1 :: (a -> a -> a) -> t a -> a Data.Foldable.foldl1 :: (a -> a -> a) -> t a -> a -- Defined in `Data.Foldable' instance Foldable [] -- Defined in `Data.Foldable' instance Foldable Maybe -- Defined in `Data.Foldable' Prelude Data.Traversable Data.Foldable> :i Tr Traversable True Prelude Data.Traversable Data.Foldable> :i Traversable class (Functor t, Foldable t) => Traversable t where traverse :: Control.Applicative.Applicative f => (a -> f b) -> t a -> f (t b) sequenceA :: Control.Applicative.Applicative f => t (f a) -> f (t a) Data.Traversable.mapM :: Monad m => (a -> m b) -> t a -> m (t b) Data.Traversable.sequence :: Monad m => t (m a) -> m (t a) -- Defined in `Data.Traversable' instance Traversable [] -- Defined in `Data.Traversable' instance Traversable Maybe -- Defined in `Data.Traversable' Prelude Data.Traversable Data.Foldable> :t foldMap foldMap :: (Foldable t, Data.Monoid.Monoid m) => (a -> m) -> t a -> m
-Mukesh
On Fri, May 31, 2013 at 2:26 PM, Giacomo Tesio
wrote: I'm looking for a class abstracting Data.List. I mean something that enable the use of say head, map, take and so on into different kind of types.
Is there already something like that?
Giacomo
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Fri, May 31, 2013 at 6:16 AM, mukesh tiwari wrote: Data.List can be abstracted using Foldable and Traversable but
unfortunately I could not find the functions corresponding to head, take. Those are, again, more general than you want. What is the `head` of a
HashMap? (Consider that an implementation may choose to randomize the hash
function to avoid hash collision attacks.) Foldable and Traversable express
the concept of a collection which has no meaningful concept of an element's
relative position within the collection. ListLike adds the concept of
position, thereby admitting an indexing operation (and, by extension,
`head` which is index 0).
--
brandon s allbery kf8nh sine nomine associates
allbery.b@gmail.com ballbery@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Do you see any issue with using ListLike? In my particular domain, the
concept of position, is actually relevant.
Giacomo
On Fri, May 31, 2013 at 4:31 PM, Brandon Allbery
On Fri, May 31, 2013 at 6:16 AM, mukesh tiwari < mukeshtiwari.iiitm@gmail.com> wrote:
Data.List can be abstracted using Foldable and Traversable but unfortunately I could not find the functions corresponding to head, take.
Those are, again, more general than you want. What is the `head` of a HashMap? (Consider that an implementation may choose to randomize the hash function to avoid hash collision attacks.) Foldable and Traversable express the concept of a collection which has no meaningful concept of an element's relative position within the collection. ListLike adds the concept of position, thereby admitting an indexing operation (and, by extension, `head` which is index 0).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Brandon,
On Fri, May 31, 2013 at 8:01 PM, Brandon Allbery
On Fri, May 31, 2013 at 6:16 AM, mukesh tiwari < mukeshtiwari.iiitm@gmail.com> wrote:
Data.List can be abstracted using Foldable and Traversable but unfortunately I could not find the functions corresponding to head, take.
Those are, again, more general than you want. What is the `head` of a HashMap? (Consider that an implementation may choose to randomize the hash function to avoid hash collision attacks.) Foldable and Traversable express the concept of a collection which has no meaningful concept of an element's relative position within the collection. ListLike adds the concept of position, thereby admitting an indexing operation (and, by extension, `head` which is index 0).
Thanks for explanation. Precisely a tree was in the mind so there is no concept of head or take. Data.Foldable.toList could be used to convert the foldable structure to list but again it's not useful because Giacomo wants to abstract the List. -Mukesh
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I need to add that it's perfectly valid to define all operation in terms of
Folds and so it's possible to define take, head, and such functions for all
Foldable instances as they have a path to fold over them:
the key idea is to store a state while folding over a structure:
headF :: (Foldable x) => x a -> a
headF = snd . F.foldl (\(s,v) n -> if s then (s,v) else (True,n)) (False,
error "empty")
takeF :: (Foldable x) => Int -> x a -> [a]
takeF c = reverse . snd . F.foldl (\(i,v) n -> if i < c then (i+1,n:v) else
(i,v)) (0,[])
In domain of a lazy languages we will even stop evaluation as soon as we
will get result without additional steps.
On 31 May 2013 18:31, Brandon Allbery
On Fri, May 31, 2013 at 6:16 AM, mukesh tiwari < mukeshtiwari.iiitm@gmail.com> wrote:
Data.List can be abstracted using Foldable and Traversable but unfortunately I could not find the functions corresponding to head, take.
Those are, again, more general than you want. What is the `head` of a HashMap? (Consider that an implementation may choose to randomize the hash function to avoid hash collision attacks.) Foldable and Traversable express the concept of a collection which has no meaningful concept of an element's relative position within the collection. ListLike adds the concept of position, thereby admitting an indexing operation (and, by extension, `head` which is index 0).
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Alexander
participants (6)
-
Alexander V Vershilov
-
Brandon Allbery
-
Giacomo Tesio
-
mukesh tiwari
-
Nadir Sampaoli
-
Peter Hall