
does anyone else think this would be useful to provide?
module Data.Perhaps where
data Perhaps = No | Maybe | Yes deriving(Eq,Ord,Show,Read,Enum,Bounded)
instance Monoid Perhaps ... ...
I only ask because it has come up as useful several times in projects I work on. John -- John Meacham - ⑆repetae.net⑆john⑈

On 8/3/06, John Meacham
does anyone else think this would be useful to provide?
module Data.Perhaps where
data Perhaps = No | Maybe | Yes deriving(Eq,Ord,Show,Read,Enum,Bounded)
instance Monoid Perhaps ... ...
Reminds me of Donald Knuth's type declaration: type enum { false, true, wow } bool; /Josef

On 8/2/06, John Meacham
does anyone else think this would be useful to provide? Maybe
(sorry, couldn't resist :-) -iavor
module Data.Perhaps where
data Perhaps = No | Maybe | Yes deriving(Eq,Ord,Show,Read,Enum,Bounded)
instance Monoid Perhaps ... ...
I only ask because it has come up as useful several times in projects I work on.
John
-- John Meacham - ⑆repetae.net⑆john⑈ _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

At Wed, 2 Aug 2006 19:42:45 -0700, John Meacham wrote:
does anyone else think this would be useful to provide?
I remember wanting something like that on several occassions in the past, but I can not remember the exact details. I think I wanted something like: data Perhaps a = No | Maybe a | Yes Or possibly: data Perhaps n m y = No n | Maybe m | Yes y But I do not remember what I was trying to do, so I am not sure. j.

John Meacham wrote:
does anyone else think this would be useful to provide?
module Data.Perhaps where
data Perhaps = No | Maybe | Yes deriving(Eq,Ord,Show,Read,Enum,Bounded)
instance Monoid Perhaps ... ...
I only ask because it has come up as useful several times in projects I work on.
I think "Maybe Bool" is better for this. It already separates out for you the notion of certainty vs. uncertainty. What Monoid did you have in mind for it? -- Ashley Yakeley

G'day all. John Meacham wrote:
does anyone else think this would be useful to provide?
Not me.
Quoting Ashley Yakeley
I think "Maybe Bool" is better for this.
I don't. I also think that 80% of the uses of Bool are wrong. Any time that you see this: doSomething :: Bool -> Stuff -> MoreStuff Not only is it not obvious what Bool means, it's not obvious what the sense of it should be. In fact, almost every time I see an argument in a function that I haven't used for a while, I find myself reaching for the documentation, because I can never remember what it means. The only exceptions to this rule that I can think of are functions of the form: possiblyDoSomething :: Bool -> Whatever In that case, it's obvious that the Bool controls the "possibly" aspect. True means do it, False means don't do it. A good example of this is showParen. As for return values, you can almost forgive property tests: isSilly :: PossiblySillyThing -> Bool though later, you find yourself also needing: isNotSilly :: PossiblySillyThing -> Bool However, there's now a robustness issue. A client of this library can easily fall into the trap that a PossiblySillyThing has precisely two states: silly or not silly. That may even be true in version 1. In Haskell, it takes one line to declare a new enumerated type with just a few elements. For very little effort, you get a huge payoff in usability: data Silliness = Silly | Sensible silliness :: PossiblySillyThing -> Silliness -- Now I don't have to remember what the first argument means or -- which way around it's supposed to be. It's obvious from the type. doSomething :: Silliness -> Stuff -> MoreStuff I'm sorry to go through this in detail, but this stuff is easy to forget. Oh, and one more thing: Everything I've said about Bool goes triply for Either. Cheers, Andrew Bromage

Andrew Bromage
I also think that 80% of the uses of Bool are wrong.
Any time that you see this:
doSomething :: Bool -> Stuff -> MoreStuff
Not only is it not obvious what Bool means, it's not obvious what the sense of it should be. In fact, almost every time I see an argument in a function that I haven't used for a while, I find myself reaching for the documentation, because I can never remember what it means.
[...]
In Haskell, it takes one line to declare a new enumerated type with just a few elements. For very little effort, you get a huge payoff in usability:
data Silliness = Silly | Sensible
silliness :: PossiblySillyThing -> Silliness
-- Now I don't have to remember what the first argument means or -- which way around it's supposed to be. It's obvious from the type. doSomething :: Silliness -> Stuff -> MoreStuff
I'm sorry to go through this in detail, but this stuff is easy to forget.
Unfortunately the relevant prelude functions, like not, &&, all, ..., are all written in a way that they don't work for Silliness.
Oh, and one more thing: Everything I've said about Bool goes triply for Either.
And for (,), of course. ;-) The trade-off currently is readability versus re-use of existing functions. A generic prelude, where ``not Silly'' is automagically ``Sensible'', might bring some of the best of both worlds, but could also spawn new confusion: with the definition above, we would probably get: < forall x :: Silliness . Silly && x = Silly < forall x :: Silliness . Sensible || x = x With respect to the name ``Silliness'', ``Silly'' intuitively corresponds to ``True'', but comes first, unlike ``True'' in data Bool = False | True ``Getting the names right'' is important, but hard. Wolfram

