[Template-haskell] quasiquoting and guards
Claus Reinke
claus.reinke at talk21.com
Thu Jun 26 12:33:52 EDT 2008
> I'd like to use quasiquotation to emulate bash's case statement in
> Haskell. That is, I'd like to turn
>
> example x = case x of
> [$rx|.*foo.*] -> "contains foo"
> _ -> "doesn't contain foo"
Assuming that regexqq produces (String -> Maybe [String]), and
works rather better for expressions than for patterns, you could
simply lift mplus to functions, and define your own caseRE (your
example doesn't really make use of case/pattern-matching):
import Control.Monad
import Data.Char
import Data.List
(matchA .|. matchB) x = matchA x `mplus` matchB x
(regex .->. rhs) x = regex x >> return rhs -- (or >>=, if prefered)
caseRE x matches otherwise = maybe otherwise id (matches x)
a x = Just [this,that]
where (this,that) = span isSpace x
b x = Nothing
test = caseRE "hello world"
( (b .->. "hi")
.|. (a .->. "ho"))
"otherwise"
Then you can either fiddle with operator priorities, or drop
the thin facade and use MonadPlus directly;-)
You might also want to be able to refer to match results in
the rhs, no matter whether that is possible in bash - this would
seem to need control over both lhs and rhs anyway.
Hth,
Claus
> into (assuming an appropriate match :: String -> String -> Bool)
>
> example x = case x of
> s | match ".*foo.*" s -> "contains foo"
> _ -> "doesn't contain foo"
>
> But it seems like I can't do so, because despite appearances, the
> difference between the two cases in the second example is not in
> "what's to the left of ->". Instead, the first has a GuardedB body
> while the second has a NormalB body. (Having reread the Haskell
> Report, I now understand why this is, but it was surprising at first.)
> Whatever my definition of the quasiquoter rx is, the first example is
> going to expand to something with two NormalB bodies, so I can't
> achieve the desired expansion.
>
> Is there a clever workaround? I tried (ab)using view patterns, but
> they're not yet supported by Template Haskell.
>
> Regards,
> Reid Barton
> _______________________________________________
> template-haskell mailing list
> template-haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/template-haskell
More information about the template-haskell
mailing list