Pattern guards

Yitzchak Gale gale at sefer.org
Sat Sep 30 20:08:35 EDT 2006


Thanks for all the responses. I get the digest,
and I was off-line for a day, so I only saw most
of them now.  Also, for the same reason, my
apologies that I am connecting this message to the
wrong spot in the thread.

First of all, I still maintain that any expression
written using pattern guards can be written just
as simply - and, in my opinion, more clearly - in
Haskell 98 using monads.

An important clarification: the main monad at work
here is the Exit monad. The "bind" notation in a
pattern guard is just an obfuscated Exit monad.
However, in many simple examples, the Maybe monad
can be used as a special case of the Exit monad.

It is true that in my proof I also use a nested
Maybe monad, but that is only for the
comma-separated sequence of multiple qualifiers in
a complex pattern guard.

Conor McBride wrote:
> Whether or not your conclusion is correct, your
> candidate proof is incomplete...  This
> translation does not appear to address programs
> with multiple left-hand sides, exploiting
> fall-through from match (hence guard) failure

Quite right, sorry. That is easy to fix.  A
corrected proof is at the bottom of this message.

David Roundy wrote:
> If all your pattern guards happen to involve the
> Maybe monad, then perhaps you can rewrite the
> pattern guard code almost as concisely using
> monadic notation

No, it works for any type.

> the moment you choose to do that you have to
> completely give up on using Haskell's existing
> pattern matching to define your function, unless
> you happen to be defining a particularly simple
> function.

No, all pattern matching is retained as before.

> How do you nearly as concisely write a function
> such as this in Haskell 98?

Hmm, believe it or not, your original example is
too simple. You can actually do the whole thing in
the Maybe monad, because none of the versions of
foo has more than one pattern guard.  I am
transposing the third and fourth foo and combinig
like LHSs to make it more interesting. Here is
your function with those modifications:

>> foo (Left "bar") = "a"
>> foo (Right x) | (b,"foo") <- break (==' ') x = "b " ++ b
>>               | ["Hello",n,"how","are","you",d@(_:_)] <- words x,
>>                 last d == '?'
>>         = n ++ " is not here right now, but " ++ n ++ " is " ++
>>           init d ++ " fine."
>> foo (Left x) | ("foo",c) <- break (==' ') x = "c " ++ c
>>              | length x == 13 = "Unlucky!"
>> foo (Right x) = x
>> foo (Left x) = x

And here it is in Haskell 98:

> foo (Left "bar") = "a"
> foo (Right x) | isExit y = runExit y
>  where y = do
>   maybeExit $ do (b,"foo") <- return $ break (==' ') x
>                  return $ "b" ++ b
>   maybeExit $ do ["Hello",n,"how","are","you",d@(_:_)] <- return $ words x
>                  guard $ last d == '?'
>                  return $ n ++ " is not here right now, but " ++
>                           n ++ " is " ++ init d ++ " fine."
> foo (Left x) | isExit y = runExit y
>  where y = do
>   maybeExit $ do ("foo",c) <- break (==' ') x
>                  return $ "c" ++ c
>   when (length x == 13) $ Exit "Unlucky!"
> foo (Right x) = x
> foo (Left x) = x

Finally, here is the corrected proof, allowing for
multiple LHSs. Actually, the proof is still not
complete - I do not treat pattern bindings, nor
other possible forms for funlhs, as enumerated in
the Report.

Proof: We first assume that the following declarations
are available, presumably from a library:

> data Exit e a = Continue a | Exit {runExit :: e}
> instance Monad (Exit e) where
>   return = Continue
>   Continue x >>= f = f x
>   Exit e >>= _ = Exit e

(Note that this is essentially the same as the Monad
instance for Either defined in Control.Monad.Error,
except without the restriction that e be an instance
of Error.)

> maybeExit :: Maybe e -> Exit e ()
> maybeExit = maybe (return ()) Exit

> isExit :: Exit e a -> Bool
> isExit (Exit _) = True
> isExit _        = False

Now given any function binding using pattern guards:

var apat1 apat2 ... apatn
 | qual11, qual12, ..., qua11n = exp1
 | qual21, qual22, ..., qual2n = exp2
 ...
we translate the function binding into Haskell 98 as:

var apat1 apat2 ... apatn | isExit y = runExit y where {y = do
 maybeExit $ do {qual11'; qual12'; ...; qual1n'; return (exp1)}
 maybeExit $ do {qual21'; qual22'; ...; qual2n'; return (exp2)}
 ...}

where

 y is a new variable
 qualij' -> pat <- return (e) if qualij is pat <- e
 qualij' -> guard (qualij) if qualij is a boolean expression
 qualij' -> qualij if qualij is a let expression

-Yitz


More information about the Haskell-prime mailing list