G'day all. Quoting kahl@cas.mcmaster.ca:
Unfortunately the relevant prelude functions, like not, &&, all, ..., are all written in a way that they don't work for Silliness.
For simple conditionals, I argue that: if not (isSilly thing) then foo else bar is no better than: case silliness thing of Sensible -> foo Silly -> bar I agree with you in part about complex conditions, however. Complex conditionals are inherently tricky things. One argument I gave for avoiding Bool is one of robustness. Complex conditionals are often inherently non-robust. Suppose, for example, you write a windowing system where every window is either Normal or Minimised. You might have your code littered with: doSomething | isWindowNormal win && isOnScreen (windowRect win) = foo | otherwise = bar Does the first part of this test mean Normal or not Minimised? When you allow windows that are Maximised or Shaded, the logic may be wrong. In this case, the most robust solution might actually be to introduce a temporary Bool view: isWindowVisible :: Window -> Bool isWindowVisible win = case windowState win of Normal -> isOnScreen (windowRect win) Minimised -> False When more window states are added, at the very least you get a compiler warning.
Oh, and one more thing: Everything I've said about Bool goes triply for Either.
And for (,), of course. ;-)
I wouldn't say "triply" in the case of (,). The argument about using built-in functions is much weaker for Either than for (,) because far fewer built-in functions work with Either than with (,).
The trade-off currently is readability versus re-use of existing functions.
No, it's readability, writability and robustness vs re-use of existing functions. And it doesn't preclude you from re-using existing functions if you want to: all isSilly things vs: all (==Silly) (map silliness things)
With respect to the name ``Silliness'', ``Silly'' intuitively corresponds to ``True'', but comes first, unlike ``True'' in
data Bool = False | True
This is because of instance Ord. Semantically, False < True makes some kind of sense. Neither Silly < Sensible nor Sensible < Silly make the same kind of sense. This is not to say, of course, that imposing _some_ ordering might make pragmatic sense, say, so you could use them as Data.Map keys. Cheers, Andrew Bromage

