[Haskell] Re: Replacing and improving pattern guards with PMC syntax

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Tue Oct 3 15:56:32 EDT 2006


I see that <= is already used... Let's take <~ (tilde) instead.

A "pseudo-sugared" version in plain Haskell for

 f (Right (Right p)) = p
 f (Left p)          = p
 f p                 = p

that is

 f p = fromJust $
     | Right q <~ p
         | Right r <~ q  = r
     | Left q <~ p       = q
     |                   = p

would be

> {-# OPTIONS_GHC -fglasgow-exts #-}
> import Control.Monad
> import Data.Maybe
> import Prelude hiding (Either,Left,Right)
> 
> class MP a b | b -> a where
>     choose :: Maybe a -> b
> 
> instance MP a (Maybe a) where
>     choose = id
> 
> instance (MP a b) => MP a (Maybe a -> b) where
>     choose x = choose . mplus x
> 
> data Path = Here | Left Path | Right Path
>     deriving Show
> 
> infixl 1 |>
> 
> (|>) :: MP a b => (Maybe a -> b) -> Maybe a -> b 
> (|>) f x = f x
>
>
>
> f :: Path -> Path
> f p = fromJust $ choose
>     |> do
>         Right q <- return p; choose
>             |> do
>                 Right r <- return q; return r
>     |> do
>         Left q <- return p; return q
>     |> do
>         return p


It's tricky to parse s.th. like

 f p = fromJust $
     | Right q <~ p
         | Right r <~ q  = r
     | Left q <~ p       = q
     |                   = p

A possibility is to add an extra keyword like "choose" and the following
grammar rules

exp10  -> "choose" {alts}
alts   -> alt1 ... altn
alt    -> "|" stmts' ["=" exp]
stmts' -> stmt'1 ";" stmt'2 ";" ... ";" stmtn'
stmt'  -> exp
        | pat <- exp
        | pat <~ exp
	| {empty token sequence}

with "choose" subject to the layout rule. This would yield

 f p = fromJust $ choose
     | Right q <~ p; choose
         | Right r <~ q  = r
     | Left q <~ p       = q
     |                   = p


The super-nice look would be a mix between "|" and "do/choose" where
lines beginning with "|" are counted as alternatives and lines without
as sequential follow-ups (possibly indented). This expends of any
unnecessary ";"

  do/choose
   | Right q <~ p
     val <- lookup key
     v <- do/choose
       | Left v <~ val
         return v
       | Right v <- val
         return v
     return (v+1)
   | Left q <~ p



Regards,
apfelmus



More information about the Haskell mailing list