{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
module Data.Unicode.Internal.Bits
(
lookupBit64
) where
import Data.Bits (finiteBitSize, popCount)
import GHC.Exts
(Addr#, Int(..), Word(..), indexWordOffAddr#, and#, andI#,
uncheckedIShiftRL#, uncheckedShiftL#)
lookupBit64 :: Addr# -> Int -> Bool
lookupBit64 addr# (I# index#) = W# (word## `and#` bitMask##) /= 0
where
!fbs@(I# fbs#) = finiteBitSize (0 :: Word) - 1
!(I# logFbs#) = case fbs of
31 -> 5
63 -> 6
_ -> popCount fbs
wordIndex# = index# `uncheckedIShiftRL#` logFbs#
word## = indexWordOffAddr# addr# wordIndex#
bitIndex# = index# `andI#` fbs#
bitMask## = 1## `uncheckedShiftL#` bitIndex#