Polymorphic `if` statement

I’d like to add to this that what defining truthy and falsey values, we must differentiate between notFalse x = x /= false and isTrue x = x == true, for some boolish values of false :: x and true :: x. When languages implicitly cast values to a boolean, they usually use notFalse, and while these two functions are the same for booleans, they are not the same for boolish values.

1 Like

Coq allows to use if _ then _ else _ expressions for every data type with exactly two constructors: Extended pattern matching — Coq 8.17.1 documentation
But this is more ad-hoc than using a typeclasses and looks directly at the definition of the datatype you are using as the first argument. The main use case is if you have for example an argument of type {n = m} + {n <> m} which tells you whether two numbers are equal or not. I.e. a better version of a boolean which doesn’t suffer from boolean blindness.

1 Like

typeclasses like Real, Integral and IsString

Notice how all of these typeclasses are unambiguous, every type that deserves an instance only has one possible correct one. Equating something to a boolean on the other hand is completely context dependent. You don’t actually gain anything from a typeclass like Boolish and the function name itself can no longer even convey what the conversion represents.

Also note that this kind of a misuse of typeclasses is already prevalent in certain parts of Haskell, for example serialization (see Some thoughts on typeclass-based codecs).

2 Likes

I recently did something akin to that idea using “Rebindable Syntax”.

Here is a minimal example:

