{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, MagicHash, UnboxedTuples, NoImplicitPrelude #-}{-# OPTIONS_GHC -O2 #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module : GHC.Float.ConversionUtils-- Copyright : (c) Daniel Fischer 2010-- License : see libraries/base/LICENSE---- Maintainer : cvs-ghc@haskell.org-- Stability : internal-- Portability : non-portable (GHC Extensions)---- Utilities for conversion between Double/Float and Rational-------------------------------------------------------------------------------
#include "MachDeps.h"
moduleGHC.Float.ConversionUtils(elimZerosInteger ,elimZerosInt# )whereimportGHC.Base importGHC.Num.Integer default()
#if WORD_SIZE_IN_BITS < 64

#define TO64 integerToInt64#
-- Double mantissae have 53 bits, too much for Int#elim64#::Int64#->Int#->(#Integer,Int##)elim64#ne=casezeroCount(int64ToInt#n)oft|isTrue#(e<=#t)->(#integerFromInt64#(uncheckedIShiftRA64#ne),0##)|isTrue#(t<#8#)->(#integerFromInt64#(uncheckedIShiftRA64#nt),e-#t#)|otherwise->elim64#(uncheckedIShiftRA64#n8#)(e-#8#)
#else

#define TO64 integerToInt#
-- Double mantissae fit it Int#elim64# ::Int# ->Int# ->(#Integer ,Int# #)elim64# :: Int# -> Int# -> (# Integer, Int# #)
elim64# =Int# -> Int# -> (# Integer, Int# #)
elimZerosInt# 
#endif
{-# INLINEelimZerosInteger #-}elimZerosInteger ::Integer ->Int# ->(#Integer ,Int# #)elimZerosInteger :: Integer -> Int# -> (# Integer, Int# #)
elimZerosInteger Integer
m Int#
e =Int# -> Int# -> (# Integer, Int# #)
elim64# (TO64m)eelimZerosInt# ::Int# ->Int# ->(#Integer ,Int# #)elimZerosInt# :: Int# -> Int# -> (# Integer, Int# #)
elimZerosInt# Int#
n Int#
e =caseInt# -> Int#
zeroCount Int#
n ofInt#
t |Int# -> Bool
isTrue# (Int#
e Int# -> Int# -> Int#
<=# Int#
t )->(#Int# -> Integer
IS (Int# -> Int# -> Int#
uncheckedIShiftRA# Int#
n Int#
e ),Int#
0##)|Int# -> Bool
isTrue# (Int#
t Int# -> Int# -> Int#
<# Int#
8#)->(#Int# -> Integer
IS (Int# -> Int# -> Int#
uncheckedIShiftRA# Int#
n Int#
t ),Int#
e Int# -> Int# -> Int#
-# Int#
t #)|Bool
otherwise ->Int# -> Int# -> (# Integer, Int# #)
elimZerosInt# (Int# -> Int# -> Int#
uncheckedIShiftRA# Int#
n Int#
8#)(Int#
e Int# -> Int# -> Int#
-# Int#
8#)-- | Number of trailing zero bits in a bytezeroCount ::Int# ->Int# zeroCount :: Int# -> Int#
zeroCount Int#
i =Int8# -> Int#
int8ToInt# (Addr# -> Int# -> Int8#
indexInt8OffAddr# Addr#
arr (Word# -> Int#
word2Int# (Word# -> Word#
narrow8Word# (Int# -> Word#
int2Word# Int#
i ))))-- index must be in [0,255]wherearr :: Addr#
arr =Addr#
"8円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円5円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円6円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円5円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円7円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円5円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円6円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円5円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円4円0円1円0円2円0円1円0円3円0円1円0円2円0円1円0円"#

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