
Hello, Cafe! There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type? As I understand arguments of the post, Bool is bad because: 1) you don't know what does True/False mean 2) after comparison you get bit (!) only but then you may need to "recover" the comparing value which was "shrink" to bit already. Let's begin from 2. As I understand the author talks about one register computers ;) if he have to "recover" a value. But shown examples are in ML, where function arguments are bound to all function body, so you don't need to "recover" anything, what was bound as function argument or with "let". Sounds totally weird and more close to psychology than to CS :) Argument #1 is more interesting. A Boolean,/b/, is either*true*, or *false*; that’s it. There is no/information/carried by a Boolean beyond its value, and that’s the rub. As Conor McBride puts it, to make use of a Boolean you have to know its/provenance/so that you can know what it/means./ Really, what does True/False mean? How to find semantic of True? It's very simple, because there is A) contract/interface which interprets True/False and also B) there is a help from science. A) There are a lot of languages (Unix shell, ML, Basic, Haskell, C/C++...) with short-circuit expressions. Ex., e1 || e2 e1 && e2 e1 orelse e2 where interface is described by its operations: ||, &&, orelse, etc and it has absolutely accurate and clear meaning: "||" executes e2 iff e1 *fails, was not success*. "&&" executes e2 iff e1 was succeeded. I don't use words "True" and "False". Because, in different languages marker of success/fail is different. For example, in Bash, the fail is any integer except 0. In Haskell fail is False. In C is 0... What does mean False (and True) is defined by contract/interface of short-circuit operations, related to boolean algebra. A rare case when type is bound with semantic! We read them literally (native English): e1 or-else e2! *This means that using of False to indicate success - is error! And no way to miss provenance/knowledge what True or False means.* (the same: what does Right/False mean?) B) The help from science. Math (and CS) has own history. And one of its mail-stones was birth of formal logic and then of Boolean algebra. CS implemented those in declarative languages (Prolog, for example). If we have some predicate in Prolog, "true" for that predicate means "it was achieved", as goal. If that predicate has side-effects, "true" means it was achieved, i.e. all its steps (side-effects) were successfully executed. Predicate write_text_to_file/2 is "true" when it wrote text to file. And no way to return False on success or to think about sacral sense of True/False :) And that sense traditionally is the same in all programming language. If you invert it, you deny contract, semantic and begin to use "inverted" logic :) We can repeat the same logic with 3.1415926.. What does it mean? Meaning, semantic is described, but contract/interface: this magic irrational was born from part of algebra, called trigonometry. And this algebra defines semantic of Pi, not programmer's usage of Pi, programming context, etc. True/False semantic is defining by its algebra: boolean. So, programmer should not change their semantic, am I right? So, my question is: is this post a april 1st trolling or author was serious? :) --- Best regards, Paul

