No Enum for (,), no Enum or Bounded for Either

I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord` * `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded` Is there a particular reason for that? It might be tricky to implement toEnum :: Int -> a fromEnum :: a -> Int but in the presence of `Bounded` that should be possible. Tom

One issue is that (Int, Int) is too big to define toEnum/fromEnum. On 06/01/2018 02:10 PM, Tom Ellis wrote:
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.
Tom
_______________________________________________ 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.

True. I think I would propose instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) instance (Bounded a, Bounded b) => Enum (Bounded a b) instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b) On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote:
One issue is that (Int, Int) is too big to define toEnum/fromEnum.
On 06/01/2018 02:10 PM, Tom Ellis wrote:
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.

I made a typo in the second one. It should be instance (Bounded a, Bounded b) => Bounded (Either a b) On Fri, Jun 01, 2018 at 07:32:55PM +0100, Tom Ellis wrote:
True. I think I would propose
instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) instance (Bounded a, Bounded b) => Enum (Bounded a b) instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b)
On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote:
One issue is that (Int, Int) is too big to define toEnum/fromEnum.
On 06/01/2018 02:10 PM, Tom Ellis wrote:
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.
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.

And to be precise, this seems to work {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} data P a b = P a b deriving (Eq, Bounded, Show) data E a b = L a | R b deriving (Eq, Show) instance (Bounded a, Bounded b) => Bounded (E a b) where minBound = L minBound maxBound = R maxBound instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (E a b) where fromEnum = \case L a -> fromEnum a R b -> fromEnum (maxBound :: a) + fromEnum b + 1 toEnum n = let m = fromEnum (maxBound :: a) in if n <= m then L (toEnum n) else R (toEnum (n - 1 - m)) instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (P a b) where fromEnum = \case P a b -> fromEnum a * (fromEnum (maxBound :: b) + 1) + fromEnum b toEnum n = let (q, r) = quotRem n (fromEnum (maxBound :: b) + 1) in P (toEnum q) (toEnum r) -- Test data Few = F1 | F2 | F3 deriving (Show, Eq, Bounded, Enum) data Several = S1 | S2 | S3 | S4 | S5 | S6 | S7 deriving (Show, Eq, Bounded, Enum) fromEnumP :: P Few Several -> Int fromEnumP = fromEnum fromEnumE :: E Few Several -> Int fromEnumE = fromEnum idP1 :: P Few Several -> P Few Several idP1 = toEnum . fromEnum idP2 :: Int -> Int idP2 = fromEnumP . toEnum idE1 :: E Few Several -> E Few Several idE1 = toEnum . fromEnum idE2 :: Int -> Int idE2 = fromEnumE . toEnum allPs :: [P Few Several] allPs = P <$> [minBound..maxBound] <*> [minBound..maxBound] -- > allPs -- [P F1 S1,P F1 S2,P F1 S3,P F1 S4,P F1 S5,P F1 S6,P F1 S7,P F2 S1,P F2 S2,P F2 S3,P F2 S4,P F2 S5,P F2 S6,P F2 S7,P F3 S1,P F3 S2,P F3 S3,P F3 S4,P F3 S5,P F3 S6,P F3 S7] allEs :: [E Few Several] allEs = map L [minBound..maxBound] ++ map R [minBound..maxBound] -- > allEs -- [L F1,L F2,L F3,R S1,R S2,R S3,R S4,R S5,R S6,R S7] test = and [ map idP2 [0..20] == [0..20] , map idE2 [0..9] == [0..9] , map idP1 allPs == allPs , map idE1 allEs == allEs ] -- > test -- True On Fri, Jun 01, 2018 at 07:43:05PM +0100, Tom Ellis wrote:
I made a typo in the second one. It should be
instance (Bounded a, Bounded b) => Bounded (Either a b)
On Fri, Jun 01, 2018 at 07:32:55PM +0100, Tom Ellis wrote:
True. I think I would propose
instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) instance (Bounded a, Bounded b) => Enum (Bounded a b) instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b)
On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote:
One issue is that (Int, Int) is too big to define toEnum/fromEnum.
On 06/01/2018 02:10 PM, Tom Ellis wrote:
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.
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.
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 Jun 1, 2018, at 3:20 PM, Tom Ellis
wrote: instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (E a b) where fromEnum = \case L a -> fromEnum a R b -> fromEnum (maxBound :: a) + fromEnum b + 1
This appears to assume that (fromEnum b) is never negative. (effectively that (minBound :: b) >= 0). Ignoring overflow issues, this should perhaps be: R b -> fromEnum (maxBound :: a) + (fromEnum b - fromEnum (minBound :: b)) + 1 This will of course overflow when ranges of a and/or b are large enough. -- Viktor.

On Fri, Jun 01, 2018 at 03:47:47PM -0400, Viktor Dukhovni wrote:
On Jun 1, 2018, at 3:20 PM, Tom Ellis
wrote: instance forall a b. (Bounded a, Bounded b, Enum a, Enum b) => Enum (E a b) where fromEnum = \case L a -> fromEnum a R b -> fromEnum (maxBound :: a) + fromEnum b + 1
This appears to assume that (fromEnum b) is never negative. (effectively that (minBound :: b) >= 0).
It assumes that minBound == 0, which we can see is wrong by considering Int.
Ignoring overflow issues, this should perhaps be:
R b -> fromEnum (maxBound :: a) + (fromEnum b - fromEnum (minBound :: b)) + 1
Yes, thanks, I think that's the kind of thing we want to do.
This will of course overflow when ranges of a and/or b are large enough.
Naturally.

Counterargument: overlapping instances instance (Bounded b, Enum b) => Enum (Either a b) instance (Bounded b) => Bounded (Either a b) instance (Applicative f, Bounded a) => Bounded (f a) instance (Bounded a, Enum a) => Enum (Either a b) instance (Bounded a) => Bounded (Either a b) instance (Bounded a, Enum a, Monoid b) => Enum (a, b) instance (Bounded b, Enum b, Monoid a) => Enum (a, b) Also note that what you're talking about is a special type of objects, namely type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds (I'm sure the mathematicians have a better name for this) So IF someone where to add these somewhere, might I suggest also adding essentials like enumAll :: (Bounded a, Enum a) => [a] -- i.e. enumAll :: (BoundedEnum a) => [a] Lastly, because it's its own type of objects, I'm sure there's a library out there doing just that. (Plus maybe other stuff like EnumMap's). On 2018-06-01 20:32, Tom Ellis wrote:
True. I think I would propose
instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) instance (Bounded a, Bounded b) => Enum (Bounded a b) instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b)
On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote:
One issue is that (Int, Int) is too big to define toEnum/fromEnum.
On 06/01/2018 02:10 PM, Tom Ellis wrote:
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.

Sorry, could you explain further? I don't understand what the implementation of any of those proposed instances is supposed to be. On Fri, Jun 01, 2018 at 09:28:07PM +0200, MarLinn wrote:
Counterargument: overlapping instances
instance (Bounded b, Enum b) => Enum (Either a b) instance (Bounded b) => Bounded (Either a b) instance (Applicative f, Bounded a) => Bounded (f a) instance (Bounded a, Enum a) => Enum (Either a b) instance (Bounded a) => Bounded (Either a b) instance (Bounded a, Enum a, Monoid b) => Enum (a, b) instance (Bounded b, Enum b, Monoid a) => Enum (a, b)
Also note that what you're talking about is a special type of objects, namely
type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds
(I'm sure the mathematicians have a better name for this)
So IF someone where to add these somewhere, might I suggest also adding essentials like
enumAll :: (Bounded a, Enum a) => [a] -- i.e. enumAll :: (BoundedEnum a) => [a]
Lastly, because it's its own type of objects, I'm sure there's a library out there doing just that. (Plus maybe other stuff like EnumMap's).
On 2018-06-01 20:32, Tom Ellis wrote:
True. I think I would propose
instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) instance (Bounded a, Bounded b) => Enum (Bounded a b) instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b)
On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote:
One issue is that (Int, Int) is too big to define toEnum/fromEnum.
On 06/01/2018 02:10 PM, Tom Ellis wrote:
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.
_______________________________________________ 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.

Sorry, could you explain further? I don't understand what the implementation of any of those proposed instances is supposed to be.
Sure. {-# LANGUAGE ConstraintKinds #-} type BoundedEnum a = (Bounded a, Enum a) instance (BoundedEnum b) => Enum (Either a b) where fromEnum (Left _) = 0 fromEnum (Right x) = 1 + fromEnum x toEnum 0 = error "toEnum: zero" -- could also add a Monoid constraint instead toEnum n = Right . toEnum $ n-1 instance (Bounded b) => Bounded (Either a b) where minBound = Right minBound maxBound = Right maxBound Rationale: these two implement the use case of working on something from a finite selection of elements inside a monad stack. In other words it's a special case of instance (Applicative f, Bounded a) => Bounded (f a) where minBound = pure minBound maxBound = pure maxBound Is it a good idea to implement this? Probably not, but it serves as an illustration. On the other hand, many error types are bounded and enumerable, so why not enhance the error handling instead? instance (BoundedEnum a, Monoid b) => Enum (Either a b) where -- okay, I cheated by adding the Monoid constraint this time fromEnum (Right _) = 0 fromEnum (Left e) = 1 + fromEnum e toEnum 0 = Right mempty toEnum n = Left . toEnum $ n-1 instance (Bounded a) => Bounded (Either a b) where minBound = Left minBound maxBound = Left maxBound Which is better? That depends. Now for product types: instance (Enum a, Monoid b) => Enum (a, b) where toEnum = (,mempty) . toEnum fromEnum = fromEnum . fst instance (Enum b, Monoid a) => Enum (a, b) where toEnum = (mempty,) . toEnum fromEnum = fromEnum . snd And to be thorough enumAll :: (BoundedEnum a) => [a] enumAll = enumFromTo minBound maxBound Hope it's clearer now what I meant.

On Fri, Jun 01, 2018 at 10:21:45PM +0200, MarLinn wrote:
Sorry, could you explain further? I don't understand what the implementation of any of those proposed instances is supposed to be.
Sure.
[...]
Hope it's clearer now what I meant.
It's clearer what you meant, but I always assumed that fromEnum and toEnum must be mutually inverse. I can't see that law written anywhere in the docs but it seems to be an almost useless class without that assumption. The default implementations of the other methods seems to be completely based on that assumption, for example: http://hackage.haskell.org/package/base-4.11.1.0/docs/src/GHC.Enum.html#Enum

The way I understand it is more like: they should be Mutual inverses if the type has fewer inhabitants than Int does, and otherwise, just kind of do the best you can. What about the instance for Integer? Sent from my iPhone
On Jun 2, 2018, at 1:39 AM, Tom Ellis
wrote: On Fri, Jun 01, 2018 at 10:21:45PM +0200, MarLinn wrote:
Sorry, could you explain further? I don't understand what the implementation of any of those proposed instances is supposed to be.
Sure. [...] Hope it's clearer now what I meant.
It's clearer what you meant, but I always assumed that fromEnum and toEnum must be mutually inverse. I can't see that law written anywhere in the docs but it seems to be an almost useless class without that assumption. The default implementations of the other methods seems to be completely based on that assumption, for example:
http://hackage.haskell.org/package/base-4.11.1.0/docs/src/GHC.Enum.html#Enum _______________________________________________ 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.

Which raises the question, why is there not an Enumerate class with Integer
in place of Int? It would agree better with Integral.
On Jun 2, 2018 07:15, "Andrew Martin"
On Jun 2, 2018, at 1:39 AM, Tom Ellis < tom-lists-haskell-cafe-2013@jaguarpaw.co.uk> wrote:
On Fri, Jun 01, 2018 at 10:21:45PM +0200, MarLinn wrote:
Sorry, could you explain further? I don't understand what the implementation of any of those proposed instances is supposed to be.
Sure. [...] Hope it's clearer now what I meant.
It's clearer what you meant, but I always assumed that fromEnum and toEnum must be mutually inverse. I can't see that law written anywhere in the docs but it seems to be an almost useless class without that assumption. The default implementations of the other methods seems to be completely based on that assumption, for example:
http://hackage.haskell.org/package/base-4.11.1.0/docs/src/GHC.Enum.html#Enum
_______________________________________________ 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.
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.

The BoundedEnum thing is already something of a sunk cost, since there's
already magic behavior of Enum when a type is also Bounded. (Go look at how
Enum deriving is specified.)
On Fri, Jun 1, 2018 at 3:28 PM MarLinn
Counterargument: overlapping instances
instance (Bounded b, Enum b) => Enum (Either a b) instance (Bounded b) => Bounded (Either a b) instance (Applicative f, Bounded a) => Bounded (f a) instance (Bounded a, Enum a) => Enum (Either a b) instance (Bounded a) => Bounded (Either a b) instance (Bounded a, Enum a, Monoid b) => Enum (a, b) instance (Bounded b, Enum b, Monoid a) => Enum (a, b)
Also note that what you're talking about is a special type of objects, namely
type BoundedEnum a = (Bounded a, Enum a) -- using ConstraintKinds
(I'm sure the mathematicians have a better name for this)
So IF someone where to add these somewhere, might I suggest also adding essentials like
enumAll :: (Bounded a, Enum a) => [a] -- i.e. enumAll :: (BoundedEnum a) => [a]
Lastly, because it's its own type of objects, I'm sure there's a library out there doing just that. (Plus maybe other stuff like EnumMap's).
On 2018-06-01 20:32, Tom Ellis wrote:
True. I think I would propose
instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (Either a b) instance (Bounded a, Bounded b) => Enum (Bounded a b) instance (Bounded a, Bounded b, Enum a, Enum b) => Enum (a, b)
On Fri, Jun 01, 2018 at 02:23:58PM -0400, Li-yao Xia wrote:
One issue is that (Int, Int) is too big to define toEnum/fromEnum.
On 06/01/2018 02:10 PM, Tom Ellis wrote:
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.
_______________________________________________ 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.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Tom Ellis
I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.
You don’t need Bounded to do that. For example, you could start at (0,0) and go out in diamond shaped rings. A more pressing reason is that there are too many possible enumerations, and if we picked one it would probably be the wrong one for most applications. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Sat, Jun 02, 2018 at 10:36:56AM +0100, Jon Fairbairn wrote:
Tom Ellis
writes: I'm a bit surprised that whilst `Either` and `(,)` have instances for `Ord`
* `(,)` has no instance for `Enum` * `Either` has no instance for `Enum` or `Bounded`
Is there a particular reason for that? It might be tricky to implement
toEnum :: Int -> a fromEnum :: a -> Int
but in the presence of `Bounded` that should be possible.
You don’t need Bounded to do that. For example, you could start at (0,0) and go out in diamond shaped rings. A more pressing reason is that there are too many possible enumerations, and if we picked one it would probably be the wrong one for most applications.
This is all true, but I was implicitly assuming that Bounded and Enum ought to agree with Ord. We've already picked Ords for (,) and Either so why not also pick the Enums and Boundeds that agree with them?
participants (8)
-
Andrew Martin
-
Brandon Allbery
-
Jon Fairbairn
-
Li-yao Xia
-
MarLinn
-
Ryan Reich
-
Tom Ellis
-
Viktor Dukhovni