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 Panne                                        Tel.: +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

Reply via email to