I think the point is well worth thinking over and thinking about in the context of programming language design though it may not change the fact that I use if expressions in my programs. In the particular example they cite with plus, what happens is: A) We have a number B) We use that number to get a boolean representing whether or not a proposition about that number holds C) We use that boolean (remembering that it represents something about the number) to pick another number However, the second approach works as follows: A) We pattern match on the number, using something about its structure to pick another number. The value "true" or "false" tells you absolutely nothing about *what* it is testing. The author is not saying "well you might have forgotten which boolean is which and used it in the wrong place," rather "we could do so much better by connecting the *process of proof* to the truth of a particular proposition." Because those are completely different things! The status quo is "only model theory matters, I'm going to ignore proof theory completely," and you shouldn't be satisfied with that! You may not change how you compose your programs overnight, but there *should* be a nagging feeling that all programming is on some level immoral. On 07/05/2018 01:28 AM, PY wrote:
Hello, Cafe!
There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type?
As I understand arguments of the post, Bool is bad because: 1) you don't know what does True/False mean 2) after comparison you get bit (!) only but then you may need to "recover" the comparing value which was "shrink" to bit already.
Let's begin from 2. As I understand the author talks about one register computers ;) if he have to "recover" a value. But shown examples are in ML, where function arguments are bound to all function body, so you don't need to "recover" anything, what was bound as function argument or with "let". Sounds totally weird and more close to psychology than to CS :)
Argument #1 is more interesting.
A Boolean, /b/, is either *true*, or *false*; that’s it. There is no /information/ carried by a Boolean beyond its value, and that’s the rub. As Conor McBride puts it, to make use of a Boolean you have to know its /provenance /so that you can know what it /means./
Really, what does True/False mean? How to find semantic of True? It's very simple, because there is A) contract/interface which interprets True/False and also B) there is a help from science.
A) There are a lot of languages (Unix shell, ML, Basic, Haskell, C/C++...) with short-circuit expressions. Ex.,
e1 || e2 e1 && e2 e1 orelse e2
where interface is described by its operations: ||, &&, orelse, etc and it has absolutely accurate and clear meaning: "||" executes e2 iff e1 *fails, was not success*. "&&" executes e2 iff e1 was succeeded. I don't use words "True" and "False". Because, in different languages marker of success/fail is different. For example, in Bash, the fail is any integer except 0. In Haskell fail is False. In C is 0... What does mean False (and True) is defined by contract/interface of short-circuit operations, related to boolean algebra. A rare case when type is bound with semantic! We read them literally (native English): e1 or-else e2!
*This means that using of False to indicate success - is error! And no way to miss provenance/knowledge what True or False means.*
(the same: what does Right/False mean?)
B) The help from science. Math (and CS) has own history. And one of its mail-stones was birth of formal logic and then of Boolean algebra. CS implemented those in declarative languages (Prolog, for example). If we have some predicate in Prolog, "true" for that predicate means "it was achieved", as goal. If that predicate has side-effects, "true" means it was achieved, i.e. all its steps (side-effects) were successfully executed. Predicate write_text_to_file/2 is "true" when it wrote text to file. And no way to return False on success or to think about sacral sense of True/False :) And that sense traditionally is the same in all programming language. If you invert it, you deny contract, semantic and begin to use "inverted" logic :)
We can repeat the same logic with 3.1415926.. What does it mean? Meaning, semantic is described, but contract/interface: this magic irrational was born from part of algebra, called trigonometry. And this algebra defines semantic of Pi, not programmer's usage of Pi, programming context, etc. True/False semantic is defining by its algebra: boolean. So, programmer should not change their semantic, am I right?
So, my question is: is this post a april 1st trolling or author was serious? :)
---
Best regards, Paul
_______________________________________________ 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.

