[Haskell-cafe] Small question

Stefan O'Rear stefanor at cox.net
Sat Aug 11 02:12:10 EDT 2007


On Sat, Aug 11, 2007 at 12:06:23AM -0400, David Menendez wrote:
> On 8/10/07, Andrew Coppin <andrewcoppin at btinternet.com> wrote:
> >
> > My program needs to make decisions based on a pair of boolean values.
> > Encoding both values as a single algebraic data type means I have to
> > keep "taking it apart" so I can work with it. I'm not sure how much time
> > this wastes...
> 
> Incidentally, there is an argument that many (perhaps most) use of
> Bool should instead be custom datatypes. That is, instead of:
> 
>     type FooBar = (Bool, Bool)
> 
> one should instead do something like
> 
>     data Foo = Foo | AntiFoo
>     data Bar = Baz | Bo
>     type FooBar = (Foo, Bar)
> 
> which makes it clearer what's going on and harder to confuse the two booleans.
> 
> Of course, now you have to replace
> 
>     \(foo, bar) -> if foo then ... else ...
> with
>     \(foo, bar) -> if foo == Foo then ... else ...
> or
>     \(foo, bar) -> case foo of { Foo -> ...; Bar -> ... }
>
> Actually, that raises an interesting question. Is there a performance
> difference between "if foo == Foo ..." and "case Foo of ..."? I think
> JHC's case-hoisting should be able to transform the former into the
> latter, but does it?

You don't need to go all the way to JHC[1] for this; GHC's case-of-case
transformation is perfectly adequate, as GHC itself will tell you:

stefan at stefans:/tmp$ ghc -c -ddump-simpl -O2 X.hs
...
X.moo :: X.Ay -> GHC.Base.Int
...
X.moo =
  \ (x_a6D :: X.Ay) -> case x_a6D of wild_Xq { X.Be -> X.lit; X.Ce -> X.lvl }
stefan at stefans:/tmp$ cat X.hs
module X where

data Ay = Be | Ce deriving(Eq)

moo x = if x == Be then 2 else (3::Int)
stefan at stefans:/tmp$ ghc -c -ddump-simpl-stats -O2 X.hs
==================== FloatOut stats: ====================
1 Lets floated to top level; 0 Lets floated elsewhere; from 4 Lambda groups
==================== FloatOut stats: ====================
0 Lets floated to top level; 0 Lets floated elsewhere; from 3 Lambda groups
==================== Grand total simplifier statistics ====================
Total ticks:     46

9 PreInlineUnconditionally
11 PostInlineUnconditionally
6 UnfoldingDone
1 RuleFired
    1 ==#->case
9 BetaReduction
2 CaseOfCase            <-------
7 KnownBranch
1 CaseMerge
11 SimplifierDone
stefan at stefans:/tmp$

Stefan

[1] GHC takes 2 hours to run a full two-stage bootstrap complete with
    the entire standard library.  Jhc takes[2] at least 4 hours (I
    didn't let it finish) to compile just the Prelude.

[2] 700MB working set, 384MiB primary store.  This makes a difference.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20070810/9a7853f6/attachment.bin


More information about the Haskell-Cafe mailing list