ersatz-0.4.8: A monad for expressing SAT or QSAT problems using observable sharing.

Copyright© Edward Kmett 2010-2015 © Eric Mertens 2014 Johan Kiviniemi 2013
LicenseBSD3
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Ersatz.Bits

Contents

Description

Bits is an arbitrary length natural number type

Synopsis

Fixed length bit vectors

newtype Bit1 Source #

A container of 1 Bit that encodes from and decodes to Word8

Constructors

Bit1 Bit 
Instances
Num Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(+) :: Bit1 -> Bit1 -> Bit1 #

(-) :: Bit1 -> Bit1 -> Bit1 #

(*) :: Bit1 -> Bit1 -> Bit1 #

negate :: Bit1 -> Bit1 #

abs :: Bit1 -> Bit1 #

signum :: Bit1 -> Bit1 #

fromInteger :: Integer -> Bit1 #

Show Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit1 -> ShowS #

show :: Bit1 -> String #

showList :: [Bit1] -> ShowS #

Generic Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit1 :: Type -> Type #

Methods

from :: Bit1 -> Rep Bit1 x #

to :: Rep Bit1 x -> Bit1 #

Codec Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit1 :: Type Source #

Variable Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit1 Source #

Boolean Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit1 Source #

true :: Bit1 Source #

false :: Bit1 Source #

(&&) :: Bit1 -> Bit1 -> Bit1 Source #

(||) :: Bit1 -> Bit1 -> Bit1 Source #

(==>) :: Bit1 -> Bit1 -> Bit1 Source #

not :: Bit1 -> Bit1 Source #

and :: Foldable t => t Bit1 -> Bit1 Source #

or :: Foldable t => t Bit1 -> Bit1 Source #

nand :: Foldable t => t Bit1 -> Bit1 Source #

nor :: Foldable t => t Bit1 -> Bit1 Source #

all :: Foldable t => (a -> Bit1) -> t a -> Bit1 Source #

any :: Foldable t => (a -> Bit1) -> t a -> Bit1 Source #

xor :: Bit1 -> Bit1 -> Bit1 Source #

choose :: Bit1 -> Bit1 -> Bit1 -> Bit1 Source #

Equatable Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit1 -> Bit1 -> Bit Source #

(/==) :: Bit1 -> Bit1 -> Bit Source #

Orderable Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit1 -> Bit1 -> Bit Source #

(<=?) :: Bit1 -> Bit1 -> Bit Source #

(>=?) :: Bit1 -> Bit1 -> Bit Source #

(>?) :: Bit1 -> Bit1 -> Bit Source #

HasBits Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit1 -> Bits Source #

type Rep Bit1 Source # 
Instance details

Defined in Ersatz.Bits

type Rep Bit1 = D1 (MetaData "Bit1" "Ersatz.Bits" "ersatz-0.4.8-GlfLYtzX6pe2io7UkNZ7WA" True) (C1 (MetaCons "Bit1" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bit)))
type Decoded Bit1 Source # 
Instance details

Defined in Ersatz.Bits

data Bit2 Source #

A container of 2 Bits that encodes from and decodes to Word8

Constructors

Bit2 !Bit !Bit 
Instances
Num Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(+) :: Bit2 -> Bit2 -> Bit2 #

(-) :: Bit2 -> Bit2 -> Bit2 #

(*) :: Bit2 -> Bit2 -> Bit2 #

negate :: Bit2 -> Bit2 #

abs :: Bit2 -> Bit2 #

signum :: Bit2 -> Bit2 #

fromInteger :: Integer -> Bit2 #

Show Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit2 -> ShowS #

show :: Bit2 -> String #

showList :: [Bit2] -> ShowS #

Generic Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit2 :: Type -> Type #

Methods

from :: Bit2 -> Rep Bit2 x #

to :: Rep Bit2 x -> Bit2 #

Codec Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit2 :: Type Source #

Variable Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit2 Source #

Boolean Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit2 Source #

true :: Bit2 Source #

false :: Bit2 Source #

(&&) :: Bit2 -> Bit2 -> Bit2 Source #

(||) :: Bit2 -> Bit2 -> Bit2 Source #

