Optimization beyond the Module Border

2008-03-19 Thread Bernd Brassel
Hi all,

I have noticed that there is a great difference between optimizing
modules separately and all at once, e.g., with -fforce-recomp. I have
had examples factors up to 15 in run time (and even different behavior
in context with unsafePerformIO).

Is there any option that makes ghc write out that intermediate
optimization data he seems to use in order to get the same efficiency in
a module-wise compilation?

Greetings
Bernd
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Optimization beyond the Module Border

2008-03-19 Thread Simon Peyton-Jones
| I have noticed that there is a great difference between optimizing
| modules separately and all at once, e.g., with -fforce-recomp. I have
| had examples factors up to 15 in run time (and even different behavior
| in context with unsafePerformIO).

GHC does a lot of cross-module inlining already, and *does* write stuff into 
interface files, provided you use -O.

I'm always interested in performance differences of a factor of 15 though!  Can 
you supply an example (as small as poss) for us to look at?

Thanks

Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Optimization beyond the Module Border

2008-03-19 Thread Bernd Brassel
Simon Peyton-Jones wrote:

 GHC does a lot of cross-module inlining already, and *does* write stuff into 
 interface files, provided you use -O.

I used -O4. Is that the bad thing?

 I'm always interested in performance differences of a factor of 15 though!  
 Can you supply an example (as small as poss) for us to look at?

Yes certainly, although small will be a big problem, I guess.
I admit that the factor 15 is a bit dubious since the fast run-time was
so small (1.88 sec vs. 0.112 sec).

I will see what I can do on the morrow.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Optimization beyond the Module Border

2008-03-19 Thread Don Stewart
bbr:
 Simon Peyton-Jones wrote:
 
  GHC does a lot of cross-module inlining already, and *does* write stuff 
  into interface files, provided you use -O.
 
 I used -O4. Is that the bad thing?

There's nothing about -O2 

However, I think that's ok -- it clamps -ON | N2 to -O2


  I'm always interested in performance differences of a factor of 15 though!  
  Can you supply an example (as small as poss) for us to look at?
 
 Yes certainly, although small will be a big problem, I guess.
 I admit that the factor 15 is a bit dubious since the fast run-time was
 so small (1.88 sec vs. 0.112 sec).
 
 I will see what I can do on the morrow.

I'd be interested in any progress here -- we noticed issues with
optimisations in the stream fusion package across module boundaries
that we never tracked down. If there's some key things not firing,
that would be good to know.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC] #2163: GHC makes thunks for Integers we are strict in

2008-03-19 Thread Ian Lynagh
On Tue, Mar 18, 2008 at 04:12:35PM -, GHC wrote:
 
  W.f =
