{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP
 , GHCForeignImportPrim
 , NoImplicitPrelude
 , MagicHash
 , UnboxedTuples
 , UnliftedFFITypes
 #-}{-# LANGUAGE CApiFFI #-}-- We believe we could deorphan this module, by moving lots of things-- around, but we haven't got there yet:{-# OPTIONS_GHC -Wno-orphans #-}{-# OPTIONS_HADDOCK hide #-}------------------------------------------------------------------------------- |-- Module : GHC.Float-- Copyright : (c) The University of Glasgow 1994-2002-- Portions obtained from hbc (c) Lennart Augusstson-- License : see libraries/base/LICENSE---- Maintainer : cvs-ghc@haskell.org-- Stability : internal-- Portability : non-portable (GHC Extensions)---- The types 'Float' and 'Double', the classes 'Floating' and 'RealFloat' and-- casting between Word32 and Float and Word64 and Double.-------------------------------------------------------------------------------#include "ieee-flpt.h"
#include "MachDeps.h"
moduleGHC.Float(moduleGHC.Float ,Float(..),Double(..),Float#,Double#,double2Int ,int2Double ,float2Int ,int2Float -- * Monomorphic equality operators-- | See GHC.Classes#matching_overloaded_methods_in_rules,eqFloat,eqDouble)whereimportData.Maybe importData.Bits importGHC.Base importGHC.List importGHC.Enum importGHC.Show importGHC.Num importGHC.Real importGHC.Word importGHC.Arr importGHC.Float.RealFracMethods importGHC.Float.ConversionUtils importGHC.Integer.Logarithms(integerLogBase#)importGHC.Integer.Logarithms.Internalsinfixr8** -------------------------------------------------------------------------- Standard numeric classes-------------------------------------------------------------------------- | Trigonometric and hyperbolic functions and related functions.---- The Haskell Report defines no laws for 'Floating'. However, '(+)', '(*)'-- and 'exp' are customarily expected to define an exponential field and have-- the following properties:---- * @exp (a + b)@ = @exp a * exp b-- * @exp (fromInteger 0)@ = @fromInteger 1@class(Fractional a )=>Floating a wherepi ::a exp ,log ,sqrt ::a ->a (** ),logBase ::a ->a ->a sin ,cos ,tan ::a ->a asin ,acos ,atan ::a ->a sinh ,cosh ,tanh ::a ->a asinh ,acosh ,atanh ::a ->a -- | @'log1p' x@ computes @'log' (1 + x)@, but provides more precise-- results for small (absolute) values of @x@ if possible.---- @since 4.9.0.0log1p ::a ->a -- | @'expm1' x@ computes @'exp' x - 1@, but provides more precise-- results for small (absolute) values of @x@ if possible.---- @since 4.9.0.0expm1 ::a ->a -- | @'log1pexp' x@ computes @'log' (1 + 'exp' x)@, but provides more-- precise results if possible.---- Examples:---- * if @x@ is a large negative number, @'log' (1 + 'exp' x)@ will be-- imprecise for the reasons given in 'log1p'.---- * if @'exp' x@ is close to @-1@, @'log' (1 + 'exp' x)@ will be-- imprecise for the reasons given in 'expm1'.---- @since 4.9.0.0log1pexp ::a ->a -- | @'log1mexp' x@ computes @'log' (1 - 'exp' x)@, but provides more-- precise results if possible.---- Examples:---- * if @x@ is a large negative number, @'log' (1 - 'exp' x)@ will be-- imprecise for the reasons given in 'log1p'.---- * if @'exp' x@ is close to @1@, @'log' (1 - 'exp' x)@ will be-- imprecise for the reasons given in 'expm1'.---- @since 4.9.0.0log1mexp ::a ->a {-# INLINE(**)#-}{-# INLINElogBase#-}{-# INLINEsqrt#-}{-# INLINEtan#-}{-# INLINEtanh#-}x ** y =exp (log x * y )logBase x y =log y / log x sqrt x =x ** 0.5tan x =sin x / cos x tanh x =sinh x / cosh x {-# INLINElog1p#-}{-# INLINEexpm1#-}{-# INLINElog1pexp#-}{-# INLINElog1mexp#-}log1p x =log (1+ x )expm1 x =exp x -1log1pexp x =log1p (exp x )log1mexp x =log1p (negate (exp x ))-- | Efficient, machine-independent access to the components of a-- floating-point number.class(RealFrac a ,Floating a )=>RealFloat a where-- | a constant function, returning the radix of the representation-- (often @2@)floatRadix ::a ->Integer-- | a constant function, returning the number of digits of-- 'floatRadix' in the significandfloatDigits ::a ->Int-- | a constant function, returning the lowest and highest values-- the exponent may assumefloatRange ::a ->(Int,Int)-- | The function 'decodeFloat' applied to a real floating-point-- number returns the significand expressed as an 'Integer' and an-- appropriately scaled exponent (an 'Int'). If @'decodeFloat' x@-- yields @(m,n)@, then @x@ is equal in value to @m*b^^n@, where @b@-- is the floating-point radix, and furthermore, either @m@ and @n@-- are both zero or else @b^(d-1) <= 'abs' m < b^d@, where @d@ is-- the value of @'floatDigits' x@.-- In particular, @'decodeFloat' 0 = (0,0)@. If the type-- contains a negative zero, also @'decodeFloat' (-0.0) = (0,0)@.-- /The result of/ @'decodeFloat' x@ /is unspecified if either of/-- @'isNaN' x@ /or/ @'isInfinite' x@ /is/ 'True'.decodeFloat ::a ->(Integer,Int)-- | 'encodeFloat' performs the inverse of 'decodeFloat' in the-- sense that for finite @x@ with the exception of @-0.0@,-- @'uncurry' 'encodeFloat' ('decodeFloat' x) = x@.-- @'encodeFloat' m n@ is one of the two closest representable-- floating-point numbers to @m*b^^n@ (or @&#177;Infinity@ if overflow-- occurs); usually the closer, but if @m@ contains too many bits,-- the result may be rounded in the wrong direction.encodeFloat ::Integer->Int->a -- | 'exponent' corresponds to the second component of 'decodeFloat'.-- @'exponent' 0 = 0@ and for finite nonzero @x@,-- @'exponent' x = snd ('decodeFloat' x) + 'floatDigits' x@.-- If @x@ is a finite floating-point number, it is equal in value to-- @'significand' x * b ^^ 'exponent' x@, where @b@ is the-- floating-point radix.-- The behaviour is unspecified on infinite or @NaN@ values.exponent ::a ->Int-- | The first component of 'decodeFloat', scaled to lie in the open-- interval (@-1@,@1@), either @0.0@ or of absolute value @>= 1\/b@,-- where @b@ is the floating-point radix.-- The behaviour is unspecified on infinite or @NaN@ values.significand ::a ->a -- | multiplies a floating-point number by an integer power of the radixscaleFloat ::Int->a ->a -- | 'True' if the argument is an IEEE \"not-a-number\" (NaN) valueisNaN ::a ->Bool-- | 'True' if the argument is an IEEE infinity or negative infinityisInfinite ::a ->Bool-- | 'True' if the argument is too small to be represented in-- normalized formatisDenormalized ::a ->Bool-- | 'True' if the argument is an IEEE negative zeroisNegativeZero ::a ->Bool-- | 'True' if the argument is an IEEE floating point numberisIEEE ::a ->Bool-- | a version of arctangent taking two real floating-point arguments.-- For real floating @x@ and @y@, @'atan2' y x@ computes the angle-- (from the positive x-axis) of the vector from the origin to the-- point @(x,y)@. @'atan2' y x@ returns a value in the range [@-pi@,-- @pi@]. It follows the Common Lisp semantics for the origin when-- signed zeroes are supported. @'atan2' y 1@, with @y@ in a type-- that is 'RealFloat', should return the same value as @'atan' y@.-- A default definition of 'atan2' is provided, but implementors-- can provide a more accurate implementation.atan2 ::a ->a ->a exponent x =ifm ==0then0elsen + floatDigits x where(m ,n )=decodeFloat x significand x =encodeFloat m (negate (floatDigits x ))where(m ,_)=decodeFloat x scaleFloat 0x =x scaleFloatk x |isFix =x |otherwise =encodeFloat m (n + clamp b k )where(m ,n )=decodeFloat x (l ,h )=floatRange x d =floatDigits x b =h -l + 4* d -- n+k may overflow, which would lead-- to wrong results, hence we clamp the-- scaling parameter.-- If n + k would be larger than h,-- n + clamp b k must be too, simliar-- for smaller than l - d.-- Add a little extra to keep clear-- from the boundary cases.isFix =x ==0||isNaN x ||isInfinite x atan2 y x |x >0=atan (y / x )|x ==0&&y >0=pi / 2|x <0&&y >0=pi + atan (y / x )|(x <=0&&y <0)||(x <0&&isNegativeZero y )||(isNegativeZero x &&isNegativeZero y )=-atan2 (-y )x |y ==0&&(x <0||isNegativeZero x )=pi -- must be after the previous test on zero y|x ==0&&y ==0=y -- must be after the other double zero tests|otherwise =x + y -- x or y is a NaN, return a NaN (via +)-------------------------------------------------------------------------- Float-------------------------------------------------------------------------- | @since 2.01-- Note that due to the presence of @NaN@, not all elements of 'Float' have an-- additive inverse.---- >>> 0/0 + (negate 0/0 :: Float)-- NaN---- Also note that due to the presence of -0, `Float`'s 'Num' instance doesn't-- have an additive identity---- >>> 0 + (-0 :: Float)-- 0.0instanceNum Floatwhere(+ )x y =plusFloat x y (-)x y =minusFloat x y negate x =negateFloat x (* )x y =timesFloat x y abs x =fabsFloat x signum x |x >0=1|x <0=negateFloat 1|otherwise =x -- handles 0.0, (-0.0), and NaN{-# INLINEfromInteger#-}fromInteger i =F#(floatFromIntegeri )-- | @since 2.01instanceReal FloatwheretoRational (F#x# )=casedecodeFloat_Int#x# of(#m# ,e# #)|isTrue#(e# >=#0#)->(smallIntegerm# `shiftLInteger`e# ):% 1|isTrue#((int2Word#m# `and#`1##)`eqWord#`0##)->caseelimZerosInt# m# (negateInt#e# )of(#n ,d# #)->n :% shiftLInteger1d# |otherwise ->smallIntegerm# :% shiftLInteger1(negateInt#e# )-- | @since 2.01-- Note that due to the presence of @NaN@, not all elements of 'Float' have an-- multiplicative inverse.---- >>> 0/0 * (recip 0/0 :: Float)-- NaNinstanceFractional Floatwhere(/ )x y =divideFloat x y {-# INLINEfromRational#-}fromRational (n :% d )=rationalToFloat n d recip x =1.0/ x rationalToFloat::Integer->Integer->Float{-# NOINLINE[1]rationalToFloat#-}rationalToFloat n 0|n ==0=0/ 0|n <0=(-1)/ 0|otherwise =1/ 0rationalToFloatn d |n ==0=encodeFloat 00|n <0=-(fromRat'' minEx mantDigs (-n )d )|otherwise =fromRat'' minEx mantDigs n d whereminEx =FLT_MIN_EXPmantDigs =FLT_MANT_DIG-- RULES for Integer and Int{-# RULES"properFraction/Float->Integer"properFraction=properFractionFloatInteger"truncate/Float->Integer"truncate=truncateFloatInteger"floor/Float->Integer"floor=floorFloatInteger"ceiling/Float->Integer"ceiling=ceilingFloatInteger"round/Float->Integer"round=roundFloatInteger"properFraction/Float->Int"properFraction=properFractionFloatInt"truncate/Float->Int"truncate=float2Int"floor/Float->Int"floor=floorFloatInt"ceiling/Float->Int"ceiling=ceilingFloatInt"round/Float->Int"round=roundFloatInt#-}-- | @since 2.01instanceRealFrac Floatwhere-- ceiling, floor, and truncate are all small{-# INLINE[1]ceiling#-}{-# INLINE[1]floor#-}{-# INLINE[1]truncate#-}-- We assume that FLT_RADIX is 2 so that we can use more efficient code#if FLT_RADIX != 2
#error FLT_RADIX must be 2
#endif
properFraction (F#x# )=casedecodeFloat_Int#x# of(#m# ,n# #)->letm =I#m# n =I#n# inifn >=0then(fromIntegral m * (2^ n ),0.0)elseleti =ifm >=0thenm `shiftR `negate n elsenegate (negate m `shiftR `negate n )f =m -(i `shiftL `negate n )in(fromIntegral i ,encodeFloat (fromIntegral f )n )truncate x =caseproperFraction x of(n ,_)->n round x =caseproperFraction x of(n ,r )->letm =ifr <0.0thenn -1elsen + 1half_down =abs r -0.5incase(comparehalf_down 0.0)ofLT->n EQ->ifeven n thenn elsem GT->m ceiling x =caseproperFraction x of(n ,r )->ifr >0.0thenn + 1elsen floor x =caseproperFraction x of(n ,r )->ifr <0.0thenn -1elsen -- | @since 2.01instanceFloating Floatwherepi =3.141592653589793238exp x =expFloat x log x =logFloat x sqrt x =sqrtFloat x sin x =sinFloat x cos x =cosFloat x tan x =tanFloat x asin x =asinFloat x acos x =acosFloat x atan x =atanFloat x sinh x =sinhFloat x cosh x =coshFloat x tanh x =tanhFloat x (** )x y =powerFloat x y logBase x y =log y / log x asinh x |x >huge =log 2+ log x |x <0=-asinh (-x )|otherwise =log (x + sqrt (1+ x * x ))wherehuge =1e10acosh x =log (x + (x + 1.0)* sqrt ((x -1.0)/ (x + 1.0)))atanh x =0.5* log ((1.0+ x )/ (1.0-x ))log1p =log1pFloat expm1 =expm1Float log1mexp a |a <=log 2=log (negate (expm1Float a ))|otherwise =log1pFloat (negate (exp a )){-# INLINElog1mexp#-}log1pexp a |a <=18=log1pFloat (exp a )|a <=100=a + exp (negate a )|otherwise =a {-# INLINElog1pexp#-}-- | @since 2.01instanceRealFloat FloatwherefloatRadix _=FLT_RADIX-- from float.hfloatDigits _=FLT_MANT_DIG-- dittofloatRange _=(FLT_MIN_EXP,FLT_MAX_EXP)-- dittodecodeFloat (F#f# )=casedecodeFloat_Int#f# of(#i ,e #)->(smallIntegeri ,I#e )encodeFloat i (I#e )=F#(encodeFloatIntegeri e )exponent x =casedecodeFloat x of(m ,n )->ifm ==0then0elsen + floatDigits x significand x =casedecodeFloat x of(m ,_)->encodeFloat m (negate (floatDigits x ))scaleFloat 0x =x scaleFloatk x |isFix =x |otherwise =casedecodeFloat x of(m ,n )->encodeFloat m (n + clamp bf k )wherebf =FLT_MAX_EXP-(FLT_MIN_EXP)+4*FLT_MANT_DIGisFix =x ==0||isFloatFinite x ==0isNaN x =0/=isFloatNaN x isInfinite x =0/=isFloatInfinite x isDenormalized x =0/=isFloatDenormalized x isNegativeZero x =0/=isFloatNegativeZero x isIEEE _=True-- | @since 2.01instanceShow FloatwhereshowsPrec x =showSignedFloat showFloat x showList =showList__ (showsPrec 0)-------------------------------------------------------------------------- Double-------------------------------------------------------------------------- | @since 2.01-- Note that due to the presence of @NaN@, not all elements of 'Double' have an-- additive inverse.---- >>> 0/0 + (negate 0/0 :: Double)-- NaN---- Also note that due to the presence of -0, `Double`'s 'Num' instance doesn't-- have an additive identity---- >>> 0 + (-0 :: Double)-- 0.0instanceNum Doublewhere(+ )x y =plusDouble x y (-)x y =minusDouble x y negate x =negateDouble x (* )x y =timesDouble x y abs x =fabsDouble x signum x |x >0=1|x <0=negateDouble 1|otherwise =x -- handles 0.0, (-0.0), and NaN{-# INLINEfromInteger#-}fromInteger i =D#(doubleFromIntegeri )-- | @since 2.01instanceReal DoublewheretoRational (D#x# )=casedecodeDoubleIntegerx# of(#m ,e# #)|isTrue#(e# >=#0#)->shiftLIntegerm e# :% 1|isTrue#((integerToWordm `and#`1##)`eqWord#`0##)->caseelimZerosInteger m (negateInt#e# )of(#n ,d# #)->n :% shiftLInteger1d# |otherwise ->m :% shiftLInteger1(negateInt#e# )-- | @since 2.01-- Note that due to the presence of @NaN@, not all elements of 'Double' have an-- multiplicative inverse.---- >>> 0/0 * (recip 0/0 :: Double)-- NaNinstanceFractional Doublewhere(/ )x y =divideDouble x y {-# INLINEfromRational#-}fromRational (n :% d )=rationalToDouble n d recip x =1.0/ x rationalToDouble::Integer->Integer->Double{-# NOINLINE[1]rationalToDouble#-}rationalToDouble n 0|n ==0=0/ 0|n <0=(-1)/ 0|otherwise =1/ 0rationalToDoublen d |n ==0=encodeFloat 00|n <0=-(fromRat'' minEx mantDigs (-n )d )|otherwise =fromRat'' minEx mantDigs n d whereminEx =DBL_MIN_EXPmantDigs =DBL_MANT_DIG-- | @since 2.01instanceFloating Doublewherepi =3.141592653589793238exp x =expDouble x log x =logDouble x sqrt x =sqrtDouble x sin x =sinDouble x cos x =cosDouble x tan x =tanDouble x asin x =asinDouble x acos x =acosDouble x atan x =atanDouble x sinh x =sinhDouble x cosh x =coshDouble x tanh x =tanhDouble x (** )x y =powerDouble x y logBase x y =log y / log x asinh x |x >huge =log 2+ log x |x <0=-asinh (-x )|otherwise =log (x + sqrt (1+ x * x ))wherehuge =1e20acosh x =log (x + (x + 1.0)* sqrt ((x -1.0)/ (x + 1.0)))atanh x =0.5* log ((1.0+ x )/ (1.0-x ))log1p =log1pDouble expm1 =expm1Double log1mexp a |a <=log 2=log (negate (expm1Double a ))|otherwise =log1pDouble (negate (exp a )){-# INLINElog1mexp#-}log1pexp a |a <=18=log1pDouble (exp a )|a <=100=a + exp (negate a )|otherwise =a {-# INLINElog1pexp#-}-- RULES for Integer and Int{-# RULES"properFraction/Double->Integer"properFraction=properFractionDoubleInteger"truncate/Double->Integer"truncate=truncateDoubleInteger"floor/Double->Integer"floor=floorDoubleInteger"ceiling/Double->Integer"ceiling=ceilingDoubleInteger"round/Double->Integer"round=roundDoubleInteger"properFraction/Double->Int"properFraction=properFractionDoubleInt"truncate/Double->Int"truncate=double2Int"floor/Double->Int"floor=floorDoubleInt"ceiling/Double->Int"ceiling=ceilingDoubleInt"round/Double->Int"round=roundDoubleInt#-}-- | @since 2.01instanceRealFrac Doublewhere-- ceiling, floor, and truncate are all small{-# INLINE[1]ceiling#-}{-# INLINE[1]floor#-}{-# INLINE[1]truncate#-}properFraction x =case(decodeFloat x )of{(m ,n )->ifn >=0then(fromInteger m * 2^ n ,0.0)elsecase(quotRem m (2^ (negate n )))of{(w ,r )->(fromInteger w ,encodeFloat r n )}}truncate x =caseproperFraction x of(n ,_)->n round x =caseproperFraction x of(n ,r )->letm =ifr <0.0thenn -1elsen + 1half_down =abs r -0.5incase(comparehalf_down 0.0)ofLT->n EQ->ifeven n thenn elsem GT->m ceiling x =caseproperFraction x of(n ,r )->ifr >0.0thenn + 1elsen floor x =caseproperFraction x of(n ,r )->ifr <0.0thenn -1elsen -- | @since 2.01instanceRealFloat DoublewherefloatRadix _=FLT_RADIX-- from float.hfloatDigits _=DBL_MANT_DIG-- dittofloatRange _=(DBL_MIN_EXP,DBL_MAX_EXP)-- dittodecodeFloat (D#x# )=casedecodeDoubleIntegerx# of(#i ,j #)->(i ,I#j )encodeFloat i (I#j )=D#(encodeDoubleIntegeri j )exponent x =casedecodeFloat x of(m ,n )->ifm ==0then0elsen + floatDigits x significand x =casedecodeFloat x of(m ,_)->encodeFloat m (negate (floatDigits x ))scaleFloat 0x =x scaleFloatk x |isFix =x |otherwise =casedecodeFloat x of(m ,n )->encodeFloat m (n + clamp bd k )wherebd =DBL_MAX_EXP-(DBL_MIN_EXP)+4*DBL_MANT_DIGisFix =x ==0||isDoubleFinite x ==0isNaN x =0/=isDoubleNaN x isInfinite x =0/=isDoubleInfinite x isDenormalized x =0/=isDoubleDenormalized x isNegativeZero x =0/=isDoubleNegativeZero x isIEEE _=True-- | @since 2.01instanceShow DoublewhereshowsPrec x =showSignedFloat showFloat x showList =showList__ (showsPrec 0)-------------------------------------------------------------------------- Enum instances------------------------------------------------------------------------{-
The @Enum@ instances for Floats and Doubles are slightly unusual.
The @toEnum@ function truncates numbers to Int. The definitions
of @enumFrom@ and @enumFromThen@ allow floats to be used in arithmetic
series: [0,0.1 .. 1.0]. However, roundoff errors make these somewhat
dubious. This example may have either 10 or 11 elements, depending on
how 0.1 is represented.
NOTE: The instances for Float and Double do not make use of the default
methods for @enumFromTo@ and @enumFromThenTo@, as these rely on there being
a `non-lossy' conversion to and from Ints. Instead we make use of the
1.2 default methods (back in the days when Enum had Ord as a superclass)
for these (@numericEnumFromTo@ and @numericEnumFromThenTo@ below.)
-}-- | @since 2.01instanceEnum Floatwheresucc x =x + 1pred x =x -1toEnum =int2Float fromEnum =fromInteger . truncate -- may overflowenumFrom =numericEnumFrom enumFromTo =numericEnumFromTo enumFromThen =numericEnumFromThen enumFromThenTo =numericEnumFromThenTo -- | @since 2.01instanceEnum Doublewheresucc x =x + 1pred x =x -1toEnum =int2Double fromEnum =fromInteger . truncate -- may overflowenumFrom =numericEnumFrom enumFromTo =numericEnumFromTo enumFromThen =numericEnumFromThen enumFromThenTo =numericEnumFromThenTo -------------------------------------------------------------------------- Printing floating point-------------------------------------------------------------------------- | Show a signed 'RealFloat' value to full precision-- using standard decimal notation for arguments whose absolute value lies-- between @0.1@ and @9,999,999@, and scientific notation otherwise.showFloat::(RealFloat a )=>a ->ShowS showFloat x =showString (formatRealFloat FFGeneric Nothing x )-- These are the format types. This type is not exported.dataFFFormat =FFExponent |FFFixed |FFGeneric -- This is just a compatibility stub, as the "alt" argument formerly-- didn't exist.formatRealFloat::(RealFloat a )=>FFFormat ->Maybe Int->a ->String formatRealFloat fmt decs x =formatRealFloatAlt fmt decs Falsex formatRealFloatAlt::(RealFloat a )=>FFFormat ->Maybe Int->Bool->a ->String formatRealFloatAlt fmt decs alt x |isNaN x ="NaN"|isInfinite x =ifx <0then"-Infinity"else"Infinity"|x <0||isNegativeZero x ='-':doFmt fmt (floatToDigits (toInteger base )(-x ))|otherwise =doFmt fmt (floatToDigits (toInteger base )x )wherebase =10doFmt format (is ,e )=letds =map intToDigit is incaseformat ofFFGeneric ->doFmt (ife <0||e >7thenFFExponent elseFFFixed )(is ,e )FFExponent ->casedecs ofNothing ->letshow_e' =show (e -1)incaseds of"0"->"0.0e0"[d ]->d :".0e"++ show_e' (d :ds' )->d :'.':ds' ++ "e"++ show_e' []->errorWithoutStackTrace "formatRealFloat/doFmt/FFExponent: []"Just d |d <=0->-- handle this case specifically since we need to omit the-- decimal point as well (#15115).-- Note that this handles negative precisions as well for consistency-- (see #15509).caseis of[0]->"0e0"_->let(ei ,is' )=roundTo base 1is n :_=map intToDigit (ifei >0theninit is' elseis' )inn :'e':show (e -1+ ei )Just dec ->letdec' =maxdec 1incaseis of[0]->'0':'.':take dec' (repeat '0')++ "e0"_->let(ei ,is' )=roundTo base (dec' + 1)is (d :ds' )=map intToDigit (ifei >0theninit is' elseis' )ind :'.':ds' ++ 'e':show (e -1+ ei )FFFixed ->letmk0 ls =casels of{""->"0";_->ls }incasedecs ofNothing |e <=0->"0."++ replicate (-e )'0'++ ds |otherwise ->letf 0s rs =mk0 (reverse s )++ '.':mk0 rs fn s ""=f (n -1)('0':s )""fn s (r :rs )=f (n -1)(r :s )rs inf e ""ds Just dec ->letdec' =maxdec 0inife >=0thenlet(ei ,is' )=roundTo base (dec' + e )is (ls ,rs )=splitAt (e + ei )(map intToDigit is' )inmk0 ls ++ (ifnull rs &&notalt then""else'.':rs )elselet(ei ,is' )=roundTo base dec' (replicate (-e )0++ is )d :ds' =map intToDigit (ifei >0thenis' else0:is' )ind :(ifnull ds' &&notalt then""else'.':ds' )roundTo::Int->Int->[Int]->(Int,[Int])roundTo base d is =casef d Trueis ofx @(0,_)->x (1,xs )->(1,1:xs )_->errorWithoutStackTrace "roundTo: bad Value"whereb2 =base `quot `2f n _[]=(0,replicate n 0)f0e (x :xs )|x ==b2 &&e &&all (==0)xs =(0,[])-- Round to even when at exactly half the base|otherwise =(ifx >=b2 then1else0,[])fn _(i :xs )|i' ==base =(1,0:ds )|otherwise =(0,i' :ds )where(c ,ds )=f (n -1)(even i )xs i' =c + i -- Based on "Printing Floating-Point Numbers Quickly and Accurately"-- by R.G. Burger and R.K. Dybvig in PLDI 96.-- This version uses a much slower logarithm estimator. It should be improved.-- | 'floatToDigits' takes a base and a non-negative 'RealFloat' number,-- and returns a list of digits and an exponent.-- In particular, if @x>=0@, and---- > floatToDigits base x = ([d1,d2,...,dn], e)---- then---- (1) @n >= 1@---- (2) @x = 0.d1d2...dn * (base**e)@---- (3) @0 <= di <= base-1@floatToDigits::(RealFloat a )=>Integer->a ->([Int],Int)floatToDigits _0=([0],0)floatToDigitsbase x =let(f0 ,e0 )=decodeFloat x (minExp0 ,_)=floatRange x p =floatDigits x b =floatRadix x minExp =minExp0 -p -- the real minimum exponent-- Haskell requires that f be adjusted so denormalized numbers-- will have an impossibly low exponent. Adjust for this.(f ,e )=letn =minExp -e0 inifn >0then(f0 `quot `(expt b n ),e0 + n )else(f0 ,e0 )(r ,s ,mUp ,mDn )=ife >=0thenletbe =expt b e iniff ==expt b (p -1)then(f * be * b * 2,2* b ,be * b ,be )-- according to Burger and Dybvigelse(f * be * 2,2,be ,be )elseife >minExp &&f ==expt b (p -1)then(f * b * 2,expt b (-e + 1)* 2,b ,1)else(f * 2,expt b (-e )* 2,1,1)k::Intk =letk0::Intk0 =ifb ==2&&base ==10then-- logBase 10 2 is very slightly larger than 8651/28738-- (about 5.3558e-10), so if log x >= 0, the approximation-- k1 is too small, hence we add one and need one fixup step less.-- If log x < 0, the approximation errs rather on the high side.-- That is usually more than compensated for by ignoring the-- fractional part of logBase 2 x, but when x is a power of 1/2-- or slightly larger and the exponent is a multiple of the-- denominator of the rational approximation to logBase 10 2,-- k1 is larger than logBase 10 x. If k1 > 1 + logBase 10 x,-- we get a leading zero-digit we don't want.-- With the approximation 3/10, this happened for-- 0.5^1030, 0.5^1040, ..., 0.5^1070 and values close above.-- The approximation 8651/28738 guarantees k1 < 1 + logBase 10 x-- for IEEE-ish floating point types with exponent fields-- <= 17 bits and mantissae of several thousand bits, earlier-- convergents to logBase 10 2 would fail for long double.-- Using quot instead of div is a little faster and requires-- fewer fixup steps for negative lx.letlx =p -1+ e0 k1 =(lx * 8651)`quot `28738iniflx >=0thenk1 + 1elsek1 else-- f :: Integer, log :: Float -> Float,-- ceiling :: Float -> Intceiling ((log (fromInteger (f + 1)::Float)+ fromIntegral e * log (fromInteger b ))/ log (fromInteger base ))--WAS: fromInt e * log (fromInteger b))fixup n =ifn >=0thenifr + mUp <=expt base n * s thenn elsefixup (n + 1)elseifexpt base (-n )* (r + mUp )<=s thenn elsefixup (n + 1)infixup k0 gen ds rn sN mUpN mDnN =let(dn ,rn' )=(rn * base )`quotRem `sN mUpN' =mUpN * base mDnN' =mDnN * base incase(rn' <mDnN' ,rn' + mUpN' >sN )of(True,False)->dn :ds (False,True)->dn + 1:ds (True,True)->ifrn' * 2<sN thendn :ds elsedn + 1:ds (False,False)->gen (dn :ds )rn' sN mUpN' mDnN' rds =ifk >=0thengen []r (s * expt base k )mUp mDn elseletbk =expt base (-k )ingen [](r * bk )s (mUp * bk )(mDn * bk )in(map fromIntegral (reverse rds ),k )-------------------------------------------------------------------------- Converting from a Rational to a RealFloa------------------------------------------------------------------------{-
[In response to a request for documentation of how fromRational works,
Joe Fasel writes:] A quite reasonable request! This code was added to
the Prelude just before the 1.2 release, when Lennart, working with an
early version of hbi, noticed that (read . show) was not the identity
for floating-point numbers. (There was a one-bit error about half the
time.) The original version of the conversion function was in fact
simply a floating-point divide, as you suggest above. The new version
is, I grant you, somewhat denser.
Unfortunately, Joe's code doesn't work! Here's an example:
main = putStr (shows (1.82173691287639817263897126389712638972163e-300::Double) "\n")
This program prints
 0.0000000000000000
instead of
 1.8217369128763981e-300
Here's Joe's code:
\begin{pseudocode}
fromRat :: (RealFloat a) => Rational -> a
fromRat x = x'
 where x' = f e
-- If the exponent of the nearest floating-point number to x
-- is e, then the significand is the integer nearest xb^(-e),
-- where b is the floating-point radix. We start with a good
-- guess for e, and if it is correct, the exponent of the
-- floating-point number we construct will again be e. If
-- not, one more iteration is needed.
 f e = if e' == e then y else f e'
 where y = encodeFloat (round (x * (1 % b)^^e)) e
 (_,e') = decodeFloat y
 b = floatRadix x'
-- We obtain a trial exponent by doing a floating-point
-- division of x's numerator by its denominator. The
-- result of this division may not itself be the ultimate
-- result, because of an accumulation of three rounding
-- errors.
 (s,e) = decodeFloat (fromInteger (numerator x) `asTypeOf` x'
 / fromInteger (denominator x))
\end{pseudocode}
Now, here's Lennart's code (which works):
-}-- | Converts a 'Rational' value into any type in class 'RealFloat'.{-# RULES"fromRat/Float"fromRat=(fromRational::Rational->Float)"fromRat/Double"fromRat=(fromRational::Rational->Double)#-}{-# NOINLINE[1]fromRat#-}fromRat::(RealFloat a )=>Rational ->a -- Deal with special cases first, delegating the real work to fromRat'fromRat (n :% 0)|n >0=1/ 0-- +Infinity|n <0=-1/ 0-- -Infinity|otherwise =0/ 0-- NaNfromRat(n :% d )|n >0=fromRat' (n :% d )|n <0=-fromRat' ((-n ):% d )|otherwise =encodeFloat 00-- Zero-- Conversion process:-- Scale the rational number by the RealFloat base until-- it lies in the range of the mantissa (as used by decodeFloat/encodeFloat).-- Then round the rational to an Integer and encode it with the exponent-- that we got from the scaling.-- To speed up the scaling process we compute the log2 of the number to get-- a first guess of the exponent.fromRat'::(RealFloat a )=>Rational ->a -- Invariant: argument is strictly positivefromRat' x =r whereb =floatRadix r p =floatDigits r (minExp0 ,_)=floatRange r minExp =minExp0 -p -- the real minimum exponentxMax =toRational (expt b p )p0 =(integerLogBase b (numerator x )-integerLogBase b (denominator x )-p )`max`minExp -- if x = n/d and ln = integerLogBase b n, ld = integerLogBase b d,-- then b^(ln-ld-1) < x < b^(ln-ld+1)f =ifp0 <0then1:% expt b (-p0 )elseexpt b p0 :% 1x0 =x / f -- if ln - ld >= minExp0, then b^(p-1) < x0 < b^(p+1), so there's at most-- one scaling step needed, otherwise, x0 < b^p and no scaling is needed(x' ,p' )=ifx0 >=xMax then(x0 / toRational b ,p0 + 1)else(x0 ,p0 )r =encodeFloat (round x' )p' -- Exponentiation with a cache for the most common numbers.minExpt,maxExpt::IntminExpt =0maxExpt =1100expt::Integer->Int->Integerexpt base n =ifbase ==2&&n >=minExpt &&n <=maxExpt thenexpts !n elseifbase ==10&&n <=maxExpt10 thenexpts10 !n elsebase ^ n expts::Array IntIntegerexpts =array (minExpt ,maxExpt )[(n ,2^ n )|n <-[minExpt ..maxExpt ]]maxExpt10::IntmaxExpt10 =324expts10::Array IntIntegerexpts10 =array (minExpt ,maxExpt10 )[(n ,10^ n )|n <-[minExpt ..maxExpt10 ]]-- Compute the (floor of the) log of i in base b.-- Simplest way would be just divide i by b until it's smaller then b, but that would-- be very slow! We are just slightly more clever, except for base 2, where-- we take advantage of the representation of Integers.-- The general case could be improved by a lookup table for-- approximating the result by integerLog2 i / integerLog2 b.integerLogBase::Integer->Integer->IntintegerLogBase b i |i <b =0|b ==2=I#(integerLog2#i )|otherwise =I#(integerLogBase#b i ){-
Unfortunately, the old conversion code was awfully slow due to
a) a slow integer logarithm
b) repeated calculation of gcd's
For the case of Rational's coming from a Float or Double via toRational,
we can exploit the fact that the denominator is a power of two, which for
these brings a huge speedup since we need only shift and add instead
of division.
The below is an adaption of fromRat' for the conversion to
Float or Double exploiting the known floatRadix and avoiding
divisions as much as possible.
-}{-# SPECIALISEfromRat''::Int->Int->Integer->Integer->Float,Int->Int->Integer->Integer->Double#-}fromRat''::RealFloat a =>Int->Int->Integer->Integer->a -- Invariant: n and d strictly positivefromRat'' minEx @(I#me# )mantDigs @(I#md# )n d =caseintegerLog2IsPowerOf2#d of(#ld# ,pw# #)|isTrue#(pw# ==#0#)->caseintegerLog2#n ofln# |isTrue#(ln# >=#(ld# +#me# -#1#))->-- this means n/d >= 2^(minEx-1), i.e. we are guaranteed to get-- a normalised number, round to mantDigs bitsifisTrue#(ln# <#md# )thenencodeFloat n (I#(negateInt#ld# ))elseletn' =n `shiftR `(I#(ln# +#1#-#md# ))n'' =caseroundingMode#n (ln# -#md# )of0#->n' 2#->n' + 1_->casefromInteger n' .&. (1::Int)of0->n' _->n' + 1inencodeFloat n'' (I#(ln# -#ld# +#1#-#md# ))|otherwise ->-- n/d < 2^(minEx-1), a denorm or rounded to 2^(minEx-1)-- the exponent for encoding is always minEx-mantDigs-- so we must shift right by (minEx-mantDigs) - (-ld)caseld# +#(me# -#md# )ofld'# |isTrue#(ld'# <=#0#)->-- we would shift left, so we don't shiftencodeFloat n (I#((me# -#md# )-#ld'# ))|isTrue#(ld'# <=#ln# )->letn' =n `shiftR `(I#ld'# )incaseroundingMode#n (ld'# -#1#)of0#->encodeFloat n' (minEx -mantDigs )1#->iffromInteger n' .&. (1::Int)==0thenencodeFloat n' (minEx -mantDigs )elseencodeFloat (n' + 1)(minEx -mantDigs )_->encodeFloat (n' + 1)(minEx -mantDigs )|isTrue#(ld'# >#(ln# +#1#))->encodeFloat 00-- result of shift < 0.5|otherwise ->-- first bit of n shifted to 0.5 placecaseintegerLog2IsPowerOf2#n of(#_,0##)->encodeFloat 00-- round to even(#_,_#)->encodeFloat 1(minEx -mantDigs )|otherwise ->letln =I#(integerLog2#n )ld =I#ld# -- 2^(ln-ld-1) < n/d < 2^(ln-ld+1)p0 =maxminEx (ln -ld )(n' ,d' )|p0 <mantDigs =(n `shiftL `(mantDigs -p0 ),d )|p0 ==mantDigs =(n ,d )|otherwise =(n ,d `shiftL `(p0 -mantDigs ))-- if ln-ld < minEx, then n'/d' < 2^mantDigs, else-- 2^(mantDigs-1) < n'/d' < 2^(mantDigs+1) and we-- may need one scaling stepscale p a b |(b `shiftL `mantDigs )<=a =(p + 1,a ,b `shiftL `1)|otherwise =(p ,a ,b )(p' ,n'' ,d'' )=scale (p0 -mantDigs )n' d' -- n''/d'' < 2^mantDigs and p' == minEx-mantDigs or n''/d'' >= 2^(mantDigs-1)rdq =casen'' `quotRem `d'' of(q ,r )->casecompare(r `shiftL `1)d'' ofLT->q EQ->iffromInteger q .&. (1::Int)==0thenq elseq + 1GT->q + 1inencodeFloat rdq p' -------------------------------------------------------------------------- Floating point numeric primops-------------------------------------------------------------------------- Definitions of the boxed PrimOps; these will be-- used in the case of partial applications, etc.plusFloat,minusFloat,timesFloat,divideFloat::Float->Float->FloatplusFloat (F#x )(F#y )=F#(plusFloat#x y )minusFloat (F#x )(F#y )=F#(minusFloat#x y )timesFloat (F#x )(F#y )=F#(timesFloat#x y )divideFloat (F#x )(F#y )=F#(divideFloat#x y )negateFloat::Float->FloatnegateFloat (F#x )=F#(negateFloat#x )gtFloat,geFloat,ltFloat,leFloat::Float->Float->BoolgtFloat (F#x )(F#y )=isTrue#(gtFloat#x y )geFloat (F#x )(F#y )=isTrue#(geFloat#x y )ltFloat (F#x )(F#y )=isTrue#(ltFloat#x y )leFloat (F#x )(F#y )=isTrue#(leFloat#x y )expFloat,logFloat,sqrtFloat,fabsFloat::Float->FloatsinFloat,cosFloat,tanFloat::Float->FloatasinFloat,acosFloat,atanFloat::Float->FloatsinhFloat,coshFloat,tanhFloat::Float->FloatexpFloat (F#x )=F#(expFloat#x )logFloat (F#x )=F#(logFloat#x )sqrtFloat (F#x )=F#(sqrtFloat#x )fabsFloat (F#x )=F#(fabsFloat#x )sinFloat (F#x )=F#(sinFloat#x )cosFloat (F#x )=F#(cosFloat#x )tanFloat (F#x )=F#(tanFloat#x )asinFloat (F#x )=F#(asinFloat#x )acosFloat (F#x )=F#(acosFloat#x )atanFloat (F#x )=F#(atanFloat#x )sinhFloat (F#x )=F#(sinhFloat#x )coshFloat (F#x )=F#(coshFloat#x )tanhFloat (F#x )=F#(tanhFloat#x )powerFloat::Float->Float->FloatpowerFloat (F#x )(F#y )=F#(powerFloat#x y )-- definitions of the boxed PrimOps; these will be-- used in the case of partial applications, etc.plusDouble,minusDouble,timesDouble,divideDouble::Double->Double->DoubleplusDouble (D#x )(D#y )=D#(x +##y )minusDouble (D#x )(D#y )=D#(x -##y )timesDouble (D#x )(D#y )=D#(x *##y )divideDouble (D#x )(D#y )=D#(x /##y )negateDouble::Double->DoublenegateDouble (D#x )=D#(negateDouble#x )gtDouble,geDouble,leDouble,ltDouble::Double->Double->BoolgtDouble (D#x )(D#y )=isTrue#(x >##y )geDouble (D#x )(D#y )=isTrue#(x >=##y )ltDouble (D#x )(D#y )=isTrue#(x <##y )leDouble (D#x )(D#y )=isTrue#(x <=##y )double2Float::Double->Floatdouble2Float (D#x )=F#(double2Float#x )float2Double::Float->Doublefloat2Double (F#x )=D#(float2Double#x )expDouble,logDouble,sqrtDouble,fabsDouble::Double->DoublesinDouble,cosDouble,tanDouble::Double->DoubleasinDouble,acosDouble,atanDouble::Double->DoublesinhDouble,coshDouble,tanhDouble::Double->DoubleexpDouble (D#x )=D#(expDouble#x )logDouble (D#x )=D#(logDouble#x )sqrtDouble (D#x )=D#(sqrtDouble#x )fabsDouble (D#x )=D#(fabsDouble#x )sinDouble (D#x )=D#(sinDouble#x )cosDouble (D#x )=D#(cosDouble#x )tanDouble (D#x )=D#(tanDouble#x )asinDouble (D#x )=D#(asinDouble#x )acosDouble (D#x )=D#(acosDouble#x )atanDouble (D#x )=D#(atanDouble#x )sinhDouble (D#x )=D#(sinhDouble#x )coshDouble (D#x )=D#(coshDouble#x )tanhDouble (D#x )=D#(tanhDouble#x )powerDouble::Double->Double->DoublepowerDouble (D#x )(D#y )=D#(x **##y )foreignimportccallunsafe"isFloatNaN"isFloatNaN::Float->Intforeignimportccallunsafe"isFloatInfinite"isFloatInfinite::Float->Intforeignimportccallunsafe"isFloatDenormalized"isFloatDenormalized::Float->Intforeignimportccallunsafe"isFloatNegativeZero"isFloatNegativeZero::Float->Intforeignimportccallunsafe"isFloatFinite"isFloatFinite::Float->Intforeignimportccallunsafe"isDoubleNaN"isDoubleNaN::Double->Intforeignimportccallunsafe"isDoubleInfinite"isDoubleInfinite::Double->Intforeignimportccallunsafe"isDoubleDenormalized"isDoubleDenormalized::Double->Intforeignimportccallunsafe"isDoubleNegativeZero"isDoubleNegativeZero::Double->Intforeignimportccallunsafe"isDoubleFinite"isDoubleFinite::Double->Int-------------------------------------------------------------------------- libm imports for extended floating------------------------------------------------------------------------foreignimportcapiunsafe"math.h log1p"log1pDouble::Double->Doubleforeignimportcapiunsafe"math.h expm1"expm1Double::Double->Doubleforeignimportcapiunsafe"math.h log1pf"log1pFloat::Float->Floatforeignimportcapiunsafe"math.h expm1f"expm1Float::Float->Float-------------------------------------------------------------------------- Coercion rules------------------------------------------------------------------------word2Double::Word->Doubleword2Double (W#w )=D#(word2Double#w )word2Float::Word->Floatword2Float (W#w )=F#(word2Float#w ){-# RULES"fromIntegral/Int->Float"fromIntegral=int2Float"fromIntegral/Int->Double"fromIntegral=int2Double"fromIntegral/Word->Float"fromIntegral=word2Float"fromIntegral/Word->Double"fromIntegral=word2Double"realToFrac/Float->Float"realToFrac=id::Float->Float"realToFrac/Float->Double"realToFrac=float2Double"realToFrac/Double->Float"realToFrac=double2Float"realToFrac/Double->Double"realToFrac=id::Double->Double"realToFrac/Int->Double"realToFrac=int2Double-- See Note [realToFrac int-to-float]"realToFrac/Int->Float"realToFrac=int2Float-- ..ditto#-}{-
Note [realToFrac int-to-float]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Don found that the RULES for realToFrac/Int->Double and simliarly
Float made a huge difference to some stream-fusion programs. Here's
an example
 import Data.Array.Vector
 n = 40000000
 main = do
 let c = replicateU n (2::Double)
 a = mapU realToFrac (enumFromToU 0 (n-1) ) :: UArr Double
 print (sumU (zipWithU (*) c a))
Without the RULE we get this loop body:
 case $wtoRational sc_sY4 of ww_aM7 { (# ww1_aM9, ww2_aMa #) ->
 case $wfromRat ww1_aM9 ww2_aMa of tpl_X1P { D# ipv_sW3 ->
 Main.$s$wfold
 (+# sc_sY4 1)
 (+# wild_X1i 1)
 (+## sc2_sY6 (*## 2.0 ipv_sW3))
And with the rule:
 Main.$s$wfold
 (+# sc_sXT 1)
 (+# wild_X1h 1)
 (+## sc2_sXV (*## 2.0 (int2Double# sc_sXT)))
The running time of the program goes from 120 seconds to 0.198 seconds
with the native backend, and 0.143 seconds with the C backend.
A few more details in Trac #2251, and the patch message
"Add RULES for realToFrac from Int".
-}-- UtilsshowSignedFloat::(RealFloat a )=>(a ->ShowS )-- ^ a function that can show unsigned values->Int-- ^ the precedence of the enclosing context->a -- ^ the value to show->ShowS showSignedFloat showPos p x |x <0||isNegativeZero x =showParen (p >6)(showChar '-'. showPos (-x ))|otherwise =showPos x {-
We need to prevent over/underflow of the exponent in encodeFloat when
called from scaleFloat, hence we clamp the scaling parameter.
We must have a large enough range to cover the maximum difference of
exponents returned by decodeFloat.
-}clamp::Int->Int->Intclamp bd k =max(-bd )(minbd k ){-
Note [Casting from integral to floating point types]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
To implement something like `reinterpret_cast` from C++ to go from a
floating-point type to an integral type one might niavely think that the
following should work:
 cast :: Float -> Word32
 cast (F# f#) = W32# (unsafeCoerce# f#)
Unfortunately that is not the case, because all the `unsafeCoerce#` does is tell
the compiler that the types have changed. When one does the above cast and
tries to operate on the resulting `Word32` the code generator will generate code
that performs an integer/word operation on a floating-point register, which
results in a compile error.
The correct way of implementing `reinterpret_cast` to implement a primpop, but
that requires a unique implementation for all supported archetectures. The next
best solution is to write the value from the source register to memory and then
read it from memory into the destination register and the best way to do that
is using CMM.
-}-- | @'castWord32ToFloat' w@ does a bit-for-bit copy from an integral value-- to a floating-point value.---- @since 4.10.0.0{-# INLINEcastWord32ToFloat#-}castWord32ToFloat::Word32 ->FloatcastWord32ToFloat (W32# w# )=F#(stgWord32ToFloat w# )foreignimportprim"stg_word32ToFloatzh"stgWord32ToFloat::Word#->Float#-- | @'castFloatToWord32' f@ does a bit-for-bit copy from a floating-point value-- to an integral value.---- @since 4.10.0.0{-# INLINEcastFloatToWord32#-}castFloatToWord32::Float->Word32 castFloatToWord32 (F#f# )=W32# (stgFloatToWord32 f# )foreignimportprim"stg_floatToWord32zh"stgFloatToWord32::Float#->Word#-- | @'castWord64ToDouble' w@ does a bit-for-bit copy from an integral value-- to a floating-point value.---- @since 4.10.0.0{-# INLINEcastWord64ToDouble#-}castWord64ToDouble::Word64 ->DoublecastWord64ToDouble (W64# w )=D#(stgWord64ToDouble w )foreignimportprim"stg_word64ToDoublezh"#if WORD_SIZE_IN_BITS == 64
stgWord64ToDouble::Word#->Double##else
stgWord64ToDouble::Word64#->Double##endif
-- | @'castFloatToWord32' f@ does a bit-for-bit copy from a floating-point value-- to an integral value.---- @since 4.10.0.0{-# INLINEcastDoubleToWord64#-}castDoubleToWord64::Double->Word64 castDoubleToWord64 (D#d# )=W64# (stgDoubleToWord64 d# )foreignimportprim"stg_doubleToWord64zh"#if WORD_SIZE_IN_BITS == 64
stgDoubleToWord64::Double#->Word##else
stgDoubleToWord64::Double#->Word64##endif

AltStyle によって変換されたページ (->オリジナル) /