Pattern guards

Iavor Diatchki iavor.diatchki at gmail.com
Thu Sep 28 14:52:15 EDT 2006


Hello,
I think that pattern guards are a nice generalization of ordinary
guards and they should be added to the language.  Of course, as you
point out, we can encode them using the Maybe monad, but the same is
true for nested patterns, and I don't think that they should be
removed from Haskell.  I think that the benefit of adding pattern
guards is similar to that of using nested patterns: it provides a
concise notation that is easy to explain and understand without having
to first learn about monads (even though there is a monad that is
hidden behind the scenes).  This, combined with the fact that pattern
guards are quite easy to implement, I think advocates in their favor.
-Iavor



On 9/28/06, Yitzchak Gale <gale at sefer.org> wrote:
> I would like to suggest a correction to ticket #56,
> "Pattern Guards".
>
> It is easy to show that every expression written
> using pattern guards can also be written in
> Haskell 98 in a way that is essentially
> equivalent in simplicity. (Proof below.)
>
> In my opinion, the Haskell 98 version below is
> more clear than the pattern guard version - it
> makes the monad explicit. Even if you disagree,
> I think it would be very difficult to argue that the
> difference is important enough to justify the extreme
> measure of adding new syntax to the language.
>
> Therefore, the first two items under "Pros" are
> false, and should be removed. The only remaining
> "Pro" is that the extension is well-specified, which
> has no value on its own.
>
> The purpose of Haskell' is to remove warts from
> Haskell, not add new ones. Pattern guards are
> a serious wart - they further overload syntax that
> is arguably already overused, as pointed out
> in the referenced paper by Martin Erwig and
> Simon Peyton Jones [EPJ].
>
> I hope that there is still time to retract the evil decree
> of "definitely in" Proposal Status for this ticket.
>
> Regards,
> Yitz
>
> 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
>
> Now given any function binding using pattern guards:
>
> funlhs
>  | qual11, qual12, ..., qual1n = exp1
>  | qual21, qual22, ..., qual2n = exp2
>  ...
>
> we translate the function binding into Haskell 98 as:
>
> funlhs = runExit $ do
>   maybeExit $ do {qual11'; qual12'; ...; qual1n'; return (exp1)}
>   maybeExit $ do {qual21'; qual22'; ...; qual2n'; return (exp2)}
>   ...
>
> where
>
>   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
>
> For a conventional guard:
>
>  | p = exp
>
> we can simplify the translation to:
>
>   when (p) $ Exit (exp)
>
> Simplifications are also possible for other special cases.
>
> This concludes the proof. Here are some examples, taken
> from [EPJ]:
>
> > clunky env var1 var2
> >  | Just val1 <- lookup env var1
> >  , Just val2 <- lookup env var2
> >  = val1 + val2
> >  ...other equations for clunky
>
> translates to:
>
> > clunky env var1 var2 = runExit $ do
> >   maybeExit $ do
> >     val1 <- lookup env var1
> >     val2 <- lookup env var2
> >     return (val1 + val2)
> >  ...other equations for clunky
>
> > filtSeq :: (a->Bool) -> Seq a -> Seq a
> > filtSeq p xs
> >  | Just (y,ys) <- lview xs, p y = lcons y (filtSeq p ys)
> >  | Just (y,ys) <- lview xs      = filtSeq p ys
> >  | otherwise                    = nil
>
> translates to:
>
> > filtSeq :: (a->Bool) -> Seq a -> Seq a
> > filtSeq p xs = runExit $ do
> >   maybeExit $ do
> >     (y,ys) <- lview xs
> >     guard $ p y
> >     return $ lcons y $ filtSeq p ys
> >   maybeExit $ do
> >     (y,ys) <- lview xs
> >     return $ filtSeq p ys
> >   Exit nil
>
> Note that in this case, the Maybe monad alone is
> sufficient. That eliminates both the double lookup and
> the double pattern match, as discussed in [EPJ]:
>
> > filtSeq :: (a->Bool) -> Seq a -> Seq a
> > filtSeq p xs = fromMaybe nil $ do
> >   (y,ys) <- lview xs
> >   return $ if (p y)
> >     then lcons y (filtSeq p ys)
> >     else filtSeq p ys
> _______________________________________________
> Haskell-prime mailing list
> Haskell-prime at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-prime
>


More information about the Haskell-prime mailing list