| Copyright | (C) 2015-2016 University of Twente 2017 Google Inc. 2021-2023 QBayLogic B.V. |
|---|---|
| License | BSD2 (see the file LICENSE) |
| Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
| Safe Haskell | Safe |
| Language | Haskell2010 |
| Extensions |
|
Clash.Annotations.TopEntity
Contents
Description
TopEntity annotations allow us to control hierarchy and naming aspects of the
Clash compiler. We have the Synthesize and TestBench annotation.
Synthesize annotation
The Synthesize annotation allows us to:
- Assign names to entities (VHDL) / modules ((System)Verilog), and their ports.
- Put generated HDL files of a logical (sub)entity in their own directory.
- Use cached versions of generated HDL, i.e., prevent recompilation of
(sub)entities that have not changed since the last run. Caching is based
on a
.manifestwhich is generated alongside the HDL; deleting this file means deleting the cache; changing this file will result in undefined behavior.
Functions with a Synthesize annotation must adhere to the following
restrictions:
- Although functions with a
Synthesizeannotation can of course depend on functions with anotherSynthesizeannotation, they must not be mutually recursive. - Functions with a
Synthesizeannotation must be completely monomorphic and first-order, and cannot have any non-representable arguments or result.
Also take the following into account when using Synthesize annotations.
- The Clash compiler is based on the GHC Haskell compiler, and the GHC
machinery does not understand
Synthesizeannotations and it might subsequently decide to inline those functions. You should therefor also add a{-# NOINLINE f #-}pragma to the functions which you give aSynthesizefunctions. - Functions with a
Synthesizeannotation will not be specialized on constants.
Finally, the root module, the module which you pass as an argument to the Clash compiler must either have:
- A function with a
Synthesizeannotation. - A function called topEntity.
You apply Synthesize annotations to functions using an ANN pragma:
{-# ANN f (Synthesize {t_name = ..., ... }) #-}
f x = ...
For example, given the following specification:
module Blinker where import Clash.Prelude import Clash.Intel.ClockGen -- Define a synthesis domain with a clock with a period of 20000 /ps/. Signal -- coming from the reset button is low when pressed, and high when not pressed.createDomainvSystem{vName="DomInput", vPeriod=20000, vResetPolarity=ActiveLow} -- Define a synthesis domain with a clock with a period of 50000 /ps/.createDomainvSystem{vName="Dom50", vPeriod=50000} topEntity :: Clock DomInput -> Reset DomInput -> Enable Dom50 -> Signal Dom50 Bit -> Signal Dom50 (BitVector 8) topEntity clk20 rstBtn enaBtn modeBtn =exposeClockResetEnable(mealyblinkerT initialStateBlinkerT .isRising1) clk50 rst50 enaBtn modeBtn where -- Start with the first LED turned on, in rotate mode, with the counter on zero initialStateBlinkerT = (1, False, 0) -- Instantiate a PLL: this stabilizes the incoming clock signal and releases -- the reset output when the signal is stable. We're also using it to -- transform an incoming clock signal running at 20 MHz to a clock signal -- running at 50 MHz. Since the signature of topEntity already specifies the -- Dom50 domain, we don't need any type signatures to specify the domain here. (clk50, rst50) =altpllSyncclk20 rstBtn blinkerT :: (BitVector 8, Bool, Index 16650001) -> Bool -> ((BitVector 8, Bool, Index 16650001), BitVector 8) blinkerT (leds,mode,cntr) key1R = ((leds',mode',cntr'),leds) where -- clock frequency = 50e6 (50 MHz) -- led update rate = 333e-3 (every 333ms) cnt_max = 16650000 -- 50e6 * 333e-3 cntr' | cntr == cnt_max = 0 | otherwise = cntr + 1 mode' | key1R = not mode | otherwise = mode leds' | cntr == 0 = if mode then complement leds else rotateL leds 1 | otherwise = leds
The Clash compiler would normally generate the following
topEntity.vhdl file:
-- Automatically generated VHDL-93
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.NUMERIC_STD.ALL;
use IEEE.MATH_REAL.ALL;
use std.textio.all;
use work.all;
use work.Blinker_topEntity_types.all;
entity topEntity is
port(-- clock
clk20 : in Blinker_topEntity_types.clk_DomInput;
-- reset
rstBtn : in Blinker_topEntity_types.rst_DomInput;
-- enable
enaBtn : in Blinker_topEntity_types.en_Dom50;
modeBtn : in std_logic;
result : out std_logic_vector(7 downto 0));
end;
architecture structural of topEntity is
...
end;However, if we add the following Synthesize annotation in the file:
{-# ANN topEntity
(Synthesize
{ t_name = "blinker"
, t_inputs = [ PortName "CLOCK_50"
, PortName "KEY0"
, PortName "KEY1"
, PortName "KEY2" ]
, t_output = PortName "LED"
}) #-}
The Clash compiler will generate the following blinker.vhdl file instead:
-- Automatically generated VHDL-93
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.NUMERIC_STD.ALL;
use IEEE.MATH_REAL.ALL;
use std.textio.all;
use work.all;
use work.blinker_types.all;
entity blinker is
port(-- clock
CLOCK_50 : in blinker_types.clk_DomInput;
-- reset
KEY0 : in blinker_types.rst_DomInput;
-- enable
KEY1 : in blinker_types.en_Dom50;
KEY2 : in std_logic;
LED : out std_logic_vector(7 downto 0));
end;
architecture structural of blinker is
...
end;Where we now have:
- A top-level component that is called
blinker. - Inputs and outputs that have a user-chosen name:
CLOCK_50,KEY0,KEY1,KEY2,LED, etc.
See the documentation of Synthesize for the meaning of all its fields.
TestBench annotation
Tell what binder is the test bench for a Synthesize-annotated binder.
entityBeingTested :: ...
entityBeingTested = ...
{-# NOINLINE entityBeingTested #-}
{-# ANN entityBeingTested (defSyn "entityBeingTested") #-}
myTestBench :: Signal System Bool
myTestBench = ... entityBeingTested ...
{-# NOINLINE myTestBench #-}
{-# ANN myTestBench (TestBench 'entityBeingTested) #-}
The TestBench annotation actually already implies a Synthesize annotation on
the device under test, so the defSyn in the example could have been omitted.
We recommend you supply defSyn explicitly nonetheless. In any case, it will
still need the NOINLINE annotation.
Data types
TopEntity annotation
Constructors
| Synthesize | Instruct the Clash compiler to use this top-level function as a separately synthesizable component. |
Fields
| |
| TestBench Name | Tell what binder is the {-# NOINLINE myTestBench #-}
{-# ANN myTestBench (TestBench 'entityBeingTested) #-}
|
Instances
| Data TopEntity Source # | |
Defined in Clash.Annotations.TopEntity Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TopEntity -> c TopEntity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TopEntity # toConstr :: TopEntity -> Constr # dataTypeOf :: TopEntity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TopEntity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopEntity) # gmapT :: (forall b. Data b => b -> b) -> TopEntity -> TopEntity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TopEntity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TopEntity -> r # gmapQ :: (forall d. Data d => d -> u) -> TopEntity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TopEntity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TopEntity -> m TopEntity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TopEntity -> m TopEntity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TopEntity -> m TopEntity # | |
| Generic TopEntity Source # | |
| Show TopEntity Source # | |
| Eq TopEntity Source # | |
| Lift TopEntity Source # | |
| type Rep TopEntity Source # | |
Defined in Clash.Annotations.TopEntity type Rep TopEntity = D1 ('MetaData "TopEntity" "Clash.Annotations.TopEntity" "clash-prelude-1.9.0-inplace" 'False) (C1 ('MetaCons "Synthesize" 'PrefixI 'True) (S1 ('MetaSel ('Just "t_name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "t_inputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PortName]) :*: S1 ('MetaSel ('Just "t_output") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PortName))) :+: C1 ('MetaCons "TestBench" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) | |
Give port names for arguments/results.
Give a data type and function:
data T = MkT Int Bool
{-# ANN f (defSyn "f") #-}
f :: Int -> T -> (T,Bool)
f a b = ...
Clash would normally generate the following VHDL entity:
entity f is
port(a : in signed(63 downto 0);
b_0 : in signed(63 downto 0);
b_1 : in boolean;
result : out std_logic_vector(65 downto 0));
end;However, we can change this by using PortNames. So by:
{-# ANN f
(Synthesize
{ t_name = "f"
, t_inputs = [ PortName "a"
, PortName "b" ]
, t_output = PortName "res" }) #-}
f :: Int -> T -> (T,Bool)
f a b = ...
we get:
entity f is
port(a : in signed(63 downto 0);
b : in std_logic_vector(64 downto 0);
res : out std_logic_vector(65 downto 0));
end;If we want to name fields for tuples/records we have to use PortProduct
{-# ANN f
(Synthesize
{ t_name = "f"
, t_inputs = [ PortName "a"
, PortProduct "" [ PortName "b", PortName "c" ] ]
, t_output = PortProduct "res" [PortName "q"] }) #-}
f :: Int -> T -> (T,Bool)
f a b = ...
So that we get:
entity f is
port(a : in signed(63 downto 0);
b : in signed(63 downto 0);
c : in boolean;
res_q : out std_logic_vector(64 downto 0);
res_1 : out boolean);
end;Notice how we didn't name the second field of the result, and the second
output port got PortProduct name, "res", as a prefix for its name.
Constructors
| PortName String | You want a port, with the given name, for the entire argument/type You can use an empty String , |
| PortProduct String [PortName] | You want to assign ports to fields of a product argument/type The first argument of
You can use an empty String , |
Instances
| Data PortName Source # | |
Defined in Clash.Annotations.TopEntity Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PortName -> c PortName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PortName # toConstr :: PortName -> Constr # dataTypeOf :: PortName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PortName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortName) # gmapT :: (forall b. Data b => b -> b) -> PortName -> PortName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PortName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PortName -> r # gmapQ :: (forall d. Data d => d -> u) -> PortName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PortName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PortName -> m PortName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PortName -> m PortName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PortName -> m PortName # | |
| Generic PortName Source # | |
| Show PortName Source # | |
| Eq PortName Source # | |
| Lift PortName Source # | |
| type Rep PortName Source # | |
Defined in Clash.Annotations.TopEntity type Rep PortName = D1 ('MetaData "PortName" "Clash.Annotations.TopEntity" "clash-prelude-1.9.0-inplace" 'False) (C1 ('MetaCons "PortName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "PortProduct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PortName]))) | |