hw-bits-0.7.1.3: Bit manipulation

Safe HaskellNone
LanguageHaskell2010

HaskellWorks.Data.Bits.Broadword

Description

Deprecated: Import the relevant module instead

Synopsis

Documentation

newtype Broadword a Source #

Constructors

Broadword a 
Instances
Functor Broadword Source # 
Instance details

Defined in HaskellWorks.Data.Bits.Broadword.Type

Methods

fmap :: (a -> b) -> Broadword a -> Broadword b #

(<$) :: a -> Broadword b -> Broadword a #

Eq a => Eq (Broadword a) Source # 
Instance details

Defined in HaskellWorks.Data.Bits.Broadword.Type

Methods

(==) :: Broadword a -> Broadword a -> Bool #

(/=) :: Broadword a -> Broadword a -> Bool #

Show a => Show (Broadword a) Source # 
Instance details

Defined in HaskellWorks.Data.Bits.Broadword.Type

Generic (Broadword a) Source # 
Instance details

Defined in HaskellWorks.Data.Bits.Broadword.Type

Associated Types

type Rep (Broadword a) :: Type -> Type #

Methods

from :: Broadword a -> Rep (Broadword a) x #

to :: Rep (Broadword a) x -> Broadword a #

NFData a => NFData (Broadword a) Source # 
Instance details

Defined in HaskellWorks.Data.Bits.Broadword.Type

Methods

rnf :: Broadword a -> () #

type Rep (Broadword a) Source # 
Instance details

Defined in HaskellWorks.Data.Bits.Broadword.Type

type Rep (Broadword a) = D1 (MetaData "Broadword" "HaskellWorks.Data.Bits.Broadword.Type" "hw-bits-0.7.1.3-1qy24AWUzBZLY1Ahglf6L0" True) (C1 (MetaCons "Broadword" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

lsb :: Word64 -> Word64 Source #

Returns the position of the least significant bit (0-based).

This is equivalent to countTrailingZeros except for when there are no bits set. In which case return a word with all bits set.

>>> lsb 8
3
>>> lsb 1
0
>>> lsb 0
18446744073709551615

h :: Int -> Word64 Source #

Initialise all sub-words of size k where k ∈ { 2, 4, 8, 16, 32, 64 } such that the highest bit is set to 1 and all other bits are cleared.

>>> import Numeric(showHex)
>>> showHex (h 2) ""
"aaaaaaaaaaaaaaaa"
>>> showHex (h 4) ""
"8888888888888888"
>>> showHex (h 8) ""
"8080808080808080"
>>> showHex (h 16) ""
"8000800080008000"
>>> showHex (h 32) ""
"8000000080000000"
>>> showHex (h 64) ""
"8000000000000000"

l :: Int -> Word64 Source #

Initialise all sub-words of size k where k ∈ { 2, 4, 8, 16, 32, 64 } such that the lowest bit is set to 1 and all other bits are cleared.

>>> import Numeric(showHex)
>>> showHex (l 2) ""
"5555555555555555"
>>> showHex (l 4) ""
"1111111111111111"
>>> showHex (l 8) ""
"101010101010101"
>>> showHex (l 16) ""
"1000100010001"
>>> showHex (l 32) ""
"100000001"
>>> showHex (l 64) ""
"1"

kBitDiff :: Int -> Word64 -> Word64 -> Word64 Source #

Broadword subtraction of sub-words of size k where k ∈ { 2, 4, 8, 16, 32, 64 }.

The subtraction respects 2's complement so sub-words may be regarded as signed or unsigned words.

>>> import Numeric(showHex)
>>> showHex (kBitDiff 8 0x0807060504030201 0x0404030302020101) ""
"403030202010100"
>>> showHex (kBitDiff 8 0x0807060504030201 0x0102030405060708) ""
"7050301fffdfbf9"
>>> showHex (kBitDiff 8 0x20000000000000ff 0x10000000000000ff) ""
"1000000000000000"

kBitDiffPos :: Int -> Word64 -> Word64 -> Word64 Source #

Broadword subtraction of sub-words of size k where k ∈ { 2, 4, 8, 16, 32, 64 } where results are bounded from below by 0.

>>> import Numeric(showHex)
>>> showHex (kBitDiffPos 8 0x0807060504030201 0x0404030302020101) ""
"403030202010100"
>>> showHex (kBitDiffPos 8 0x0807060504030201 0x0102030405060708) ""
"705030100000000"
>>> showHex (kBitDiffPos 8 0x20000000000000ff 0x10000000000000ff) ""
"1000000000000000"

kBitDiffUnsafe :: Int -> Word64 -> Word64 -> Word64 Source #

Broadword subtraction of sub-words of size k where k ∈ { 2, 4, 8, 16, 32, 64 } where all the sub-words of x and y must not have the signed bit set for the result to be meaningful.

>>> import Numeric(showHex)
>>> showHex (kBitDiffUnsafe 8 0x0807060504030201 0x0404030302020101) ""
"403030202010100"
>>> showHex (kBitDiffUnsafe 8 0x0807060504030201 0x0102030405060708) ""
"7050301fffdfbf9"
>>> showHex (kBitDiffUnsafe 8 0x20000000000000ff 0x10000000000000ff) "" -- produces nonsense in the last sub-word
"1000000000000080"