RE: Converting float to double.

2000-05-10 Thread Simon Marlow


   The compiler cannot guess that some primitive Float-Double 
   function can
   be used instead of going through Rational.
  
  If enough inlining is done, then it should be able to deforest the
  intermediate Rational and generate the same code.  But I 
 agree, using RULES
  here is quicker and doesn't rely on some hefty unfoldings.
 Unless ghc has gotten incredibly clever I don't believe that.  Look at
 the code involved in such a conversion.  It involves, among 
 many other things,
 encodeFloat and decodeFloat.  So unless you have taught ghc about how
 floating point numbers are represented on all your target 
 machines (I mean,
 it doesn't have to be IEEE) you can't really inline these at 
 compile time.
 No, this is a perfect example of where you need a RULE.
 
 (BTW, hbc has optimized these conversion since about 6 years ago.)

Ah yes, I forgot how complex fromRat was.  Good point.

Simon




Re: Converting float to double.

2000-05-10 Thread Sven Panne

Simon Marlow wrote:
 Is this 4.06?  The current prelude contains
 
 {-# SPECIALIZE realToFrac :: [ blah blah ] #-}
 realToFrac  :: (Real a, Fractional b) = a - b
 realToFrac  =  fromRational . toRational
 
 which should provide for all your float-converting needs :-)

Not exactly, let's have a look at e.g.:

-
module Foo where

test1 :: Float - Double - Float
test1 x y = x + realToFrac y

test2 :: Double - Float - Double
test2 x y = x + realToFrac y

test3 :: Double - Double - Double
test3 x y = x + realToFrac y

test4 :: Float - Float - Float
test4 x y = x + realToFrac y
-

GHC currently generates the following STG code:

-
test1 =
NO_CCS srt: (0,2)[] \r[x y]
case x of wild {
  F# x1 -
  case PrelFloat.tpl63 y of stg_c2ds {
DEFAULT -
case PrelFloat.$sfromRat stg_c2ds of wild1 {
  F# y1 - case plusFloat# [x1 y1] of s { DEFAULT - F# [s] };
}
  };
};
SRT: [PrelFloat.$sfromRat, PrelFloat.tpl63]
test2 =
NO_CCS srt: (0,2)[] \r[x y]
case x of wild {
  D# x1 -
  case PrelFloat.tpl37 y of stg_c2dG {
DEFAULT -
case PrelFloat.$sfromRat1 stg_c2dG of wild1 {
  D# y1 - case +## [x1 y1] of s { DEFAULT - D# [s] };
}
  };
};
SRT: [PrelFloat.$sfromRat1, PrelFloat.tpl37]
test4 =
NO_CCS srt: (0,2)[] \r[x y]
case x of wild {
  F# x1 -
  case PrelFloat.tpl37 y of stg_c2dU {
DEFAULT -
case PrelFloat.$sfromRat stg_c2dU of wild1 {
  F# y1 - case plusFloat# [x1 y1] of s { DEFAULT - F# [s] };
}
  };
};
SRT: [PrelFloat.$sfromRat, PrelFloat.tpl37]
test3 =
NO_CCS srt: (0,2)[] \r[x y]
case x of wild {
  D# x1 -
  case PrelFloat.tpl63 y of stg_c2e8 {
DEFAULT -
case PrelFloat.$sfromRat1 stg_c2e8 of wild1 {
  D# y1 - case +## [x1 y1] of s { DEFAULT - D# [s] };
}
  };
};
SRT: [PrelFloat.$sfromRat1, PrelFloat.tpl63]
-

I've just added 4 RULES instead, so it now generates much better code
(Float-Float/Double-Double are NOPs, and Float-Double/Double-Float
are simple casts):

-
test1 =
NO_CCS[] \r[x y]
case x of wild {
  F# x1 -
  case y of wild1 {
D# d -
case double2Float# [d] of stg_c2ef {
  DEFAULT - case plusFloat# [x1 stg_c2ef] of s { DEFAULT - F# 
[s] }
};
  };
};
SRT: []
test2 =
NO_CCS[] \r[x y]
case x of wild {
  D# x1 -
  case y of wild1 {
F# f -
case float2Double# [f] of stg_c2et {
  DEFAULT - case +## [x1 stg_c2et] of s { DEFAULT - D# [s] }
};
  };
};
SRT: []
test4 =
NO_CCS[] \r[x y]
case x of wild {
  F# x1 -
  case y of wild1 {
F# y1 - case plusFloat# [x1 y1] of s { DEFAULT - F# [s] };
  };
};
SRT: []
test3 =
NO_CCS[] \r[x y]
case x of wild {
  D# x1 -
  case y of wild1 {
D# y1 - case +## [x1 y1] of s { DEFAULT - D# [s] };
  };
};
SRT: []
-

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne




Re: Converting float to double.

2000-05-10 Thread Lennart Augustsson

 How? RULES similar to ghc? Or built-in compiler magic for this case?
Built in magic.  Since this was the only way to convert between floating
types it obviously needed a special case.

-- Lennart




Re: Converting float to double.

2000-05-10 Thread Sven Panne

Simon Marlow wrote:
 [...] If enough inlining is done, then it should be able to deforest
 the intermediate Rational and generate the same code. [...]

I really doubt that, e.g. GHC doesn't know about the relationships
between the functions in StgPrimFloat.c, PrelFloat.fromRat' is a
rather complex piece of code, etc. So RULES are currently the only
way to go.

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne




RE: Converting float to double.

2000-05-10 Thread Lennart Augustsson

  The compiler cannot guess that some primitive Float-Double 
  function can
  be used instead of going through Rational.
 
 If enough inlining is done, then it should be able to deforest the
 intermediate Rational and generate the same code.  But I agree, using RULES
 here is quicker and doesn't rely on some hefty unfoldings.
Unless ghc has gotten incredibly clever I don't believe that.  Look at
the code involved in such a conversion.  It involves, among many other things,
encodeFloat and decodeFloat.  So unless you have taught ghc about how
floating point numbers are represented on all your target machines (I mean,
it doesn't have to be IEEE) you can't really inline these at compile time.
No, this is a perfect example of where you need a RULE.

(BTW, hbc has optimized these conversion since about 6 years ago.)

-- Lennart




RE: Converting float to double.

2000-05-10 Thread Marcin 'Qrczak' Kowalczyk

On Wed, 10 May 2000, Simon Marlow wrote:

  {-# RULES
  "realToFrac/Float-Double" realToFrac = floatToDouble
  "realToFrac/Double-Float" realToFrac = doubleToFloat #-}

 Is this 4.06?  The current prelude contains
 
 {-# SPECIALIZE realToFrac ::

 which should provide for all your float-converting needs :-)

It only provides specialization of this definition, i.e. fromRational and
toRational dispatching is done at compile time (which, I hope, is done
automatically anyway at least in cases where such function gets inlined).

The compiler cannot guess that some primitive Float-Double function can
be used instead of going through Rational.

AFAIR integral types do have {-#RULES#-} for conversions between each pair
of them, including Int16/Word64/etc. I'm not sure about Int-Double etc.
(both fromIntegral and realToFrac can be used here!).

-- 
Marcin 'Qrczak' Kowalczyk





Re: Converting float to double.

2000-05-10 Thread Sven Panne

Lennart Augustsson wrote:
 [...]
 (BTW, hbc has optimized these conversion since about 6 years ago.)

I've just added a whole bunch of RULES for fromIntegral, realToFrac
and truncate to the GHC in CVS, so perhaps we've already catched up...
:-)

Cheers,
   Sven
-- 
Sven PanneTel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen  Oettingenstr. 67
mailto:[EMAIL PROTECTED]D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne




Re: Converting float to double.

2000-05-10 Thread Marcin 'Qrczak' Kowalczyk

Wed, 10 May 2000 13:49:30 +0200 (CEST), Lennart Augustsson [EMAIL PROTECTED] 
pisze:

 (BTW, hbc has optimized these conversion since about 6 years ago.)

How? RULES similar to ghc? Or built-in compiler magic for this case?

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-





Re: Converting float to double.

2000-05-09 Thread Marcin 'Qrczak' Kowalczyk

Mon, 8 May 2000 20:42:10 -0700 (PDT), Ronald J. Legere [EMAIL PROTECTED] pisze:

  I have a very simple question. What is the best way to 
 convert a float to a double?
  I use fromRational.toRational, and the notes in the prelude
 seem to imply that this is optimized into something sensible..

The Prelude contains:

realToFrac:: (Real a, Fractional b) = a - b
realToFrac = fromRational . toRational

Unfortunately GHC currently does not optimize this into anything
smarter than going through Rational. Fortunately it contains enough
machinery so you can let it optimize it yourself :-)  Just add:

import NumExts (floatToDouble, doubleToFloat)

{-# RULES
"realToFrac/Float-Double" realToFrac = floatToDouble
"realToFrac/Double-Float" realToFrac = doubleToFloat #-}

and compile with  -syslib lang -O  and use realToFrac.

To GHC developers: please add it to the GHC's library.

-- 
 __("Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/  GCS/M d- s+:-- a23 C+++$ UL++$ P+++ L++$ E-
  ^^  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK  5? X- R tv-- b+++ DI D- G+ e h! r--%++ y-