[Haskell-cafe] Guards (Was: Some random newbie questions)
Lemming
schlepptop at henning-thielemann.de
Sat Jan 8 12:46:04 EST 2005
Jon Cast wrote:
> Absolutely. In Haskell's syntax, if-then-else-if interacts badly with
> do notation, and Haskell lacks a direct analogy to Lisp's cond.
>
> case () of
> () | p1 -> e1
> | p2 -> e2
> ...
No problem:
select :: a -> [(Bool, a)] -> a
select def = maybe def snd . List.find fst
Use it this way:
select defaultE
[(p1, e1),
(p2, e2)]
Would be a nice Prelude function.
> parseCmd ln
> | Left err <- parse cmd "Commands" ln
> = BadCmd $ unwords $ lines $ show err
> | Right x <- parse cmd "Commands" ln
> = x
>
> with the Haskell-98 alternative
>
> parseCmd ln = case parse cmd "Commands" ln of
> Left err -> BadCmd $ unwords $ lines $ show err
> Right x -> x
Really, the second alternative is cleaner in my opinion.
> Furthermore, guards are an extension of pattern matching, which means
> you can write code like this:
>
> xn !! n | n < 0 = error "Prelude.(!!): Negative index"
> [] !! n = error "Prelude.(!!): Index overflow"
> (x:xn) !! n | n == 0 = x
> (x:xn) !! n = xn !! (n - 1)
>
> Exactly one equation for each edge in the control-flow graph, which is
> nice and not easily done (I'm not sure it's even possible) without
> guards.
At least one guard can nicely be avoided:
(x:xn) !! n = if n == 0 then x else xn !! (n - 1)
But I see that guards can be used to let pattern matching fail.
> Pattern guards are also nice for implementing ‘views’:
>
> -- | Convert an 'XMLData' into an equivalent application of
> -- 'Balanced', if possible. In any case, return an equivalent data
> -- structure.
> balance (Balanced es) = Balanced es
> balance (LeftLeaning (LeftBalanced e:es))
> | Balanced es' <- balance (LeftLeaning es)
> = Balanced (e:es')
I don't know what this means exactly, but I think I can transform it
formally to:
balance e'@(LeftLeaning (LeftBalanced e:es)) =
case balance (LeftLeaning es) of
Balanced es' -> Balanced (e:es')
_ -> e'
This way it is more clear for me, that 'balance' can return something
different from 'Balanced' and that the data is returned unchanged in
this case.
> balance (LeftLeaning []) = Balanced []
> balance (RightLeaning [("", "", es)]) = Balanced es
> balance (RightLeaning []) = Balanced []
> balance e = e
> Well, I could never do without them.
Sometimes I see people abusing guards, e.g. they write a 'length x == 1'
guard, where the pattern '[x0]' would be clearly the better choice. So
I'm always thinking twice before using a guard.
More information about the Haskell-Cafe
mailing list