basement-0.0.10: Foundation scrap box of array & string

LicenseBSD-style
MaintainerHaskell Foundation
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Basement.Bits

Description

 
Synopsis

Documentation

class BitOps bits where Source #

operation over bits

Minimal complete definition

(.&.), (.|.), (.^.), (.<<.), (.>>.)

Methods

(.&.) :: bits -> bits -> bits infixl 7 Source #

(.|.) :: bits -> bits -> bits infixl 5 Source #

(.^.) :: bits -> bits -> bits infixl 6 Source #

(.<<.) :: bits -> CountOf Bool -> bits infixl 8 Source #

(.>>.) :: bits -> CountOf Bool -> bits infixl 8 Source #

bit :: Offset Bool -> bits Source #

construct a bit set with the bit at the given index set.

bit :: Integral bits => Offset Bool -> bits Source #

construct a bit set with the bit at the given index set.

isBitSet :: bits -> Offset Bool -> Bool Source #

test the bit at the given index is set

isBitSet :: (Integral bits, Eq bits) => bits -> Offset Bool -> Bool Source #

test the bit at the given index is set

setBit :: bits -> Offset Bool -> bits Source #

set the bit at the given index

setBit :: Integral bits => bits -> Offset Bool -> bits Source #

set the bit at the given index

clearBit :: bits -> Offset Bool -> bits Source #

clear the bit at the given index

clearBit :: FiniteBitsOps bits => bits -> Offset Bool -> bits Source #

clear the bit at the given index

Instances
BitOps Bool Source # 
Instance details

Defined in Basement.Bits

BitOps Int8 Source # 
Instance details

Defined in Basement.Bits

BitOps Int16 Source # 
Instance details

Defined in Basement.Bits

BitOps Int32 Source # 
Instance details

Defined in Basement.Bits

BitOps Int64 Source # 
Instance details

Defined in Basement.Bits

BitOps Word Source # 
Instance details

Defined in Basement.Bits

BitOps Word8 Source # 
Instance details

Defined in Basement.Bits

BitOps Word16 Source # 
Instance details

Defined in Basement.Bits

BitOps Word32 Source # 
Instance details

Defined in Basement.Bits

BitOps Word64 Source # 
Instance details

Defined in Basement.Bits

BitOps Word128 Source # 
Instance details

Defined in Basement.Bits

BitOps Word256 Source # 
Instance details

Defined in Basement.Bits

