
I'll answer my own post to elaborate: If Day (and Month) where NOT instances of Bounded, the following would be possible: [Monday .. Sunday] => should return [Monday, Tuesday ... Saturday, Sunday] => but returns [] [Saturday .. Tuesday] => should return [Saturday, Sunday, Monday, Tuesday] => but returns [] succ Saturday => should return Sunday => but yields an exception It would feel natural to be able to get the desired results above. The Haskell98 report stipulates: --->8--- For any type that is an instance of class Bounded as well as Enum, the following should hold: The calls succ maxBound and pred minBound should result in a runtime error. --->8--- So, the standard library System.Time respects that and yields exception for succ Saturday. But if Day was not an instance of Bounded should it not be legal for succ Saturday to return Sunday? Now I cannot see the advantage of letting Day (and Month) be instances of Bounded. The only thing we get out of that is access to functions maxBound and minBound, but those do not seem useful to me for either Day or Month. /Johan

On Fri, 14 Jul 2006, Johan Holmquist wrote:
I'll answer my own post to elaborate:
If Day (and Month) where NOT instances of Bounded, the following would be possible:
[Monday .. Sunday] => should return [Monday, Tuesday ... Saturday, Sunday] => but returns []
Why not [Monday, Tuesday ... Saturday, Sunday, Monday, Tuesday ... Saturday, Sunday] ? Since the days are cycling, what is more natural about your result compared to my one? I assume the Bounded instance exists in order to allow loops like liftM2 (,) [0..] [minBound .. (maxBound::System.Time.Month)]

"Johan Holmquist"
If Day (and Month) where NOT instances of Bounded, the following would be possible:
[Saturday .. Tuesday] => should return [Saturday, Sunday, Monday, Tuesday] => but returns []
This does seem like a reasonable argument to me. Some enumerations are semantically cyclic, rather than linear. But how do you feel about the way it breaks some algebraic laws? fromEnum x < fromEnum (succ x) fromEnum x > fromEnum (pred x) Of course, such laws are not explicitly stated anywhere in the definition of the classes, so one would be foolish to rely on them in any case. Regards, Malcolm

Try this:
module Cycle (Cyclic(..)) where
import System.Time import Data.Word import Data.Int
class (Eq c,Enum c, Bounded c) => Cyclic c where cyclePeriod :: c -> Int cyclePeriod _ = fromEnum (maxBound :: c) - fromEnum (minBound :: c) + 1 succCycle :: c -> c succCycle c | c == maxBound = minBound | otherwise = succ c predCycle :: c-> c predCycle c | c == minBound = maxBound | otherwise = pred c fromCycle :: c -> Int fromCycle = fromEnum toCycle :: Int -> c toCycle = toEnum . (`mod` (cyclePeriod (undefined::c))) cycleFrom :: c -> [c] cycleFrom x = map toCycle [fromCycle x ..] cycleFromTo :: c -> c -> [c] cycleFromTo x y = let xi = fromCycle x yi = fromCycle y zi = if xi > yi then yi + cyclePeriod (undefined::c) else yi in map toCycle [xi .. zi] cycleFromThen :: c -> c -> [c] cycleFromThen x y = let xi = fromCycle x yi = fromCycle y in map toCycle [xi, yi ..] cycleFromThenTo :: c -> c -> c -> [c] cycleFromThenTo x y z = let c = cyclePeriod (undefined::c) xi = fromCycle x; yi = fromCycle y; zi = fromCycle z zi' = if xi <= yi then if yi <= zi then zi else zi + c else if zi <= yi then zi else zi - c in map toCycle [xi, yi .. zi']
instance Cyclic Day instance Cyclic Month instance Cyclic Bool instance Cyclic () instance Cyclic Ordering instance Cyclic Int instance Cyclic Char instance Cyclic Int8 -- Imported from GHC.Int instance Cyclic Int64 -- Imported from GHC.Int instance Cyclic Int32 -- Imported from GHC.Int instance Cyclic Int16 -- Imported from GHC.Int instance Cyclic Word8 -- Imported from GHC.Word instance Cyclic Word64 -- Imported from GHC.Word instance Cyclic Word32 -- Imported from GHC.Word instance Cyclic Word16 -- Imported from GHC.Word