You may not change how you compose your programs overnight, but there *should* be a nagging feeling that all programming is on some level immoral.
Perhaps elaborating on this is tangential to the issue at hand, but I’d
love to hear/read more behind this thought process. Could you elaborate?
On Thu, 5 Jul 2018 at 09:05, Vanessa McHale
I think the point is well worth thinking over and thinking about in the context of programming language design though it may not change the fact that I use if expressions in my programs.
In the particular example they cite with plus, what happens is:
A) We have a number B) We use that number to get a boolean representing whether or not a proposition about that number holds C) We use that boolean (remembering that it represents something about the number) to pick another number
However, the second approach works as follows:
A) We pattern match on the number, using something about its structure to pick another number.
The value "true" or "false" tells you absolutely nothing about *what* it is testing. The author is not saying "well you might have forgotten which boolean is which and used it in the wrong place," rather "we could do so much better by connecting the *process of proof* to the truth of a particular proposition." Because those are completely different things!
The status quo is "only model theory matters, I'm going to ignore proof theory completely," and you shouldn't be satisfied with that! You may not change how you compose your programs overnight, but there *should* be a nagging feeling that all programming is on some level immoral.
On 07/05/2018 01:28 AM, PY wrote:
Hello, Cafe!
There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type?
As I understand arguments of the post, Bool is bad because: 1) you don't know what does True/False mean 2) after comparison you get bit (!) only but then you may need to "recover" the comparing value which was "shrink" to bit already.
Let's begin from 2. As I understand the author talks about one register computers ;) if he have to "recover" a value. But shown examples are in ML, where function arguments are bound to all function body, so you don't need to "recover" anything, what was bound as function argument or with "let". Sounds totally weird and more close to psychology than to CS :)
Argument #1 is more interesting.
A Boolean, *b*, is either *true*, or *false*; that’s it. There is no *information* carried by a Boolean beyond its value, and that’s the rub. As Conor McBride puts it, to make use of a Boolean you have to know its *provenance *so that you can know what it *means.*
Really, what does True/False mean? How to find semantic of True? It's very simple, because there is A) contract/interface which interprets True/False and also B) there is a help from science.
A) There are a lot of languages (Unix shell, ML, Basic, Haskell, C/C++...) with short-circuit expressions. Ex.,
e1 || e2 e1 && e2 e1 orelse e2
where interface is described by its operations: ||, &&, orelse, etc and it has absolutely accurate and clear meaning: "||" executes e2 iff e1 *fails, was not success*. "&&" executes e2 iff e1 was succeeded. I don't use words "True" and "False". Because, in different languages marker of success/fail is different. For example, in Bash, the fail is any integer except 0. In Haskell fail is False. In C is 0... What does mean False (and True) is defined by contract/interface of short-circuit operations, related to boolean algebra. A rare case when type is bound with semantic! We read them literally (native English): e1 or-else e2!
*This means that using of False to indicate success - is error! And no way to miss provenance/knowledge what True or False means.*
(the same: what does Right/False mean?)
B) The help from science. Math (and CS) has own history. And one of its mail-stones was birth of formal logic and then of Boolean algebra. CS implemented those in declarative languages (Prolog, for example). If we have some predicate in Prolog, "true" for that predicate means "it was achieved", as goal. If that predicate has side-effects, "true" means it was achieved, i.e. all its steps (side-effects) were successfully executed. Predicate write_text_to_file/2 is "true" when it wrote text to file. And no way to return False on success or to think about sacral sense of True/False :) And that sense traditionally is the same in all programming language. If you invert it, you deny contract, semantic and begin to use "inverted" logic :)
We can repeat the same logic with 3.1415926.. What does it mean? Meaning, semantic is described, but contract/interface: this magic irrational was born from part of algebra, called trigonometry. And this algebra defines semantic of Pi, not programmer's usage of Pi, programming context, etc. True/False semantic is defining by its algebra: boolean. So, programmer should not change their semantic, am I right?
So, my question is: is this post a april 1st trolling or author was serious? :)
---
Best regards, Paul
_______________________________________________ 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 05/07/18 08:28, PY wrote:
Hello, Cafe!
There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type?
The text never uses the word "dangerous" or "bad", it says that the Bool type is boring, carries no information and leads to blindness. For instance, let's say that you want to call `head` on a list. But `head` is a partial function, so you need to check first if the list is not empty. Then you branch on the result of the test and call `head` or do something else in the other branch. At first the code is clear and easy to follow. But after several refactorings and new features, the call to `head` was pushed far away from the emptiness test. As you can see, this code is now very fragile. If someone changes the test to something else it will still compile but `head` may now fail at run time. On the other hand, if you use a type expressive enough to encode a proof that the list is not empty (trivial in Agda or Idris), that proof will be in scope and a total version of `head` will only compile if it finds the proof. Cheers, -- -alex https://unendli.ch/

There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type?
To me the argument boils down to the `head` case mentioned by Alex. Most programming languages force you to write code like if List.empty l then ... else ... x = List.head l ... where the problem is that the fact that the List.head call will find the list non-empty is not obvious (in the sense that it requires reasoning). In contrast case l | nil => ... | cons x xs => ... makes it trivially obvious that `x` is extracted from a non-empty list without any reasoning needed at all. Stefan

