|
1 | 1 |
|
| 2 | +-- The plugin relies on Arrows and BlockArguments to be enabled. These |
| 3 | +-- dependencies will be dropped in the future. |
| 4 | +{-# LANGUAGE Arrows #-} |
| 5 | +{-# LANGUAGE BlockArguments #-} |
2 | 6 |
|
3 |
| -{-# LANGUAGE Arrows #-} |
4 |
| -{-# LANGUAGE BlockArguments #-} |
5 |
| -{-# LANGUAGE DeriveFunctor #-} |
6 |
| -{-# LANGUAGE ScopedTypeVariables #-} |
7 |
| -{-# LANGUAGE TypeFamilies #-} |
8 |
| -{-# LANGUAGE DataKinds #-} |
9 |
| - |
| 7 | +-- | This /must/ be enabled in order for the plugin to do its work. You might |
| 8 | +-- want to add this to 'ghc-options' in your cabal file. |
10 | 9 | {-# OPTIONS -fplugin=Protocols.Plugin #-}
|
11 | 10 |
|
12 | 11 | module Tests.Protocols.Plugin where
|
13 | 12 |
|
14 | 13 | import qualified Clash.Prelude as C
|
15 | 14 |
|
16 | 15 | import Protocols
|
17 |
| -import Protocols.Df.Simple (Dfs) |
18 | 16 | import qualified Protocols.Df.Simple as Dfs
|
19 | 17 |
|
| 18 | +-- | Simply swap two streams. Note that the 'circuit' is a magic keyword the |
| 19 | +-- 'Protocols.Plugin' looks for in order to do its work. |
20 | 20 | swapC :: Circuit (a, b) (b, a)
|
21 | 21 | swapC = circuit $ \(a, b) -> (b, a)
|
22 | 22 |
|
23 |
| -unvecC :: Circuit (C.Vec 2 a) (a, a) |
24 |
| -unvecC = circuit \[x,y] -> (x, y) |
25 | 23 |
|
| 24 | +-- | Put 'registerFwd' on both 'Dfs' input streams. |
26 | 25 | registerBoth ::
|
27 |
| - (C.NFDataX a, C.NFDataX b, C.KnownDomain dom, C.HiddenClockResetEnable dom) => |
| 26 | + (C.NFDataX a, C.NFDataX b, C.HiddenClockResetEnable dom) => |
28 | 27 | Circuit (Dfs dom a, Dfs dom b) (Dfs dom a, Dfs dom b)
|
29 | 28 | registerBoth = circuit $ \(a, b) -> do
|
| 29 | + -- We route /a/ to into a 'registerFwd'. Note that this takes care of routing |
| 30 | + -- both the /forward/ and /backward/ parts, even though it seems that it only |
| 31 | + -- handles the /forward/ part. |
30 | 32 | a' <- Dfs.registerFwd -< a
|
| 33 | + |
| 34 | + -- Similarly, we route /b/ to a register too |
31 | 35 | b' <- Dfs.registerFwd -< b
|
| 36 | + |
| 37 | + -- The final line of a circuit-do block needs to be an "assignment". Because |
| 38 | + -- we want to simply bundle two streams, we use 'idC' as our circuit of choice. |
32 | 39 | idC -< (a', b')
|
| 40 | + |
| 41 | + |
| 42 | +-- | Fanout a stream and interact with some of the result streams. |
| 43 | +fanOutThenRegisterMiddle :: |
| 44 | + C.HiddenClockResetEnable dom => |
| 45 | + Circuit (Dfs dom Int) (Dfs dom Int, Dfs dom Int, Dfs dom Int) |
| 46 | +fanOutThenRegisterMiddle = circuit $ \a -> do |
| 47 | + -- List notation can be used to specify a Vec. In this instance, fanout will |
| 48 | + -- infer that it needs to produce a 'Vec 3 Int'. |
| 49 | + [x, y, z] <- Dfs.fanout -< a |
| 50 | + |
| 51 | + -- Like in 'registerBoth', we can put a register on the forward part of 'y'. |
| 52 | + y' <- Dfs.registerFwd -< y |
| 53 | + |
| 54 | + -- We can use any Haskell notation between the arrows, as long as it results |
| 55 | + -- in a properly typed circuit. For example, we could map the function (+5) |
| 56 | + -- over the stream 'z'. |
| 57 | + z' <- Dfs.map (+5) -< z |
| 58 | + |
| 59 | + idC -< (x, y', z') |
| 60 | + |
| 61 | + |
| 62 | +-- | Forget the /left/ part of a tuple of 'Dfs' streams |
| 63 | +forgetLeft :: Circuit (Dfs dom a, Dfs dom b) (Dfs dom b) |
| 64 | +forgetLeft = circuit $ \(a, b) -> do |
| 65 | + -- We can use an underscore to indicate that we'd like to throw away any |
| 66 | + -- data from stream 'a'. For 'Dfs' like protocols, a constant acknowledgement |
| 67 | + -- will be driven on the /backwards/ part of the protocol. |
| 68 | + _a <- idC -< a |
| 69 | + |
| 70 | + idC -< b |
| 71 | + |
| 72 | + |
| 73 | +-- | Forget the /left/ part of a tuple of 'Dfs' streams. |
| 74 | +forgetLeft2 :: Circuit (Dfs dom a, Dfs dom b) (Dfs dom b) |
| 75 | +forgetLeft2 = |
| 76 | + -- If we know right from the start that'd we'd like to ignore an incoming |
| 77 | + -- stream, we can simply mark it with an underscore. |
| 78 | + circuit $ \(_a, b) -> b |
| 79 | + |
| 80 | + |
| 81 | +-- | Convert a 2-vector into a 2-tuple |
| 82 | +unvec :: Circuit (C.Vec 2 a) (a, a) |
| 83 | +unvec = |
| 84 | + -- We don't always need /do/ notation |
| 85 | + circuit \[x,y] -> (x, y) |
0 commit comments