{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash #-}
#endif
#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Trustworthy #-}
#endif
-----------------------------------------------------------------------------
-- |
-- Module      :  Data.BitUtil
-- Copyright   :  (c) Clark Gaebel 2012
--                (c) Johan Tibel 2012
-- License     :  BSD-style
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
-----------------------------------------------------------------------------

module Data.BitUtil
    ( highestBitMask
    ) where

-- On GHC, include MachDeps.h to get WORD_SIZE_IN_BITS macro.
#if defined(__GLASGOW_HASKELL__)
# include "MachDeps.h"
#endif

import Data.Bits ((.|.), xor)

#if __GLASGOW_HASKELL__
import GHC.Exts (Word(..), Int(..))
import GHC.Prim (uncheckedShiftRL#)
#else
import Data.Word (shiftL, shiftR)
#endif

-- The highestBitMask implementation is based on
-- http://graphics.stanford.edu/~seander/bithacks.html#RoundUpPowerOf2
-- which has been put in the public domain.

-- | Return a word where only the highest bit is set.
highestBitMask :: Word -> Word
highestBitMask :: Word -> Word
highestBitMask Word
x1 = let x2 :: Word
x2 = Word
x1 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
x1 Word -> Int -> Word
`shiftRL` Int
1
                        x3 :: Word
x3 = Word
x2 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
x2 Word -> Int -> Word
`shiftRL` Int
2
                        x4 :: Word
x4 = Word
x3 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
x3 Word -> Int -> Word
`shiftRL` Int
4
                        x5 :: Word
x5 = Word
x4 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
x4 Word -> Int -> Word
`shiftRL` Int
8
                        x6 :: Word
x6 = Word
x5 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
x5 Word -> Int -> Word
`shiftRL` Int
16
#if !(defined(__GLASGOW_HASKELL__) && WORD_SIZE_IN_BITS==32)
                        x7 :: Word
x7 = Word
x6 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
x6 Word -> Int -> Word
`shiftRL` Int
32
                     in Word
x7 Word -> Word -> Word
forall a. Bits a => a -> a -> a
`xor` (Word
x7 Word -> Int -> Word
`shiftRL` Int
1)
#else
                     in x6 `xor` (x6 `shiftRL` 1)
#endif
{-# INLINE highestBitMask #-}

-- Right and left logical shifts.
shiftRL :: Word -> Int -> Word
#if __GLASGOW_HASKELL__
{--------------------------------------------------------------------
  GHC: use unboxing to get @shiftRL@ inlined.
--------------------------------------------------------------------}
shiftRL :: Word -> Int -> Word
shiftRL (W# Word#
x) (I# Int#
i) = Word# -> Word
W# (Word# -> Int# -> Word#
uncheckedShiftRL# Word#
x Int#
i)
#else
shiftRL x i   = shiftR x i
#endif
{-# INLINE shiftRL #-}