{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Clash.Verification.Internal
( AssertionResult(..)
, Property(..)
, Assertion(..)
, RenderAs(..)
, IsTemporal(..)
, AssertionValue(toAssertionValue)
, Assertion'(..)
, Property'(..)
, toTemporal
, isTemporal
, assertion
)
where
import Data.Text (Text)
import Clash.Annotations.BitRepresentation
(ConstrRepr(..), DataReprAnn(..), liftQ)
import Clash.Signal.Internal (Domain, Signal)
data RenderAs
= PSL
| SVA
| AutoRenderAs
| YosysFormal
deriving (Show, Eq)
data IsTemporal
= IsNotTemporal
| IsTemporal
deriving (Eq, Ord)
data Assertion' a
= CvPure a
| CvToTemporal (Assertion' a)
| CvLit Bool
| CvNot (Assertion' a)
| CvAnd (Assertion' a) (Assertion' a)
| CvOr (Assertion' a) (Assertion' a)
| CvImplies (Assertion' a) (Assertion' a)
| CvNext Word (Assertion' a)
| CvBefore (Assertion' a) (Assertion' a)
| CvTemporalImplies Word (Assertion' a) (Assertion' a)
| CvAlways (Assertion' a)
| CvNever (Assertion' a)
| CvEventually (Assertion' a)
deriving (Show, Functor, Foldable, Traversable)
data Property' a
= CvAssert (Assertion' a)
| CvCover (Assertion' a)
| CvAssume (Assertion' a)
deriving (Show, Functor, Foldable, Traversable)
data Assertion (dom :: Domain) =
Assertion IsTemporal (Assertion' (Maybe Text, Signal dom Bool))
toTemporal :: Assertion dom -> Assertion' (Maybe Text, Signal dom Bool)
toTemporal (Assertion IsTemporal a) = a
toTemporal (Assertion IsNotTemporal a) = CvToTemporal a
{-# INLINE toTemporal #-}
isTemporal :: Assertion dom -> IsTemporal
isTemporal (Assertion it _assert) = it
{-# INLINE isTemporal #-}
assertion :: Assertion dom -> Assertion' (Maybe Text, Signal dom Bool)
assertion (Assertion _it assert) = assert
{-# INLINE assertion #-}
newtype Property (dom :: Domain) =
Property (Property' (Maybe Text, Signal dom Bool))
data AssertionResult = AssertionResult
{ cvPropName :: !String
, cvPass :: !Bool
}
deriving (Eq)
{-# ANN module (
DataReprAnn
$(liftQ [t| AssertionResult |])
0
[ ConstrRepr 'AssertionResult 0 0 [0b0, 0b0]
]) #-}
class AssertionValue dom a | a -> dom where
toAssertionValue :: a -> Assertion dom
instance AssertionValue dom (Signal dom Bool) where
toAssertionValue s = Assertion IsNotTemporal (CvPure (Nothing, s))
{-# INLINE toAssertionValue #-}
instance AssertionValue dom (Assertion dom) where
toAssertionValue = id
{-# INLINE toAssertionValue #-}