SizeValid n => BitOps (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

(.&.) :: Bits n -> Bits n -> Bits n Source #

(.|.) :: Bits n -> Bits n -> Bits n Source #

(.^.) :: Bits n -> Bits n -> Bits n Source #

(.<<.) :: Bits n -> CountOf Bool -> Bits n Source #

(.>>.) :: Bits n -> CountOf Bool -> Bits n Source #

bit :: Offset Bool -> Bits n Source #

isBitSet :: Bits n -> Offset Bool -> Bool Source #

setBit :: Bits n -> Offset Bool -> Bits n Source #

clearBit :: Bits n -> Offset Bool -> Bits n Source #

class FiniteBitsOps bits where Source #

operation over finite bits

Minimal complete definition

numberOfBits, rotateL, rotateR, popCount, bitFlip

Methods

numberOfBits :: bits -> CountOf Bool Source #

get the number of bits in the given object

rotateL :: bits -> CountOf Bool -> bits infixl 8 Source #

rotate the given bit set.

rotateR :: bits -> CountOf Bool -> bits infixl 8 Source #

rotate the given bit set.

popCount :: bits -> CountOf Bool Source #

count of number of bit set to 1 in the given bit set.

bitFlip :: bits -> bits Source #

reverse all bits in the argument

countLeadingZeros :: bits -> CountOf Bool Source #

count of the number of leading zeros

countLeadingZeros :: BitOps bits => bits -> CountOf Bool Source #

count of the number of leading zeros

countTrailingZeros :: bits -> CountOf Bool Source #

count of the number of trailing zeros

countTrailingZeros :: BitOps bits => bits -> CountOf Bool Source #

count of the number of trailing zeros

Instances
FiniteBitsOps Bool Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int8 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int16 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int32 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Int64 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Word Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Word8 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Word16 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Word32 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Word64 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Word128 Source # 
Instance details

Defined in Basement.Bits

FiniteBitsOps Word256 Source # 
Instance details

Defined in Basement.Bits

(SizeValid n, NatWithinBound (CountOf Bool) n) => FiniteBitsOps (Bits n) Source # 
Instance details

Defined in Basement.Bits

data Bits (n :: Nat) Source #

Bool set of n bits.

Instances
SizeValid n => Bounded (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

minBound :: Bits n #

maxBound :: Bits n #

SizeValid n => Enum (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

succ :: Bits n -> Bits n #

pred :: Bits n -> Bits n #

toEnum :: Int -> Bits n #

fromEnum :: Bits n -> Int #

enumFrom :: Bits n -> [Bits n] #

enumFromThen :: Bits n -> Bits n -> [Bits n] #

enumFromTo :: Bits n -> Bits n -> [Bits n] #

enumFromThenTo :: Bits n -> Bits n -> Bits n -> [Bits n] #

Eq (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

(==) :: Bits n -> Bits n -> Bool #

(/=) :: Bits n -> Bits n -> Bool #

Ord (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

compare :: Bits n -> Bits n -> Ordering #

(<) :: Bits n -> Bits n -> Bool #

(<=) :: Bits n -> Bits n -> Bool #

(>) :: Bits n -> Bits n -> Bool #

(>=) :: Bits n -> Bits n -> Bool #

max :: Bits n -> Bits n -> Bits n #

min :: Bits n -> Bits n -> Bits n #

Show (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

showsPrec :: Int -> Bits n -> ShowS #

show :: Bits n -> String #

showList :: [Bits n] -> ShowS #

SizeValid n => Subtractive (Bits n) Source # 
Instance details

Defined in Basement.Bits

Associated Types

type Difference (Bits n) :: Type Source #

Methods

(-) :: Bits n -> Bits n -> Difference (Bits n) Source #

SizeValid n => Additive (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

azero :: Bits n Source #

(+) :: Bits n -> Bits n -> Bits n Source #

scale :: IsNatural n0 => n0 -> Bits n -> Bits n Source #

SizeValid n => IDivisible (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

div :: Bits n -> Bits n -> Bits n Source #

mod :: Bits n -> Bits n -> Bits n Source #

divMod :: Bits n -> Bits n -> (Bits n, Bits n) Source #

SizeValid n => Multiplicative (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

midentity :: Bits n Source #

(*) :: Bits n -> Bits n -> Bits n Source #

(^) :: (IsNatural n0, Enum n0, IDivisible n0) => Bits n -> n0 -> Bits n Source #

SizeValid n => BitOps (Bits n) Source # 
Instance details

Defined in Basement.Bits

Methods

(.&.) :: Bits n -> Bits n -> Bits n Source #

(.|.) :: Bits n -> Bits n -> Bits n Source #

(.^.) :: Bits n -> Bits n -> Bits n Source #

(.<<.) :: Bits n -> CountOf Bool -> Bits n Source #

(.>>.) :: Bits n -> CountOf Bool -> Bits n Source #

bit :: Offset Bool -> Bits n Source #

isBitSet :: Bits n -> Offset Bool -> Bool Source #

setBit :: Bits n -> Offset Bool -> Bits n Source #

clearBit :: Bits n -> Offset Bool -> Bits n Source #

(SizeValid n, NatWithinBound (CountOf Bool) n) => FiniteBitsOps (Bits n) Source # 
Instance details

Defined in Basement.Bits

type Difference (Bits n) Source # 
Instance details

Defined in Basement.Bits

type Difference (Bits n) = Bits n

toBits :: SizeValid n => Natural -> Bits n Source #

convert the given Natural into a Bits of size n

if bits that are not within the boundaries of the 'Bits n' will be truncated.

allOne :: forall n. SizeValid n => Bits n Source #

construct a Bits with all bits set.

this function is equivalet to maxBound