(==>) :: Bit2 -> Bit2 -> Bit2 Source #

not :: Bit2 -> Bit2 Source #

and :: Foldable t => t Bit2 -> Bit2 Source #

or :: Foldable t => t Bit2 -> Bit2 Source #

nand :: Foldable t => t Bit2 -> Bit2 Source #

nor :: Foldable t => t Bit2 -> Bit2 Source #

all :: Foldable t => (a -> Bit2) -> t a -> Bit2 Source #

any :: Foldable t => (a -> Bit2) -> t a -> Bit2 Source #

xor :: Bit2 -> Bit2 -> Bit2 Source #

choose :: Bit2 -> Bit2 -> Bit2 -> Bit2 Source #

Equatable Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit2 -> Bit2 -> Bit Source #

(/==) :: Bit2 -> Bit2 -> Bit Source #

Orderable Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit2 -> Bit2 -> Bit Source #

(<=?) :: Bit2 -> Bit2 -> Bit Source #

(>=?) :: Bit2 -> Bit2 -> Bit Source #

(>?) :: Bit2 -> Bit2 -> Bit Source #

HasBits Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit2 -> Bits Source #

type Rep Bit2 Source # 
Instance details

Defined in Ersatz.Bits

type Decoded Bit2 Source # 
Instance details

Defined in Ersatz.Bits

data Bit3 Source #

A container of 3 Bits that encodes from and decodes to Word8

Constructors

Bit3 !Bit !Bit !Bit 
Instances
Show Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit3 -> ShowS #

show :: Bit3 -> String #

showList :: [Bit3] -> ShowS #

Generic Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit3 :: Type -> Type #

Methods

from :: Bit3 -> Rep Bit3 x #

to :: Rep Bit3 x -> Bit3 #

Codec Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit3 :: Type Source #

Variable Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit3 Source #

Boolean Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit3 Source #

true :: Bit3 Source #

false :: Bit3 Source #

(&&) :: Bit3 -> Bit3 -> Bit3 Source #

(||) :: Bit3 -> Bit3 -> Bit3 Source #

(==>) :: Bit3 -> Bit3 -> Bit3 Source #

not :: Bit3 -> Bit3 Source #

and :: Foldable t => t Bit3 -> Bit3 Source #

or :: Foldable t => t Bit3 -> Bit3 Source #

nand :: Foldable t => t Bit3 -> Bit3 Source #

nor :: Foldable t => t Bit3 -> Bit3 Source #

all :: Foldable t => (a -> Bit3) -> t a -> Bit3 Source #

any :: Foldable t => (a -> Bit3) -> t a -> Bit3 Source #

xor :: Bit3 -> Bit3 -> Bit3 Source #

choose :: Bit3 -> Bit3 -> Bit3 -> Bit3 Source #

Equatable Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit3 -> Bit3 -> Bit Source #

(/==) :: Bit3 -> Bit3 -> Bit Source #

Orderable Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit3 -> Bit3 -> Bit Source #

(<=?) :: Bit3 -> Bit3 -> Bit Source #

(>=?) :: Bit3 -> Bit3 -> Bit Source #

(>?) :: Bit3 -> Bit3 -> Bit Source #

HasBits Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit3 -> Bits Source #

type Rep Bit3 Source # 
Instance details

Defined in Ersatz.Bits

type Decoded Bit3 Source # 
Instance details

Defined in Ersatz.Bits

data Bit4 Source #

A container of 4 Bits that encodes from and decodes to Word8

Constructors

Bit4 !Bit !Bit !Bit !Bit 
Instances
Show Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit4 -> ShowS #

show :: Bit4 -> String #

showList :: [Bit4] -> ShowS #

Generic Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit4 :: Type -> Type #

Methods

from :: Bit4 -> Rep Bit4 x #

to :: Rep Bit4 x -> Bit4 #

Codec Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit4 :: Type Source #

Variable Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit4 Source #

Boolean Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit4 Source #

true :: Bit4 Source #

false :: Bit4 Source #

(&&) :: Bit4 -> Bit4 -> Bit4 Source #

(||) :: Bit4 -> Bit4 -> Bit4 Source #

