
consider the following examples:
-- do-notation: explicit return; explicit guard; monadic result d _ = do { Just b <- return (Just True); guard b; return 42 }
-- list comprehension: explicit return; implicit guard; monadic (list) result lc _ = [ 42 | Just b <- return (Just True), b ]
-- pattern guard: implicit return; implicit guard; non-monadic result pg _ | Just b <- Just True, b = 42
This ongoing discussion has made me curious about whether we could actually get rid of these irregularities in the language, without losing any of the features we like so much. === attempt 1 (a) boolean statements vs guards this looks straightforward. Bool is a type, so can never be an instance of constructor class Monad, so a boolean statement in a monadic context is always invalid at the moment. that means we could simply extend our syntactic sugar to take account of types, and read every ((e :: Bool) :: Monad m => m _) in a statement of a do block as a shorthand for (guard (e :: Bool) :: Monad m => m ()) (b) missing return in pattern guards this could be made to fit the general pattern, if we had (return == id). that would put us into the Identity monad, which seems fine at first, since we only need return, bind, guard, and fail. unfortunately, those are only the requirements for a single pattern guard - to handle not just failure, but also fall-through, we also need mplus. which means that the Identity monad does not have enough structure, we need at least Maybe.. this first attempt leaves us with two problems. not only is (return==id) not sufficient for (b), but the suggested approach to (a) is also not very haskellish: instead of having syntactic sugar depend on type information, the typical haskell approach is to have type-independent sugar that introduces overloaded operations, such as fromInteger :: Num a => Integer -> a to be resolved by the usual type class machinery. addressing these two issues leads us to === attempt 2 (a) overloading Bool following the approach of Num and overloaded numeric literals, we could introduce a type class Boolean class Boolean b where fromBool :: Bool -> b instance Boolean Bool where fromBool = id and implicitly translate every literal expression of type Bool True ~~> fromBool True False ~~> fromBool False now we can embed Boolean statements as monadic statements simply by defining an additional instance instance MonadPlus m => Boolean (m ()) where fromBool = guard (b) adding a strictly matching monadic let we can't just have (return==id), and we do not want the hassle of having to write pattern <- return expr in pattern guards. the alternative of using let doesn't work either let pattern = expr because we do want pattern match failure to abort the pattern guard and lead to overall match failure and fall-through. so what we really seem to want is a shorthand notation for a strict variant of monadic let bindings. apfelmus suggested to use '<=' for this purpose, so that, wherever monadic generators are permitted pattern <= expr ~~> pattern <- return expr === returning to the examples, the approach of attempt 2 would allow us to write -- do-notation: implicit return; implicit guard; monadic result d _ = do { Just b <= Just True; b; return 42 } -- list comprehension: implicit return; implicit guard; monadic (list) result lc _ = [ 42 | Just b <= Just True, b ] -- pattern guard: implicit return; implicit guard; non-monadic result pg _ | Just b <= Just True, b = 42 almost resolving the irregularities, and permitting uniform handling of related syntactic constructs. hooray!-) I say "almost", because Bool permeates large parts of language and libraries, so one would need to check every occurence of the type and possibly replace Bool by (Boolean b => b). the Boolean Bool instance should mean that this process could be incremental (ie, even without replacements, things should still work, with more replacements generalizing more functionality, similar to the Int vs Integer issue), but that hope ought to be tested in practice. one issue arising in practice is that we would like to have fromBool :: MonadPlus m => Bool -> m a but the current definition of guard would fix the type to fromBool :: MonadPlus m => Bool -> m () which would require type annotations for Booleans used as guards. see the attached example for an easy workaround. on the positive side, this approach would not just make pattern guards more regular, but '<=' and 'MonadPlus m => Boolean (m ()) would be useful for monadic code in general. even better than that, those of use doing embedded DSLs in Haskell have been looking for a way to overload Bools for a long time, and the implicit 'Boolean b => fromBool :: Bool -> b' ought to get us started in the right direction. most likely, we would need more Bool-based constructs to be overloaded for Boolean, including at least a function equivalent for if-then-else: class If condition branch where if' :: condition -> branch -> branch -> branch instance If Bool e where if' c t e = if c then t else e instance Monad m => If (m Bool) (m a) where if' c t e = c >>= \b-> if b then t else e with associated desugaring if b then t else e ~~> if' b t e which would also enable us to get around another do notation annoyance, and write things like if (fmap read getLine :: IO Bool) then putStrLn "hi" else putStrLn "ho" all in all, this looks promising, so: thank you, Yitzchak, for insistencing in pointing out the inconsistencies of '<-' (it did cost me some sleep, but I like the results so far!-) I assume there might be downsides as well - any suggestions? Claus