{-# LANGUAGE GADTs            #-}
{-# LANGUAGE RebindableSyntax #-}

import           Prelude

class IfThenElse a b where
    ifThenElse :: a -> b -> b -> b

-- For some weird eDSL
data Expr a where
  Lit      :: a -> Expr a
  Add      :: Expr Int  -> Expr Int -> Expr Int
  LessThan :: Expr Int  -> Expr Int -> Expr Bool
  ITE      :: Expr Bool -> Expr a -> Expr a -> Expr a

deriving instance Show a => Show (Expr a)

instance IfThenElse (Expr Bool) (Expr a) where
    ifThenElse c a b = ITE c a b

f :: Int -> Int -> String
f a b = show $
  if LessThan (Add (Lit a) (Lit b)) (Lit 100) then Lit "Not enough" else Lit "Thank you"

-- Compatible with built-in Bool

instance IfThenElse Bool a where
    ifThenElse True  a _ = a
    ifThenElse False _ b = b

g a b = if a + b < 100 then "Not enough" else "Thank you"
1 Like

Having a polymorphic version of if is useful for embedded DSLs. sbv, for example, has an SBool type with its own versions of if-then-else, == and so on, since it needs to turn if-the-else into logic formulas at runtime rather than taking one branch or the other.

I’ve wanted the same kind of functionality myself before. RebindableSyntax lets us have it in principle, but it’s a pretty painful extension to use in practice. And, even if you have it, all the existing code involving Bool doesn’t get generalized the way Num/Floating/etc code does.

Now, this is a bit of a niche usecase and it’s not clear that it would justify the extra complexity to have some sort of Boolean class in the standard library, but there is value to having a language sufficiently adaptable that even conditionals can be generalized and interpreted in different ways.

Of course, this is also a totally different usecase from the suggestion that started this thread, which would be emulating automatic “truthiness” of languages like Python or JavaScript which I’ve had mixed experiences with in practice. Sometimes it’s great, sometimes it causes reasonable-looking code to behave in unexpected ways. Either way, it definitely wouldn’t fit with Haskell’s broader design philosophy!

Possibly related?

1 Like

Thanks all for your answers!

I know that this is not that important, but just for the sake of discussion, let me provide an example:

consider a datatype

data ShouldShow
  = Show
  | Hide

if we want to consume a value shouldShow of that type, the most Haskelly way to do it is to use pattern matching

case shouldShow of
  Show -> ...
  Hide -> ...

I would say that such a code would read better if it was written like

if shouldShow then ... else ...

but that is not possible. The best we could get in that direction is to use a toBool :: ShouldShow -> Bool function and have

if toBool shouldShow then ... else ...

I would argue that the toBool before shouldShow does not help neither the writer nor the reader of the code, but it is there just to please the type checker.

The same this happens whenever you have a newtype over Bool.

This is not a big deal, but it’s still a little annoying.

There I thought about generalising the if statement so that it could accept something which could be turned into a boolean.

The idea is not to have instances for anything and introduce a concept of truthiness like you have in dynamic languages. I would have instances basically only for types with cardinality 2 where their meaning is clear. @maxigit I would not have Boolish a => Boolish (Maybe a), or Boolish String or Boolish Int

@BurningWitness, it wouldn’t be an implicit cast, but explicitly defined by the instance definition. So @ApothecaLabs there would be no confusion between isTrue and notFalse; If a value get eveluated to True, it goes to the then branch, if it evaluates to False, it goes to the else branch

1 Like

It seems to me that the primary value of OverloadedStrings comes from convenient syntax for introduction forms, that is, string literals.

But the compelling DSL use case that @Tikhon identified seems best served by overloaded elimination forms - writing STrue is not so painful, but writing ite A B C is.

Not that Haskell really needs more extensions, but OverloadedIf that replaced calls to if E1 then E2 else E3, guards on patterns, and conditions in list comprehensions with the equivalent of if toBool E1 then E2 else E3, with

class BoolLike a where
  toBool :: a -> Bool

instance BoolLike Bool where
  toBool = id

would get part of the way there. I still think it would fall down painfully, though, because of the lack of something like Num to overload && and friends - I’m not sure what makes a Heyting algebra class a better choice than a Boolean algebra here, but introducing either would be a severely painful breaking change. But users of a DSL can selectively import the prelude, so there’s a reasonable workaround there.

I actually disagree here! Bool-like datatypes are a frequent source of confusion for me when they’re used this way in Coq, as I have a hard time figuring out which case is truthy and which is falsy. Here, I’d really rather see the case expression when reading the code - it looks less nice, but it requires less puzzling on my part.

3 Likes

I think the Haskell way of doing things is instead writing

data Visibility = Visible | Hidden

isVisible Visible = True
isVisible Hidden  = False

This way there is no implication that either of the states is the default one and the function is now reusable (compare (not . isVisible) visibility against (not . toBool) shouldShow).

3 Likes

If you reall don’t want to pattern match you can still use if shouldShow == Show ....
What is wrong with it ?

nothing is wrong with it, that works OK. It just doesn’t read very well, but it could be just me. This is more an exercise of style that anything else

It doesn’t read because shouldShow suggests a true/false value, so I indeed, as it looks like a boolean, one might be tempted to write/read if shouldShow.
But that`s due to the original name of the type, which could have been different.
I guess you are trying to avoid boolean blindness, and as such use name which would suit better a type alias.

If you rename it to ShowOrHide, then the boolish temptation disappear. if showOrHide == Show seems perfectly reasonable.

TDLR;
You are forcing the “boolish” issue by chosing a boolish name.

1 Like

Hi, I just want to express my agreement on the wish for splitting up -XRebindableSyntax, it would be nice, to e.g. have a -XQualifiedSyntax extension that works like -XQualifiedDo but for literally everything that can be overloaded with -XRebindableSyntax, I think this would lift Haskell’s eDSL capabilities to another level. :3

An example usage would be

import SomeEDSL qualified as E -- has a definition for ifThenElse 

a x = E.if x then 3 else 4 
1 Like

really the worse part about -XRebindableSyntax is imo, that you have to write classes like

type IsIfThenElse :: Type -> Type -> Type -> Constraint
class IsIfThenElse b x y where
  type IfThenElse b x y :: Type
  ifThenElse :: b -> x -> y -> IfThenElse b x y

to make it possible to instantiate it at the usual definition, but the issue is that you have no way to use e.g. Proxies or Type applications with the overloaded syntax, so you end up writing instances like:

instance (x ~ y) => IsIfThenElse Bool x y where
  type IfThenElse Bool x y = x
  ifThenElse True x _ = x
  ifThenElse False _ y = y

automatically ruling out other, possibly valuable instances because you have to make the instance resolution commit on the type.

So the greatest advantage of being able to qualify syntax would be that you would not have to overload your overloading to accommodate the usual usages.

1 Like

Because of lazyness, you can easily define your own control flow by just defining function or operator.
For example you can write something like

a x = if_  x `then_` 3 `else_` 4

or

a x = x ?? 3 ?: 4

or eouivalent. The rebinding syntax you are proposing is there only to reuse keywords (which is different from qualifiedDo which is really expanded to something else).

afaict it’s exactly the same, you reuse syntax sugar for a different desugaring. e.g. if you do

import MyEDSL qualified as E

smth = E.do 
  statement 
  anotherStatement 

This will exactly require the operators that this is desugared to, namely >>

This is worse than RebindableSyntax in terms of UI

What about (assuming we have a Boolish class)

ifte :: Boolish a => a -> b -> b -> b
ifte test then_ else_ = if (toBool test) then then_ else else_

Using ArgumendDo

ifte shouldShow
   do ...
   do ...

The biggest pain point is having to enable RebindableSyntax, which is quite heavy. Something like QualifiedIf might be nice, although it would be a lot more niche than QualifiedDo.