Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Enabled a = Maybe a
- packEnabled :: (Rep a, sig ~ Signal clk) => sig Bool -> sig a -> sig (Enabled a)
- unpackEnabled :: (Rep a, sig ~ Signal clk) => sig (Enabled a) -> (sig Bool, sig a)
- enabledVal :: (Rep a, sig ~ Signal clk) => sig (Enabled a) -> sig a
- isEnabled :: (Rep a, sig ~ Signal clk) => sig (Enabled a) -> sig Bool
- mapEnabled :: (Rep a, Rep b, sig ~ Signal clk) => (forall clk'. Signal clk' a -> Signal clk' b) -> sig (Enabled a) -> sig (Enabled b)
- enabledS :: (Rep a, sig ~ Signal clk) => sig a -> sig (Enabled a)
- disabledS :: (Rep a, sig ~ Signal clk) => sig (Enabled a)
- registerEnabled :: (Rep a, Clock clk, sig ~ Signal clk) => a -> sig (Enabled a) -> sig a
- type Pipe a d = Enabled (a, d)
- type Memory clk a d = Signal clk a -> Signal clk d
- writeMemory :: forall a d clk1 sig. (Clock clk1, sig ~ Signal clk1, Size a, Rep a, Rep d) => sig (Pipe a d) -> sig (a -> d)
- syncRead :: forall a d sig clk. (Clock clk, sig ~ Signal clk, Size a, Rep a, Rep d) => sig (a -> d) -> sig a -> sig d
- asyncRead :: forall a d sig clk. (Clock clk, sig ~ Signal clk, Size a, Rep a, Rep d) => sig (a -> d) -> sig a -> sig d
- memoryToMatrix :: (Integral a, Size a, Rep a, Rep d, Clock clk, sig ~ Signal clk) => sig (a -> d) -> sig (Matrix a d)
- enabledToPipe :: (Rep x, Rep y, Rep z, sig ~ Signal clk) => (forall j. Signal j x -> Signal j (y, z)) -> sig (Enabled x) -> sig (Pipe y z)
- rom :: (Rep a, Rep b, Clock clk) => Signal clk a -> (a -> Maybe b) -> Signal clk b
- toAckBox :: (Rep a, Clock c, sig ~ Signal c) => Patch [Maybe a] (sig (Enabled a)) () (sig Ack)
- toAckBox' :: (Rep a, Clock c, sig ~ Signal c) => [Int] -> Patch [Maybe a] (sig (Enabled a)) () (sig Ack)
- fromAckBox :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) [Maybe a] (sig Ack) ()
- fromAckBox' :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => [Int] -> Patch (sig (Enabled a)) [Maybe a] (sig Ack) ()
- enabledToAckBox :: (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) () (sig Ack)
- ackBoxToEnabled :: (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) ()
- shallowAckBoxBridge :: forall sig c a. (Rep a, Clock c, sig ~ Signal c, Show a) => ([Int], [Int]) -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack)
- probeAckBoxP :: forall sig a c. (Rep a, Clock c, sig ~ Signal c) => String -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack)
- runAckBoxP :: forall sig c a b. (c ~ CLK, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled a)) (sig (Enabled b)) (sig Ack) (sig Ack) -> [a] -> [b]
- sinkAckP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) () (sig Ack) ()
- alwaysAckP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => a -> Patch () (sig (Enabled a)) () (sig Ack)
- neverAckP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch () (sig (Enabled a)) () (sig Ack)
- toReadyBox :: (Rep a, Clock c, sig ~ Signal c) => Patch [Maybe a] (sig (Enabled a)) () (sig Ready)
- toReadyBox' :: (Rep a, Clock c, sig ~ Signal c) => [Int] -> Patch [Maybe a] (sig (Enabled a)) () (sig Ready)
- fromReadyBox :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) [Maybe a] (sig Ready) ()
- fromReadyBox' :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => [Int] -> Patch (sig (Enabled a)) [Maybe a] (sig Ready) ()
- shallowReadyBoxBridge :: forall sig c a. (Rep a, Clock c, sig ~ Signal c, Show a) => ([Int], [Int]) -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ready) (sig Ready)
- probeReadyBoxP :: forall sig a c. (Rep a, Clock c, sig ~ Signal c) => String -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ready) (sig Ready)
- runReadyBoxP :: forall sig c a b. (c ~ CLK, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled a)) (sig (Enabled b)) (sig Ready) (sig Ready) -> [a] -> [b]
- sinkReadyP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) () (sig Ready) ()
- alwaysReadyP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => a -> Patch () (sig (Enabled a)) () (sig Ready)
- neverReadyP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch () (sig (Enabled a)) () (sig Ready)
- newtype Ack = Ack {}
- toAck :: (sig ~ Signal clk) => sig Bool -> sig Ack
- fromAck :: (sig ~ Signal clk) => sig Ack -> sig Bool
- newtype Ready = Ready {}
- toReady :: (sig ~ Signal clk) => sig Bool -> sig Ready
- fromReady :: (sig ~ Signal clk) => sig Ready -> sig Bool
- type Patch lhs_in rhs_out lhs_out rhs_in = (lhs_in, rhs_in) -> (lhs_out, rhs_out)
- outputP :: a -> Patch () a () ()
- runP :: (Unit u1, Unit u2) => Patch u1 a u2 () -> a
- execP :: Patch a b c d -> (a, d) -> (c, b)
- emptyP :: Patch a a b b
- fstP :: Patch a b c e -> Patch (a :> f) (b :> f) (c :> g) (e :> g)
- sndP :: Patch a b c d -> Patch (f :> a) (f :> b) (g :> c) (g :> d)
- forwardP :: (li -> ro) -> Patch li ro b b
- backwardP :: (ri -> lo) -> Patch a a lo ri
- stackP :: Patch li1 ro1 lo1 ri1 -> Patch li2 ro2 lo2 ri2 -> Patch (li1 :> li2) (ro1 :> ro2) (lo1 :> lo2) (ri1 :> ri2)
- matrixStackP :: (m ~ Matrix x, Size x) => m (Patch li ro lo ri) -> Patch (m li) (m ro) (m lo) (m ri)
- loopP :: Patch (a :> b) (a :> c) (d :> e) (d :> f) -> Patch b c e f
- openP :: Patch c (() :> c) d (() :> d)
- mapP :: forall a b c sig ack. (Rep a, Rep b, Clock c, sig ~ Signal c) => (forall clk'. Signal clk' a -> Signal clk' b) -> Patch (sig (Enabled a)) (sig (Enabled b)) ack ack
- class Unit unit where
- unit :: unit
- unUnit :: Unit unit => unit -> ()
- rawReadP :: FilePath -> IO (Patch () [Maybe U8] () ())
- readP :: Read a => FilePath -> IO (Patch () [Maybe a] () ())
- rawWriteP :: (Unit u1, Unit u2) => FilePath -> Int -> Patch u1 [Maybe U8] u2 () -> IO ()
- writeP :: (Show a, Unit u1, Unit u2) => FilePath -> Int -> Patch u1 [Maybe a] u2 () -> IO ()
- ($$) :: Patch li1 o lo1 i -> Patch o ro2 i ri2 -> Patch li1 ro2 lo1 ri2
- readyToAckBridge :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ready) (sig Ack)
- ackToReadyBridge :: (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ready)
- dupP :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled a)) (sig (Enabled a) :> sig (Enabled a)) (sig Ack) (sig Ack :> sig Ack)
- matrixDupP :: (Clock c, sig ~ Signal c, Rep a, Size x) => Patch (sig (Enabled a)) (Matrix x (sig (Enabled a))) (sig Ack) (Matrix x (sig Ack))
- unzipP :: (Clock c, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled (a, b))) (sig (Enabled a) :> sig (Enabled b)) (sig Ack) (sig Ack :> sig Ack)
- matrixUnzipP :: (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (sig (Enabled (Matrix x a))) (Matrix x (sig (Enabled a))) (sig Ack) (Matrix x (sig Ack))
- deMuxP :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled Bool) :> sig (Enabled a)) (sig (Enabled a) :> sig (Enabled a)) (sig Ack :> sig Ack) (sig Ack :> sig Ack)
- matrixDeMuxP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (sig (Enabled x) :> sig (Enabled a)) (Matrix x (sig (Enabled a))) (sig Ack :> sig Ack) (Matrix x (sig Ack))
- zipP :: (Clock c, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled a) :> sig (Enabled b)) (sig (Enabled (a, b))) (sig Ack :> sig Ack) (sig Ack)
- matrixZipP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (Matrix x (sig (Enabled a))) (sig (Enabled (Matrix x a))) (Matrix x (sig Ack)) (sig Ack)
- muxP :: (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled Bool) :> (sig (Enabled a) :> sig (Enabled a))) (sig (Enabled a)) (sig Ack :> (sig Ack :> sig Ack)) (sig Ack)
- matrixMuxP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (sig (Enabled x) :> Matrix x (sig (Enabled a))) (sig (Enabled a)) (sig Ack :> Matrix x (sig Ack)) (sig Ack)
- fifo1 :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack)
- fifo2 :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack)
- matrixToElementsP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x, Num x, Enum x) => Patch (sig (Enabled (Matrix x a))) (sig (Enabled a)) (sig Ack) (sig Ack)
- matrixFromElementsP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x, Num x, Enum x) => Patch (sig (Enabled a)) (sig (Enabled (Matrix x a))) (sig Ack) (sig Ack)
- globalClockP :: (clk ~ CLK, sig ~ Signal clk) => Patch (sig a) (sig a) (sig b) (sig b)
- cycleP :: forall a c ix sig. (Size ix, Rep a, Rep ix, Num ix, Clock c, sig ~ Signal c) => Matrix ix a -> Patch () (sig (Enabled a)) () (sig Ack)
- constP :: forall a c ix sig. (Size ix, Rep a, Rep ix, Num ix, Clock c, sig ~ Signal c) => Matrix ix a -> Patch () (sig (Enabled a)) () (sig Ack)
- prependP :: forall a c ix sig. (Size ix, Rep a, Rep ix, Num ix, Clock c, sig ~ Signal c) => Matrix ix a -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack)
- data MergePlan
- mergeP :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => MergePlan -> Patch (sig (Enabled a) :> sig (Enabled a)) (sig (Enabled a)) (sig Ack :> sig Ack) (sig Ack)
- matrixMergeP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x, Num x, Enum x) => MergePlan -> Patch (Matrix x (sig (Enabled a))) (sig (Enabled a)) (Matrix x (sig Ack)) (sig Ack)
- type FabricPatch fab lhs_in rhs_out lhs_out rhs_in = (lhs_in, rhs_in) -> fab (lhs_out, rhs_out)
- patchF :: MonadFix fab => Patch a b c d -> FabricPatch fab a b c d
- (|$|) :: MonadFix fab => FabricPatch fab a b d e -> FabricPatch fab b c e f -> FabricPatch fab a c d f
- runF :: MonadFix fab => FabricPatch fab () a () () -> fab a
- buildF :: MonadFix fab => ((a, d) -> fab (c, b)) -> FabricPatch fab a b c d
- emptyF :: MonadFix fab => FabricPatch fab a a b b
- stackF :: MonadFix fab => FabricPatch fab li1 ro1 lo1 ri1 -> FabricPatch fab li2 ro2 lo2 ri2 -> FabricPatch fab (li1 :> li2) (ro1 :> ro2) (lo1 :> lo2) (ri1 :> ri2)
Documentation
packEnabled :: (Rep a, sig ~ Signal clk) => sig Bool -> sig a -> sig (Enabled a) Source
Combine a boolean control signal and an data signal into an enabled signal.
unpackEnabled :: (Rep a, sig ~ Signal clk) => sig (Enabled a) -> (sig Bool, sig a) Source
Break the representation of an Enabled signal into a Bool signal (for whether the value is valid) and a signal for the data.
enabledVal :: (Rep a, sig ~ Signal clk) => sig (Enabled a) -> sig a Source
Drop the Enabled control from the signal. The output signal will be Rep unknown if the input signal is not enabled.
isEnabled :: (Rep a, sig ~ Signal clk) => sig (Enabled a) -> sig Bool Source
Determine if the the circuit is enabled.
mapEnabled :: (Rep a, Rep b, sig ~ Signal clk) => (forall clk'. Signal clk' a -> Signal clk' b) -> sig (Enabled a) -> sig (Enabled b) Source
This is lifting *Comb* because Comb is stateless, and the en
Bool being
passed on assumes no history, in the 'a -> b' function.
enabledS :: (Rep a, sig ~ Signal clk) => sig a -> sig (Enabled a) Source
Lift a data signal to be an Enabled signal, that's always enabled.
disabledS :: (Rep a, sig ~ Signal clk) => sig (Enabled a) Source
Create a signal that's never enabled.
registerEnabled :: (Rep a, Clock clk, sig ~ Signal clk) => a -> sig (Enabled a) -> sig a Source
Optionally updatable register, based on the value of the enabled signal.
type Memory clk a d = Signal clk a -> Signal clk d Source
A Memory takes in a sequence of addresses, and returns a sequence of data at that address.
writeMemory :: forall a d clk1 sig. (Clock clk1, sig ~ Signal clk1, Size a, Rep a, Rep d) => sig (Pipe a d) -> sig (a -> d) Source
Write the input pipe to memory, return a circuit that does reads.
syncRead :: forall a d sig clk. (Clock clk, sig ~ Signal clk, Size a, Rep a, Rep d) => sig (a -> d) -> sig a -> sig d Source
Read a series of addresses. Respects the latency of Xilinx BRAMs.
asyncRead :: forall a d sig clk. (Clock clk, sig ~ Signal clk, Size a, Rep a, Rep d) => sig (a -> d) -> sig a -> sig d Source
Read a series of addresses.
memoryToMatrix :: (Integral a, Size a, Rep a, Rep d, Clock clk, sig ~ Signal clk) => sig (a -> d) -> sig (Matrix a d) Source
memoryToMatrix should be used with caution/simulation only, because this actually clones the memory to allow this to work, generating lots of LUTs and BRAMS.
enabledToPipe :: (Rep x, Rep y, Rep z, sig ~ Signal clk) => (forall j. Signal j x -> Signal j (y, z)) -> sig (Enabled x) -> sig (Pipe y z) Source
Apply a function to the Enabled input signal producing a Pipe.
rom :: (Rep a, Rep b, Clock clk) => Signal clk a -> (a -> Maybe b) -> Signal clk b Source
Generate a read-only memory.
toAckBox :: (Rep a, Clock c, sig ~ Signal c) => Patch [Maybe a] (sig (Enabled a)) () (sig Ack) Source
Take a list of shallow values and create a stream which can be sent into a FIFO, respecting the write-ready flag that comes out of the FIFO.
:: (Rep a, Clock c, sig ~ Signal c) | |
=> [Int] | list wait states after every succesful post |
-> Patch [Maybe a] (sig (Enabled a)) () (sig Ack) |
An AckBox producer that will go through a series of wait states after each time it drives the data output.
fromAckBox :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) [Maybe a] (sig Ack) () Source
Take stream from a FIFO and return an asynchronous read-ready flag, which is given back to the FIFO, and a shallow list of values. I'm sure this space-leaks.
fromAckBox' :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => [Int] -> Patch (sig (Enabled a)) [Maybe a] (sig Ack) () Source
An ackBox that goes through a series of intermediate states each time consumes a value from the input stream and then issues an Ack.
enabledToAckBox :: (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) () (sig Ack) Source
enableToAckBox
turns an Enabled signal into a (1-sided) Patch.
ackBoxToEnabled :: (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) () Source
ackBoxToEnabled
turns the AckBox protocol into the Enabled protocol.
The assumptions is the circuit on the right is fast enough to handle the
streamed data.
shallowAckBoxBridge :: forall sig c a. (Rep a, Clock c, sig ~ Signal c, Show a) => ([Int], [Int]) -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack) Source
This introduces protocol-compliant delays (in the shallow embedding)
probeAckBoxP :: forall sig a c. (Rep a, Clock c, sig ~ Signal c) => String -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack) Source
probeAckBoxPatch
creates a patch with a named probe, probing the data and ack
signals in an Ack interface.
runAckBoxP :: forall sig c a b. (c ~ CLK, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled a)) (sig (Enabled b)) (sig Ack) (sig Ack) -> [a] -> [b] Source
sinkAckP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) () (sig Ack) () Source
A sink patch throws away its data input (generating a () data
output). sinkReadyP
uses an enabled/ack protocol.
alwaysAckP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => a -> Patch () (sig (Enabled a)) () (sig Ack) Source
A source patch takes no input and generates a stream of values. It
corresponds to a top-level input port. sourceReadyP
uses the enabled/ack
protocol.
neverAckP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch () (sig (Enabled a)) () (sig Ack) Source
stub, no data ever sent.
toReadyBox :: (Rep a, Clock c, sig ~ Signal c) => Patch [Maybe a] (sig (Enabled a)) () (sig Ready) Source
Take a list of shallow values and create a stream which can be sent into a FIFO, respecting the write-ready flag that comes out of the FIFO.
:: (Rep a, Clock c, sig ~ Signal c) | |
=> [Int] | list wait states after every succesful post |
-> Patch [Maybe a] (sig (Enabled a)) () (sig Ready) |
A readybox that goes through a sequence of intermediate states after issuing each enable, and before it looks for the next Ready.
fromReadyBox :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) [Maybe a] (sig Ready) () Source
Take stream from a FIFO and return an asynchronous read-ready flag, which is given back to the FIFO, and a shallow list of values. I'm sure this space-leaks.
fromReadyBox' :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => [Int] -> Patch (sig (Enabled a)) [Maybe a] (sig Ready) () Source
Like fromReadyBox, but which goes through a series of intermediate states after receiving an enable before issuing another Ready.
shallowReadyBoxBridge :: forall sig c a. (Rep a, Clock c, sig ~ Signal c, Show a) => ([Int], [Int]) -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ready) (sig Ready) Source
Introduces protocol-compliant delays (in the shallow embedding)
probeReadyBoxP :: forall sig a c. (Rep a, Clock c, sig ~ Signal c) => String -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ready) (sig Ready) Source
probeReadyBoxPatch
creates a patch with a named probe, probing the data and ready
signals in a Ready interface.
runReadyBoxP :: forall sig c a b. (c ~ CLK, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled a)) (sig (Enabled b)) (sig Ready) (sig Ready) -> [a] -> [b] Source
sinkReadyP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) () (sig Ready) () Source
A sink patch throws away its data input (generating a () data
output). sinkReadyP
uses an enabled/ready protocol.
alwaysReadyP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => a -> Patch () (sig (Enabled a)) () (sig Ready) Source
A source patch takes no input and generates a stream of values. It
corresponds to a top-level input port. alwaysReadyP
uses the
ready/enabled protocol.
neverReadyP :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch () (sig (Enabled a)) () (sig Ready) Source
stub, no data ever sent.
An Ack is always in response to an incoming packet or message.
An Ready is always in response to an incoming packet or message
toReady :: (sig ~ Signal clk) => sig Bool -> sig Ready Source
Convert a Bool signal to a Ready
signal.
fromReady :: (sig ~ Signal clk) => sig Ready -> sig Bool Source
Convert a Ready
signal to a Bool signal.
type Patch lhs_in rhs_out lhs_out rhs_in = (lhs_in, rhs_in) -> (lhs_out, rhs_out) Source
A Patch is a data signal with an associated control signal. The lhs_in
type parameter is the type of the data input, the rhs_out
type parameter is
the type of the data output. The rhs_in
is the type of the control input
(e.g. a ready
signal), and the lhs_out
is the type of the control output
(e.g. ack
).
outputP :: a -> Patch () a () () Source
outputP produces a constant data output. The control inputs/outputs are unit, so they contain no data.
fstP :: Patch a b c e -> Patch (a :> f) (b :> f) (c :> g) (e :> g) Source
Given a patch, add to the data and control inputs/outputs a second set of signals that are passed-through. The signals of the argument patch to fstP will appear as the first element of the pair in the resulting patch.
sndP :: Patch a b c d -> Patch (f :> a) (f :> b) (g :> c) (g :> d) Source
Given a patch, add to the data and control inputs/outputs a second set of signals that are passed-through. The signals of the argument patch to sndP will appear as the second element of the pair in the resulting patch.
forwardP :: (li -> ro) -> Patch li ro b b Source
Lift a function to a patch, applying the function to the data input.
backwardP :: (ri -> lo) -> Patch a a lo ri Source
Lift a function to a patch, applying the function to the control input.
stackP :: Patch li1 ro1 lo1 ri1 -> Patch li2 ro2 lo2 ri2 -> Patch (li1 :> li2) (ro1 :> ro2) (lo1 :> lo2) (ri1 :> ri2) infixr 3 Source
Given two patches, tuple their data/control inputs and outputs.
matrixStackP :: (m ~ Matrix x, Size x) => m (Patch li ro lo ri) -> Patch (m li) (m ro) (m lo) (m ri) Source
Given a homogeneous list (Matrix) of patches, combine them into a single patch, collecting the datacontrol inputsoutputs into matrices.
loopP :: Patch (a :> b) (a :> c) (d :> e) (d :> f) -> Patch b c e f Source
loopP is a fixpoint style combinator, for backedges.
mapP :: forall a b c sig ack. (Rep a, Rep b, Clock c, sig ~ Signal c) => (forall clk'. Signal clk' a -> Signal clk' b) -> Patch (sig (Enabled a)) (sig (Enabled b)) ack ack Source
An instance of the Unit type contains a value that carries no information.
rawReadP :: FilePath -> IO (Patch () [Maybe U8] () ()) Source
rawReadP
reads a binary file into Patch, which will become the
lefthand side of a chain of patches.
readP :: Read a => FilePath -> IO (Patch () [Maybe a] () ()) Source
readPatch
reads an encoded file into Patch, which will become the
lefthand side of a chain of patches.
rawWriteP :: (Unit u1, Unit u2) => FilePath -> Int -> Patch u1 [Maybe U8] u2 () -> IO () Source
rawWriteP
runs a complete circuit for the given
number of cycles, writing the result to a given file in binary format.
writeP :: (Show a, Unit u1, Unit u2) => FilePath -> Int -> Patch u1 [Maybe a] u2 () -> IO () Source
writeP
runs a complete circuit for the given
number of cycles, writing the result to a given file in string format.
($$) :: Patch li1 o lo1 i -> Patch o ro2 i ri2 -> Patch li1 ro2 lo1 ri2 infixr 5 Source
($$) composes two patches serially, sharing a common control protocol. The data output of the first patch is fed to the data input of the second patch. The control output of the second patch is fed to the control input of the first patch, and the control output of the first patch is fed to the control input of the second patch.
readyToAckBridge :: forall a c sig. (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ready) (sig Ack) Source
readyToAckBridge
converts from a ready interface to an ACK interface
by preemptively giving the ready signal, and holding the resulting data
from the device on the input side if no ACK is received by the device on
the output side. If data is currently being held, then the ready signal
will not be given. This bridge is fine for deep embedding (can be
represented in hardware).
ackToReadyBridge :: (Rep a, Clock c, sig ~ Signal c) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ready) Source
ackToReadyBridge
converts from a Ack interface to an Ready interface
by ANDing the ready signal from the receiving component with the input
enable from the sending component. This may not be necessary at times
if the sending component ignores ACKs when no data is sent. This bridge
is fine for deep embedding (can be represented in hardware).
dupP :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled a)) (sig (Enabled a) :> sig (Enabled a)) (sig Ack) (sig Ack :> sig Ack) Source
This duplicates the incomming datum. This has the behavior that neither branch sees the value until both can recieve it.
matrixDupP :: (Clock c, sig ~ Signal c, Rep a, Size x) => Patch (sig (Enabled a)) (Matrix x (sig (Enabled a))) (sig Ack) (Matrix x (sig Ack)) Source
This duplicate the incoming datam over many handshaken streams.
unzipP :: (Clock c, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled (a, b))) (sig (Enabled a) :> sig (Enabled b)) (sig Ack) (sig Ack :> sig Ack) Source
unzipP creates a patch that takes in an Enabled data pair, and produces a pair of Enabled data outputs.
matrixUnzipP :: (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (sig (Enabled (Matrix x a))) (Matrix x (sig (Enabled a))) (sig Ack) (Matrix x (sig Ack)) Source
matrixUnzipP is the generalization of unzipP to homogeneous matrices.
deMuxP :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled Bool) :> sig (Enabled a)) (sig (Enabled a) :> sig (Enabled a)) (sig Ack :> sig Ack) (sig Ack :> sig Ack) Source
TODO: Andy write docs for this.
matrixDeMuxP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (sig (Enabled x) :> sig (Enabled a)) (Matrix x (sig (Enabled a))) (sig Ack :> sig Ack) (Matrix x (sig Ack)) Source
matrixDeMuxP is the generalization of deMuxP to a matrix of signals.
zipP :: (Clock c, sig ~ Signal c, Rep a, Rep b) => Patch (sig (Enabled a) :> sig (Enabled b)) (sig (Enabled (a, b))) (sig Ack :> sig Ack) (sig Ack) Source
Combine two enabled data inputs into a single Enabled tupled data input.
matrixZipP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (Matrix x (sig (Enabled a))) (sig (Enabled (Matrix x a))) (Matrix x (sig Ack)) (sig Ack) Source
Extension of zipP to homogeneous matrices.
muxP :: (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled Bool) :> (sig (Enabled a) :> sig (Enabled a))) (sig (Enabled a)) (sig Ack :> (sig Ack :> sig Ack)) (sig Ack) Source
muxP
chooses a the 2nd or 3rd value, based on the Boolean value.
matrixMuxP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x) => Patch (sig (Enabled x) :> Matrix x (sig (Enabled a))) (sig (Enabled a)) (sig Ack :> Matrix x (sig Ack)) (sig Ack) Source
matrixMuxP
chooses the n-th value, based on the index value.
fifo1 :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack) Source
FIFO with depth 1.
fifo2 :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack) Source
FIFO with depth 2.
matrixToElementsP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x, Num x, Enum x) => Patch (sig (Enabled (Matrix x a))) (sig (Enabled a)) (sig Ack) (sig Ack) Source
matrixToElementsP
turns a matrix into a sequences of elements from the array, in ascending order.
matrixFromElementsP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x, Num x, Enum x) => Patch (sig (Enabled a)) (sig (Enabled (Matrix x a))) (sig Ack) (sig Ack) Source
matrixFromElementsP
turns a sequence of elements (in ascending order) into a matrix.
ascending order.
globalClockP :: (clk ~ CLK, sig ~ Signal clk) => Patch (sig a) (sig a) (sig b) (sig b) Source
globalClockP forces the handshaking to use the CLK clock. Which is useful for testing.
cycleP :: forall a c ix sig. (Size ix, Rep a, Rep ix, Num ix, Clock c, sig ~ Signal c) => Matrix ix a -> Patch () (sig (Enabled a)) () (sig Ack) Source
cycleP cycles through a constant list (actually a matrix) of values. Generates an async ROM on hardware.
constP :: forall a c ix sig. (Size ix, Rep a, Rep ix, Num ix, Clock c, sig ~ Signal c) => Matrix ix a -> Patch () (sig (Enabled a)) () (sig Ack) Source
prependP :: forall a c ix sig. (Size ix, Rep a, Rep ix, Num ix, Clock c, sig ~ Signal c) => Matrix ix a -> Patch (sig (Enabled a)) (sig (Enabled a)) (sig Ack) (sig Ack) Source
PriorityMerge | The first element always has priority |
RoundRobinMerge | Turn about, can be slower |
mergeP :: forall c sig a. (Clock c, sig ~ Signal c, Rep a) => MergePlan -> Patch (sig (Enabled a) :> sig (Enabled a)) (sig (Enabled a)) (sig Ack :> sig Ack) (sig Ack) Source
matrixMergeP :: forall c sig a x. (Clock c, sig ~ Signal c, Rep a, Rep x, Size x, Num x, Enum x) => MergePlan -> Patch (Matrix x (sig (Enabled a))) (sig (Enabled a)) (Matrix x (sig Ack)) (sig Ack) Source
type FabricPatch fab lhs_in rhs_out lhs_out rhs_in = (lhs_in, rhs_in) -> fab (lhs_out, rhs_out) Source
patchF :: MonadFix fab => Patch a b c d -> FabricPatch fab a b c d Source
(|$|) :: MonadFix fab => FabricPatch fab a b d e -> FabricPatch fab b c e f -> FabricPatch fab a c d f infixr 4 Source
runF :: MonadFix fab => FabricPatch fab () a () () -> fab a Source
buildF :: MonadFix fab => ((a, d) -> fab (c, b)) -> FabricPatch fab a b c d Source
emptyF :: MonadFix fab => FabricPatch fab a a b b Source
A fabric patch that passes through data and control.
stackF :: MonadFix fab => FabricPatch fab li1 ro1 lo1 ri1 -> FabricPatch fab li2 ro2 lo2 ri2 -> FabricPatch fab (li1 :> li2) (ro1 :> ro2) (lo1 :> lo2) (ri1 :> ri2) infixr 3 Source
Given two fabric patches, tuple their data/control inputs and outputs.