Hello kahl, Monday, August 14, 2006, 8:15:05 AM, you wrote:
Unfortunately the relevant prelude functions, like not, &&, all, ..., are all written in a way that they don't work for Silliness.
type classes is universal answer to almost any question ;) data B = F | T deriving Boolean and :: (Boolean t, Foldable c) => c t -> t or, in the fashion i just described in cafe: and :: Foldable Boolean -> Boolean btw, class Enum a => Boolean a where fromBool :: Bool -> a toBool :: a -> Bool fromBool = fromEnum.toEnum toBool = fromEnum.toEnum so the only change required in Haskell compilers to make possible implementing this idea is to make: data T = ... deriving C equivalent to instance C T for classes whose automatic deriving is not supported by the Haskell itself -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
type classes is universal answer to almost any question ;)
Argh! Every complex problem has a simple and wrong answer, huh? At some point you should stop generalizing, because doing everything equally bad is the same as doing nothing right (but requires more work).
data B = F | T deriving Boolean
Now is toBool :: Silliness -> Bool equivalent to isSilly or to isSensible? See, the gain in readability is... uhm... questionable.
btw,
class Enum a => Boolean a where fromBool :: Bool -> a toBool :: a -> Bool fromBool = fromEnum.toEnum toBool = fromEnum.toEnum
btw, fromBool :: Enum b => Bool -> b fromBool = fromEnum.toEnum toBool :: Enum b => b -> Bool toBool = fromEnum.toEnum is a lot simpler and exactly as useful (read: not at all). Udo. PS: No, I don't think 'perhaps' is all that useful. It lacks obvious semantics and is easily defined should you need it, in which case you also know how it should behave. -- I loathe people who keep dogs. They are cowards who haven't got the guts to bite people themselves. -- August Strindberg

Hello Udo, Monday, August 14, 2006, 4:22:55 PM, you wrote:
Now is
toBool :: Silliness -> Bool
equivalent to isSilly or to isSensible? See, the gain in readability is... uhm... questionable.
yes, you are right. 'and' is useless, not because we can't reimplement it in more general way but because 'and sillyThings' don't have obvious meaning. (all (==Silly) sillyThings) is the right readable way -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Mon, Aug 14, 2006 at 12:15:05AM -0400, kahl@cas.mcmaster.ca wrote:
Unfortunately the relevant prelude functions, like not, &&, all, ..., are all written in a way that they don't work for Silliness.
newtype deriving is really great here. newtype NumberOfBalls = NumberOfBalls Int deriving(Num,Eq,Ord) now you have a type that works almost the same as Int, you can add, substract, etc.. on it. but you can't accidentally add one to a plain old Int. Of course, to take the most advantage of this sort of thing, you want to define your own classes for some shared syntax. class HasSize a where size :: a -> Int class IsEmpty a where isEmpty :: a -> Bool newtype IdMap a = IdMap (Map.Map Id a) deriving(HasSize,Monoid,IsEmpty) and so forth. John -- John Meacham - ⑆repetae.net⑆john⑈

G'day all.
Quoting John Meacham
newtype deriving is really great here.
It's really great, but in the case of Silliness, I wouldn't say it's great _here_. Incidentally, getting back to the original topic, the argument of using built-in functions fails for Perhaps.
Of course, to take the most advantage of this sort of thing, you want to define your own classes for some shared syntax.
Slightly contradicting myself, here's one that I use: class TestableProperty prop a | prop -> a where is :: prop -> a -> Bool data Prime = Prime instance TestableProperty Prime Integer where is Prime x = {- detail omitted -} The only problem with this is that with the fundep, you can't do this: instance (Integral i) => TestableProperty Prime i where is Prime x = {- same detail -} Cheers, Andrew Bromage

ajb@spamcop.net wrote:
Slightly contradicting myself, here's one that I use:
class TestableProperty prop a | prop -> a where is :: prop -> a -> Bool
data Prime = Prime
instance TestableProperty Prime Integer where is Prime x = {- detail omitted -}
The only problem with this is that with the fundep, you can't do this:
instance (Integral i) => TestableProperty Prime i where is Prime x = {- same detail -}
Maybe I'm dense but couldn't you just drop the fundep? Cheers, Ben
participants (10)
-
ajb@spamcop.net
-
Ashley Yakeley
-
Benjamin Franksen
-
Bulat Ziganshin
-
Iavor Diatchki
-
Jeremy Shaw
-
John Meacham
-
Josef Svenningsson
-
kahl@cas.mcmaster.ca
-
Udo Stenzel