clash-prelude-1.0.0: CAES Language for Synchronous Hardware - Prelude library
Copyright(C) 2018 Google Inc.
2019 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Signal.Trace

Description

Utilities for tracing signals and dumping them in various ways. Example usage:

import Clash.Prelude hiding (writeFile)
import Data.Text.IO  (writeFile)

-- | Count and wrap around
subCounter :: SystemClockResetEnable => Signal System (Index 3)
subCounter = traceSignal1 "sub" counter
  where
    counter =
      register 0 (fmap succ' counter)

    succ' c
      | c == maxBound = 0
      | otherwise     = c + 1

-- | Count, but only when my subcounter is wrapping around
mainCounter :: SystemClockResetEnable => Signal System (Signed 64)
mainCounter = traceSignal1 "main" counter
  where
    counter =
      register 0 (fmap succ' $ bundle (subcounter,counter))

    succ' (sc, c)
      | sc == maxBound = c + 1
      | otherwise      = c

-- | Collect traces, and dump them to a VCD file.
main :: SystemClockResetEnable => IO ()
main = do
  let cntrOut = exposeClockResetEnable mainCounter systemClockGen systemResetGen
  vcd <- dumpVCD (0, 100) cntrOut ["main", "sub"]
  case vcd of
    Left msg ->
      error msg
    Right contents ->
      writeFile "mainCounter.vcd" contents
Synopsis

Tracing functions

Simple

traceSignal1 Source #

Arguments

:: (KnownNat (BitSize a), BitPack a, NFDataX a, Typeable a) 
=> String

Name of signal in the VCD output

-> Signal dom a

Signal to trace

-> Signal dom a 

Trace a single signal. Will emit an error if a signal with the same name was previously registered.

NB associates the traced signal with a clock period of 1, which results in incorrect VCD files when working with circuits that have multiple clocks. Use traceSignal when working with circuits that have multiple clocks.

traceVecSignal1 Source #

Arguments

:: (KnownNat (BitSize a), KnownNat n, BitPack a, NFDataX a, Typeable a) 
=> String

Name of signal in debugging output. Will be appended by _0, _1, ..., _n.

-> Signal dom (Vec (n + 1) a)

Signal to trace

-> Signal dom (Vec (n + 1) a) 

Trace a single vector signal: each element in the vector will show up as a different trace. If the trace name already exists, this function will emit an error.

NB associates the traced signal with a clock period of 1, which results in incorrect VCD files when working with circuits that have multiple clocks. Use traceSignal when working with circuits that have multiple clocks.

Tracing in a multi-clock environment

traceSignal Source #

Arguments

:: forall dom a. (KnownDomain dom, KnownNat (BitSize a), BitPack a, NFDataX a, Typeable a) 
=> String

Name of signal in the VCD output

-> Signal dom a

Signal to trace

-> Signal dom a 

Trace a single signal. Will emit an error if a signal with the same name was previously registered.

NB Works correctly when creating VCD files from traced signal in multi-clock circuits. However traceSignal1 might be more convenient to use when the domain of your circuit is polymorphic.

traceVecSignal Source #

Arguments

:: forall dom a n. (KnownDomain dom, KnownNat (BitSize a), KnownNat n, BitPack a, NFDataX a, Typeable a) 
=> String

Name of signal in debugging output. Will be appended by _0, _1, ..., _n.

-> Signal dom (Vec (n + 1) a)

Signal to trace

-> Signal dom (Vec (n + 1) a) 

Trace a single vector signal: each element in the vector will show up as a different trace. If the trace name already exists, this function will emit an error.

NB Works correctly when creating VCD files from traced signal in multi-clock circuits. However traceSignal1 might be more convinient to use when the domain of your circuit is polymorphic.

VCD dump functions

dumpVCD Source #

Arguments

:: NFDataX a 
=> (Int, Int)

(offset, number of samples)

-> Signal dom a

(One of) the outputs of the circuit containing the traces

-> [String]

The names of the traces you definitely want to be dumped in the VCD file

-> IO (Either String Text) 

Produce a four-state VCD (Value Change Dump) according to IEEE 1364-{1995,2001}. This function fails if a trace name contains either non-printable or non-VCD characters.

Due to lazy evaluation, the created VCD files might not contain all the traces you were expecting. You therefore have to provide a list of names you definately want to be dumped in the VCD file.

For example:

vcd <- dumpVCD (0, 100) cntrOut ["main", "sub"]

Evaluates cntrOut long enough in order for to guarantee that the main, and sub traces end up in the generated VCD file.

Replay functions

dumpReplayable Source #

Arguments

:: forall a dom. NFDataX a 
=> Int

Number of samples

-> Signal dom a

(One of) the outputs of the circuit containing the traces

-> String

Name of trace to dump

-> IO ByteString 

Dump a number of samples to a replayable bytestring.

replay :: forall a dom n. (Typeable a, NFDataX a, BitPack a, KnownNat n, n ~ BitSize a) => ByteString -> Either String (Signal dom a) Source #

Take a serialized signal (dumped with dumpReplayable) and convert it back into a signal. Will error if dumped type does not match requested type. The first value in the signal that fails to decode will stop the decoding process and yield an error. Not that this always happens if you evaluate more values than were originally dumped.

Internal

Types

type Width = Int Source #

type TraceMap = Map String (TypeRepBS, Period, Width, [Value]) Source #

Functions

traceSignal# Source #

Arguments

:: forall dom a. (KnownNat (BitSize a), BitPack a, NFDataX a, Typeable a) 
=> IORef TraceMap

Map to store the trace

-> Int

The associated clock period for the trace

-> String

Name of signal in the VCD output

-> Signal dom a

Signal to trace

-> IO (Signal dom a) 

Trace a single signal. Will emit an error if a signal with the same name was previously registered.

traceVecSignal# Source #

Arguments

:: forall dom n a. (KnownNat (BitSize a), KnownNat n, BitPack a, NFDataX a, Typeable a) 
=> IORef TraceMap

Map to store the traces

-> Int

Associated clock period for the trace

-> String

Name of signal in the VCD output. Will be appended by _0, _1, ..., _n.

-> Signal dom (Vec (n + 1) a)

Signal to trace

-> IO (Signal dom (Vec (n + 1) a)) 

Trace a single vector signal: each element in the vector will show up as a different trace. If the trace name already exists, this function will emit an error.

dumpVCD# Source #

Arguments

:: NFDataX a 
=> IORef TraceMap

Map with collected traces

-> (Int, Int)

(offset, number of samples)

-> Signal dom a

(One of) the output(s) the circuit containing the traces

-> [String]

The names of the traces you definitely want to be dumped to the VCD file

-> IO (Either String Text) 

Same as dumpVCD, but supplied with a custom tracemap

dumpVCD## Source #

Arguments

:: (Int, Int)

(offset, number of samples)

-> TraceMap 
-> UTCTime 
-> Either String Text 

Same as dumpVCD, but supplied with a custom tracemap and a custom timestamp

waitForTraces# Source #

Arguments

:: NFDataX a 
=> IORef TraceMap

Map with collected traces

-> Signal dom a

(One of) the output(s) the circuit containing the traces

-> [String]

The names of the traces you definitely want to be dumped to the VCD file

-> IO () 

Keep evaluating given signal until all trace names are present.

traceMap# :: IORef TraceMap Source #

Map of traces used by the non-internal trace and dumpvcd functions.