(==>) :: Bit4 -> Bit4 -> Bit4 Source #

not :: Bit4 -> Bit4 Source #

and :: Foldable t => t Bit4 -> Bit4 Source #

or :: Foldable t => t Bit4 -> Bit4 Source #

nand :: Foldable t => t Bit4 -> Bit4 Source #

nor :: Foldable t => t Bit4 -> Bit4 Source #

all :: Foldable t => (a -> Bit4) -> t a -> Bit4 Source #

any :: Foldable t => (a -> Bit4) -> t a -> Bit4 Source #

xor :: Bit4 -> Bit4 -> Bit4 Source #

choose :: Bit4 -> Bit4 -> Bit4 -> Bit4 Source #

Equatable Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit4 -> Bit4 -> Bit Source #

(/==) :: Bit4 -> Bit4 -> Bit Source #

Orderable Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit4 -> Bit4 -> Bit Source #

(<=?) :: Bit4 -> Bit4 -> Bit Source #

(>=?) :: Bit4 -> Bit4 -> Bit Source #

(>?) :: Bit4 -> Bit4 -> Bit Source #

HasBits Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit4 -> Bits Source #

type Rep Bit4 Source # 
Instance details

Defined in Ersatz.Bits

type Decoded Bit4 Source # 
Instance details

Defined in Ersatz.Bits

data Bit5 Source #

A container of 5 Bits that encodes from and decodes to Word8

Constructors

Bit5 !Bit !Bit !Bit !Bit !Bit 
Instances
Show Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit5 -> ShowS #

show :: Bit5 -> String #

showList :: [Bit5] -> ShowS #

Generic Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit5 :: Type -> Type #

Methods

from :: Bit5 -> Rep Bit5 x #

to :: Rep Bit5 x -> Bit5 #

Codec Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit5 :: Type Source #

Variable Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit5 Source #

Boolean Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit5 Source #

true :: Bit5 Source #

false :: Bit5 Source #

(&&) :: Bit5 -> Bit5 -> Bit5 Source #

(||) :: Bit5 -> Bit5 -> Bit5 Source #

(==>) :: Bit5 -> Bit5 -> Bit5 Source #

not :: Bit5 -> Bit5 Source #

and :: Foldable t => t Bit5 -> Bit5 Source #

or :: Foldable t => t Bit5 -> Bit5 Source #

nand :: Foldable t => t Bit5 -> Bit5 Source #

nor :: Foldable t => t Bit5 -> Bit5 Source #

all :: Foldable t => (a -> Bit5) -> t a -> Bit5 Source #

any :: Foldable t => (a -> Bit5) -> t a -> Bit5 Source #

xor :: Bit5 -> Bit5 -> Bit5 Source #

choose :: Bit5 -> Bit5 -> Bit5 -> Bit5 Source #

Equatable Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit5 -> Bit5 -> Bit Source #

(/==) :: Bit5 -> Bit5 -> Bit Source #

Orderable Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit5 -> Bit5 -> Bit Source #

(<=?) :: Bit5 -> Bit5 -> Bit Source #

(>=?) :: Bit5 -> Bit5 -> Bit Source #

(>?) :: Bit5 -> Bit5 -> Bit Source #

HasBits Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit5 -> Bits Source #

type Rep Bit5 Source # 
Instance details

Defined in Ersatz.Bits

type Decoded Bit5 Source # 
Instance details

Defined in Ersatz.Bits

data Bit6 Source #

A container of 6 Bits that encodes from and decodes to Word8

Constructors

Bit6 !Bit !Bit !Bit !Bit !Bit !Bit 
Instances
Show Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit6 -> ShowS #

show :: Bit6 -> String #

showList :: [Bit6] -> ShowS #

Generic Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit6 :: Type -> Type #

Methods

from :: Bit6 -> Rep Bit6 x #

to :: Rep Bit6 x -> Bit6 #

Codec Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit6 :: Type Source #

Variable Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit6 Source #

Boolean Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit6 Source #

true :: Bit6 Source #

false :: Bit6 Source #

(&&) :: Bit6 -> Bit6 -> Bit6 Source #

(||) :: Bit6 -> Bit6 -> Bit6 Source #

