[Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Asger Feldthaus
Haskell doesn't seem to support disjunctive patterns, and I'm having a
difficult time writing good Haskell code in situations that would otherwise
call for that type of pattern.

Suppose for an example I have this data type:

data T = Foo Int | Bar Int | Baz

In OCaml I can write something like:

(* foo : T - T - int *)
fun foo x y = match (x,y) with
  | (Foo a | Bar a, Foo b | Bar b) - a + b
  | (Baz, Foo a)
  | (Bar a, Baz) - -a
  | (Baz, Bar a)
  | (Foo a, Baz) - a
  | _ - 0

In Haskell I can't find any equivalent to the disjunctive pattern. If
expanded naively, my Haskell version would look like this:

foo :: T - T - Int
foo x y = case (x,y) of
  (Foo a, Foo b) - a + b
  (Foo a, Bar b) - a + b
  (Bar a, Foo b) - a + b
  (Bar a, Bar b) - a + b
  (Baz, Foo a) - -a
  (Bar a, Baz) - -a
  (Baz, Bar a) - a
  (Foo a, Baz) - a
  _ - 0

While my example is still managable in size, this quickly goes out of hand
in practice. I've tried using pattern guards but with limited success. For
example:

foo2 :: T - T - Int
foo2 x y = case (x,y) of
  (x,y) | Just a - open x,
  Just b - open y -
a+b
  (Baz, Foo a) - -a
  (Bar a, Baz) - -a
  (Baz, Bar a) - a
  (Foo a, Baz) - a
  _ - 0
  where
open (Foo x) = Just x
open (Bar x) = Just x
open Baz = Nothing

I admit it doesn't look that bad in my crafted example, but this approach
doesn't seem to well work for me in practice. In any case, it's still far
more verbose than the disjunctive pattern version.

Nesting the case expressions instead of tuple-matching can reduce some code
duplication, but in general it becomes really verbose, and it is easy to
make mistakes when you have partially overlapped patterns in the
disjunctive-pattern version. Here's the example with nested cases:

foo3 :: T - T - Int
foo3 x y = case x of
  Foo a - case y of
Foo b - a+b
Bar b - a+b
Baz - a
  Bar a - case y of
Foo b - a+b
Bar b - a+b
Baz - -a
  Baz - case y of
Foo b - -b
Bar b - b
Baz - 0

What do people do in this situation - is there a good trick I've
overlooked? And is there some reason why Haskell does not support
disjunctive patterns?

Thanks,
Asger
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Serguey Zefirov
2011/12/8 Asger Feldthaus asger.feldth...@gmail.com:
 Haskell doesn't seem to support disjunctive patterns, and I'm having a
 difficult time writing good Haskell code in situations that would otherwise
 call for that type of pattern.

 Suppose for an example I have this data type:

 data T = Foo Int | Bar Int | Baz

 In OCaml I can write something like:

 (* foo : T - T - int *)
 fun foo x y = match (x,y) with
   | (Foo a | Bar a, Foo b | Bar b) - a + b

I solve that kind of problem by introducing operation enumerations.

I can write expression definition like that:
data Expr = Plus Int Int | Minus Int Int | Mul Int Int | Neg Int | Inv
Int | Var String

And then I will have exactly your problem.

I prefer to write such definition like that:
data Expr = Bin BinOp Int Int | Un UnOp Int | Var String
data BinOp = Plus | Minus | Mul
data UnOp = Neg | Inv

And I have to write less code in all subsequent constructions and
pattern matches.

This is especially good when I used that method for an expression with
result size:
data Expr size where
Bin :: BinOp xSize ySize resultSize - Expr xSize - Expr ySize -
Expr resultSize

data BinOp a b r where
Plus :: BinOp a a a
Concatenate :: BinOp a b (Plus a b)
Equal :: BinOp a a ONE

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Emil Axelsson

Instead of pattern guards you can use ViewPatterns:

  http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

This reduces some of the noise.


{-# LANGUAGE ViewPatterns #-}

data T = Foo Int | Bar Int | Baz

fooBar (Foo a) = Just a
fooBar (Bar a) = Just a
fooBar _   = Nothing

foo :: T - T - Int
foo x y = case (x,y) of
  (fooBar - Just a, fooBar - Just b) - a + b
  (Bar a, Baz) - -a
  (Foo a, Baz) - a
  _ - 0


/ Emil


2011-12-08 11:13, Asger Feldthaus skrev:

Haskell doesn't seem to support disjunctive patterns, and I'm having a
difficult time writing good Haskell code in situations that would
otherwise call for that type of pattern.

Suppose for an example I have this data type:

data T = Foo Int | Bar Int | Baz

In OCaml I can write something like:

(* foo : T - T - int *)
fun foo x y = match (x,y) with
   | (Foo a | Bar a, Foo b | Bar b) - a + b
   | (Baz, Foo a)
   | (Bar a, Baz) - -a
   | (Baz, Bar a)
   | (Foo a, Baz) - a
   | _ - 0

In Haskell I can't find any equivalent to the disjunctive pattern. If
expanded naively, my Haskell version would look like this:

foo :: T - T - Int
foo x y = case (x,y) of
   (Foo a, Foo b) - a + b
   (Foo a, Bar b) - a + b
   (Bar a, Foo b) - a + b
   (Bar a, Bar b) - a + b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0

While my example is still managable in size, this quickly goes out of
hand in practice. I've tried using pattern guards but with limited
success. For example:

foo2 :: T - T - Int
foo2 x y = case (x,y) of
   (x,y) | Just a - open x,
   Just b - open y -
 a+b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0
   where
 open (Foo x) = Just x
 open (Bar x) = Just x
 open Baz = Nothing

I admit it doesn't look that bad in my crafted example, but this
approach doesn't seem to well work for me in practice. In any case, it's
still far more verbose than the disjunctive pattern version.

Nesting the case expressions instead of tuple-matching can reduce some
code duplication, but in general it becomes really verbose, and it is
easy to make mistakes when you have partially overlapped patterns in the
disjunctive-pattern version. Here's the example with nested cases:

foo3 :: T - T - Int
foo3 x y = case x of
   Foo a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - a
   Bar a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - -a
   Baz - case y of
 Foo b - -b
 Bar b - b
 Baz - 0

What do people do in this situation - is there a good trick I've
overlooked? And is there some reason why Haskell does not support
disjunctive patterns?

Thanks,
Asger


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Øystein Kolsrud
Or perhaps this?

data T = Foo Int | Bar Int | Baz

fooBar (Foo a) = Just a
fooBar (Bar a) = Just a
fooBar _   = Nothing

foo :: T - T - Int
foo x y = sum $ catMaybes $ map fooBar [x,y]

/Øystein

On Thu, Dec 8, 2011 at 1:15 PM, Emil Axelsson e...@chalmers.se wrote:

 Instead of pattern guards you can use ViewPatterns:

  
 http://hackage.haskell.org/**trac/ghc/wiki/ViewPatternshttp://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

 This reduces some of the noise.

 ~~**~~
 {-# LANGUAGE ViewPatterns #-}


 data T = Foo Int | Bar Int | Baz

 fooBar (Foo a) = Just a
 fooBar (Bar a) = Just a
 fooBar _   = Nothing


 foo :: T - T - Int
 foo x y = case (x,y) of
  (fooBar - Just a, fooBar - Just b) - a + b
  (Bar a, Baz) - -a

  (Foo a, Baz) - a
  _ - 0
 ~~**~~

 / Emil


 2011-12-08 11:13, Asger Feldthaus skrev:

 Haskell doesn't seem to support disjunctive patterns, and I'm having a
 difficult time writing good Haskell code in situations that would
 otherwise call for that type of pattern.

 Suppose for an example I have this data type:

 data T = Foo Int | Bar Int | Baz

 In OCaml I can write something like:

 (* foo : T - T - int *)
 fun foo x y = match (x,y) with
   | (Foo a | Bar a, Foo b | Bar b) - a + b
   | (Baz, Foo a)
   | (Bar a, Baz) - -a
   | (Baz, Bar a)
   | (Foo a, Baz) - a
   | _ - 0

 In Haskell I can't find any equivalent to the disjunctive pattern. If
 expanded naively, my Haskell version would look like this:

 foo :: T - T - Int
 foo x y = case (x,y) of
   (Foo a, Foo b) - a + b
   (Foo a, Bar b) - a + b
   (Bar a, Foo b) - a + b
   (Bar a, Bar b) - a + b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0

 While my example is still managable in size, this quickly goes out of
 hand in practice. I've tried using pattern guards but with limited
 success. For example:

 foo2 :: T - T - Int
 foo2 x y = case (x,y) of
   (x,y) | Just a - open x,
   Just b - open y -
 a+b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0
   where
 open (Foo x) = Just x
 open (Bar x) = Just x
 open Baz = Nothing

 I admit it doesn't look that bad in my crafted example, but this
 approach doesn't seem to well work for me in practice. In any case, it's
 still far more verbose than the disjunctive pattern version.

 Nesting the case expressions instead of tuple-matching can reduce some
 code duplication, but in general it becomes really verbose, and it is
 easy to make mistakes when you have partially overlapped patterns in the
 disjunctive-pattern version. Here's the example with nested cases:

 foo3 :: T - T - Int
 foo3 x y = case x of
   Foo a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - a
   Bar a - case y of
 Foo b - a+b
 Bar b - a+b
 Baz - -a
   Baz - case y of
 Foo b - -b
 Bar b - b
 Baz - 0

 What do people do in this situation - is there a good trick I've
 overlooked? And is there some reason why Haskell does not support
 disjunctive patterns?

 Thanks,
 Asger


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Mvh Øystein Kolsrud
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread David Waern
2011/12/8 Asger Feldthaus asger.feldth...@gmail.com:
 Haskell doesn't seem to support disjunctive patterns, and I'm having a
 difficult time writing good Haskell code in situations that would otherwise
 call for that type of pattern.

I've also missed this after having done a bit of OCaml coding. Perhaps
if a good syntax can be found (since | is already taken) it could be
added as an extension to GHC.

David

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disjunctive patterns

2011-12-08 Thread Holger Siegel

Am 08.12.2011 um 11:13 schrieb Asger Feldthaus:

 Haskell doesn't seem to support disjunctive patterns, and I'm having a 
 difficult time writing good Haskell code in situations that would otherwise 
 call for that type of pattern.
 
 

 In Haskell I can't find any equivalent to the disjunctive pattern. If 
 expanded naively, my Haskell version would look like this:
 
 foo :: T - T - Int
 foo x y = case (x,y) of
   (Foo a, Foo b) - a + b
   (Foo a, Bar b) - a + b
   (Bar a, Foo b) - a + b
   (Bar a, Bar b) - a + b
   (Baz, Foo a) - -a
   (Bar a, Baz) - -a
   (Baz, Bar a) - a
   (Foo a, Baz) - a
   _ - 0
 
 While my example is still managable in size, this quickly goes out of hand in 
 practice. I've tried using pattern guards but with limited success.

value :: T - Int
value (Foo a) = a
value (Bar a) = a
value Baz = 0

foo :: T - T - Int
foo Baz (Foo a) = -a
foo (Bar a) Baz = -a
foo x y = value x + value y


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe