RE: Bools are not unboxed

2004-10-06 Thread Simon Marlow
On 06 October 2004 11:36, Josef Svenningsson wrote:

> Simon Marlow wrote:
> 
>> On 06 October 2004 00:53, John Meacham wrote:
>> 
>> 
>> 
>>> This seems like it could be nicely generalized such that all
>>> enumeration types unbox to the unboxed integer of their offset. so
>>> 
>>> data Perhaps = Yes | Maybe | No
>>> 
>>> can unbox to an Int# with 0# == Yes 1# == Maybe and 2# == No.
>>> 
>>> 
>> 
>> Yes, a strict enumeration should be implemented as an Int#, both in
>> the strictness analyser and also when you {-# UNPACK #-} a
>> constructor field.  This is something we'd like to try, but haven't
>> got around to it yet.  Maybe a good bite-sized project for a budding
>> GHC hacker? :-) 
>> 
>> 
>> 
> Would it really be correct to translate it to Int#? AFAIK, unboxed
> values may not contain bottom while a data type most certainly can. I
> would imagine translating it to Int, and then relying on GHC's
> optimiser to optimize this into Int# whenever possible.

Note I said a *strict* enumeration.  You're right that in general it
wouldn't be correct to implement Bool by Int#.  Only when the strictness
analyser has determined that a function argument of enumeration type is
strict, or the programmer has added a strictness annotation to a
constructor field.

Certainly right now you can use Int everywhere instead of enumeration
types, and perhaps get better performance because GHC will unbox the Int
whenever possible.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bools are not unboxed

2004-10-06 Thread Josef Svenningsson
Simon Marlow wrote:
On 06 October 2004 00:53, John Meacham wrote:
 

This seems like it could be nicely generalized such that all
enumeration types unbox to the unboxed integer of their offset. so
data Perhaps = Yes | Maybe | No
can unbox to an Int# with 0# == Yes 1# == Maybe and 2# == No.
   

Yes, a strict enumeration should be implemented as an Int#, both in the
strictness analyser and also when you {-# UNPACK #-} a constructor
field.  This is something we'd like to try, but haven't got around to it
yet.  Maybe a good bite-sized project for a budding GHC hacker? :-)
 

Would it really be correct to translate it to Int#? AFAIK, unboxed 
values may not contain bottom while a data type most certainly can. I 
would imagine translating it to Int, and then relying on GHC's optimiser 
to optimize this into Int# whenever possible.

  /Josef
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Bools are not unboxed

2004-10-06 Thread Simon Marlow
On 06 October 2004 00:53, John Meacham wrote:

> On Tue, Oct 05, 2004 at 01:48:30PM +0100, Simon Marlow wrote:
>> It would probably be better to return 0#/1# instead of a Bool from
>> the comparison primops, because this would expose slightly more
>> detail to the simplifier and might result in slightly better code in
>> some cases (but no dramatic improvements).  It would also let us
>> remove a bit of complexity from the code generator.
> 
> This seems like it could be nicely generalized such that all
> enumeration types unbox to the unboxed integer of their offset. so
> 
> data Perhaps = Yes | Maybe | No
> 
> can unbox to an Int# with 0# == Yes 1# == Maybe and 2# == No.

Yes, a strict enumeration should be implemented as an Int#, both in the
strictness analyser and also when you {-# UNPACK #-} a constructor
field.  This is something we'd like to try, but haven't got around to it
yet.  Maybe a good bite-sized project for a budding GHC hacker? :-)

> Then we get the Bool optimization for free.

The original question was about the primitive comparisons, so I think
we'd still have to change the types of these primitives.  Furthermore
we'd probably have to teach the compiler that the result of the
comparison primops is compatible with a strict Bool.  It wouldn't be
entirely free.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bools are not unboxed

2004-10-05 Thread John Meacham
On Tue, Oct 05, 2004 at 01:48:30PM +0100, Simon Marlow wrote:
> It would probably be better to return 0#/1# instead of a Bool from the
> comparison primops, because this would expose slightly more detail to
> the simplifier and might result in slightly better code in some cases
> (but no dramatic improvements).  It would also let us remove a bit of
> complexity from the code generator.

This seems like it could be nicely generalized such that all enumeration
types unbox to the unboxed integer of their offset. so

data Perhaps = Yes | Maybe | No

can unbox to an Int# with 0# == Yes 1# == Maybe and 2# == No.

Then we get the Bool optimization for free. 

John


-- 
John Meacham - ârepetae.netâjohnâ 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Bools are not unboxed

2004-10-05 Thread Simon Marlow
On 03 October 2004 14:07, Tomasz Zielonka wrote:

> Then I noticed the cause:
> GHC.Prim.<# returns a boxed, heap allocated Bool, and so do other
> primitive comparison operators.
> 
> Would it be difficult to add Bool unboxing to GHC?
> Maybe it would suffice to use preallocated False and True?

Just to clarify a little more:  although the raw primitive operations do
appear to return fully boxed True & False values, in practice they
rarely do, because the code genrator optimises

  case a >=# b of
 True -> e1
 False -> e2

to 

  if (a >=# b) { 
.. code for e1 ...
  } else { 
.. code for e2 ..
  }

(well, more or less).  Only if the result of the comparison is actually
being returned from a function does it get turned into a real Bool.

It would probably be better to return 0#/1# instead of a Bool from the
comparison primops, because this would expose slightly more detail to
the simplifier and might result in slightly better code in some cases
(but no dramatic improvements).  It would also let us remove a bit of
complexity from the code generator.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Bools are not unboxed

2004-10-04 Thread Simon Peyton-Jones
| > for :: Int -> IO () -> IO ()
| > for 0 _ = return ()
| > for n x = x >> for (n - 1) x

Good example (allocates lots of silly thunks).  I'd come across this
before, and fixed the HEAD, but the 6.2 branch is still doing badly.
We'll try to fix that.  

| Playing with the code generated by ghc is a great way to waste time
| for me.  Wait until you have found the RULES-pragma :-)

In general, GHC's optimiser should behave predictably; small changes in
the source program should not have big effects.  Of course, sometimes
they do, and for good reason.  But not always; I'm keen to identify
cases where the optimiser does a poor/unpredictable job, and fix them.

So please let me know when that happens.  The more you can boil down a
program, and identify the culprit, as Carsten did so accurately in this
case, the more likely I am to fix it.  At the other end of the spectrum
"this 1000 line program goes slower than I expect" is less helpful :-)

Incidentally, GHC does use pre-allocated True and False booleans.

Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bools are not unboxed

2004-10-03 Thread Tomasz Zielonka
On Sun, Oct 03, 2004 at 04:03:55PM +0200, Carsten Schultz wrote:
> Hi Tomasz!

Hi Carsten!

> > To my surprise, it was much slower and made many allocations:
> [...
> > Then I noticed the cause: 
> > GHC.Prim.<# returns a boxed, heap allocated Bool, and so do other
> > primitive comparison operators.

I should have asked one fundamental question first: am I right? ;)

> That's not really the cause.  A function returning a boxed value does
> not necessarily have to allocate it, it is just a vectored return
> afaik.

I haven't heard about 'vectored return' before. I will try to find
more information about it. Maybe you can recommend something for me
to read?

> (Notice that $wfor again take three arguments, the last one being the
> state.)

Hmmm, I noticed that the number of arguments differed, there were even
some quiet alarm bells in my head, but I ignored it.

> for4 :: Int -> IO () -> IO ()
> for4 n x = if n `gt` 0 == 0 then return () else x >> (for4 (n-1) x)
> 
> gt :: Int -> Int -> Int
> gt x y = if x > y then 1 else 0
> 
> If you test it, it should be fast.

It is even slightly faster than my fastest version :)

> BTW, although counting upwards (and not solving the problem
> generally), the following is ok too:
> 
> for2 :: Int -> IO () -> IO ()
> for2 n x = sequence_ [x | i <- [1..n]]

This one is amazing. It's 3 times faster than the previous one in spite
of being written in high level style.

I guess it's worth checking idiomatic Haskell style first, because there
is a big chance that GHC was optimised for it :)

However, it would be nice if all versions were as efficient... 

> Playing with the code generated by ghc is a great way to waste time
> for me.

Well, but you seem to be very good at it. Maybe it won't be such a waste
of time in the long term :)

> Wait until you have found the RULES-pragma :-)

I've already found it some time ago. I even tried to use them to
optimise vector/matrix expressions (to eliminate intermediate vectors),
but I remember that sometimes the rules didn't fire and I didn't
understand why.

> Have fun,
> 
> Carsten

Hope this will teach me to avoid premature conclusions :-/

Thanks,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bools are not unboxed

2004-10-03 Thread Carsten Schultz
Hi Tomasz!

On Sun, Oct 03, 2004 at 03:07:01PM +0200, Tomasz Zielonka wrote:
> Hello!
> 
> I was playing with monadic looping a'la replicateM_ and I created this
> function:
> 
> for :: Int -> IO () -> IO ()
> for 0 _ = return ()
> for n x = x >> for (n - 1) x
> 
> Compiled with -O2, it is really fast and makes no unnecessary
> allocations.

Yes, good code:

T.$wfor =
\r [ww w w1]
case ww of ds {
  __DEFAULT ->
  case w w1 of wild {
GHC.Prim.(#,#) new_s a41 ->
case -# [ds 1] of sat_s1ZG {
  __DEFAULT -> T.$wfor sat_s1ZG w new_s;
};
  };
  0 -> GHC.Prim.(#,#) [w1 GHC.Base.()];
};
SRT(T.$wfor): []
T.for =
\r [w w1 w2] case w of w3 { GHC.Base.I# ww -> T.$wfor ww w1 w2; };
SRT(T.for): []

> So I made another version:
> 
> for :: Int -> IO () -> IO ()
> for n x | n > 0 = x >> for (n - 1) x
>   | otherwise = return ()
> 
> To my surprise, it was much slower and made many allocations:
[...
> Then I noticed the cause: 
> GHC.Prim.<# returns a boxed, heap allocated Bool, and so do other
> primitive comparison operators.

That's not really the cause.  A function returning a boxed value does
not necessarily have to allocate it, it is just a vectored return
afaik.

The code is:

T.$wfor' =
\r [ww w]
case ># [ww 0] of wild {
  GHC.Base.True ->
  let {
k = \u []
case -# [ww 1] of sat_s1Z9 {
  __DEFAULT -> T.$wfor' sat_s1Z9 w;
}; } in
  let {
sat_s20d =
\r [eta]
case w eta of wild1 
{ GHC.Prim.(#,#) new_s a41 -> k new_s; };
  } in  sat_s20d;
  GHC.Base.False -> lvl4;
};
SRT(T.$wfor'): []
T.for' =
\r [w w1] case w of w2 { GHC.Base.I# ww -> T.$wfor' ww w1; };
SRT(T.for'): []

The culprit is `let { k = \u ... }'.  The cause seems to be that eta
expansion is done at the wrong place, I do not know why.  The code we
would want is

T.$wfor4 =
\r [ww w w1]
case ># [ww 0] of wild {
  GHC.Base.True ->
  case w w1 of wild1 {
GHC.Prim.(#,#) new_s a41 ->
case -# [ww 1] of sat_s1Y0 {
  __DEFAULT -> T.$wfor4 sat_s1Y0 w new_s;
};
  };
  GHC.Base.False -> GHC.Prim.(#,#) [w1 GHC.Base.()];
};
SRT(T.$wfor4): []
T.for4 =
\r [w w1 w2] case w of w3 { GHC.Base.I# ww -> T.$wfor4 ww w1 w2; };
SRT(T.for4): []

(Notice that $wfor again take three arguments, the last one being the
state.)

Actually, this is produced by the following, although I have no idea
why.  Just the optimizer working unpredictably, I guess.

for4 :: Int -> IO () -> IO ()
for4 n x = if n `gt` 0 == 0 then return () else x >> (for4 (n-1) x)

gt :: Int -> Int -> Int
gt x y = if x > y then 1 else 0

If you test it, it should be fast.

BTW, although counting upwards (and not solving the problem
generally), the following is ok too:

for2 :: Int -> IO () -> IO ()
for2 n x = sequence_ [x | i <- [1..n]]

T.lvl = \r [s] GHC.Prim.(#,#) [s GHC.Base.()];
SRT(T.lvl): []
T.$wfor2 =
\r [ww w]
case ># [1 ww] of wild {
  GHC.Base.True -> T.lvl;
  GHC.Base.False ->
  let {
go10 =
\r [x1 eta]
case w eta of wild1 {
  GHC.Prim.(#,#) new_s a41 ->
  case ==# [x1 ww] of wild11 {
GHC.Base.True -> 
GHC.Prim.(#,#) [new_s GHC.Base.()];
GHC.Base.False ->
case +# [x1 1] of sat_s1XA {
  __DEFAULT -> go10 sat_s1XA new_s;
};
  };
};
  } in  go10 1;
};
SRT(T.$wfor2): []

T.for2 =
\r [w w1] case w of w2 { GHC.Base.I# ww -> T.$wfor2 ww w1; };
SRT(T.for2): []


Playing with the code generated by ghc is a great way to waste time
for me.  Wait until you have found the RULES-pragma :-)

Have fun,

Carsten

-- 
Carsten Schultz (2:38, 33:47), FB Mathematik, FU Berlin
http://carsten.codimi.de/
PGP/GPG key on the pgp.net key servers, 
fingerprint on my home page.


pgpbPCeYXZmU3.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bools are not unboxed

2004-10-03 Thread Tomasz Zielonka
On Sun, Oct 03, 2004 at 03:07:01PM +0200, Tomasz Zielonka wrote:
> Then I noticed the cause: 
> GHC.Prim.<# returns a boxed, heap allocated Bool, and so do other
> primitive comparison operators.
> 
> Would it be difficult to add Bool unboxing to GHC?
> Maybe it would suffice to use preallocated False and True?

I forgot about some questions:

Do you think that many applications could benefit from such an improvement?

IMO, yes, for example, there are many Int comparisons waiting for this
optimisation in io, networking and posix libraries. But I am not sure
how big would that benefit be in a non-toy application.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users