(==>) :: Bit6 -> Bit6 -> Bit6 Source #

not :: Bit6 -> Bit6 Source #

and :: Foldable t => t Bit6 -> Bit6 Source #

or :: Foldable t => t Bit6 -> Bit6 Source #

nand :: Foldable t => t Bit6 -> Bit6 Source #

nor :: Foldable t => t Bit6 -> Bit6 Source #

all :: Foldable t => (a -> Bit6) -> t a -> Bit6 Source #

any :: Foldable t => (a -> Bit6) -> t a -> Bit6 Source #

xor :: Bit6 -> Bit6 -> Bit6 Source #

choose :: Bit6 -> Bit6 -> Bit6 -> Bit6 Source #

Equatable Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit6 -> Bit6 -> Bit Source #

(/==) :: Bit6 -> Bit6 -> Bit Source #

Orderable Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit6 -> Bit6 -> Bit Source #

(<=?) :: Bit6 -> Bit6 -> Bit Source #

(>=?) :: Bit6 -> Bit6 -> Bit Source #

(>?) :: Bit6 -> Bit6 -> Bit Source #

HasBits Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit6 -> Bits Source #

type Rep Bit6 Source # 
Instance details

Defined in Ersatz.Bits

type Decoded Bit6 Source # 
Instance details

Defined in Ersatz.Bits

data Bit7 Source #

A container of 7 Bits that encodes from and decodes to Word8

Constructors

Bit7 !Bit !Bit !Bit !Bit !Bit !Bit !Bit 
Instances
Show Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit7 -> ShowS #

show :: Bit7 -> String #

showList :: [Bit7] -> ShowS #

Generic Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit7 :: Type -> Type #

Methods

from :: Bit7 -> Rep Bit7 x #

to :: Rep Bit7 x -> Bit7 #

Codec Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit7 :: Type Source #

Variable Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit7 Source #

Boolean Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit7 Source #

true :: Bit7 Source #

false :: Bit7 Source #

(&&) :: Bit7 -> Bit7 -> Bit7 Source #

(||) :: Bit7 -> Bit7 -> Bit7 Source #

(==>) :: Bit7 -> Bit7 -> Bit7 Source #

not :: Bit7 -> Bit7 Source #

and :: Foldable t => t Bit7 -> Bit7 Source #

or :: Foldable t => t Bit7 -> Bit7 Source #

nand :: Foldable t => t Bit7 -> Bit7 Source #

nor :: Foldable t => t Bit7 -> Bit7 Source #

all :: Foldable t => (a -> Bit7) -> t a -> Bit7 Source #

any :: Foldable t => (a -> Bit7) -> t a -> Bit7 Source #

xor :: Bit7 -> Bit7 -> Bit7 Source #

choose :: Bit7 -> Bit7 -> Bit7 -> Bit7 Source #

Equatable Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit7 -> Bit7 -> Bit Source #

(/==) :: Bit7 -> Bit7 -> Bit Source #

Orderable Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit7 -> Bit7 -> Bit Source #

(<=?) :: Bit7 -> Bit7 -> Bit Source #

(>=?) :: Bit7 -> Bit7 -> Bit Source #

(>?) :: Bit7 -> Bit7 -> Bit Source #

HasBits Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit7 -> Bits Source #

type Rep Bit7 Source # 
Instance details

Defined in Ersatz.Bits

type Decoded Bit7 Source # 
Instance details

Defined in Ersatz.Bits

data Bit8 Source #

A container of 8 Bits that encodes from and decodes to Word8

Constructors

Bit8 !Bit !Bit !Bit !Bit !Bit !Bit !Bit !Bit 
Instances
Show Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bit8 -> ShowS #

show :: Bit8 -> String #

showList :: [Bit8] -> ShowS #

Generic Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Rep Bit8 :: Type -> Type #

Methods

from :: Bit8 -> Rep Bit8 x #

to :: Rep Bit8 x -> Bit8 #

Codec Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bit8 :: Type Source #

Variable Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

literally :: MonadSAT s m => m Literal -> m Bit8 Source #

Boolean Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bool :: Bool -> Bit8 Source #

true :: Bit8 Source #

