clash-prelude-1.5.0: Clash: a functional hardware description language - Prelude library
Safe HaskellNone
LanguageHaskell2010

Clash.Class.Counter.Internal

Synopsis

Documentation

>>> import Clash.Class.Counter
>>> import Clash.Sized.BitVector (BitVector)
>>> import Clash.Sized.Index (Index)
>>> import Clash.Sized.Signed (Signed)
>>> import Clash.Sized.Unsigned (Unsigned)

class Counter a where Source #

Counter is a class that composes multiple counters into a single one. It is similar to odometers found in olds cars, once all counters reach their maximum they reset to zero - i.e. odometer rollover. See countSucc and countPred for API usage examples.

Example use case: when driving a monitor through VGA you would like to keep track at least two counters: one counting a horizontal position, and one vertical. Perhaps a fancy VGA driver would also like to keep track of the number of drawn frames. To do so, the three counters are setup with different types. On each round of the horizontal counter the vertical counter should be increased. On each round of the vertical counter the frame counter should be increased. With this class you could simply use the type:

(FrameCount, VerticalCount, HorizontalCount)

and have countSucc work as described.

N.B.: This class exposes four functions countMin, countMax, countSuccOverflow, and countPredOverflow. These functions are considered an internal API. Users are encouraged to use countSucc and countPred.

Minimal complete definition

Nothing

Methods

countMin :: a Source #

Value counter wraps around to on a countSuccOverflow overflow

default countMin :: Bounded a => a Source #

countMax :: a Source #

Value counter wraps around to on a countPredOverflow overflow

default countMax :: Bounded a => a Source #

countSuccOverflow :: a -> (Bool, a) Source #

Gets the successor of a. If it overflows, the left part of the tuple will be set to True.

default countSuccOverflow :: (Eq a, Enum a, Bounded a) => a -> (Bool, a) Source #

countPredOverflow :: a -> (Bool, a) Source #

Gets the predecessor of a. If it overflows, the left part of the tuple will be set to True.

default countPredOverflow :: (Eq a, Enum a, Bounded a) => a -> (Bool, a) Source #

Instances

Instances details
KnownNat n => Counter (BitVector n) Source # 
Instance details

Defined in Clash.Class.Counter.Internal

(1 <= n, KnownNat n) => Counter (Index n) Source # 
Instance details

Defined in Clash.Class.Counter.Internal

KnownNat n => Counter (Unsigned n) Source # 
Instance details

Defined in Clash.Class.Counter.Internal

KnownNat n => Counter (Signed n) Source # 
Instance details

Defined in Clash.Class.Counter.Internal

(Counter a, Counter b) => Counter (Either a b) Source #

Counter instance that flip-flops between Left and Right. Examples:

>>> type T = Either (Index 2) (Unsigned 2)
>>> countSucc @T (Left 0)
Left 1
>>> countSucc @T (Left 1)
Right 0
>>> countSucc @T (Right 0)
Right 1
Instance details

Defined in Clash.Class.Counter.Internal

(Counter a0, Counter a1) => Counter (a0, a1) Source #

Counters on tuples increment from right-to-left. This makes sense from the perspective of LSB/MSB; MSB is on the left-hand-side and LSB is on the right-hand-side in other Clash types.

>>> type T = (Unsigned 2, Index 2, Index 2)
>>> countSucc @T (0, 0, 0)
(0,0,1)
>>> countSucc @T (0, 0, 1)
(0,1,0)
>>> countSucc @T (0, 1, 0)
(0,1,1)
>>> countSucc @T (0, 1, 1)
(1,0,0)

N.B.: The documentation only shows the instances up to 3-tuples. By default, instances up to and including 12-tuples will exist. If the flag large-tuples is set instances up to the GHC imposed limit will exist. The GHC imposed limit is either 62 or 64 depending on the GHC version.

Instance details

Defined in Clash.Class.Counter.Internal

Methods

countMin :: (a0, a1) Source #

countMax :: (a0, a1) Source #

countSuccOverflow :: (a0, a1) -> (Bool, (a0, a1)) Source #

countPredOverflow :: (a0, a1) -> (Bool, (a0, a1)) Source #

(Counter a0, Counter a1, Counter a2) => Counter (a0, a1, a2) Source # 
Instance details

Defined in Clash.Class.Counter.Internal

Methods

countMin :: (a0, a1, a2) Source #

countMax :: (a0, a1, a2) Source #

countSuccOverflow :: (a0, a1, a2) -> (Bool, (a0, a1, a2)) Source #

countPredOverflow :: (a0, a1, a2) -> (Bool, (a0, a1, a2)) Source #