1-------------------------------------------------------------------------------
2--
3-- Copyright 2018 Ettus Research, a National Instruments Company
4--
5-- SPDX-License-Identifier: LGPL-3.0-or-later
6--
7--
8-- Purpose:
9--
10-- This top level module orchestrates both of the TDC Cores for the RP and SP. It
11-- handles PPS capture, resets, re-run logic, and PPS crossing logic. The guts of the TDC
12-- are all located in the Cores.
13--
14-- This file (and the Cores) follows exactly the "TDC Detail" diagram from this document:
15-- //MI/RF/HW/USRP/N310/HWCode/Common/Synchronization/design/Diagrams.vsdx
16--
17--
18--
19-- To control this module:
20--  0) Default values expected to be driven on the control inputs:
21--       aReset     <= true
22--       rResetTdc  <= true
23--       rEnableTdc <= false
24--       rReRunEnable <= false
25--       rEnablePpsCrossing   <= false
26--       sPpsClkCrossDelayVal <= don't care
27--     Prior to starting the core, the Sync Pulse counters must be loaded. Apply the
28--     correct count values to rRpPeriodInRClks, etc, and then pulse the load bit for
29--     each RP and SP. It is critical that this step is performed before de-asserting
30--     reset.
31--
32--  1) De-assert the global reset, aReset, as well as the synchronous reset, rResetTdc,
33--     after all clocks are active and stable. Wait until rResetTdcDone is de-asserted.
34--     If it doesn't de-assert, then one of your clocks isn't running.
35--
36--  2) At any point after rResetTdcDone de-asserts it is safe to assert rEnableTdc.
37--     The rPpsPulse input is now actively listening for PPS activity and the TDC
38--     will begin on the first PPS pulse received. After a PPS is received, the
39--     rPpsPulseCaptured bit will assert and will remain asserted until aReset or
40--     rResetTdc is asserted.
41--
42--  3) When the TDC measurement completes, mRpOffsetDone and mSpOffsetDone will assert
43--     (not necessarily at the same time). The results of the measurements will be valid
44--     on mRpOffset and mSpOffset.
45--
46--  4) To cross the PPS trigger into the SampleClk domain, first write the correct delay
47--     value to sPpsClkCrossDelayVal. Then (or at the same time), enable the crossing
48--     logic by asserting rEnablePpsCrossing. All subsequent PPS pulses will be crossed
49--     deterministically. Although not the typical use case, sPpsClkCrossDelayVal can
50--     be adjusted on the fly without producing output glitches, although output pulses
51--     may be skipped.
52--
53--  5) To run the measurement again, assert the rReRunEnable input and capture the new
54--     offsets whenever mRpOffsetValid or mSpOffsetValid asserts.
55--
56--
57--
58-- Sync Pulse = RP and SP, which are the repeated pulses that are some integer
59--  divisor of the Reference and Sample clocks. RP = Reference Pulse in the
60--  RefClk domain. SP = Repeated TClk pulse in the SampleClk domain.
61--
62--
63-- Clock period relationship requirements to meet system concerns:
64--   1) MeasClkPeriod < 2*RefClkPeriod
65--   2) MeasClkPeriod < 4*SampleClkPeriod
66--
67--
68-- vreview_group Tdc
69-------------------------------------------------------------------------------
70
71library ieee;
72  use ieee.std_logic_1164.all;
73  use ieee.numeric_std.all;
74  use ieee.math_real.all;
75
76entity TdcTop is
77  generic (
78    -- Determines the maximum number of bits required to create the restart
79    -- pulser. This value is based off of the RefClk and RePulse rates.
80    kRClksPerRePulsePeriodBitsMax : integer range 3 to 32 := 24;
81    -- Determines the maximum number of bits required to create the Gated and Freerunning
82    -- sync pulsers. This value is based off of the RefClk and SyncPulse rates.
83    kRClksPerRpPeriodBitsMax  : integer range 3 to 16 := 16;
84    -- This value is based off of the SampleClk and SyncPulse rates.
85    kSClksPerSpPeriodBitsMax  : integer range 3 to 16 := 16;
86    -- Number of MeasClk periods required to count one period of RP or SP (in bits).
87    kPulsePeriodCntSize       : integer := 13;
88    -- Number of FreqRef periods to be measured (in bits).
89    kFreqRefPeriodsToCheckSize: integer := 17;
90    -- Number of Sync Pulse Periods to be timestamped (in bits).
91    kSyncPeriodsToStampSize   : integer := 10
92  );
93  port (
94
95    -- Clocks and Resets : --------------------------------------------------------------
96    -- Asynchronous global reset.
97    aReset          : in  boolean;
98    -- Reference Clock
99    RefClk          : in  std_logic;
100    -- Sample Clock
101    SampleClk       : in  std_logic;
102    -- Measurement Clock must run at a very specific frequency, determined by the
103    -- SampleClk, RefClk, and Sync Pulse rates... oh and a lot of math/luck.
104    MeasClk         : in  std_logic;
105
106
107    -- Controls and Status : ------------------------------------------------------------
108    -- Soft reset for the module. Wait until rResetTdcDone asserts before de-asserting
109    -- the reset.
110    rResetTdc          : in  boolean;
111    rResetTdcDone      : out boolean;
112    -- Once enabled, the TDC waits for the next PPS pulse to begin measurements. Leave
113    -- this signal asserted for the measurement duration (there is no need to de-assert
114    -- it unless you want to capture a different PPS edge).
115    rEnableTdc         : in  boolean;
116    -- Assert this bit to allow the TDC to perform repeated measurements.
117    rReRunEnable       : in  boolean;
118
119    -- Only required to pulse 1 RefClk cycle.
120    rPpsPulse          : in  boolean;
121    -- Debug, held asserted when pulse is captured.
122    rPpsPulseCaptured  : out boolean;
123
124    -- Programmable value for delaying the RP and SP pulsers from when the Restart
125    -- Pulser begins.
126    rPulserEnableDelayVal : in  unsigned(3 downto 0);
127
128
129    -- Crossing PPS into Sample Clock : -------------------------------------------------
130    -- Enable crossing rPpsPulse into SampleClk domain. This should remain de-asserted
131    -- until the TDC measurements are complete and sPpsClkCrossDelayVal is written.
132    rEnablePpsCrossing   : in  boolean;
133    -- Programmable delay value for crossing clock domains. This is used to compensate
134    -- for differences in sSP pulses across modules. This value is typically set once
135    -- after running initial synchronization.
136    sPpsClkCrossDelayVal : in  unsigned(3 downto 0);
137    -- PPS pulse output on the SampleClk domain.
138    sPpsPulse            : out boolean;
139
140
141    -- FTDC Measurement Results : -------------------------------------------------------
142    -- Final FTDC measurements in MeasClk ticks. Done will assert when *Offset
143    -- becomes valid and will remain asserted until aReset or rResetTdc asserts.
144    -- FXP<+40,13> where kPulsePeriodCntSize is the number of integer bits.
145    mRpOffset       : out unsigned(kPulsePeriodCntSize+
146                                   kSyncPeriodsToStampSize+
147                                   kFreqRefPeriodsToCheckSize-1 downto 0);
148    mSpOffset       : out unsigned(kPulsePeriodCntSize+
149                                   kSyncPeriodsToStampSize+
150                                   kFreqRefPeriodsToCheckSize-1 downto 0);
151    mOffsetsDone    : out boolean;
152    mOffsetsValid   : out boolean;
153
154
155    -- Setup for Pulsers : --------------------------------------------------------------
156    -- Only load these counts when rResetTdc is asserted and rEnableTdc is de-asserted!!!
157    -- If both of the above conditions are met, load the counts by pulsing Load
158    -- when the counts are valid. It is not necessary to keep the count values valid
159    -- after pulsing Load.
160    rLoadRePulseCounts      : in boolean; -- RePulse
161    rRePulsePeriodInRClks   : in unsigned(kRClksPerRePulsePeriodBitsMax - 1 downto 0);
162    rRePulseHighTimeInRClks : in unsigned(kRClksPerRePulsePeriodBitsMax - 1 downto 0);
163    rLoadRpCounts       : in boolean; -- RP
164    rRpPeriodInRClks    : in unsigned(kRClksPerRpPeriodBitsMax - 1 downto 0);
165    rRpHighTimeInRClks  : in unsigned(kRClksPerRpPeriodBitsMax - 1 downto 0);
166    rLoadRptCounts      : in boolean; -- RP-transfer
167    rRptPeriodInRClks   : in unsigned(kRClksPerRpPeriodBitsMax - 1 downto 0);
168    rRptHighTimeInRClks : in unsigned(kRClksPerRpPeriodBitsMax - 1 downto 0);
169    sLoadSpCounts       : in boolean; -- SP
170    sSpPeriodInSClks    : in unsigned(kSClksPerSpPeriodBitsMax - 1 downto 0);
171    sSpHighTimeInSClks  : in unsigned(kSClksPerSpPeriodBitsMax - 1 downto 0);
172    sLoadSptCounts      : in boolean; -- SP-transfer
173    sSptPeriodInSClks   : in unsigned(kSClksPerSpPeriodBitsMax - 1 downto 0);
174    sSptHighTimeInSClks : in unsigned(kSClksPerSpPeriodBitsMax - 1 downto 0);
175
176
177    -- Sync Pulse Outputs : -------------------------------------------------------------
178    -- The repeating pulses can be useful for many things, including passing triggers.
179    -- The rising edges will always have a fixed (but unknown) phase relationship to one
180    -- another. This fixed phase relationship is valid across daughterboards and all
181    -- modules using the same Reference Clock and Sample Clock rates and sources.
182    rRpTransfer        : out boolean;
183    sSpTransfer        : out boolean;
184
185    -- Pin bouncers out and in. Must go to unused and unconnected pins on the FPGA!
186    rGatedPulseToPin   : inout std_logic;
187    sGatedPulseToPin   : inout std_logic
188  );
189end TdcTop;
190
191
192architecture struct of TdcTop is
193
194  component TdcCore
195    generic (
196      kSourceClksPerPulseMaxBits : integer range 3 to 16 := 16;
197      kPulsePeriodCntSize        : integer := 13;
198      kFreqRefPeriodsToCheckSize : integer := 17;
199      kSyncPeriodsToStampSize    : integer := 10);
200    port (
201      aReset             : in  boolean;
202      MeasClk            : in  std_logic;
203      mResetPeriodMeas   : in  boolean;
204      mPeriodMeasDone    : out boolean;
205      mResetTdcMeas      : in  boolean;
206      mRunTdcMeas        : in  boolean;
207      mGatedPulse        : out boolean;
208      mAvgOffset         : out unsigned(kPulsePeriodCntSize+kSyncPeriodsToStampSize+kFreqRefPeriodsToCheckSize-1 downto 0);
209      mAvgOffsetDone     : out boolean;
210      mAvgOffsetValid    : out boolean;
211      SourceClk          : in  std_logic;
212      sResetTdc          : in  boolean;
213      sSyncPulseLoadCnt  : in  boolean;
214      sSyncPulsePeriod   : in  unsigned(kSourceClksPerPulseMaxBits-1 downto 0);
215      sSyncPulseHighTime : in  unsigned(kSourceClksPerPulseMaxBits-1 downto 0);
216      sSyncPulseEnable   : in  boolean;
217      sGatedPulse        : out boolean;
218      sGatedPulseToPin   : inout std_logic);
219  end component;
220
221  --vhook_sigstart
222  signal mRP: boolean;
223  signal mRpOffsetDoneLcl: boolean;
224  signal mRpOffsetValidLcl: boolean;
225  signal mRunTdc: boolean;
226  signal mSP: boolean;
227  signal mSpOffsetDoneLcl: boolean;
228  signal mSpOffsetValidLcl: boolean;
229  signal rCrossTrigRFI: boolean;
230  signal rGatedCptrPulseIn: boolean;
231  signal rRePulse: boolean;
232  signal rRePulseEnable: boolean;
233  signal rRpEnable: boolean;
234  signal rRptPulse: boolean;
235  signal sSpEnable: boolean;
236  signal sSptPulse: boolean;
237  --vhook_sigend
238
239  signal sSpEnable_ms : boolean;
240
241  -- Delay chain for enables.
242  constant kDelaySizeForRpEnable  : integer := 15;
243  constant kAddtlDelayForSpEnable : integer := 3;
244  signal rSyncPulseEnableDly :
245    std_logic_vector(kDelaySizeForRpEnable+
246                     kAddtlDelayForSpEnable-1 downto 0) := (others => '0');
247  -- Adding kAddtlDelayForSpEnable stages, so this vector needs to handle one extra
248  -- bit of range (hence no -1 downto 0).
249  signal rSyncPulseEnableDlyVal : unsigned(rPulserEnableDelayVal'length downto 0);
250
251  signal rResetTdcFlop_ms, rResetTdcFlop,
252         rResetTdcDone_ms,
253         rSpEnable,
254         mRunTdcEnable_ms, mRunTdcEnable,
255         mRunTdcEnableDly, mRunTdcEnableRe,
256         mResetTdc_ms,     mResetTdc,
257         sResetTdc_ms,     sResetTdc,
258         mRpValidStored,  mSpValidStored,
259         mOffsetsValidLcl,
260         rPpsPulseDly,  rPpsPulseRe,
261         mReRunEnable_ms,  mReRunEnable  : boolean;
262
263  signal rPpsCaptured : std_logic;
264
265  type EnableFsmState_t is (Disabled, WaitForRunComplete, ReRuns);
266  signal mEnableState : EnableFsmState_t;
267
268  attribute ASYNC_REG : string;
269  attribute ASYNC_REG of sSpEnable_ms : signal is "true";
270  attribute ASYNC_REG of sSpEnable    : signal is "true";
271  attribute ASYNC_REG of rResetTdcFlop_ms    : signal is "true";
272  attribute ASYNC_REG of rResetTdcFlop       : signal is "true";
273  attribute ASYNC_REG of rResetTdcDone_ms    : signal is "true";
274  attribute ASYNC_REG of rResetTdcDone       : signal is "true";
275  attribute ASYNC_REG of mRunTdcEnable_ms    : signal is "true";
276  attribute ASYNC_REG of mRunTdcEnable       : signal is "true";
277  attribute ASYNC_REG of mResetTdc_ms        : signal is "true";
278  attribute ASYNC_REG of mResetTdc           : signal is "true";
279  attribute ASYNC_REG of sResetTdc_ms        : signal is "true";
280  attribute ASYNC_REG of sResetTdc           : signal is "true";
281  attribute ASYNC_REG of mReRunEnable_ms     : signal is "true";
282  attribute ASYNC_REG of mReRunEnable        : signal is "true";
283
284begin
285
286
287  -- Generate Resets : ------------------------------------------------------------------
288  -- Double-sync the reset to the MeasClk domain and then back to the RefClk domain to
289  -- prove it made it all the way into the TDC. Also move it into the SampleClk domain.
290  -- ------------------------------------------------------------------------------------
291  GenResets : process(aReset, RefClk)
292  begin
293    if aReset then
294      rResetTdcFlop_ms <= true;
295      rResetTdcFlop    <= true;
296      rResetTdcDone_ms <= true;
297      rResetTdcDone    <= true;
298    elsif rising_edge(RefClk) then
299      -- Run this through a double-sync in case the user defaults it to false, which
300      -- could cause rResetTdcFlop_ms to go meta-stable.
301      rResetTdcFlop_ms <= rResetTdc;
302      rResetTdcFlop    <= rResetTdcFlop_ms;
303      -- Second double-sync to move the reset from the MeasClk domain back to RefClk.
304      rResetTdcDone_ms <= mResetTdc;
305      rResetTdcDone    <= rResetTdcDone_ms;
306    end if;
307  end process;
308
309  GenResetsMeasClk : process(aReset, MeasClk)
310  begin
311    if aReset then
312      mResetTdc_ms <= true;
313      mResetTdc    <= true;
314    elsif rising_edge(MeasClk) then
315      -- Move the reset from the RefClk to the MeasClk domain.
316      mResetTdc_ms <= rResetTdcFlop;
317      mResetTdc    <= mResetTdc_ms;
318    end if;
319  end process;
320
321  GenResetsSampleClk : process(aReset, SampleClk)
322  begin
323    if aReset then
324      sResetTdc_ms <= true;
325      sResetTdc    <= true;
326    elsif rising_edge(SampleClk) then
327      -- Move the reset from the RefClk to the SampleClk domain.
328      sResetTdc_ms <= rResetTdcFlop;
329      sResetTdc    <= sResetTdc_ms;
330    end if;
331  end process;
332
333
334  -- Generate Enables for TDCs : --------------------------------------------------------
335  -- When the TDC is enabled by asserting rEnableTdc, we start "listening" for a PPS
336  -- rising edge to occur. We capture the first edge we see and then keep the all the
337  -- enables asserted until the TDC is disabled.
338  -- ------------------------------------------------------------------------------------
339  rPpsPulseRe <= rPpsPulse and not rPpsPulseDly;
340
341  EnableTdc : process(aReset, RefClk)
342  begin
343    if aReset then
344      rPpsPulseDly <= false;
345      rPpsCaptured <= '0';
346      rSyncPulseEnableDly <= (others => '0');
347    elsif rising_edge(RefClk) then
348      -- RE detector for PPS to ONLY trigger on the edge and not accidentally half
349      -- way through the high time.
350      rPpsPulseDly <= rPpsPulse;
351      -- When the TDC is enabled we capture the first PPS. This starts the Sync Pulses
352      -- (RP / SP) as well as enables the TDC measurement for capturing edges. Note
353      -- that this is independent from any synchronous reset such that we can control
354      -- the PPS capture and the edge capture independently.
355      if rEnableTdc then
356        if rPpsPulseRe then
357          rPpsCaptured <= '1';
358        end if;
359      else
360        rPpsCaptured <= '0';
361        rSyncPulseEnableDly <= (others => '0');
362      end if;
363
364      -- Delay chain for the enable bits. Shift left low to high.
365      rSyncPulseEnableDly <=
366        rSyncPulseEnableDly(rSyncPulseEnableDly'high-1 downto 0) & rPpsCaptured;
367    end if;
368  end process;
369
370  rSyncPulseEnableDlyVal <= resize(rPulserEnableDelayVal, rSyncPulseEnableDlyVal'length);
371
372  -- Enables for the RePulse/RP/SP. The RePulse enable must be asserted two cycles
373  -- before the other enables to allow the TDC to start running before the RP/SP begin.
374  rRePulseEnable <= rPpsCaptured = '1'; -- no delay
375  rRpEnable <= rSyncPulseEnableDly(to_integer(rSyncPulseEnableDlyVal)) = '1';
376  rSpEnable <= rSyncPulseEnableDly(to_integer(rSyncPulseEnableDlyVal)+kAddtlDelayForSpEnable-1) = '1';
377
378  -- Local to output.
379  rPpsPulseCaptured <= rPpsCaptured = '1';
380
381  -- Sync rSpEnable to the SampleClk now... based on the "TDC 2.0" diagram.
382  SyncEnableToSampleClk : process(aReset, SampleClk)
383  begin
384    if aReset then
385      sSpEnable_ms <= false;
386      sSpEnable    <= false;
387    elsif rising_edge(SampleClk) then
388      sSpEnable_ms <= rSpEnable;
389      sSpEnable    <= sSpEnable_ms;
390    end if;
391  end process;
392
393  --vhook_e Pulser ReRunPulser
394  --vhook_a kClksPerPulseMaxBits kRClksPerRePulsePeriodBitsMax
395  --vhook_a Clk            RefClk
396  --vhook_a cLoadLimits    rLoadRePulseCounts
397  --vhook_a cPeriod        rRePulsePeriodInRClks
398  --vhook_a cHighTime      rRePulseHighTimeInRClks
399  --vhook_a cEnablePulse   rRePulseEnable
400  --vhook_a cPulse         rRePulse
401  ReRunPulser: entity work.Pulser (rtl)
402    generic map (kClksPerPulseMaxBits => kRClksPerRePulsePeriodBitsMax)  --integer range 3:32 :=16
403    port map (
404      aReset       => aReset,                   --in  boolean
405      Clk          => RefClk,                   --in  std_logic
406      cLoadLimits  => rLoadRePulseCounts,       --in  boolean
407      cPeriod      => rRePulsePeriodInRClks,    --in  unsigned(kClksPerPulseMaxBits-1:0)
408      cHighTime    => rRePulseHighTimeInRClks,  --in  unsigned(kClksPerPulseMaxBits-1:0)
409      cEnablePulse => rRePulseEnable,           --in  boolean
410      cPulse       => rRePulse);                --out boolean
411
412  mRunTdcEnableRe <= mRunTdcEnable and not mRunTdcEnableDly;
413
414  -- FSM to generate the master Run signal, as well as the repeat run.
415  SyncEnableToMeasClk : process(aReset, MeasClk)
416  begin
417    if aReset then
418      mRunTdcEnable_ms <= false;
419      mRunTdcEnable    <= false;
420      mReRunEnable_ms  <= false;
421      mReRunEnable     <= false;
422      mRunTdcEnableDly <= false;
423      mRunTdc          <= false;
424      mEnableState     <= Disabled;
425    elsif rising_edge(MeasClk) then
426      -- rRePulse is many, many MeasClk cycles high/low, so this is safe to double-sync.
427      mRunTdcEnable_ms <= rRePulse;
428      mRunTdcEnable    <= mRunTdcEnable_ms;
429      mReRunEnable_ms  <= rReRunEnable;
430      mReRunEnable     <= mReRunEnable_ms;
431
432      mRunTdcEnableDly <= mRunTdcEnable;
433
434      -- STATE MACHINE STARTUP !!! ------------------------------------------------------
435      -- This state machine starts safely because it cannot change state until
436      -- mRunTdcEnable is asserted, which cannot happen until several cycles after
437      -- aReset de-assertion due to the double-synchronizer from the RefClk domain.
438      -- --------------------------------------------------------------------------------
439      -- De-assert strobe.
440      mRunTdc <= false;
441
442      case mEnableState is
443        -- Transition to WaitForRunComplete when the TDC is enabled. Pulse mRunTdc here,
444        -- and then wait for it to complete in WaitForRunComplete.
445        when Disabled =>
446          if mRunTdcEnableRe then
447            mRunTdc <= true;
448            mEnableState <= WaitForRunComplete;
449          end if;
450
451        -- The TDC measurement is complete when both offsets are valid. Go to the re-run
452        -- state regardless of whether re-runs are enabled. If they aren't we just sit
453        -- there and wait for more instructions...
454        when WaitForRunComplete =>
455          if mOffsetsValidLcl then
456            mEnableState <= ReRuns;
457          end if;
458
459        -- Only pulse mRunTdc again if re-runs are enabled and the rising edge of
460        -- the enable signal occurs. This guarantees our RP/SP have the correct phase
461        -- relationship every time the TDC is run.
462        when ReRuns =>
463          if mReRunEnable and mRunTdcEnableRe then
464            mRunTdc <= true;
465            mEnableState <= WaitForRunComplete;
466          end if;
467
468        when others =>
469          mEnableState <= Disabled;
470      end case;
471
472      -- Synchronous reset for FSM.
473      if mResetTdc then
474        mEnableState <= Disabled;
475        mRunTdc <= false;
476      end if;
477
478    end if;
479  end process;
480
481
482
483  -- Generate Output Valid Signals : ----------------------------------------------------
484  -- Depending on how fast SW can read the measurements (and in what order they read)
485  -- the readings could be out of sync with one another. This section conditions the
486  -- output valid signals from each core and asserts a single output valid pulse after
487  -- BOTH valids have asserted. It is agnostic to the order in which the valids assert.
488  -- It creates a delay in the output valid assertion. Minimal delay is one MeasClk cycle
489  -- if the core valids assert together. Worst-case delay is two MeasClk cycles after
490  -- the latter of the two valids asserts. This is acceptable delay because the core
491  -- cannot be re-run until both valids have asserted (mOffsetsValidLcl is fed back into
492  -- the ReRun FSM above).
493  -- ------------------------------------------------------------------------------------
494  ConditionDataValidProc : process(aReset, MeasClk) is
495  begin
496    if aReset then
497      mOffsetsValidLcl <= false;
498      mRpValidStored   <= false;
499      mSpValidStored   <= false;
500    elsif rising_edge(MeasClk) then
501      -- Reset the strobe signals.
502      mOffsetsValidLcl <= false;
503
504      -- First, we're sensitive to the TDC sync reset signal.
505      if mResetTdc then
506        mOffsetsValidLcl <= false;
507        mRpValidStored   <= false;
508        mSpValidStored   <= false;
509      -- Case 1: Both Valid signals pulse at the same time.
510      -- Case 4: Both Valid signals have been stored independently. Yes, this incurs
511      --         a one-cycle delay in the output valid (from when the second one asserts)
512      --         but it makes for cleaner code and is safe because by design because the
513      --         valid signals cannot assert again for a longggg time.
514      elsif (mRpOffsetValidLcl and mSpOffsetValidLcl) or
515            (mRpValidStored    and mSpValidStored) then
516        mOffsetsValidLcl <= true;
517        mRpValidStored   <= false;
518        mSpValidStored   <= false;
519      -- Case 2: RP Valid pulses alone.
520      elsif mRpOffsetValidLcl then
521        mRpValidStored <= true;
522      -- Case 3: SP Valid pulses alone.
523      elsif mSpOffsetValidLcl then
524        mSpValidStored <= true;
525      end if;
526    end if;
527  end process;
528
529  -- Local to output.
530  mOffsetsValid <= mOffsetsValidLcl;
531  -- Only assert done with both cores are done.
532  mOffsetsDone  <= mRpOffsetDoneLcl and mSpOffsetDoneLcl;
533
534
535
536  -- Reference Clock TDC (RP) : ---------------------------------------------------------
537  -- mRP is only used for testbenching purposes, so ignore vhook warnings.
538  --vhook_nowarn mRP
539  -- ------------------------------------------------------------------------------------
540
541  --vhook   TdcCore    RpTdc
542  --vhook_g kSourceClksPerPulseMaxBits kRClksPerRpPeriodBitsMax
543  --vhook_a mResetPeriodMeas mResetTdc
544  --vhook_a mResetTdcMeas    mResetTdc
545  --vhook_a mPeriodMeasDone  open
546  --vhook_a mRunTdcMeas      mRunTdc
547  --vhook_a mGatedPulse      mRP
548  --vhook_a mAvgOffset       mRpOffset
549  --vhook_a mAvgOffsetDone   mRpOffsetDoneLcl
550  --vhook_a mAvgOffsetValid  mRpOffsetValidLcl
551  --vhook_a SourceClk        RefClk
552  --vhook_a sResetTdc        rResetTdcFlop
553  --vhook_a sSyncPulseLoadCnt  rLoadRpCounts
554  --vhook_a sSyncPulsePeriod   rRpPeriodInRClks
555  --vhook_a sSyncPulseHighTime rRpHighTimeInRClks
556  --vhook_a sSyncPulseEnable   rRpEnable
557  --vhook_a sGatedPulse        open
558  --vhook_a {^sGated(.*)}      rGated$1
559  RpTdc: TdcCore
560    generic map (
561      kSourceClksPerPulseMaxBits => kRClksPerRpPeriodBitsMax,    --integer range 3:16 :=16
562      kPulsePeriodCntSize        => kPulsePeriodCntSize,         --integer:=13
563      kFreqRefPeriodsToCheckSize => kFreqRefPeriodsToCheckSize,  --integer:=17
564      kSyncPeriodsToStampSize    => kSyncPeriodsToStampSize)     --integer:=10
565    port map (
566      aReset             => aReset,              --in  boolean
567      MeasClk            => MeasClk,             --in  std_logic
568      mResetPeriodMeas   => mResetTdc,           --in  boolean
569      mPeriodMeasDone    => open,                --out boolean
570      mResetTdcMeas      => mResetTdc,           --in  boolean
571      mRunTdcMeas        => mRunTdc,             --in  boolean
572      mGatedPulse        => mRP,                 --out boolean
573      mAvgOffset         => mRpOffset,           --out unsigned(kPulsePeriodCntSize+ kSyncPeriodsToStampSize+ kFreqRefPeriodsToCheckSize-1:0)
574      mAvgOffsetDone     => mRpOffsetDoneLcl,    --out boolean
575      mAvgOffsetValid    => mRpOffsetValidLcl,   --out boolean
576      SourceClk          => RefClk,              --in  std_logic
577      sResetTdc          => rResetTdcFlop,       --in  boolean
578      sSyncPulseLoadCnt  => rLoadRpCounts,       --in  boolean
579      sSyncPulsePeriod   => rRpPeriodInRClks,    --in  unsigned(kSourceClksPerPulseMaxBits-1:0)
580      sSyncPulseHighTime => rRpHighTimeInRClks,  --in  unsigned(kSourceClksPerPulseMaxBits-1:0)
581      sSyncPulseEnable   => rRpEnable,           --in  boolean
582      sGatedPulse        => open,                --out boolean
583      sGatedPulseToPin   => rGatedPulseToPin);   --inout std_logic
584
585  --vhook_e Pulser RpTransferPulse
586  --vhook_a kClksPerPulseMaxBits kRClksPerRpPeriodBitsMax
587  --vhook_a Clk            RefClk
588  --vhook_a cLoadLimits    rLoadRptCounts
589  --vhook_a cPeriod        rRptPeriodInRClks
590  --vhook_a cHighTime      rRptHighTimeInRClks
591  --vhook_a cEnablePulse   rRpEnable
592  --vhook_a cPulse         rRptPulse
593  RpTransferPulse: entity work.Pulser (rtl)
594    generic map (kClksPerPulseMaxBits => kRClksPerRpPeriodBitsMax)  --integer range 3:32 :=16
595    port map (
596      aReset       => aReset,               --in  boolean
597      Clk          => RefClk,               --in  std_logic
598      cLoadLimits  => rLoadRptCounts,       --in  boolean
599      cPeriod      => rRptPeriodInRClks,    --in  unsigned(kClksPerPulseMaxBits-1:0)
600      cHighTime    => rRptHighTimeInRClks,  --in  unsigned(kClksPerPulseMaxBits-1:0)
601      cEnablePulse => rRpEnable,            --in  boolean
602      cPulse       => rRptPulse);           --out boolean
603
604  -- Local to output
605  rRpTransfer <= rRptPulse;
606
607
608  -- Sample Clock TDC (SP) : ------------------------------------------------------------
609  -- mSP is only used for testbenching purposes, so ignore vhook warnings.
610  --vhook_nowarn mSP
611  -- ------------------------------------------------------------------------------------
612
613  --vhook   TdcCore    SpTdc
614  --vhook_g kSourceClksPerPulseMaxBits kSClksPerSpPeriodBitsMax
615  --vhook_a mResetPeriodMeas mResetTdc
616  --vhook_a mResetTdcMeas    mResetTdc
617  --vhook_a mPeriodMeasDone  open
618  --vhook_a mRunTdcMeas      mRunTdc
619  --vhook_a mGatedPulse      mSP
620  --vhook_a mAvgOffset       mSpOffset
621  --vhook_a mAvgOffsetDone   mSpOffsetDoneLcl
622  --vhook_a mAvgOffsetValid  mSpOffsetValidLcl
623  --vhook_a SourceClk        SampleClk
624  --vhook_a sResetTdc        sResetTdc
625  --vhook_a sSyncPulseLoadCnt  sLoadSpCounts
626  --vhook_a sSyncPulsePeriod   sSpPeriodInSClks
627  --vhook_a sSyncPulseHighTime sSpHighTimeInSClks
628  --vhook_a sSyncPulseEnable sSpEnable
629  --vhook_a sGatedPulse      open
630  --vhook_a {^sGated(.*)}    sGated$1
631  SpTdc: TdcCore
632    generic map (
633      kSourceClksPerPulseMaxBits => kSClksPerSpPeriodBitsMax,    --integer range 3:16 :=16
634      kPulsePeriodCntSize        => kPulsePeriodCntSize,         --integer:=13
635      kFreqRefPeriodsToCheckSize => kFreqRefPeriodsToCheckSize,  --integer:=17
636      kSyncPeriodsToStampSize    => kSyncPeriodsToStampSize)     --integer:=10
637    port map (
638      aReset             => aReset,              --in  boolean
639      MeasClk            => MeasClk,             --in  std_logic
640      mResetPeriodMeas   => mResetTdc,           --in  boolean
641      mPeriodMeasDone    => open,                --out boolean
642      mResetTdcMeas      => mResetTdc,           --in  boolean
643      mRunTdcMeas        => mRunTdc,             --in  boolean
644      mGatedPulse        => mSP,                 --out boolean
645      mAvgOffset         => mSpOffset,           --out unsigned(kPulsePeriodCntSize+ kSyncPeriodsToStampSize+ kFreqRefPeriodsToCheckSize-1:0)
646      mAvgOffsetDone     => mSpOffsetDoneLcl,    --out boolean
647      mAvgOffsetValid    => mSpOffsetValidLcl,   --out boolean
648      SourceClk          => SampleClk,           --in  std_logic
649      sResetTdc          => sResetTdc,           --in  boolean
650      sSyncPulseLoadCnt  => sLoadSpCounts,       --in  boolean
651      sSyncPulsePeriod   => sSpPeriodInSClks,    --in  unsigned(kSourceClksPerPulseMaxBits-1:0)
652      sSyncPulseHighTime => sSpHighTimeInSClks,  --in  unsigned(kSourceClksPerPulseMaxBits-1:0)
653      sSyncPulseEnable   => sSpEnable,           --in  boolean
654      sGatedPulse        => open,                --out boolean
655      sGatedPulseToPin   => sGatedPulseToPin);   --inout std_logic
656
657  --vhook_e Pulser SpTransferPulse
658  --vhook_a kClksPerPulseMaxBits kSClksPerSpPeriodBitsMax
659  --vhook_a Clk            SampleClk
660  --vhook_a cLoadLimits    sLoadSptCounts
661  --vhook_a cPeriod        sSptPeriodInSClks
662  --vhook_a cHighTime      sSptHighTimeInSClks
663  --vhook_a cEnablePulse   sSpEnable
664  --vhook_a cPulse         sSptPulse
665  SpTransferPulse: entity work.Pulser (rtl)
666    generic map (kClksPerPulseMaxBits => kSClksPerSpPeriodBitsMax)  --integer range 3:32 :=16
667    port map (
668      aReset       => aReset,               --in  boolean
669      Clk          => SampleClk,            --in  std_logic
670      cLoadLimits  => sLoadSptCounts,       --in  boolean
671      cPeriod      => sSptPeriodInSClks,    --in  unsigned(kClksPerPulseMaxBits-1:0)
672      cHighTime    => sSptHighTimeInSClks,  --in  unsigned(kClksPerPulseMaxBits-1:0)
673      cEnablePulse => sSpEnable,            --in  boolean
674      cPulse       => sSptPulse);           --out boolean
675
676  -- Local to output
677  sSpTransfer <= sSptPulse;
678
679
680  -- Cross PPS to SampleClk : ----------------------------------------------------------
681  -- Cross it safely and with deterministic delay.
682  -- ------------------------------------------------------------------------------------
683
684  -- Keep the module from over-pulsing itself by gating the input with the RFI signal,
685  -- although at 1 Hz, this module should never run into the RFI de-asserted case
686  -- by design.
687  rGatedCptrPulseIn <= rCrossTrigRFI and rPpsPulseRe;
688
689  --vhook_e CrossTrigger CrossCptrPulse
690  --vhook_a rRP               rRptPulse
691  --vhook_a rReadyForInput    rCrossTrigRFI
692  --vhook_a rEnableTrigger    rEnablePpsCrossing
693  --vhook_a rTriggerIn        rGatedCptrPulseIn
694  --vhook_a sSP               sSptPulse
695  --vhook_a sElasticBufferPtr sPpsClkCrossDelayVal
696  --vhook_a sTriggerOut       sPpsPulse
697  CrossCptrPulse: entity work.CrossTrigger (rtl)
698    port map (
699      aReset            => aReset,                --in  boolean
700      RefClk            => RefClk,                --in  std_logic
701      rRP               => rRptPulse,             --in  boolean
702      rReadyForInput    => rCrossTrigRFI,         --out boolean
703      rEnableTrigger    => rEnablePpsCrossing,    --in  boolean
704      rTriggerIn        => rGatedCptrPulseIn,     --in  boolean
705      SampleClk         => SampleClk,             --in  std_logic
706      sSP               => sSptPulse,             --in  boolean
707      sElasticBufferPtr => sPpsClkCrossDelayVal,  --in  unsigned(3:0)
708      sTriggerOut       => sPpsPulse);            --out boolean
709
710
711end struct;
712
713
714
715
716
717
718
719--------------------------------------------------------------------------------
720-- Testbench for TdcTop
721--------------------------------------------------------------------------------
722
723--synopsys translate_off
724library ieee;
725  use ieee.std_logic_1164.all;
726  use ieee.numeric_std.all;
727  use ieee.math_real.all;
728
729entity tb_TdcTop is end tb_TdcTop;
730
731architecture test of tb_TdcTop is
732
733  -- Constants for the clock periods.
734  constant kSPer : time :=   8.000 ns; -- 125.00 MHz
735  constant kMPer : time :=   5.050 ns; -- 198.00 MHz
736  constant kRPer : time := 100.000 ns; --  10.00 MHz
737
738  constant kRClksPerRePulsePeriodBitsMax : integer := 24;
739  constant kRClksPerRpPeriodBitsMax      : integer := 16;
740  constant kSClksPerSpPeriodBitsMax      : integer := 16;
741
742  -- Constants for the RP/SP pulses, based on the clock frequencies above. The periods
743  -- should all divide into one another without remainders, so this is safe to do...
744  -- High time is 50% duty cycle, or close to it if the period isn't a round number.
745  constant kRpPeriod           : time    :=  1000 ns;
746  constant kRpPeriodInRClks    : integer := kRpPeriod/kRPer;
747  constant kRpHighTimeInRClks  : integer := integer(floor(real(kRpPeriodInRClks)/2.0));
748  constant kRptPeriod          : time    := 25000 ns;
749  constant kRptPeriodInRClks   : integer := kRptPeriod/kRPer;
750  constant kRptHighTimeInRClks : integer := integer(floor(real(kRptPeriodInRClks)/2.0));
751  constant kSpPeriod           : time    :=   800 ns;
752  constant kSpPeriodInSClks    : integer := kSpPeriod/kSPer;
753  constant kSpHighTimeInSClks  : integer := integer(floor(real(kSpPeriodInSClks)/2.0));
754  constant kSptPeriod          : time    := 25000 ns;
755  constant kSptPeriodInSClks   : integer := kSptPeriod/kSPer;
756  constant kSptHighTimeInSClks : integer := integer(floor(real(kSptPeriodInSClks)/2.0));
757  constant kRePulsePeriod      : time    := 2.500 ms;
758  constant kRePulsePeriodInRClks   : integer := kRePulsePeriod/kRPer;
759  constant kRePulseHighTimeInRClks : integer := integer(floor(real(kRePulsePeriodInRClks)/2.0));
760
761  -- This doesn't come out to a nice number (or shouldn't), but that's ok. Round up.
762  constant kMeasClksPerRp : integer := kRpPeriod/kMPer+1;
763
764  -- Inputs to DUT
765  constant kPulsePeriodCntSize       : integer := integer(ceil(log2(real(kMeasClksPerRp))));
766  constant kFreqRefPeriodsToCheckSize: integer := 12; -- usually 17, but to save run time...
767  constant kSyncPeriodsToStampSize   : integer := 10;
768
769  constant kMeasurementTimeout : time :=
770             kMPer*(kMeasClksPerRp*(2**kSyncPeriodsToStampSize) +
771                    40*(2**kSyncPeriodsToStampSize) +
772                    kMeasClksPerRp*(2**kFreqRefPeriodsToCheckSize)
773                   );
774
775  --vhook_sigstart
776  signal aReset: boolean;
777  signal MeasClk: std_logic := '0';
778  signal mOffsetsDone: boolean;
779  signal mOffsetsValid: boolean;
780  signal mRpOffset: unsigned(kPulsePeriodCntSize+kSyncPeriodsToStampSize+kFreqRefPeriodsToCheckSize-1 downto 0);
781  signal mSpOffset: unsigned(kPulsePeriodCntSize+kSyncPeriodsToStampSize+kFreqRefPeriodsToCheckSize-1 downto 0);
782  signal RefClk: std_logic := '0';
783  signal rEnablePpsCrossing: boolean;
784  signal rEnableTdc: boolean;
785  signal rGatedPulseToPin: std_logic;
786  signal rLoadRePulseCounts: boolean;
787  signal rLoadRpCounts: boolean;
788  signal rLoadRptCounts: boolean;
789  signal rPpsPulse: boolean;
790  signal rPpsPulseCaptured: boolean;
791  signal rPulserEnableDelayVal: unsigned(3 downto 0);
792  signal rReRunEnable: boolean;
793  signal rResetTdc: boolean;
794  signal rResetTdcDone: boolean;
795  signal rRpTransfer: boolean;
796  signal SampleClk: std_logic := '0';
797  signal sGatedPulseToPin: std_logic;
798  signal sLoadSpCounts: boolean;
799  signal sLoadSptCounts: boolean;
800  signal sPpsClkCrossDelayVal: unsigned(3 downto 0);
801  signal sPpsPulse: boolean;
802  signal sSpTransfer: boolean;
803  --vhook_sigend
804
805  signal StopSim : boolean;
806  signal EnableOutputChecks : boolean := true;
807
808  signal ExpectedRpOutput,
809         ExpectedFinalMeas,
810         ExpectedSpOutput : real := 0.0;
811
812  alias mRunTdc is <<signal .tb_TdcTop.dutx.mRunTdc : boolean>>;
813  alias mSP is <<signal .tb_TdcTop.dutx.mSP : boolean>>;
814  alias mRP is <<signal .tb_TdcTop.dutx.mRP : boolean>>;
815
816  procedure ClkWait(
817    signal   Clk   : in std_logic;
818    X : positive := 1) is
819  begin
820    for i in 1 to X loop
821      wait until rising_edge(Clk);
822    end loop;
823  end procedure ClkWait;
824
825  function OffsetToReal (Offset : unsigned) return real is
826    variable TempVar : real := 0.0;
827  begin
828    TempVar :=
829      real(to_integer(
830        Offset(Offset'high downto kFreqRefPeriodsToCheckSize+kSyncPeriodsToStampSize))) +
831      real(to_integer(
832        Offset(kFreqRefPeriodsToCheckSize+kSyncPeriodsToStampSize-1 downto 0)))*
833      real(2.0**(-(kFreqRefPeriodsToCheckSize+kSyncPeriodsToStampSize)));
834    return TempVar;
835  end OffsetToReal;
836
837begin
838
839  SampleClk   <= not SampleClk   after kSPer/2 when not StopSim else '0';
840  RefClk      <= not RefClk      after kRPer/2 when not StopSim else '0';
841  MeasClk     <= not MeasClk     after kMPer/2 when not StopSim else '0';
842
843
844  main: process
845  begin
846    -- Defaults, per instructions in Purpose
847    sPpsClkCrossDelayVal  <= to_unsigned(0, sPpsClkCrossDelayVal'length);
848    rPulserEnableDelayVal <= to_unsigned(1, rPulserEnableDelayVal'length);
849    rResetTdc    <= true;
850    rEnableTdc   <= false;
851    rReRunEnable <= false;
852    rEnablePpsCrossing <= false;
853    rPpsPulse  <= false;
854    rLoadRePulseCounts <= false;
855    rLoadRpCounts  <= false;
856    rLoadRptCounts <= false;
857    sLoadSpCounts  <= false;
858    sLoadSptCounts <= false;
859
860    aReset <= true, false after kRPer*4;
861    ClkWait(RefClk,10);
862
863    -- Step 0 : -------------------------------------------------------------------------
864    -- Prior to de-asserting reset, we need to load the counters, so pulse the loads.
865    ClkWait(RefClk);
866    rLoadRePulseCounts <= true;
867    rLoadRpCounts  <= true;
868    rLoadRptCounts <= true;
869    ClkWait(RefClk);
870    rLoadRePulseCounts <= false;
871    rLoadRpCounts  <= false;
872    rLoadRptCounts <= false;
873    ClkWait(SampleClk);
874    sLoadSpCounts  <= true;
875    sLoadSptCounts <= true;
876    ClkWait(SampleClk);
877    sLoadSpCounts  <= false;
878    sLoadSptCounts <= false;
879
880
881    -- Step 1 : -------------------------------------------------------------------------
882    report "De-asserting Synchronous Reset..." severity note;
883    ClkWait(RefClk);
884    rResetTdc <= false;
885    wait until not rResetTdcDone for (kRPer*4)+(kMPer*2);
886    assert not rResetTdcDone
887      report "rRestTdcDone didn't de-assert in time"
888      severity error;
889
890
891    -- Step 2 : -------------------------------------------------------------------------
892    report "Enabling TDC Measurement & Capturing PPS..." severity note;
893    rEnableTdc <= true;
894    ClkWait(RefClk,5);
895
896    -- Trigger a PPS one-cycle pulse.
897    rPpsPulse <= true;
898    ClkWait(RefClk);
899    rPpsPulse <= false;
900    ClkWait(RefClk);
901    assert rPpsPulseCaptured report "PPS not captured" severity error;
902
903
904    -- Step 3 : -------------------------------------------------------------------------
905    report "Waiting for Measurements to Complete..." severity note;
906    wait until mOffsetsDone for kMeasurementTimeout;
907    assert mOffsetsDone
908      report "Offset measurements not completed within timeout"
909      severity error;
910
911    -- Offset values checked below in CheckOutput.
912
913    report "Printing Results..." & LF &
914       "RP:   " & real'image(OffsetToReal(mRpOffset)) &
915       " Expected: " & real'image(ExpectedRpOutput) & LF &
916       "SP:  " & real'image(OffsetToReal(mSpOffset)) &
917       " Expected: " & real'image(ExpectedSpOutput) & LF &
918       "Meas: " & real'image((OffsetToReal(mSpOffset-mRpOffset)*real(kMPer/1 ns)+
919                              real(kRPer/1 ns)-real(kSPer/1 ns))/real(kSPer/1 ns)) &
920       " Expected: " & real'image(ExpectedFinalMeas)
921      severity note;
922
923
924    -- Step 4 : -------------------------------------------------------------------------
925    -- Trigger another PPS one-cycle pulse to watch it all cross over correctly.
926    -- Issue the trigger around where a real PPS pulse will come (RE of RP).
927    -- First, set the programmable delay sPpsClkCrossDelayVal.
928    ClkWait(SampleClk);
929    sPpsClkCrossDelayVal <= to_unsigned(4, sPpsClkCrossDelayVal'length);
930    ClkWait(RefClk);
931    rEnablePpsCrossing   <= true;
932    wait until rRpTransfer and not rRpTransfer'delayed;
933    rPpsPulse <= true;
934    ClkWait(RefClk);
935    rPpsPulse <= false;
936    ClkWait(RefClk);
937
938    -- We expect the PPS output pulse to arrive after FE and RE of sSP have passed,
939    -- and then a few extra cycles of SampleClk delay on there as well.
940    wait until (not sSpTransfer) and (    sSpTransfer'delayed); -- FE
941    wait until (    sSpTransfer) and (not sSpTransfer'delayed); -- RE
942    ClkWait(SampleClk, 2 + to_integer(sPpsClkCrossDelayVal));
943    -- Check on falling edge of clock.
944    wait until falling_edge(SampleClk);
945    assert sPpsPulse and not sPpsPulse'delayed(kSPer) report "sPpsPulse did not assert";
946    wait until falling_edge(SampleClk);
947    assert not sPpsPulse report "sPpsPulse did not pulse correctly";
948
949
950    -- Step 5 : -------------------------------------------------------------------------
951    report "Repeating TDC Measurement..." severity note;
952    ClkWait(RefClk);
953    rReRunEnable <= true;
954
955    -- Now wait for the measurement to complete.
956    wait until mOffsetsValid for kMeasurementTimeout;
957    assert mOffsetsValid
958      report "Offset measurements not re-completed within timeout"
959      severity error;
960
961    -- Offset values checked below in CheckOutput.
962
963    report "Printing Results..." & LF &
964       "RP:   " & real'image(OffsetToReal(mRpOffset)) &
965       " Expected: " & real'image(ExpectedRpOutput) & LF &
966       "SP:   " & real'image(OffsetToReal(mSpOffset)) &
967       " Expected: " & real'image(ExpectedSpOutput) & LF &
968       "Meas: " & real'image((OffsetToReal(mSpOffset-mRpOffset)*real(kMPer/1 ns)+
969                              real(kRPer/1 ns)-real(kSPer/1 ns))/real(kSPer/1 ns)) &
970       " Expected: " & real'image(ExpectedFinalMeas)
971      severity note;
972
973    ClkWait(MeasClk,100);
974
975
976    -- Let it run for a while : ---------------------------------------------------------
977    for i in 0 to 9 loop
978      wait until mOffsetsValid for kMeasurementTimeout;
979      assert mOffsetsValid
980        report "Offset measurements not re-completed within timeout"
981        severity error;
982      report "Printing Results..." & LF &
983         "RP:   " & real'image(OffsetToReal(mRpOffset)) &
984         " Expected: " & real'image(ExpectedRpOutput) & LF &
985         "SP:   " & real'image(OffsetToReal(mSpOffset)) &
986         " Expected: " & real'image(ExpectedSpOutput) & LF &
987         "Meas: " & real'image((OffsetToReal(mSpOffset-mRpOffset)*real(kMPer/1 ns)+
988                                real(kRPer/1 ns)-real(kSPer/1 ns))/real(kSPer/1 ns)) &
989         " Expected: " & real'image(ExpectedFinalMeas)
990        severity note;
991    end loop;
992
993
994    -- And stop it : --------------------------------------------------------------------
995    report "Stopping Repeating TDC Measurements..." severity note;
996    ClkWait(RefClk);
997    rReRunEnable <= false;
998    -- Wait to make sure it doesn't keep going.
999    wait until mOffsetsValid
1000         for 2*(kMPer*(kMeasClksPerRp*(2**kSyncPeriodsToStampSize) + 40*(2**kSyncPeriodsToStampSize)));
1001    assert not mOffsetsValid;
1002
1003
1004
1005    -- Let it run for a while : ---------------------------------------------------------
1006    report "Starting again Repeating TDC Measurements..." severity note;
1007    ClkWait(RefClk);
1008    rReRunEnable <= true;
1009    for i in 0 to 2 loop
1010      wait until mOffsetsValid for kMeasurementTimeout;
1011      assert mOffsetsValid
1012        report "Offset measurements not re-completed within timeout"
1013        severity error;
1014      report "Printing Results..." & LF &
1015         "RP:   " & real'image(OffsetToReal(mRpOffset)) &
1016         " Expected: " & real'image(ExpectedRpOutput) & LF &
1017         "SP:   " & real'image(OffsetToReal(mSpOffset)) &
1018         " Expected: " & real'image(ExpectedSpOutput) & LF &
1019         "Meas: " & real'image((OffsetToReal(mSpOffset-mRpOffset)*real(kMPer/1 ns)+
1020                                real(kRPer/1 ns)-real(kSPer/1 ns))/real(kSPer/1 ns)) &
1021         " Expected: " & real'image(ExpectedFinalMeas)
1022        severity note;
1023    end loop;
1024
1025
1026    StopSim <= true;
1027    wait;
1028  end process;
1029
1030
1031  ExpectedFinalMeasGen : process
1032    variable StartTime : time := 0 ns;
1033  begin
1034    wait until rPpsPulse;
1035    wait until rRpTransfer;
1036    StartTime := now;
1037    wait until sSpTransfer;
1038    ExpectedFinalMeas <= real((now - StartTime)/1 ps)/real((kSPer/1 ps));
1039    wait until rResetTdc;
1040  end process;
1041
1042
1043  ExpectedRpOutputGen : process
1044    variable StartTime : time := 0 ns;
1045  begin
1046    wait until mRunTdc;
1047    StartTime := now;
1048    wait until mRP;
1049    ExpectedRpOutput <= real((now - StartTime)/1 ps)/real((kMPer/1 ps));
1050    wait until mOffsetsValid;
1051  end process;
1052
1053  ExpectedSpOutputGen : process
1054    variable StartTime : time := 0 ns;
1055  begin
1056    wait until mRunTdc;
1057    StartTime := now;
1058    wait until mSP;
1059    ExpectedSpOutput <= real((now - StartTime)/1 ps)/real((kMPer/1 ps));
1060    wait until mOffsetsValid;
1061  end process;
1062
1063  CheckOutput : process(MeasClk)
1064  begin
1065    if falling_edge(MeasClk) then
1066      if EnableOutputChecks then
1067
1068        if mOffsetsValid then
1069          assert (OffsetToReal(mRpOffset) < ExpectedRpOutput + 1.0) and
1070                 (OffsetToReal(mRpOffset) > ExpectedRpOutput - 1.0)
1071            report "Mismatch between mRpOffset and expected!" & LF &
1072               "Actual: " & real'image(OffsetToReal(mRpOffset)) & LF &
1073               "Expect: " & real'image(ExpectedRpOutput)
1074            severity error;
1075          assert (OffsetToReal(mSpOffset) < ExpectedSpOutput + 1.0) and
1076                 (OffsetToReal(mSpOffset) > ExpectedSpOutput - 1.0)
1077            report "Mismatch between mSpOffset and expected!" & LF &
1078               "Actual: " & real'image(OffsetToReal(mSpOffset)) & LF &
1079               "Expect: " & real'image(ExpectedSpOutput)
1080            severity error;
1081        end if;
1082      end if;
1083    end if;
1084  end process;
1085
1086
1087  --vhook_e TdcTop dutx
1088  --vhook_a rRpPeriodInRClks    to_unsigned(kRpPeriodInRClks,   kRClksPerRpPeriodBitsMax)
1089  --vhook_a rRpHighTimeInRClks  to_unsigned(kRpHighTimeInRClks, kRClksPerRpPeriodBitsMax)
1090  --vhook_a sSpPeriodInSClks    to_unsigned(kSpPeriodInSClks,   kSClksPerSpPeriodBitsMax)
1091  --vhook_a sSpHighTimeInSClks  to_unsigned(kSpHighTimeInSClks, kSClksPerSpPeriodBitsMax)
1092  --vhook_a rRptPeriodInRClks   to_unsigned(kRptPeriodInRClks,   kRClksPerRpPeriodBitsMax)
1093  --vhook_a rRptHighTimeInRClks to_unsigned(kRptHighTimeInRClks, kRClksPerRpPeriodBitsMax)
1094  --vhook_a sSptPeriodInSClks   to_unsigned(kSptPeriodInSClks,   kSClksPerSpPeriodBitsMax)
1095  --vhook_a sSptHighTimeInSClks to_unsigned(kSptHighTimeInSClks, kSClksPerSpPeriodBitsMax)
1096  --vhook_a rRePulsePeriodInRClks   to_unsigned(kRePulsePeriodInRClks,   kRClksPerRePulsePeriodBitsMax)
1097  --vhook_a rRePulseHighTimeInRClks to_unsigned(kRePulseHighTimeInRClks, kRClksPerRePulsePeriodBitsMax)
1098  dutx: entity work.TdcTop (struct)
1099    generic map (
1100      kRClksPerRePulsePeriodBitsMax => kRClksPerRePulsePeriodBitsMax,  --integer range 3:32 :=24
1101      kRClksPerRpPeriodBitsMax      => kRClksPerRpPeriodBitsMax,       --integer range 3:16 :=16
1102      kSClksPerSpPeriodBitsMax      => kSClksPerSpPeriodBitsMax,       --integer range 3:16 :=16
1103      kPulsePeriodCntSize           => kPulsePeriodCntSize,            --integer:=13
1104      kFreqRefPeriodsToCheckSize    => kFreqRefPeriodsToCheckSize,     --integer:=17
1105      kSyncPeriodsToStampSize       => kSyncPeriodsToStampSize)        --integer:=10
1106    port map (
1107      aReset                  => aReset,                                                               --in  boolean
1108      RefClk                  => RefClk,                                                               --in  std_logic
1109      SampleClk               => SampleClk,                                                            --in  std_logic
1110      MeasClk                 => MeasClk,                                                              --in  std_logic
1111      rResetTdc               => rResetTdc,                                                            --in  boolean
1112      rResetTdcDone           => rResetTdcDone,                                                        --out boolean
1113      rEnableTdc              => rEnableTdc,                                                           --in  boolean
1114      rReRunEnable            => rReRunEnable,                                                         --in  boolean
1115      rPpsPulse               => rPpsPulse,                                                            --in  boolean
1116      rPpsPulseCaptured       => rPpsPulseCaptured,                                                    --out boolean
1117      rPulserEnableDelayVal   => rPulserEnableDelayVal,                                                --in  unsigned(3:0)
1118      rEnablePpsCrossing      => rEnablePpsCrossing,                                                   --in  boolean
1119      sPpsClkCrossDelayVal    => sPpsClkCrossDelayVal,                                                 --in  unsigned(3:0)
1120      sPpsPulse               => sPpsPulse,                                                            --out boolean
1121      mRpOffset               => mRpOffset,                                                            --out unsigned(kPulsePeriodCntSize+ kSyncPeriodsToStampSize+ kFreqRefPeriodsToCheckSize-1:0)
1122      mSpOffset               => mSpOffset,                                                            --out unsigned(kPulsePeriodCntSize+ kSyncPeriodsToStampSize+ kFreqRefPeriodsToCheckSize-1:0)
1123      mOffsetsDone            => mOffsetsDone,                                                         --out boolean
1124      mOffsetsValid           => mOffsetsValid,                                                        --out boolean
1125      rLoadRePulseCounts      => rLoadRePulseCounts,                                                   --in  boolean
1126      rRePulsePeriodInRClks   => to_unsigned(kRePulsePeriodInRClks, kRClksPerRePulsePeriodBitsMax),    --in  unsigned(kRClksPerRePulsePeriodBitsMax-1:0)
1127      rRePulseHighTimeInRClks => to_unsigned(kRePulseHighTimeInRClks, kRClksPerRePulsePeriodBitsMax),  --in  unsigned(kRClksPerRePulsePeriodBitsMax-1:0)
1128      rLoadRpCounts           => rLoadRpCounts,                                                        --in  boolean
1129      rRpPeriodInRClks        => to_unsigned(kRpPeriodInRClks, kRClksPerRpPeriodBitsMax),              --in  unsigned(kRClksPerRpPeriodBitsMax-1:0)
1130      rRpHighTimeInRClks      => to_unsigned(kRpHighTimeInRClks, kRClksPerRpPeriodBitsMax),            --in  unsigned(kRClksPerRpPeriodBitsMax-1:0)
1131      rLoadRptCounts          => rLoadRptCounts,                                                       --in  boolean
1132      rRptPeriodInRClks       => to_unsigned(kRptPeriodInRClks, kRClksPerRpPeriodBitsMax),             --in  unsigned(kRClksPerRpPeriodBitsMax-1:0)
1133      rRptHighTimeInRClks     => to_unsigned(kRptHighTimeInRClks, kRClksPerRpPeriodBitsMax),           --in  unsigned(kRClksPerRpPeriodBitsMax-1:0)
1134      sLoadSpCounts           => sLoadSpCounts,                                                        --in  boolean
1135      sSpPeriodInSClks        => to_unsigned(kSpPeriodInSClks, kSClksPerSpPeriodBitsMax),              --in  unsigned(kSClksPerSpPeriodBitsMax-1:0)
1136      sSpHighTimeInSClks      => to_unsigned(kSpHighTimeInSClks, kSClksPerSpPeriodBitsMax),            --in  unsigned(kSClksPerSpPeriodBitsMax-1:0)
1137      sLoadSptCounts          => sLoadSptCounts,                                                       --in  boolean
1138      sSptPeriodInSClks       => to_unsigned(kSptPeriodInSClks, kSClksPerSpPeriodBitsMax),             --in  unsigned(kSClksPerSpPeriodBitsMax-1:0)
1139      sSptHighTimeInSClks     => to_unsigned(kSptHighTimeInSClks, kSClksPerSpPeriodBitsMax),           --in  unsigned(kSClksPerSpPeriodBitsMax-1:0)
1140      rRpTransfer             => rRpTransfer,                                                          --out boolean
1141      sSpTransfer             => sSpTransfer,                                                          --out boolean
1142      rGatedPulseToPin        => rGatedPulseToPin,                                                     --inout std_logic
1143      sGatedPulseToPin        => sGatedPulseToPin);                                                    --inout std_logic
1144
1145
1146end test;
1147--synopsys translate_on
1148