[Haskell] pattern matching woes

Ryan Paul segphault at sbcglobal.net
Thu Nov 18 17:26:18 EST 2004


I recently elected to employ Haskell for my functional programming needs
rather than Ocaml. Thus far, I have been relatively happy with the
expressiveness and syntactic grace of Haskell, but there are a few
aspects of Haskell's syntax that irritate me...

In OCaml, when I am doing pattern matching, I can string together
patterns to which I wish to assign the same result.

for example:
match a with X z | Y z | Z z -> True | _ -> False

I cannot find a good way to do this with Haskell. I would really like to
be able to do that, and I cant think of any reasons why it shouldnt be
possible - could such a feature be added to the Haskell standard?

If anybody can suggest possible alternatives, I would like to see them -
the following is the actual code in question, from one of my compiler
projects:

The Haskell code:

flatten a = case a of
  App l -> flatten' l
  List l -> a : flatten' l
  Arg l -> a : flatten l
  Ret l -> a : flatten l
  Fun _ l -> a : flatten' l
  Call _ l -> a : flatten' l
  Assign _ l -> a : flatten l
  Op x _ z -> a : flatten x ++ flatten z
  _ -> [a]

  where
    flatten' l = foldl (\x y -> x ++ (flatten y)) [] l

As compared to the ocaml equivelent:

let rec flatten a =
  let proc l = (List.fold_left (fun x y -> x @ (flatten y)) [] l) in
  match a with
  | Op (x,y,z) -> a :: (flatten x) @ (flatten z)
  | Assign (n,l) -> a :: (flatten l)
  | Fun (n,l) | Call (n,l) -> a :: (proc l)
  | App l | List l -> a :: (proc l)
  | Arg l | Ret l -> a :: (flatten l)
  | _ -> [a]


My second issue is with modules. I regularly use modules to clean up
namespace issues. When I want to do this with Haskell, I have to define
the module in a separate file and then use qualified import to bring it
into the file in which I want to use it. Often, I dont particularly want
or need to use the module again elsewhere, so putting it in a separate
file is counterintuitive. I would like to be able to nest my modules,
and have the parent module be able to do a qualified import on the
modules inside of it.

The following is an example of how I use nested modules in OCaml:

module Get =
  struct

  let funcs    = function App l       -> l >< Is.func    | _ -> [] ;;
  let params   = function Fun (n,l)   -> l >< Is.param   | _ -> [] ;;
  let assigns  = function Fun (n,l)   -> l >< Is.assign  | _ -> [] ;;
  let calls    = function Fun (n,l)   -> l >< Is.call    | _ -> [] ;;
  let vargs    = function Call (n,l)  -> l >< Is.varg    | _ -> [] ;;

  module All =
    struct
    
    let funcs   a = (flatten a) >< Is.func     ;;
    let assigns a = (flatten a) >< Is.assign   ;;
    let strs    a = (flatten a) >< Is.str      ;;
    let consts  a = (flatten a) >< Is.const    ;;
    let calls   a = (flatten a) >< Is.call     ;;
    
    end
  end

When I want to extract all the calls from a func recursively, I would do
something like:

Get.All.calls somefunc

If I just wanted to get the calls at the very top level, I would do:

Get.calls somefunc

Note: i'm not subscribed to the mailing list, so if you respond, please
cc your response to my email address.

Thanks!

-- SegPhault



More information about the Haskell mailing list