So, the problem is that test of emptiness does not force you to something right. And possible errors are: if empty: # do if NOT empty - BUG! else: # do if EMPTY - BUG TOO! or # do if NOT empty - BUG! if NOT empty: # now nothing or old "do if NOT EMPTY" OK, I understand it. But how is it related to Booleans? :) Sure, if you use Maybe or Either you are forced with nature of ">>=": it cuts off incorrect branches. With if-then - it does not. But it's not related to Bool: Bool is result for predicates. Maybe/Either forces you with magic operation ">>=" (which is hidden by do-sugar). Bool does not force you - right. But it's problem of Haskell implementation. For example, Prolog "forces" you: Haskell forces you in monad "do": do someInt <- someMaybe -- will not be executed if someMaybe is Nothing Prolog forces you too but on success/fail (Boolean?): someGoal, anotherGoal % anotherGoal will not be executed if someGoal is False Haskell adds only "bool" function which is close to ">>=" in terms of it hides semantic of right bool's processing, avoid those possible errors. If you will use "bool" anywhere when you use Bool as result - all will be fine, or? Sure, you can move "head" usage out of "bool" but you will get empty "bool"s argument. So, IMHO examples of problem with booleans is not related to Bool type at whole, but related to problem that Bool has kind * but not * -> * to be processed in monadic style (and to has needed ">>=" semantic to force you). OK, but original article was not about Haskell's monads, but about Bool in general :) Also what I can't understand: if we will think in such manner does it mean that "if..test" construct is "boring"/"blindness" (excuse my English:) at whole? And all predicates must be removed from the language? What will happen to `filter` function without predicates? And no way to avoid "if..else" construct and predicates functions. As for me, this question is related to static-types fanaticism and "How many angels could dance on the head of a pin". Example with "head" is totally incorrect - it can deconstruct list and no need to predicate function. But what I should do with isSpace, isLower, etc? How to use predicates at whole? :) To map a -> Bool to a -> Maybe a ? What about function which returns IO Bool? Action which can ends with non-critical failure (and need optionally logging, for example) ? 05.07.2018 17:27, Stefan Monnier wrote:
There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type? To me the argument boils down to the `head` case mentioned by Alex.
Most programming languages force you to write code like
if List.empty l then ... else ... x = List.head l ...
where the problem is that the fact that the List.head call will find the list non-empty is not obvious (in the sense that it requires reasoning).
In contrast
case l | nil => ... | cons x xs => ...
makes it trivially obvious that `x` is extracted from a non-empty list without any reasoning needed at all.
Stefan
_______________________________________________ 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.

Happily, all of this has nothing to do with monads or Haskell's special syntax for monads. :) I would not call it static-types fanaticism, but rather, pattern-matching fanaticism. To me, "boolean blindness" is a cute way to describe how this: -- | Sum the first two ints of a list, if possible foo1 :: [Int] -> Maybe Int foo1 (x:y:_) = Just (x + y) foo1 [x] = Just x foo1 [] = Nothing is better than this: -- | Same thing, but with "blind bools" foo2 :: [Int] -> Maybe Int foo2 xs = if length x >= 2 then Just ((x!!1) + (x!!2)) else if length x == 1 then Just (x!!1) else Nothing NB: I already had to correct one mistake in that second code while writing it, and there may be others (I forget if it's (!!) or (!), and I also forget if it's 0-based or 1-based). The first is a description of what I want. It is correct by construction. The second requires converting the description of what I want (sum of the first two ints) into a description of how it is computed, with steps like "find the length and compare it to 2". By using pattern matching, I get both a guarantee of the structure I need, as well as information from within the structure at the same time. With an operational description, I have to do it in separate steps. To me, that's the crux of boolean blindness: Use pattern matching whenever possible! On 07/05/2018 11:04 AM, PY wrote:
So, the problem is that test of emptiness does not force you to something right. And possible errors are:
if empty: # do if NOT empty - BUG! else: # do if EMPTY - BUG TOO!
or
# do if NOT empty - BUG! if NOT empty: # now nothing or old "do if NOT EMPTY"
OK, I understand it. But how is it related to Booleans? :) Sure, if you use Maybe or Either you are forced with nature of ">>=": it cuts off incorrect branches. With if-then - it does not. But it's not related to Bool: Bool is result for predicates. Maybe/Either forces you with magic operation ">>=" (which is hidden by do-sugar). Bool does not force you - right. But it's problem of Haskell implementation. For example, Prolog "forces" you:
Haskell forces you in monad "do": do someInt <- someMaybe -- will not be executed if someMaybe is Nothing
Prolog forces you too but on success/fail (Boolean?): someGoal, anotherGoal % anotherGoal will not be executed if someGoal is False
Haskell adds only "bool" function which is close to ">>=" in terms of it hides semantic of right bool's processing, avoid those possible errors. If you will use "bool" anywhere when you use Bool as result - all will be fine, or? Sure, you can move "head" usage out of "bool" but you will get empty "bool"s argument. So, IMHO examples of problem with booleans is not related to Bool type at whole, but related to problem that Bool has kind * but not * -> * to be processed in monadic style (and to has needed ">>=" semantic to force you).
OK, but original article was not about Haskell's monads, but about Bool in general :) Also what I can't understand: if we will think in such manner does it mean that "if..test" construct is "boring"/"blindness" (excuse my English:) at whole? And all predicates must be removed from the language? What will happen to `filter` function without predicates? And no way to avoid "if..else" construct and predicates functions.
As for me, this question is related to static-types fanaticism and "How many angels could dance on the head of a pin". Example with "head" is totally incorrect - it can deconstruct list and no need to predicate function. But what I should do with isSpace, isLower, etc? How to use predicates at whole? :) To map a -> Bool to a -> Maybe a ? What about function which returns IO Bool? Action which can ends with non-critical failure (and need optionally logging, for example) ?
05.07.2018 17:27, Stefan Monnier wrote:
There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type? To me the argument boils down to the `head` case mentioned by Alex.
Most programming languages force you to write code like
if List.empty l then ... else ... x = List.head l ...
where the problem is that the fact that the List.head call will find the list non-empty is not obvious (in the sense that it requires reasoning).
In contrast
case l | nil => ... | cons x xs => ...
makes it trivially obvious that `x` is extracted from a non-empty list without any reasoning needed at all.
Stefan
_______________________________________________ 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.

