{-# LANGUAGE CPP #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE QuasiQuotes #-}
module Clash.Explicit.Verification
(
Assertion
, Property
, AssertionValue
, RenderAs(..)
, name
, lit
, not
, and
, or
, implies
, next
, nextN
, before
, timplies
, timpliesOverlapping
, always
, never
, eventually
, assert
, cover
, assume
, check
, checkI
, hideAssertion
)
where
import Prelude
(Bool, Word, (.), pure, max, concat)
import Data.Text (Text)
import Data.Maybe (Maybe(Just))
import Data.String.Interpolate (__i)
import Clash.Annotations.Primitive
(Primitive(InlineYamlPrimitive), HDL(..))
import Clash.Signal.Internal (KnownDomain, Signal, Clock, Reset)
import Clash.XException (errorX, hwSeqX)
import Clash.Verification.Internal
name :: Text -> Signal dom Bool -> Assertion dom
name nm signal = Assertion IsNotTemporal (CvPure (Just nm, signal))
{-# INLINE name #-}
lit :: Bool -> Assertion dom
lit = Assertion IsNotTemporal . CvLit
{-# INLINE lit #-}
not :: AssertionValue dom a => a -> Assertion dom
not (toAssertionValue -> a) = Assertion (isTemporal a) (CvNot (assertion a))
{-# INLINE not #-}
and :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom
and (toAssertionValue -> a) (toAssertionValue -> b) =
Assertion
(max (isTemporal a) (isTemporal b))
(CvAnd (assertion a) (assertion b))
{-# INLINE and #-}
or :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom
or (toAssertionValue -> a) (toAssertionValue -> b) =
Assertion
(max (isTemporal a) (isTemporal b))
(CvOr (assertion a) (assertion b))
{-# INLINE or #-}
implies :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom
implies (toAssertionValue -> Assertion aTmp a) (toAssertionValue -> Assertion bTmp b) =
Assertion (max aTmp bTmp) (CvImplies a b)
{-# INLINE implies #-}
next :: AssertionValue dom a => a -> Assertion dom
next = nextN 1
{-# INLINE next #-}
nextN :: AssertionValue dom a => Word -> a -> Assertion dom
nextN n = Assertion IsTemporal . CvNext n . assertion . toAssertionValue
{-# INLINE nextN #-}
before :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom
before a0 b0 = Assertion IsTemporal (CvBefore a1 b1)
where
a1 = assertion (toAssertionValue a0)
b1 = assertion (toAssertionValue b0)
{-# INLINE before #-}
timplies :: (AssertionValue dom a, AssertionValue dom b) => a -> b -> Assertion dom
timplies a0 b0 = Assertion IsTemporal (CvTemporalImplies 1 a1 b1)
where
a1 = toTemporal (toAssertionValue a0)
b1 = toTemporal (toAssertionValue b0)
{-# INLINE timplies #-}
timpliesOverlapping
:: (AssertionValue dom a, AssertionValue dom b)
=> a
-> b
-> Assertion dom
timpliesOverlapping a0 b0 =
Assertion IsTemporal (CvTemporalImplies 0 a1 b1)
where
a1 = toTemporal (toAssertionValue a0)
b1 = toTemporal (toAssertionValue b0)
{-# INLINE timpliesOverlapping #-}
always :: AssertionValue dom a => a -> Assertion dom
always = Assertion IsTemporal . CvAlways . assertion . toAssertionValue
{-# INLINE always #-}
never :: AssertionValue dom a => a -> Assertion dom
never = Assertion IsTemporal . CvNever . assertion . toAssertionValue
{-# INLINE never #-}
eventually :: AssertionValue dom a => a -> Assertion dom
eventually = Assertion IsTemporal . CvEventually . assertion . toAssertionValue
{-# INLINE eventually #-}
assert :: AssertionValue dom a => a -> Property dom
assert = Property . CvAssert . assertion . toAssertionValue
{-# INLINE assert #-}
cover :: AssertionValue dom a => a -> Property dom
cover = Property . CvCover . assertion . toAssertionValue
{-# INLINE cover #-}
assume :: AssertionValue dom a => a -> Property dom
assume = Property . CvAssume . assertion . toAssertionValue
{-# INLINE assume #-}
check
:: KnownDomain dom
=> Clock dom
-> Reset dom
-> Text
-> RenderAs
-> Property dom
-> Signal dom AssertionResult
check !_clk !_rst !_propName !_renderAs !_prop =
pure (errorX (concat [
"Simulation for Clash.Verification not yet implemented. If you need this,"
, " create an issue at https://github.com/clash-compiler/clash-lang/issues." ]))
{-# CLASH_OPAQUE check #-}
{-# ANN check (InlineYamlPrimitive [Verilog, SystemVerilog, VHDL] [__i|
BlackBoxHaskell:
name: Clash.Explicit.Verification.check
templateFunction: Clash.Primitives.Verification.checkBBF
|]) #-}
checkI
:: KnownDomain dom
=> Clock dom
-> Reset dom
-> Text
-> RenderAs
-> Property dom
-> Signal dom a
-> Signal dom a
checkI clk rst propName renderAs prop =
hideAssertion (check clk rst propName renderAs prop)
hideAssertion :: Signal dom AssertionResult -> Signal dom a -> Signal dom a
hideAssertion = hwSeqX