\ (x_a5h :: GHC.Num.Integer) -
  let {
x'_sa7 [ALWAYS Just S] :: GHC.Num.Integer
[Str: DmdType]
x'_sa7 = GHC.Num.plusInteger x_a5h W.lvl } in
  GHC.Num.timesInteger x'_sa7 x'_sa7
 
  `let` can be strict in Core - it doesn't always indicate a thunk.

Aha! I knew that let was strict for types like Int#, but didn't realise
that it could be for normal types too.

What is it in the above let that shows that it will be evaluated
strictly? The Just S?

Also, what is the advantage to having strictly evaluated let's, both for
unboxed and normal types? Presumably it helps with some optimisation -
perhaps let-bound things might be inlined, whereas case'd things aren't,
which reduces the number of cases the optimiser needs to consider, or
something?

  (don't worry, this often catches me out too.  Perhaps a strict let
  should be indicated more explicitly in `-ddump-simpl`).

I'd certainly find it useful if it was clearer.


Thanks
Ian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Optimization beyond the Module Border

2008-03-19 Thread Malcolm Wallace
 I'd be interested in any progress here -- we noticed issues with
 optimisations in the stream fusion package across module boundaries
 that we never tracked down. If there's some key things not firing,
 that would be good to know.

I suspect that if all modules are compiled -O0, then you recompile one
module with -O2, high up in the dependency graph (i.e. it depends on
many lower-level modules), plus all things that in turn depend on it
(--make), you will not get the good performance you expect.  None of the
lower-level functions will have exported inlinings or fusion rules into
the interface file.  _All_ modules must be recompiled with -O2,
especially the bottom of the dependency chain, to get the best benefit
from optimisation.

Regards,
Malcolm
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Expected behavior of deriving Ord?

2008-03-19 Thread Conal Elliott
I have an algebraic data type (not newtype) that derives Ord:

data AddBounds a = MinBound | NoBound a | MaxBound
deriving (Eq, Ord, Read, Show)

I was hoping to get a min method defined in terms of the min method of the
type argument (a).  Instead, I think GHC is producing something in terms of
compare or (=).  Maybe it's defaulting min altogether.  What is the
expected behavior in (a) the language standard and (b) GHC?

The reason I care is that my type parameter a turns out to have partial
information, specifically lower bounds.  The type of min allows this partial
info to be used in producing partial info about the result, while the type
of (=) and compare do not.

Thanks,  - Conal
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Expected behavior of deriving Ord?

2008-03-19 Thread Duncan Coutts

On Wed, 2008-03-19 at 14:11 -0700, Conal Elliott wrote:
 I have an algebraic data type (not newtype) that derives Ord:
 
 data AddBounds a = MinBound | NoBound a | MaxBound
 deriving (Eq, Ord, Read, Show)
 
 I was hoping to get a min method defined in terms of the min method of
 the type argument (a).  Instead, I think GHC is producing something in
 terms of compare or (=).  Maybe it's defaulting min altogether.  What
 is the expected behavior in (a) the language standard and (b) GHC?

The H98 report says:

10.1  Derived instances of Eq and Ord
The class methods automatically introduced by derived instances
of Eq and Ord are (==), (/=), compare, (), (=), (), (=),
max, and min. The latter seven operators are defined so as to
compare their arguments lexicographically with respect to the
constructor set given, with earlier constructors in the datatype
declaration counting as smaller than later ones. For example,
for the Bool datatype, we have that (True  False) == True.

Derived comparisons always traverse constructors from left to
right. These examples illustrate this property: 

  (1,undefined) == (2,undefined) =False
  (undefined,1) == (undefined,2) =_|_

All derived operations of class Eq and Ord are strict in both
arguments. For example, False = _|_ is _|_, even though False
is the first constructor of the Bool type.

Which doesn't seem to help but looking at the later example:

10.5  An Example
As a complete example, consider a tree datatype:

  data Tree a = Leaf a | Tree a :^: Tree a
   deriving (Eq, Ord, Read, Show)

Automatic derivation of instance declarations for Bounded and
Enum are not possible, as Tree is not an enumeration or
single-constructor datatype. The complete instance declarations
for Tree are shown in Figure 10.1, Note the implicit use of
default class method definitions---for example, only = is
defined for Ord, with the other class methods (, , =, max,
and min) being defined by the defaults given in the class
declaration shown in Figure 6.1 (page ).

So that is relying on the default class methods:

max x y | x = y=  y
| otherwise =  x
min x y | x = y=  x
| otherwise =  y

As for GHC, Looking at the comments in compiler/typecheck/TcGenDeriv.lhs
it says that it generates code that uses compare like so:

max a b = case (compare a b) of { LT - b; EQ - a;  GT - a }
min a b = case (compare a b) of { LT - a; EQ - b;  GT - b }

 The reason I care is that my type parameter a turns out to have
 partial information, specifically lower bounds.  The type of min
 allows this partial info to be used in producing partial info about
 the result, while the type of (=) and compare do not.

So I suggest that you use an explicit Ord instance and define min/max
the way you want.

Duncan

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Expected behavior of deriving Ord?

2008-03-19 Thread Conal Elliott
Thanks for the pointers.  I'd found 10.1 but hadn't noticed 10.5.

So I suggest that you use an explicit Ord instance and define min/max the
 way you want.


Yep.  That's my solution:

instance Ord a = Ord (AddBounds a) where
  MinBound  = _ = True
  NoBound _ = MinBound  = False
  NoBound a = NoBound b = a = b
  NoBound _ = MaxBound  = True
  MaxBound  = MaxBound  = True
  MaxBound  = _ = False

  MinBound  `min` _ = MinBound
  _ `min` MinBound  = MinBound
  NoBound a `min` NoBound b = NoBound (a `min` b)
  u `min` MaxBound  = u
  MaxBound  `min` v = v

  MinBound  `max` v = v
  u `max` MinBound  = u
  NoBound a `max` NoBound b = NoBound (a `max` b)
  _ `max` MaxBound  = MaxBound
  MaxBound  `max` _ = MaxBound

Cheers,  - Conal


On Wed, Mar 19, 2008 at 2:35 PM, Duncan Coutts [EMAIL PROTECTED]
wrote:


 On Wed, 2008-03-19 at 14:11 -0700, Conal Elliott wrote:
  I have an algebraic data type (not newtype) that derives Ord:
 
  data AddBounds a = MinBound | NoBound a | MaxBound
  deriving (Eq, Ord, Read, Show)
 
  I was hoping to get a min method defined in terms of the min method of
  the type argument (a).  Instead, I think GHC is producing something in
  terms of compare or (=).  Maybe it's defaulting min altogether.  What
  is the expected behavior in (a) the language standard and (b) GHC?

 The H98 report says:

10.1  Derived instances of Eq and Ord
The class methods automatically introduced by derived instances
of Eq and Ord are (==), (/=), compare, (), (=), (), (=),
max, and min. The latter seven operators are defined so as to
compare their arguments lexicographically with respect to the
constructor set given, with earlier constructors in the datatype
declaration counting as smaller than later ones. For example,
for the Bool datatype, we have that (True  False) == True.

Derived comparisons always traverse constructors from left to
right. These examples illustrate this property:

  (1,undefined) == (2,undefined) =False
  (undefined,1) == (undefined,2) =_|_

All derived operations of class Eq and Ord are strict in both
arguments. For example, False = _|_ is _|_, even though False
is the first constructor of the Bool type.

 Which doesn't seem to help but looking at the later example:

10.5  An Example
As a complete example, consider a tree datatype:

  data Tree a = Leaf a | Tree a :^: Tree a
deriving (Eq, Ord, Read, Show)

 Automatic derivation of instance declarations for Bounded and
Enum are not possible, as Tree is not an enumeration or
single-constructor datatype. The complete instance declarations
for Tree are shown in Figure 10.1, Note the implicit use of
default class method definitions---for example, only = is
defined for Ord, with the other class methods (, , =, max,
and min) being defined by the defaults given in the class
declaration shown in Figure 6.1 (page ).

 So that is relying on the default class methods:

max x y | x = y=  y
| otherwise =  x
min x y | x = y=  x
| otherwise =  y

 As for GHC, Looking at the comments in compiler/typecheck/TcGenDeriv.lhs
 it says that it generates code that uses compare like so:

max a b = case (compare a b) of { LT - b; EQ - a;  GT - a }
min a b = case (compare a b) of { LT - a; EQ - b;  GT - b }

  The reason I care is that my type parameter a turns out to have
  partial information, specifically lower bounds.  The type of min
  allows this partial info to be used in producing partial info about
  the result, while the type of (=) and compare do not.

 So I suggest that you use an explicit Ord instance and define min/max
 the way you want.

 Duncan


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC] #2163: GHC makes thunks for Integers we are strict in