false :: Bit8 Source #

(&&) :: Bit8 -> Bit8 -> Bit8 Source #

(||) :: Bit8 -> Bit8 -> Bit8 Source #

(==>) :: Bit8 -> Bit8 -> Bit8 Source #

not :: Bit8 -> Bit8 Source #

and :: Foldable t => t Bit8 -> Bit8 Source #

or :: Foldable t => t Bit8 -> Bit8 Source #

nand :: Foldable t => t Bit8 -> Bit8 Source #

nor :: Foldable t => t Bit8 -> Bit8 Source #

all :: Foldable t => (a -> Bit8) -> t a -> Bit8 Source #

any :: Foldable t => (a -> Bit8) -> t a -> Bit8 Source #

xor :: Bit8 -> Bit8 -> Bit8 Source #

choose :: Bit8 -> Bit8 -> Bit8 -> Bit8 Source #

Equatable Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bit8 -> Bit8 -> Bit Source #

(/==) :: Bit8 -> Bit8 -> Bit Source #

Orderable Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bit8 -> Bit8 -> Bit Source #

(<=?) :: Bit8 -> Bit8 -> Bit Source #

(>=?) :: Bit8 -> Bit8 -> Bit Source #

(>?) :: Bit8 -> Bit8 -> Bit Source #

HasBits Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit8 -> Bits Source #

type Rep Bit8 Source # 
Instance details

Defined in Ersatz.Bits

type Decoded Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Variable length bit vectors

newtype Bits Source #

Constructors

Bits [Bit] 
Instances
Num Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

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

(-) :: Bits -> Bits -> Bits #

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

negate :: Bits -> Bits #

abs :: Bits -> Bits #

signum :: Bits -> Bits #

fromInteger :: Integer -> Bits #

Show Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

showsPrec :: Int -> Bits -> ShowS #

show :: Bits -> String #

showList :: [Bits] -> ShowS #

Codec Bits Source # 
Instance details

Defined in Ersatz.Bits

Associated Types

type Decoded Bits :: Type Source #

Equatable Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

(===) :: Bits -> Bits -> Bit Source #

(/==) :: Bits -> Bits -> Bit Source #

Orderable Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

(<?) :: Bits -> Bits -> Bit Source #

(<=?) :: Bits -> Bits -> Bit Source #

(>=?) :: Bits -> Bits -> Bit Source #

(>?) :: Bits -> Bits -> Bit Source #

HasBits Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bits -> Bits Source #

type Decoded Bits Source # 
Instance details

Defined in Ersatz.Bits

class HasBits a where Source #

HasBits provides the bits method for embedding fixed with numeric encoding types into the arbitrary width Bits type.

Methods

bits :: a -> Bits Source #

Instances
HasBits Bit Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit -> Bits Source #

HasBits Bits Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bits -> Bits Source #

HasBits Bit8 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit8 -> Bits Source #

HasBits Bit7 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit7 -> Bits Source #

HasBits Bit6 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit6 -> Bits Source #

HasBits Bit5 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit5 -> Bits Source #

HasBits Bit4 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit4 -> Bits Source #

HasBits Bit3 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit3 -> Bits Source #

HasBits Bit2 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit2 -> Bits Source #

HasBits Bit1 Source # 
Instance details

Defined in Ersatz.Bits

Methods

bits :: Bit1 -> Bits Source #

isEven :: HasBits b => b -> Bit Source #

Predicate for even-valued Bitss.

isOdd :: HasBits b => b -> Bit Source #

Predicate for odd-valued Bitss.

sumBit :: Foldable t => t Bit -> Bits Source #

Optimization of sumBits enabled when summing individual Bits.

sumBits :: (Foldable t, HasBits a) => t a -> Bits Source #

Compute the sum of a source of Bits values.

Adders

fullAdder Source #

Arguments

:: Bit 
-> Bit 
-> Bit 
-> (Bit, Bit)

(sum, carry)

Compute the sum and carry bit from adding three bits.

halfAdder Source #

Arguments

:: Bit 
-> Bit 
-> (Bit, Bit)

(sum, carry)

Compute the sum and carry bit from adding two bits.