[Haskell-cafe] conditional branching vs pattern matching: pwn3d by GHC

2013-04-22 Thread Albert Y. C. Lai

When I was writing
http://www.vex.net/~trebla/haskell/crossroad.xhtml
I wanted to write: branching on predicates and then using selectors is 
less efficient than pattern matching, since selectors repeat the tests 
already done by predicates.


It is only ethical to verify this claim before writing it. So here it 
goes, eval uses pattern matching, fval uses predicates and selectors:


module E where

data E = Val{fromVal::Integer} | Neg{fromNeg::E}
  | Add{fromAdd0, fromAdd1 :: E}
isVal Val{} = True
isVal _ = False
isNeg Neg{} = True
isNeg _ = False
isAdd Add{} = True
isAdd _ = False

eval (Val n) = n
eval (Neg e0) = - eval e0
eval (Add e0 e1) = eval e0 + eval e1

fval e | isVal e = fromVal e
   | isNeg e = - fval (fromNeg e)
   | isAdd e = fval (fromAdd0 e) + fval (fromAdd1 e)

Simple and clear. What could possibly go wrong!

$ ghc -O -c -ddump-simpl -dsuppress-all -dsuppress-uniques E.hs

...

Rec {
fval
fval =
  \ e -
case e of _ {
  Val ds - ds;
  Neg ds - negateInteger (fval ds);
  Add ipv ipv1 - plusInteger (fval ipv) (fval ipv1)
}
end Rec }

Rec {
eval
eval =
  \ ds -
case ds of _ {
  Val n - n;
  Neg e0 - negateInteger (eval e0);
  Add e0 e1 - plusInteger (eval e0) (eval e1)
}
end Rec }

Which of the following best describes my feeling?
[ ] wait, what?
[ ] lol
[ ] speechless
[ ] oh man
[ ] I am so pwn3d
[ ] I can't believe it
[ ] what can GHC not do?!
[ ] but what am I going to say in my article?!
[ ] why is GHC making my life hard?!
[X] all of the above

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


Re: [Haskell-cafe] conditional branching vs pattern matching: pwn3d by GHC

2013-04-22 Thread Edward Z. Yang
Note that, unfortunately, GHC's exhaustiveness checker is *not* good
enough to figure out that your predicates are covering. :o)  Perhaps
there is an improvement to be had here.

Edward

Excerpts from Albert Y. C. Lai's message of Mon Apr 22 00:51:46 -0700 2013:
 When I was writing
 http://www.vex.net/~trebla/haskell/crossroad.xhtml
 I wanted to write: branching on predicates and then using selectors is 
 less efficient than pattern matching, since selectors repeat the tests 
 already done by predicates.
 
 It is only ethical to verify this claim before writing it. So here it 
 goes, eval uses pattern matching, fval uses predicates and selectors:
 
 module E where
 
 data E = Val{fromVal::Integer} | Neg{fromNeg::E}
| Add{fromAdd0, fromAdd1 :: E}
 isVal Val{} = True
 isVal _ = False
 isNeg Neg{} = True
 isNeg _ = False
 isAdd Add{} = True
 isAdd _ = False
 
 eval (Val n) = n
 eval (Neg e0) = - eval e0
 eval (Add e0 e1) = eval e0 + eval e1
 
 fval e | isVal e = fromVal e
 | isNeg e = - fval (fromNeg e)
 | isAdd e = fval (fromAdd0 e) + fval (fromAdd1 e)
 
 Simple and clear. What could possibly go wrong!
 
 $ ghc -O -c -ddump-simpl -dsuppress-all -dsuppress-uniques E.hs
 
 ...
 
 Rec {
 fval
 fval =
\ e -
  case e of _ {
Val ds - ds;
Neg ds - negateInteger (fval ds);
Add ipv ipv1 - plusInteger (fval ipv) (fval ipv1)
  }
 end Rec }
 
 Rec {
 eval
 eval =
\ ds -
  case ds of _ {
Val n - n;
Neg e0 - negateInteger (eval e0);
Add e0 e1 - plusInteger (eval e0) (eval e1)
  }
 end Rec }
 
 Which of the following best describes my feeling?
 [ ] wait, what?
 [ ] lol
 [ ] speechless
 [ ] oh man
 [ ] I am so pwn3d
 [ ] I can't believe it
 [ ] what can GHC not do?!
 [ ] but what am I going to say in my article?!
 [ ] why is GHC making my life hard?!
 [X] all of the above
 

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