Hello Bryan! IMHO a discrepancy arises from the to different flows: * With pattern matching we create 2 branches with *data flow* (typical for ML): 1. Result exists - to be processed (head of list) 2. Result does not exist, nothing to process (no head at whole) * With boolean testing we create 2 branches in *logical flow* (typical for Prolog): 1. Predicate is true and further sequential processing is possible 2. Predicate is false and other part of the sentence is false too (no more further processing) So, my misunderstanding is that I try to think about ML/Haskell as about declarative languages, but they are imperative. 05.07.2018 20:51, Bryan Richter wrote:
Happily, all of this has nothing to do with monads or Haskell's special syntax for monads. :)
I would not call it static-types fanaticism, but rather, pattern-matching fanaticism. To me, "boolean blindness" is a cute way to describe how this:
-- | Sum the first two ints of a list, if possible foo1 :: [Int] -> Maybe Int foo1 (x:y:_) = Just (x + y) foo1 [x] = Just x foo1 [] = Nothing
is better than this:
-- | Same thing, but with "blind bools" foo2 :: [Int] -> Maybe Int foo2 xs = if length x >= 2 then Just ((x!!1) + (x!!2)) else if length x == 1 then Just (x!!1) else Nothing
NB: I already had to correct one mistake in that second code while writing it, and there may be others (I forget if it's (!!) or (!), and I also forget if it's 0-based or 1-based).
The first is a description of what I want. It is correct by construction.
The second requires converting the description of what I want (sum of the first two ints) into a description of how it is computed, with steps like "find the length and compare it to 2".
By using pattern matching, I get both a guarantee of the structure I need, as well as information from within the structure at the same time. With an operational description, I have to do it in separate steps.
To me, that's the crux of boolean blindness: Use pattern matching whenever possible!
On 07/05/2018 11:04 AM, PY wrote:
So, the problem is that test of emptiness does not force you to something right. And possible errors are:
if empty: # do if NOT empty - BUG! else: # do if EMPTY - BUG TOO!
or
# do if NOT empty - BUG! if NOT empty: # now nothing or old "do if NOT EMPTY"
OK, I understand it. But how is it related to Booleans? :) Sure, if you use Maybe or Either you are forced with nature of ">>=": it cuts off incorrect branches. With if-then - it does not. But it's not related to Bool: Bool is result for predicates. Maybe/Either forces you with magic operation ">>=" (which is hidden by do-sugar). Bool does not force you - right. But it's problem of Haskell implementation. For example, Prolog "forces" you:
Haskell forces you in monad "do": do someInt <- someMaybe -- will not be executed if someMaybe is Nothing
Prolog forces you too but on success/fail (Boolean?): someGoal, anotherGoal % anotherGoal will not be executed if someGoal is False
Haskell adds only "bool" function which is close to ">>=" in terms of it hides semantic of right bool's processing, avoid those possible errors. If you will use "bool" anywhere when you use Bool as result - all will be fine, or? Sure, you can move "head" usage out of "bool" but you will get empty "bool"s argument. So, IMHO examples of problem with booleans is not related to Bool type at whole, but related to problem that Bool has kind * but not * -> * to be processed in monadic style (and to has needed ">>=" semantic to force you).
OK, but original article was not about Haskell's monads, but about Bool in general :) Also what I can't understand: if we will think in such manner does it mean that "if..test" construct is "boring"/"blindness" (excuse my English:) at whole? And all predicates must be removed from the language? What will happen to `filter` function without predicates? And no way to avoid "if..else" construct and predicates functions.
As for me, this question is related to static-types fanaticism and "How many angels could dance on the head of a pin". Example with "head" is totally incorrect - it can deconstruct list and no need to predicate function. But what I should do with isSpace, isLower, etc? How to use predicates at whole? :) To map a -> Bool to a -> Maybe a ? What about function which returns IO Bool? Action which can ends with non-critical failure (and need optionally logging, for example) ?
05.07.2018 17:27, Stefan Monnier wrote:
There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result. I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/ and was shocked. How popular is such opinion? Is it true, that bool is "bad" type? To me the argument boils down to the `head` case mentioned by Alex.
Most programming languages force you to write code like
if List.empty l then ... else ... x = List.head l ...
where the problem is that the fact that the List.head call will find the list non-empty is not obvious (in the sense that it requires reasoning).
In contrast
case l | nil => ... | cons x xs => ...
makes it trivially obvious that `x` is extracted from a non-empty list without any reasoning needed at all.
Stefan
_______________________________________________ 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.
_______________________________________________ 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, the criticism is valid but mostly irrelevant.
There is an opinion that Bool type has problems. It's "dangerous", because it's not good to be used as flag for success/fail result.
Actually that's the one good use case. Also, Boolean-as-a-type means that you do not need a separate language concept of Condition, Conditions are just those Expressions that happen to be of type Boolean. And suddenly you can write functions that operate on Conditions, or define operators for them (if the language allows operator definitions), etc.
I read this post: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/
Well, the first two paragraphs are just overgeneralizations of personal observations.
and was shocked. How popular is such opinion?
It's a fringe opinion. Most people don't even think about whether Boolean is an appropriate type.
Is it true, that bool is "bad" type?
As I understand arguments of the post, Bool is bad because: 1) you don't know what does True/False mean 2) after comparison you get bit (!) only but then you may need to "recover" the comparing value which was "shrink" to bit already.
Sure. That's a valid point the post is making. So you shouldn't move the creation of a Boolean too far away from its consumption. The same argument holds for any numeric data type; if you pass around Floats, you quickly lose knowledge whether it's yards or meters (that kind of problem actually made an interplanetary probe miss its destination planet). So you simply use whatever the language offers for making binary distinctions. In C you use the preprocessor to say PRESENT or ABSENT instead of true or false (actually 0 or 1); in Java you use an enum, in Haskell you use a data type.
Really, what does True/False mean? How to find semantic of True? It's very simple, because there is A) contract/interface which interprets True/False and also B) there is a help from science.
This works as long as the contract is easily deducible from the context in the program. I.e. if you have a file-is-open function, then the contract of that function says that the result is True or False, and as long as the value from the function is kept in contexts where it's clear that we are talking about a file-open status, that's good enough. Things can get nasty when you start moving a file-is-open Boolean into a "valid" attribute. You (as a human reader) lose the information that the value is related to a file-open status. Note that such a loss of context may actually be intentional, if the goal is to have more abstract code and we don't care anymore whether that valid=False status relates to files or whether it's a weekday. Though that's exactly the situation where the blog post's arguments are irrelevant, too :-)
*This means that using of False to indicate success - is error!
Not really. It can mislead a human reader, so it should be avoided. But I have had some rare occasions where isFailure: Boolean was the correct declaration to use (e.g. if isFailure is False by default - actually that's not a too rare situation now that I think about it).
And no way to miss provenance/knowledge what True or False means.*
Except that if you pass the value to a variable named "isSuccess", you have a bug.
(the same: what does Right/False mean?)
Personally, I avoid the True/False terminology; it (mis)applies the concept of "desirable" or "truth", and boolean values aren't about desirability or truth. Just assume the values are "Yes" and "No"; actually this is exactly the issue the blog post is really talking about: "Yes" and "No" are answers, but answers are useful only as long as you know the question. (Reminds me of "42" in the Douglas Adams fiction: the supercomputer gave that as the ultimate answer, now they are building a larger supercomputer to find out what the question to that answer is.)
B) The help from science.
Science is not too relevant here. The blog post is talking about maintainability, i.e. programmer psychology. For Booleans, science tells you a lot about what you can do with them, but it does not tell you what the results of your operations *mean*.
So, my question is: is this post a april 1st trolling or author was serious? :)
The latter, but you missed the point ;-) (SCNR) BTW the post is pretty rambling, it touches a lot of points but is never quite precise. I hope I did better but I'll leave that to better judgement than mine :-)

Hello Joachim! Very nice answer and explanations! So: 05.07.2018 21:48, Joachim Durchholz wrote:
Is it true, that bool is "bad" type?
As I understand arguments of the post, Bool is bad because: 1) you don't know what does True/False mean 2) after comparison you get bit (!) only but then you may need to "recover" the comparing value which was "shrink" to bit already.
Sure. That's a valid point the post is making. So you shouldn't move the creation of a Boolean too far away from its consumption.
The same argument holds for any numeric data type; if you pass around Floats, you quickly lose knowledge whether it's yards or meters (that kind of problem actually made an interplanetary probe miss its destination planet).
Yes! And I can not imagine Bool which is not bound to some meaningful named variable (flag) like "enabled", "isClosed", etc. Bool is always flag or a result of predicate.
Really, what does True/False mean? How to find semantic of True? It's very simple, because there is A) contract/interface which interprets True/False and also B) there is a help from science.
This works as long as the contract is easily deducible from the context in the program. I.e. if you have a file-is-open function, then the contract of that function says that the result is True or False, and as long as the value from the function is kept in contexts where it's clear that we are talking about a file-open status, that's good enough. Things can get nasty when you start moving a file-is-open Boolean into a "valid" attribute. You (as a human reader) lose the information that the value is related to a file-open status.
Yes, makes sense. What is difficult to me, to imagine true/false itself, without predicate or flag. So, it's difficult to me to imagine bool which looses its original sense. It's the same as to forget the sense of Right or Left. Actually, what does Left mean? Success result? Or something else? Totally depends on context, on semantic. You can encode good result as "Left Smth" and failure as "Right smth". And only implementation of ">>=" will be problem in such inversion. But ML (in the original article) has not ">>=", so no way to force you to keep in mind success-result == "Right Smth". This was the reason why I made accent to monadic operations.
Personally, I avoid the True/False terminology; it (mis)applies the concept of "desirable" or "truth", and boolean values aren't about desirability or truth.
Just assume the values are "Yes" and "No"; actually this is exactly the issue the blog post is really talking about: "Yes" and "No" are answers, but answers are useful only as long as you know the question. (Reminds me of "42" in the Douglas Adams fiction: the supercomputer gave that as the ultimate answer, now they are building a larger supercomputer to find out what the question to that answer is.) Yes, you are absolutely right here too. So I was talking about contract/interface: in Bash the value of "truth" is 0, the value of "false" is multiple values. In Haskell: only True and False. But with BoolValue and Boolean instances we can map Bash case to Haskell case.
B) The help from science.
Science is not too relevant here. The blog post is talking about maintainability, i.e. programmer psychology. Yes, I see now that it's more relevant to psychology :) When I talked about science, I mean that I think not "file-open -> {True|False}" but "openedFile -> {achieved|not achieved}". For me, action is already predicate. So when we map functional style to declarative style we must treat Bool in this way. In Prolog is don't need to separate predicate and its result (Boolean - is some variable) but I'm using predicate instead of Bool. May be problem here is that FP is imperative and not declarative.
participants (7)
-
Alex Silva
-
Bryan Richter
-
Joachim Durchholz
-
Leandro Ostera
-
PY
-
Stefan Monnier
-
Vanessa McHale