{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise #-}
module Clash.Signal.Trace
(
traceSignal1
, traceVecSignal1
, traceSignal
, traceVecSignal
, dumpVCD
, dumpReplayable
, replay
, Period
, Changed
, Value
, Width
, TraceMap
, TypeRepBS
, traceSignal#
, traceVecSignal#
, dumpVCD#
, dumpVCD##
, waitForTraces#
, traceMap#
) where
import Clash.Annotations.Primitive (hasBlackBox)
import Clash.Signal.Internal (fromList)
import Clash.Signal
(KnownDomain(..), SDomainConfiguration(..), Signal, bundle, unbundle)
import Clash.Sized.Vector (Vec, iterateI)
import qualified Clash.Sized.Vector as Vector
import Clash.Class.BitPack (BitPack, BitSize, pack, unpack)
import Clash.Promoted.Nat (snatToNum, SNat(..))
import Clash.Signal.Internal (Signal ((:-)), sample)
import Clash.XException (deepseqX, NFDataX)
import Clash.Sized.Internal.BitVector
(BitVector(BV))
import Control.Monad (foldM)
import Data.Bits (testBit)
import Data.Binary (encode, decodeOrFail)
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as ByteStringLazy
import Data.Char (ord, chr)
import Data.IORef
(IORef, atomicModifyIORef', atomicWriteIORef, newIORef, readIORef)
import Data.List (foldl1', foldl', unzip4, transpose, uncons)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe, catMaybes)
import qualified Data.Text as Text
import Data.Time.Clock (UTCTime, getCurrentTime)
import Data.Time.Format (formatTime, defaultTimeLocale)
import GHC.Natural (Natural)
import GHC.Stack (HasCallStack)
import GHC.TypeLits (KnownNat, type (+))
import System.IO.Unsafe (unsafePerformIO)
import Type.Reflection (Typeable, TypeRep, typeRep)
#ifdef CABAL
import qualified Data.Version
import qualified Paths_clash_prelude
#endif
type Period = Int
type Changed = Bool
type Value = (Natural, Natural)
type Width = Int
type TypeRepBS = ByteString
type TraceMap = Map.Map String (TypeRepBS, Period, Width, [Value])
traceMap# :: IORef TraceMap
traceMap# = unsafePerformIO (newIORef Map.empty)
{-# CLASH_OPAQUE traceMap# #-}
mkTrace
:: HasCallStack
=> BitPack a
=> NFDataX a
=> Signal dom a
-> [Value]
mkTrace signal = sample (unsafeToTup . pack <$> signal)
where
unsafeToTup (BV mask value) = (mask, value)
traceSignal#
:: forall dom a
. ( BitPack a
, NFDataX a
, Typeable a )
=> IORef TraceMap
-> Int
-> String
-> Signal dom a
-> IO (Signal dom a)
traceSignal# traceMap period traceName signal =
atomicModifyIORef' traceMap $ \m ->
if Map.member traceName m then
error $ "Already tracing a signal with the name: '" ++ traceName ++ "'."
else
( Map.insert
traceName
( encode (typeRep @a)
, period
, width
, mkTrace signal)
m
, signal)
where
width = snatToNum (SNat @(BitSize a))
{-# CLASH_OPAQUE traceSignal# #-}
traceVecSignal#
:: forall dom n a
. ( KnownNat n
, BitPack a
, NFDataX a
, Typeable a )
=> IORef TraceMap
-> Int
-> String
-> Signal dom (Vec (n+1) a)
-> IO (Signal dom (Vec (n+1) a))
traceVecSignal# traceMap period vecTraceName (unbundle -> vecSignal) =
fmap bundle . sequenceA $
Vector.zipWith trace' (iterateI succ (0 :: Int)) vecSignal
where
trace' i s = traceSignal# traceMap period (name' i) s
name' i = vecTraceName ++ "_" ++ show i
{-# CLASH_OPAQUE traceVecSignal# #-}
traceSignal
:: forall dom a
. ( KnownDomain dom
, BitPack a
, NFDataX a
, Typeable a )
=> String
-> Signal dom a
-> Signal dom a
traceSignal traceName signal =
case knownDomain @dom of
SDomainConfiguration{sPeriod} ->
unsafePerformIO $
traceSignal# traceMap# (snatToNum sPeriod) traceName signal
{-# CLASH_OPAQUE traceSignal #-}
{-# ANN traceSignal hasBlackBox #-}
traceSignal1
:: ( BitPack a
, NFDataX a
, Typeable a )
=> String
-> Signal dom a
-> Signal dom a
traceSignal1 traceName signal =
unsafePerformIO (traceSignal# traceMap# 1 traceName signal)
{-# CLASH_OPAQUE traceSignal1 #-}
{-# ANN traceSignal1 hasBlackBox #-}
traceVecSignal
:: forall dom a n
. ( KnownDomain dom
, KnownNat n
, BitPack a
, NFDataX a
, Typeable a )
=> String
-> Signal dom (Vec (n+1) a)
-> Signal dom (Vec (n+1) a)
traceVecSignal traceName signal =
case knownDomain @dom of
SDomainConfiguration{sPeriod} ->
unsafePerformIO $
traceVecSignal# traceMap# (snatToNum sPeriod) traceName signal
{-# CLASH_OPAQUE traceVecSignal #-}
{-# ANN traceVecSignal hasBlackBox #-}
traceVecSignal1
:: ( KnownNat n
, BitPack a
, NFDataX a
, Typeable a )
=> String
-> Signal dom (Vec (n+1) a)
-> Signal dom (Vec (n+1) a)
traceVecSignal1 traceName signal =
unsafePerformIO $ traceVecSignal# traceMap# 1 traceName signal
{-# CLASH_OPAQUE traceVecSignal1 #-}
{-# ANN traceVecSignal1 hasBlackBox #-}
iso8601Format :: UTCTime -> String
iso8601Format = formatTime defaultTimeLocale "%Y-%m-%dT%H:%M:%S"
toPeriodMap :: TraceMap -> Map.Map Period [(String, Width, [Value])]
toPeriodMap m = foldl' go Map.empty (Map.assocs m)
where
go periodMap (traceName, (_rep, period, width, values)) =
Map.alter (Just . go') period periodMap
where
go' = ((traceName, width, values):) . (fromMaybe [])
flattenMap :: Map.Map a [b] -> [(a, b)]
flattenMap m = concat [[(a, b) | b <- bs] | (a, bs) <- Map.assocs m]
printable :: Char -> Bool
printable (ord -> c) = 33 <= c && c <= 126
dumpVCD##
:: (Int, Int)
-> TraceMap
-> UTCTime
-> Either String Text.Text
dumpVCD## (offset, cycles) traceMap now
| offset < 0 =
error $ "dumpVCD: offset was " ++ show offset ++ ", but cannot be negative."
| cycles < 0 =
error $ "dumpVCD: cycles was " ++ show cycles ++ ", but cannot be negative."
| null traceMap =
error $ "dumpVCD: no traces found. Extend the given trace names."
| Map.size traceMap > 126 - 33 =
Left $ "Tracemap contains more than 93 traces, which is not supported by VCD."
| (nm:_) <- offensiveNames =
Left $ unwords [ "Trace '" ++ nm ++ "' contains"
, "non-printable ASCII characters, which is not"
, "supported by VCD." ]
| otherwise =
Right $ Text.unlines [ Text.unwords headerDate
, Text.unwords headerVersion
, Text.unwords headerComment
, Text.pack $ unwords headerTimescale
, "$scope module logic $end"
, Text.intercalate "\n" headerWires
, "$upscope $end"
, "$enddefinitions $end"
, "#0"
, "$dumpvars"
, Text.intercalate "\n" initValues
, "$end"
, Text.intercalate "\n" $ catMaybes bodyParts
]
where
offensiveNames = filter (any (not . printable)) traceNames
labels = map chr [33..126]
timescale = foldl1' gcd (Map.keys periodMap)
periodMap = toPeriodMap traceMap
(periods, traceNames, widths, valuess) =
unzip4 $ map
(\(a, (b, c, d)) -> (a, b, c, d))
(flattenMap periodMap)
periods' = map (`quot` timescale) periods
valuess' = map slice $ zipWith normalize periods' valuess
normalize period values = concatMap (replicate period) values
slice values = drop offset $ take cycles values
headerDate = ["$date", Text.pack $ iso8601Format now, "$end"]
#ifdef CABAL
clashVer = Data.Version.showVersion Paths_clash_prelude.version
#else
clashVer = "development"
#endif
headerVersion = ["$version", "Generated by Clash", Text.pack clashVer , "$end"]
headerComment = ["$comment", "No comment", "$end"]
headerTimescale = ["$timescale", (show timescale) ++ "ps", "$end"]
headerWires = [ Text.unwords $ headerWire w l n
| (w, l, n) <- (zip3 widths labels traceNames)]
headerWire w l n = map Text.pack ["$var wire", show w, [l], n, "$end"]
initValues = map Text.pack $ zipWith ($) formatters inits
formatters = zipWith format widths labels
inits = map (maybe (error "dumpVCD##: empty value") fst . uncons) valuess'
tails = map changed valuess'
format :: Width -> Char -> Value -> String
format 1 label (0,0) = ['0', label, '\n']
format 1 label (0,1) = ['1', label, '\n']
format 1 label (1,_) = ['x', label, '\n']
format 1 label (mask,val) =
error $ "Can't format 1 bit wide value for " ++ show label ++ ": value " ++ show val ++ " and mask " ++ show mask
format n label (mask,val) =
"b" ++ map digit (reverse [0..n-1]) ++ " " ++ [label]
where
digit d = case (testBit mask d, testBit val d) of
(False,False) -> '0'
(False,True) -> '1'
(True,_) -> 'x'
changed :: [Value] -> [(Changed, Value)]
changed (s:ss) = zip (zipWith (/=) (s:ss) ss) ss
changed [] = []
bodyParts :: [Maybe Text.Text]
bodyParts = zipWith go [0..] (map bodyPart (Data.List.transpose tails))
where
go :: Int -> Maybe Text.Text -> Maybe Text.Text
go (Text.pack . show -> n) t =
let pre = Text.concat ["#", n, "\n"] in
fmap (Text.append pre) t
bodyPart :: [(Changed, Value)] -> Maybe Text.Text
bodyPart values =
let formatted = [(c, f v) | (f, (c,v)) <- zip formatters values]
formatted' = map (Text.pack . snd) $ filter fst $ formatted in
if null formatted' then Nothing else Just $ Text.intercalate "\n" formatted'
dumpVCD#
:: NFDataX a
=> IORef TraceMap
-> (Int, Int)
-> Signal dom a
-> [String]
-> IO (Either String Text.Text)
dumpVCD# traceMap slice signal traceNames = do
waitForTraces# traceMap signal traceNames
m <- readIORef traceMap
fmap (dumpVCD## slice m) getCurrentTime
dumpVCD
:: NFDataX a
=> (Int, Int)
-> Signal dom a
-> [String]
-> IO (Either String Text.Text)
dumpVCD = dumpVCD# traceMap#
dumpReplayable
:: forall a dom
. NFDataX a
=> Int
-> Signal dom a
-> String
-> IO ByteString
dumpReplayable n oSignal traceName = do
waitForTraces# traceMap# oSignal [traceName]
replaySignal <- (Map.! traceName) <$> readIORef traceMap#
let (tRep, _period, _width, samples) = replaySignal
pure (ByteStringLazy.concat (tRep : map encode (take n samples)))
replay
:: forall a dom n
. ( Typeable a
, NFDataX a
, BitPack a
, KnownNat n
, n ~ BitSize a )
=> ByteString
-> Either String (Signal dom a)
replay bytes0 = samples1
where
samples1 =
case decodeOrFail bytes0 of
Left (_, _, err) ->
Left ("Failed to decode typeRep. Parser reported:\n\n" ++ err)
Right (bytes1, _, _ :: TypeRep a) ->
let samples0 = decodeSamples bytes1 in
let err = "Failed to decode value in signal. Parser reported:\n\n " in
Right (fromList (map (either (error . (err ++)) id) samples0))
decodeSamples
:: forall a n
. ( BitPack a
, KnownNat n
, n ~ BitSize a )
=> ByteString
-> [Either String a]
decodeSamples bytes0 =
case decodeOrFail bytes0 of
Left (_, _, err) ->
[Left err]
Right (bytes1, _, (m, v)) ->
(Right (unpack (BV m v))) : decodeSamples bytes1
waitForTraces#
:: NFDataX a
=> IORef TraceMap
-> Signal dom a
-> [String]
-> IO ()
waitForTraces# traceMap signal traceNames = do
atomicWriteIORef traceMap Map.empty
rest <- foldM go signal traceNames
seq rest (return ())
where
go (s0 :- ss) nm = do
m <- readIORef traceMap
if Map.member nm m then
deepseqX s0 (return ss)
else
deepseqX
s0
(go ss nm)