Okay...final version attached. This one fixes the toCycle bugs and changes from Int to Integer so overflow is no longer an issue. The result of cycleFromThenTo fits what I would expect, but you are free to drop this or adapt it. cycleFrom and cycleFromTo and cycleFromThen are easy, since there is no difference between ascending and descending. Note that the returned list is never null. cycleFromThenTo can be either ascending or descending depending on the first two arguments, and it considers the first occurrence of the third argument in that direction of the cycle starting from the initial argument: *Cycle> cycleFromThenTo Monday Wednesday Tuesday [Monday] instead of
*Cycle> cycleFromThenTo Monday Wednesday Tuesday [Monday,Wednesday,Friday,Sunday,Tuesday]
This agrees with things like [1,3 .. 2] returning [1] and [3,1 .. 2] returning [3].
{- By Chris Kuklewicz

Yes, it would be possible to make ones own class and instantiate from that. I was just thinking Day and Month should be cyclic per default. from Henning Thielemann:
Since the days are cycling, what is more natural about your result compared to my one?
I would prefer the one without any repetitions.
I assume the Bounded instance exists in order to allow loops like liftM2 (,) [0..] [minBound .. (maxBound::System.Time.Month)]
Would not "liftM2 (,) [0..] [Sunday .. Saturday]" do the trick? Sure there are subtleties, like what should [Monday .. Monday] return, either: [Monday] or [Monday, Tuesday ... Sunday] but to settle for one would be ok to me. from Malcolm Wallace:
But how do you feel about the way it breaks some algebraic laws? fromEnum x < fromEnum (succ x) fromEnum x > fromEnum (pred x)
I would take the irresponsible and easy path and just accept it. As you said, it is not stated that any such relations must hold. Probably the cleanest approach is the one suggested by Chris Kuklewicz: Make the cyclings explicit in their own class and escape all surprises involved in sudden cyclic Enums. /Johan

On Fri, 14 Jul 2006, Johan Holmquist wrote:
from Henning Thielemann:
Since the days are cycling, what is more natural about your result compared to my one?
I would prefer the one without any repetitions.
I assume the Bounded instance exists in order to allow loops like liftM2 (,) [0..] [minBound .. (maxBound::System.Time.Month)]
Would not "liftM2 (,) [0..] [Sunday .. Saturday]" do the trick?
You mean liftM2 (,) [0..] [January .. December] ? (I chose Months in order to get a sensible example.) I assume that the Bounded class exists in order to stay independent from the particular type. With minBound and maxBound you do not rely on whether the counting starts on Sunday or Monday if you only want to do something for all days.
Sure there are subtleties, like what should [Monday .. Monday] return, either: [Monday] or [Monday, Tuesday ... Sunday] but to settle for one would be ok to me.
You mean [Monday, Tuesday ... Sunday, Monday] ? I also think that there must be a possibility to obtain an empty list. Now I get it with [Monday .. Sunday] but I assume that you prefer [Monday, Tuesday ... Sunday]

Would not "liftM2 (,) [0..] [Sunday .. Saturday]" do the trick?
You mean liftM2 (,) [0..] [January .. December] ? (I chose Months in order to get a sensible example.)
Ah, yes. My mistake.
I assume that the Bounded class exists in order to stay independent from the particular type. With minBound and maxBound you do not rely on whether the counting starts on Sunday or Monday if you only want to do something for all days.
Now I see. Sure, your code can be used for any bounded type while mine is specific to Days (or Months). Well, to achieve the same with cyclic enums I would need yet another type class to get bounds which do not put any constraints on exceptions for succ and pred. That would be rather stupid, I think. Would be better with a dedicated cyclic enum class that do not have the succ and pred constraints for bounded instances.
Sure there are subtleties, like what should [Monday .. Monday] return, either: [Monday] or [Monday, Tuesday ... Sunday] but to settle for one would be ok to me.
You mean [Monday, Tuesday ... Sunday, Monday] ?
Actually not. No repetitions.
I also think that there must be a possibility to obtain an empty list.
That would be tricky. Not sure why an empty list must be obtained. /Johan

On 14/07/06, Johan Holmquist
You mean [Monday, Tuesday ... Sunday, Monday] ?
Actually not. No repetitions.
That seems like a very bad idea. '..' normally means 'inclusive', breaking those semantics would be a very weird thing to do, and breaks the principle of least surprise. -- -David House, dmhouse@gmail.com

2006/7/14, David House
On 14/07/06, Johan Holmquist
wrote: You mean [Monday, Tuesday ... Sunday, Monday] ?
Actually not. No repetitions.
That seems like a very bad idea. '..' normally means 'inclusive', breaking those semantics would be a very weird thing to do, and breaks the principle of least surprise.
Good point. When I think about it [Monday .. Monday] should probably not return the same as [Tuesday .. Monday]. (Ofcourse a new class would not permit the use of the [X .. Y] notation if not added to the language somehow.)

Interestingly, your Cyclic class idea may have practical purposes beyond enumeration. Integers modulo some number are also cyclical, and can come in very handy. In fact, raw unsigned ints are modulo 2^32 (or something like that), so they really ought (under one interpretation) to be members of Cyclic rather than Bounded. It would certainly be more efficient, since you wouldn't need to do any overflow checking, and the cpu implements the Cyclic operations, but not the Bounded operations. Anyhow, just thought I'd mention that this isn't useful only for "ordinary" cyclic objects like dates. -- David Roundy

On 14/07/06, David Roundy
Anyhow, just thought I'd mention that this isn't useful only for "ordinary" cyclic objects like dates.
Correct. Which is why Chris Kuklewicz included instances for, e.g., Int :) I think this would be a great class to have in the standard libs. It would be even better if we could derive it. -- -David House, dmhouse@gmail.com

David House wrote:
On 14/07/06, David Roundy
wrote: Anyhow, just thought I'd mention that this isn't useful only for "ordinary" cyclic objects like dates.
Correct. Which is why Chris Kuklewicz included instances for, e.g., Int :)
And the new version takes everything to Integer so there is never any internal overflow.
I think this would be a great class to have in the standard libs. It would be even better if we could derive it.
All the existing instances are just three words: instance Cyclic Foo You only need more if you have something strange, or you want to avoid projecting to Integer. -- Chris

On Fri, Jul 14, 2006 at 02:28:20PM +0100, David House wrote:
On 14/07/06, David Roundy
wrote: Anyhow, just thought I'd mention that this isn't useful only for "ordinary" cyclic objects like dates.
Correct. Which is why Chris Kuklewicz included instances for, e.g., Int :)
Ah, that's what I get for just skimming the thread! :)
I think this would be a great class to have in the standard libs. It would be even better if we could derive it.
I agree, it sounds very nice (although I've obviously not even looked at the implementation). -- David Roundy
participants (6)
-
Chris Kuklewicz
-
David House
-
David Roundy
-
Henning Thielemann
-
Johan Holmquist
-
Malcolm Wallace