clash-prelude-1.2.0: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2017 Google Inc.
2019 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Signal.BiSignal

Description

Wires are fundamentally bidirectional, and in traditional HDLs we can exploit this aspect by explicitly marking the endpoint, or port, of such a wire as inout, thereby making this port function as both a source and a drain for the signals flowing over the wire.

Clash has support for inout ports through the implementation of BiSignals. To cleanly map to functions (and thus support software simulation using Haskell), a BiSignal comes in two parts; the in part:

BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)

and the out part:

BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat)

Where:

  • The internal representation is a BitVector
  • n indicates the number of bits in the BitVector
  • dom is the clock- (and reset-) domain to which the memory elements manipulating these BiSignals belong.
  • Lastly, ds indicates the default behavior for the BiSignal if nothing is being written (pull-down, pull-up, or undefined).

BiSignalIn is used by Clash to generate the inout ports on a HDL level, while BiSignalOut is only used for simulation purposes and generally discarded by the compiler.

Example

The following describes a system where two circuits, in alternating fashion, read the current value from the bus, increment it, and write it on the next cycle.

-- | Alternatively read / increment+write
counter
  :: (Bool, Int)
  -- ^ Internal flip + previous read
  -> Int
  -- ^ Int from inout
  -> ((Bool, Int), Maybe Int)
counter (write, prevread) i = ((write', prevread'), output)
  where
    output    = if write then Just (succ prevread) else Nothing
    prevread' = if write then prevread else i
    write' = not write

-- | Write on odd cyles
f :: Clock System
  -> Reset System
  -> BiSignalIn  Floating System (BitSize Int)
  -> BiSignalOut Floating System (BitSize Int)
f clk rst s = writeToBiSignal s (mealy clk rst counter (False, 0) (readFromBiSignal s))

-- | Write on even cyles
g :: Clock System
  -> Reset System
  -> BiSignalIn  Floating System (BitSize Int)
  -> BiSignalOut Floating System (BitSize Int)
g clk rst s = writeToBiSignal s (mealy clk rst counter (True, 0) (readFromBiSignal s))


-- | Connect the f and g circuits to the same bus
topEntity
  :: Clock System
  -> Reset System
  -> Signal System Int
topEntity clk rst = readFromBiSignal bus'
  where
    bus  = mergeBiSignalOuts $ f clk rst bus' :> g clk rst bus' :> Nil
    bus' = veryUnsafeToBiSignalIn bus
Synopsis

Documentation

data BiSignalIn (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #

The in part of an inout port

data BiSignalOut (ds :: BiSignalDefault) (dom :: Domain) (n :: Nat) Source #

The out part of an inout port

Wraps (multiple) writing signals. The semantics are such that only one of the signals may write at a single time step.

Instances
Semigroup (BiSignalOut defaultState dom n) Source # 
Instance details

Defined in Clash.Signal.BiSignal

Methods

(<>) :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n #

sconcat :: NonEmpty (BiSignalOut defaultState dom n) -> BiSignalOut defaultState dom n #

stimes :: Integral b => b -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n #

Monoid (BiSignalOut defaultState dom n) Source #

Monoid instance to support concatenating

NB Not synthesizable

Instance details

Defined in Clash.Signal.BiSignal

Methods

mempty :: BiSignalOut defaultState dom n #

mappend :: BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n -> BiSignalOut defaultState dom n #

mconcat :: [BiSignalOut defaultState dom n] -> BiSignalOut defaultState dom n #

type HasDomain dom1 (BiSignalOut ds dom2 n) Source # 
Instance details

Defined in Clash.Signal.BiSignal

type HasDomain dom1 (BiSignalOut ds dom2 n) = DomEq dom1 dom2
type TryDomain t (BiSignalOut ds dom n) Source # 
Instance details

Defined in Clash.Signal.BiSignal

type TryDomain t (BiSignalOut ds dom n) = Found dom

data BiSignalDefault Source #

Used to specify the default behavior of a BiSignal, i.e. what value is read when no value is being written to it.

Constructors

PullUp

inout port behaves as if connected to a pull-up resistor

PullDown

inout port behaves as if connected to a pull-down resistor

Floating

inout port behaves as if is floating. Reading a floating BiSignal value in simulation will yield an errorX (undefined value).

mergeBiSignalOuts :: (HasCallStack, KnownNat n) => Vec n (BiSignalOut defaultState dom m) -> BiSignalOut defaultState dom m Source #

Combine several inout signals into one.

readFromBiSignal Source #

Arguments

:: (HasCallStack, BitPack a) 
=> BiSignalIn ds d (BitSize a)

A BiSignalIn with a number of bits needed to represent a

-> Signal d a 

Read the value from an inout port

writeToBiSignal Source #

Arguments

:: (HasCallStack, BitPack a) 
=> BiSignalIn ds d (BitSize a) 
-> Signal d (Maybe a)

Value to write

  • Just a writes an a value
  • Nothing puts the port in a high-impedance state
-> BiSignalOut ds d (BitSize a) 

Write to an inout port

veryUnsafeToBiSignalIn :: (HasCallStack, KnownNat n, Given (SBiSignalDefault ds)) => BiSignalOut ds d n -> BiSignalIn ds d n Source #

Converts the out part of a BiSignal to an 'in' part. In simulation it checks whether multiple components are writing and will error accordingly. Make sure this is only called ONCE for every BiSignal.