2008-03-19 Thread Ian Lynagh
On Wed, Mar 19, 2008 at 05:31:08PM +, Ian Lynagh wrote:
 On Tue, Mar 18, 2008 at 04:12:35PM -, GHC wrote:
  
   (don't worry, this often catches me out too.  Perhaps a strict let
   should be indicated more explicitly in `-ddump-simpl`).
 
 I'd certainly find it useful if it was clearer.

In fact, simpl hides more than I'd realised. With these definitions:

f :: Integer - Integer - Integer - Integer
f x y z | y == 1 = x * z
| otherwise = f (x * x) y (z * z)

g :: Integer - Integer - Integer - Integer
g x y z | y == 1 = x
| otherwise = g (x * x) y (z * z)

simpl shows

B.f (GHC.Num.timesInteger x_a5B x_a5B) y_a5D
(GHC.Num.timesInteger z_a5F z_a5F);

and

B.g (GHC.Num.timesInteger x_a74 x_a74) y_a76
(GHC.Num.timesInteger z_a78 z_a78);

for the recursive calls, although in the STG you can see that the
multiplication of z is done strictly in f but not g (which is correct,
as g is not strict in z).

So perhaps the solution is just that I should look at the STG rather
than the simpl when I want to see what's going on.


Thanks
Ian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC] #2163: GHC makes thunks for Integers we are strict in

2008-03-19 Thread Don Stewart
igloo:
 On Wed, Mar 19, 2008 at 05:31:08PM +, Ian Lynagh wrote:
  On Tue, Mar 18, 2008 at 04:12:35PM -, GHC wrote:
   
(don't worry, this often catches me out too.  Perhaps a strict let
should be indicated more explicitly in `-ddump-simpl`).
  
  I'd certainly find it useful if it was clearer.
 
 In fact, simpl hides more than I'd realised. With these definitions:
 
 f :: Integer - Integer - Integer - Integer
 f x y z | y == 1 = x * z
 | otherwise = f (x * x) y (z * z)
 
 g :: Integer - Integer - Integer - Integer
 g x y z | y == 1 = x
 | otherwise = g (x * x) y (z * z)
 
 simpl shows
 
 B.f (GHC.Num.timesInteger x_a5B x_a5B) y_a5D
 (GHC.Num.timesInteger z_a5F z_a5F);
 
 and
 
 B.g (GHC.Num.timesInteger x_a74 x_a74) y_a76
 (GHC.Num.timesInteger z_a78 z_a78);
 
 for the recursive calls, although in the STG you can see that the
 multiplication of z is done strictly in f but not g (which is correct,
 as g is not strict in z).
 
 So perhaps the solution is just that I should look at the STG rather
 than the simpl when I want to see what's going on.
 
 
 Thanks

We really need an official and blessed view of the optimised core, with
full, relevant information, in human readable form.

Just simplifiying the obvious qualified names would be a start, and 
some simple alpha renaming. 

-- Don
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users