how to Enumerate without lists?

Dear Cafe (again), I was trying to write sum $ map (^ 2) $ [ 1 :: Int .. 10^8 ] in a list-free style getSum $ foldMap (Sum . (^ 2)) $ [ 1 :: Int .. 10^8 ] This avoids building an intermediate list (of squares) but it will allocate, since foldMap uses foldr (by default, and it's not overridden for lists) The conclusion would be: not to use lists at all. Which will be the point of my talk anyway. But here, we get a list from enumFromTo. Can we avoid that? Let's try: we just reify enumFromTo data Enumerator a = Enumerator {from :: a, to :: a} we have this for decades, it is called (a,a) in Data.Ix, and then instance Foldable Enumerator where ... Oh no, foldMap (and others) would need an Enum constraint! - J

I don't really understand your purpose. There are many ways to write code that GHC is good at optimizing, but there are far fewer ways to write code that will compile to non-allocating loops without optimization. Heck, without the worker-wrapper transformation demand analysis enables, you can't even get a non-allocating counter without unboxing by hand and using primops for arithmetic. On Tue, Sep 4, 2018, 1:00 PM Johannes Waldmann < johannes.waldmann@htwk-leipzig.de> wrote:
Dear Cafe (again),
I was trying to write
sum $ map (^ 2) $ [ 1 :: Int .. 10^8 ]
in a list-free style
getSum $ foldMap (Sum . (^ 2)) $ [ 1 :: Int .. 10^8 ]
This avoids building an intermediate list (of squares) but it will allocate, since foldMap uses foldr (by default, and it's not overridden for lists)
The conclusion would be: not to use lists at all. Which will be the point of my talk anyway.
But here, we get a list from enumFromTo. Can we avoid that?
Let's try: we just reify enumFromTo
data Enumerator a = Enumerator {from :: a, to :: a}
we have this for decades, it is called (a,a) in Data.Ix, and then
instance Foldable Enumerator where ...
Oh no, foldMap (and others) would need an Enum constraint!
- J
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
On Sep 4, 2018 1:00 PM, "Johannes Waldmann" < johannes.waldmann@htwk-leipzig.de> wrote: Dear Cafe (again), I was trying to write sum $ map (^ 2) $ [ 1 :: Int .. 10^8 ] in a list-free style getSum $ foldMap (Sum . (^ 2)) $ [ 1 :: Int .. 10^8 ] This avoids building an intermediate list (of squares) but it will allocate, since foldMap uses foldr (by default, and it's not overridden for lists) The conclusion would be: not to use lists at all. Which will be the point of my talk anyway. But here, we get a list from enumFromTo. Can we avoid that? Let's try: we just reify enumFromTo data Enumerator a = Enumerator {from :: a, to :: a} we have this for decades, it is called (a,a) in Data.Ix, and then instance Foldable Enumerator where ... Oh no, foldMap (and others) would need an Enum constraint! - J _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi David, Thanks for responding. Let me re-phrase the technical question: in some hypothetical
instance Foldable Enumerator where ...
the methods (e.g., foldMap) would be overconstrained. Is there a way to still write something like it? It seems not, as shown by these examples: Data.EnumSet cannot implement Foldable because of Enum k. http://hackage.haskell.org/package/enummapset/docs/Data-EnumSet.html Data.IntSet cannot implement Foldable because of k ~ Int. - J.

You could always do a Coyoneda transform. data IntSetF a = IntSetF !IntSet (Int -> a) The Functor and Foldable instances are pretty obvious from it. Similarly with your Enumerator idea. On Wed, Sep 5, 2018, 05:56 Johannes Waldmann < johannes.waldmann@htwk-leipzig.de> wrote:
Hi David,
Thanks for responding. Let me re-phrase the technical question: in some hypothetical
instance Foldable Enumerator where ...
the methods (e.g., foldMap) would be overconstrained. Is there a way to still write something like it?
It seems not, as shown by these examples:
Data.EnumSet cannot implement Foldable because of Enum k. http://hackage.haskell.org/package/enummapset/docs/Data-EnumSet.html
Data.IntSet cannot implement Foldable because of k ~ Int.
- J. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Try this: {-#LANGUAGE GADTs#-} data Enumerator a b where Enumerator :: a -> a -> Enumerator a a instance Enum a => Foldable (Enumerator a) where foldMap f (Enumerator x y) | fromEnum x > fromEnum y = mempty | otherwise = f x <> foldMap f (Enumerator (succ x) y) Here we're using a GADT to express that our two-parameter Enumerator type in practice always has a == b (at the type level). Which lets us constrain the values inside our new Foldable structure, while still having a type of kind (* -> *) like the the typeclass requires. On Wed, Sep 5, 2018 at 6:56 AM Johannes Waldmann < johannes.waldmann@htwk-leipzig.de> wrote:
Hi David,
Thanks for responding. Let me re-phrase the technical question: in some hypothetical
instance Foldable Enumerator where ...
the methods (e.g., foldMap) would be overconstrained. Is there a way to still write something like it?
It seems not, as shown by these examples:
Data.EnumSet cannot implement Foldable because of Enum k. http://hackage.haskell.org/package/enummapset/docs/Data-EnumSet.html
Data.IntSet cannot implement Foldable because of k ~ Int.
- J. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Wed, Sep 05, 2018 at 11:37:07AM -0400, Ben Doyle wrote:
{-#LANGUAGE GADTs#-}
data Enumerator a b where Enumerator :: a -> a -> Enumerator a a
instance Enum a => Foldable (Enumerator a) where foldMap f (Enumerator x y) | fromEnum x > fromEnum y = mempty | otherwise = f x <> foldMap f (Enumerator (succ x) y)
Here we're using a GADT to express that our two-parameter Enumerator type in practice always has a == b (at the type level). Which lets us constrain the values inside our new Foldable structure, while still having a type of kind (* -> *) like the the typeclass requires.
This is ingenious!
participants (5)
-
Ben Doyle
-
David Feuer
-
Johannes Waldmann
-
Tom Ellis
-
Zemyla