{-|
  Copyright  :  (C) 2013-2016, University of Twente,
                    2016-2017, Myrtle Software Ltd,
                    2017     , QBayLogic, Google Inc.
  License    :  BSD2 (see the file LICENSE)
  Maintainer :  Christiaan Baaij <christiaan.baaij@gmail.com>

  Type definitions used by the Driver module
-}

{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}

module Clash.Driver.Types where

-- For Int/Word size
#include "MachDeps.h"

import           Control.DeepSeq                (NFData)
import           Data.Binary                    (Binary)
import           Data.Hashable
import qualified Data.Set                       as Set
import           Data.Text                      (Text)
import           GHC.Generics                   (Generic)

import           BasicTypes                     (InlineSpec)
import           SrcLoc                         (SrcSpan)
import           Util                           (OverridingBool(..))

import           Clash.Core.Term                (Term)
import           Clash.Core.Var                 (Id)
import           Clash.Core.VarEnv              (VarEnv)
import           Clash.Netlist.BlackBox.Types   (HdlSyn (..))


-- A function binder in the global environment.
--
data Binding = Binding
  { Binding -> Id
bindingId :: Id
  , Binding -> SrcSpan
bindingLoc :: SrcSpan
  , Binding -> InlineSpec
bindingSpec :: InlineSpec
  , Binding -> Term
bindingTerm :: Term
  } deriving (Get Binding
[Binding] -> Put
Binding -> Put
(Binding -> Put)
-> Get Binding -> ([Binding] -> Put) -> Binary Binding
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Binding] -> Put
$cputList :: [Binding] -> Put
get :: Get Binding
$cget :: Get Binding
put :: Binding -> Put
$cput :: Binding -> Put
Binary, (forall x. Binding -> Rep Binding x)
-> (forall x. Rep Binding x -> Binding) -> Generic Binding
forall x. Rep Binding x -> Binding
forall x. Binding -> Rep Binding x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Binding x -> Binding
$cfrom :: forall x. Binding -> Rep Binding x
Generic, Binding -> ()
(Binding -> ()) -> NFData Binding
forall a. (a -> ()) -> NFData a
rnf :: Binding -> ()
$crnf :: Binding -> ()
NFData, Int -> Binding -> ShowS
[Binding] -> ShowS
Binding -> String
(Int -> Binding -> ShowS)
-> (Binding -> String) -> ([Binding] -> ShowS) -> Show Binding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Binding] -> ShowS
$cshowList :: [Binding] -> ShowS
show :: Binding -> String
$cshow :: Binding -> String
showsPrec :: Int -> Binding -> ShowS
$cshowsPrec :: Int -> Binding -> ShowS
Show)

-- | Global function binders
--
-- Global functions cannot be mutually recursive, only self-recursive.
type BindingMap = VarEnv Binding

-- | Debug Message Verbosity
data DebugLevel
  = DebugNone
  -- ^ Don't show debug messages
  | DebugSilent
  -- ^ Run invariant checks and err if violated (enabled by any debug flag)
  | DebugFinal
  -- ^ Show completely normalized expressions
  | DebugName
  -- ^ Show names of applied transformations
  | DebugTry
  -- ^ Show names of tried AND applied transformations
  | DebugApplied
  -- ^ Show sub-expressions after a successful rewrite
  | DebugAll
  -- ^ Show all sub-expressions on which a rewrite is attempted
  deriving (DebugLevel -> DebugLevel -> Bool
(DebugLevel -> DebugLevel -> Bool)
-> (DebugLevel -> DebugLevel -> Bool) -> Eq DebugLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugLevel -> DebugLevel -> Bool
$c/= :: DebugLevel -> DebugLevel -> Bool
== :: DebugLevel -> DebugLevel -> Bool
$c== :: DebugLevel -> DebugLevel -> Bool
Eq,Eq DebugLevel
Eq DebugLevel
-> (DebugLevel -> DebugLevel -> Ordering)
-> (DebugLevel -> DebugLevel -> Bool)
-> (DebugLevel -> DebugLevel -> Bool)
-> (DebugLevel -> DebugLevel -> Bool)
-> (DebugLevel -> DebugLevel -> Bool)
-> (DebugLevel -> DebugLevel -> DebugLevel)
-> (DebugLevel -> DebugLevel -> DebugLevel)
-> Ord DebugLevel
DebugLevel -> DebugLevel -> Bool
DebugLevel -> DebugLevel -> Ordering
DebugLevel -> DebugLevel -> DebugLevel
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DebugLevel -> DebugLevel -> DebugLevel
$cmin :: DebugLevel -> DebugLevel -> DebugLevel
max :: DebugLevel -> DebugLevel -> DebugLevel
$cmax :: DebugLevel -> DebugLevel -> DebugLevel
>= :: DebugLevel -> DebugLevel -> Bool
$c>= :: DebugLevel -> DebugLevel -> Bool
> :: DebugLevel -> DebugLevel -> Bool
$c> :: DebugLevel -> DebugLevel -> Bool
<= :: DebugLevel -> DebugLevel -> Bool
$c<= :: DebugLevel -> DebugLevel -> Bool
< :: DebugLevel -> DebugLevel -> Bool
$c< :: DebugLevel -> DebugLevel -> Bool
compare :: DebugLevel -> DebugLevel -> Ordering
$ccompare :: DebugLevel -> DebugLevel -> Ordering
$cp1Ord :: Eq DebugLevel
Ord,ReadPrec [DebugLevel]
ReadPrec DebugLevel
Int -> ReadS DebugLevel
ReadS [DebugLevel]
(Int -> ReadS DebugLevel)
-> ReadS [DebugLevel]
-> ReadPrec DebugLevel
-> ReadPrec [DebugLevel]
-> Read DebugLevel
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DebugLevel]
$creadListPrec :: ReadPrec [DebugLevel]
readPrec :: ReadPrec DebugLevel
$creadPrec :: ReadPrec DebugLevel
readList :: ReadS [DebugLevel]
$creadList :: ReadS [DebugLevel]
readsPrec :: Int -> ReadS DebugLevel
$creadsPrec :: Int -> ReadS DebugLevel
Read,Int -> DebugLevel
DebugLevel -> Int
DebugLevel -> [DebugLevel]
DebugLevel -> DebugLevel
DebugLevel -> DebugLevel -> [DebugLevel]
DebugLevel -> DebugLevel -> DebugLevel -> [DebugLevel]
(DebugLevel -> DebugLevel)
-> (DebugLevel -> DebugLevel)
-> (Int -> DebugLevel)
-> (DebugLevel -> Int)
-> (DebugLevel -> [DebugLevel])
-> (DebugLevel -> DebugLevel -> [DebugLevel])
-> (DebugLevel -> DebugLevel -> [DebugLevel])
-> (DebugLevel -> DebugLevel -> DebugLevel -> [DebugLevel])
-> Enum DebugLevel
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: DebugLevel -> DebugLevel -> DebugLevel -> [DebugLevel]
$cenumFromThenTo :: DebugLevel -> DebugLevel -> DebugLevel -> [DebugLevel]
enumFromTo :: DebugLevel -> DebugLevel -> [DebugLevel]
$cenumFromTo :: DebugLevel -> DebugLevel -> [DebugLevel]
enumFromThen :: DebugLevel -> DebugLevel -> [DebugLevel]
$cenumFromThen :: DebugLevel -> DebugLevel -> [DebugLevel]
enumFrom :: DebugLevel -> [DebugLevel]
$cenumFrom :: DebugLevel -> [DebugLevel]
fromEnum :: DebugLevel -> Int
$cfromEnum :: DebugLevel -> Int
toEnum :: Int -> DebugLevel
$ctoEnum :: Int -> DebugLevel
pred :: DebugLevel -> DebugLevel
$cpred :: DebugLevel -> DebugLevel
succ :: DebugLevel -> DebugLevel
$csucc :: DebugLevel -> DebugLevel
Enum,(forall x. DebugLevel -> Rep DebugLevel x)
-> (forall x. Rep DebugLevel x -> DebugLevel) -> Generic DebugLevel
forall x. Rep DebugLevel x -> DebugLevel
forall x. DebugLevel -> Rep DebugLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DebugLevel x -> DebugLevel
$cfrom :: forall x. DebugLevel -> Rep DebugLevel x
Generic,Int -> DebugLevel -> Int
DebugLevel -> Int
(Int -> DebugLevel -> Int)
-> (DebugLevel -> Int) -> Hashable DebugLevel
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DebugLevel -> Int
$chash :: DebugLevel -> Int
hashWithSalt :: Int -> DebugLevel -> Int
$chashWithSalt :: Int -> DebugLevel -> Int
Hashable)

data ClashOpts = ClashOpts { ClashOpts -> Int
opt_inlineLimit :: Int
                           , ClashOpts -> Int
opt_specLimit   :: Int
                           , ClashOpts -> Word
opt_inlineFunctionLimit :: Word
                           , ClashOpts -> Word
opt_inlineConstantLimit :: Word
                           , ClashOpts -> DebugLevel
opt_dbgLevel    :: DebugLevel
                           , ClashOpts -> Set String
opt_dbgTransformations :: Set.Set String
                           , ClashOpts -> Int
opt_dbgTransformationsFrom :: Int
                           -- ^ Only output debug information from (applied)
                           -- transformation n
                           , ClashOpts -> Int
opt_dbgTransformationsLimit :: Int
                           -- ^ Only output debug information for n (applied)
                           -- transformations. If this limit is exceeded, Clash
                           -- will stop normalizing.
                           , ClashOpts -> Bool
opt_cachehdl    :: Bool
                           , ClashOpts -> Bool
opt_cleanhdl    :: Bool
                           , ClashOpts -> Bool
opt_primWarn    :: Bool
                           , ClashOpts -> OverridingBool
opt_color       :: OverridingBool
                           , ClashOpts -> Int
opt_intWidth    :: Int
                           , ClashOpts -> Maybe String
opt_hdlDir      :: Maybe String
                           -- ^ Directory to store temporary files in. Will be
                           -- cleaned after Clash has finished executing.
                           , ClashOpts -> HdlSyn
opt_hdlSyn      :: HdlSyn
                           , ClashOpts -> Bool
opt_errorExtra  :: Bool
                           , ClashOpts -> Bool
opt_floatSupport :: Bool
                           , ClashOpts -> [String]
opt_importPaths :: [FilePath]
                           , ClashOpts -> Maybe String
opt_componentPrefix :: Maybe String
                           , ClashOpts -> Bool
opt_newInlineStrat :: Bool
                           , ClashOpts -> Bool
opt_escapedIds :: Bool
                           , ClashOpts -> Bool
opt_ultra :: Bool
                           -- ^ Perform a high-effort compile, trading improved
                           -- performance for potentially much longer compile
                           -- times.
                           --
                           -- Name inspired by Design Compiler's /compile_ultra/
                           -- flag.
                           , ClashOpts -> Maybe (Maybe Int)
opt_forceUndefined :: Maybe (Maybe Int)
                           -- ^
                           -- * /Nothing/: generate undefined's in the HDL
                           --
                           -- * /Just Nothing/: replace undefined's by a
                           -- constant in the HDL; the compiler decides what's
                           -- best
                           --
                           -- * /Just (Just x)/: replace undefined's by /x/ in
                           -- the HDL
                           , ClashOpts -> Bool
opt_checkIDir   :: Bool
                           , ClashOpts -> Bool
opt_aggressiveXOpt :: Bool
                           -- ^ Enable aggressive X optimization, which may
                           -- remove undefineds from generated HDL by replaced
                           -- with defined alternatives.
                           , ClashOpts -> Word
opt_inlineWFCacheLimit :: Word
                           -- ^ At what size do we cache normalized work-free
                           -- top-level binders.
                           }

instance Hashable ClashOpts where
  hashWithSalt :: Int -> ClashOpts -> Int
hashWithSalt Int
s ClashOpts {Bool
Int
[String]
Maybe String
Maybe (Maybe Int)
Word
Set String
OverridingBool
HdlSyn
DebugLevel
opt_inlineWFCacheLimit :: Word
opt_aggressiveXOpt :: Bool
opt_checkIDir :: Bool
opt_forceUndefined :: Maybe (Maybe Int)
opt_ultra :: Bool
opt_escapedIds :: Bool
opt_newInlineStrat :: Bool
opt_componentPrefix :: Maybe String
opt_importPaths :: [String]
opt_floatSupport :: Bool
opt_errorExtra :: Bool
opt_hdlSyn :: HdlSyn
opt_hdlDir :: Maybe String
opt_intWidth :: Int
opt_color :: OverridingBool
opt_primWarn :: Bool
opt_cleanhdl :: Bool
opt_cachehdl :: Bool
opt_dbgTransformationsLimit :: Int
opt_dbgTransformationsFrom :: Int
opt_dbgTransformations :: Set String
opt_dbgLevel :: DebugLevel
opt_inlineConstantLimit :: Word
opt_inlineFunctionLimit :: Word
opt_specLimit :: Int
opt_inlineLimit :: Int
opt_inlineWFCacheLimit :: ClashOpts -> Word
opt_aggressiveXOpt :: ClashOpts -> Bool
opt_checkIDir :: ClashOpts -> Bool
opt_forceUndefined :: ClashOpts -> Maybe (Maybe Int)
opt_ultra :: ClashOpts -> Bool
opt_escapedIds :: ClashOpts -> Bool
opt_newInlineStrat :: ClashOpts -> Bool
opt_componentPrefix :: ClashOpts -> Maybe String
opt_importPaths :: ClashOpts -> [String]
opt_floatSupport :: ClashOpts -> Bool
opt_errorExtra :: ClashOpts -> Bool
opt_hdlSyn :: ClashOpts -> HdlSyn
opt_hdlDir :: ClashOpts -> Maybe String
opt_intWidth :: ClashOpts -> Int
opt_color :: ClashOpts -> OverridingBool
opt_primWarn :: ClashOpts -> Bool
opt_cleanhdl :: ClashOpts -> Bool
opt_cachehdl :: ClashOpts -> Bool
opt_dbgTransformationsLimit :: ClashOpts -> Int
opt_dbgTransformationsFrom :: ClashOpts -> Int
opt_dbgTransformations :: ClashOpts -> Set String
opt_dbgLevel :: ClashOpts -> DebugLevel
opt_inlineConstantLimit :: ClashOpts -> Word
opt_inlineFunctionLimit :: ClashOpts -> Word
opt_specLimit :: ClashOpts -> Int
opt_inlineLimit :: ClashOpts -> Int
..} =
    Int
s Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Int
opt_inlineLimit Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Int
opt_specLimit Int -> Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Word
opt_inlineFunctionLimit Int -> Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Word
opt_inlineConstantLimit Int -> DebugLevel -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    DebugLevel
opt_dbgLevel Int -> Set String -> Int
forall a. Hashable a => Int -> Set a -> Int
`hashSet`
    Set String
opt_dbgTransformations Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Int
opt_dbgTransformationsFrom Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Int
opt_dbgTransformationsLimit Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_cachehdl Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_cleanhdl Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_primWarn Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_cleanhdl Int -> OverridingBool -> Int
`hashOverridingBool`
    OverridingBool
opt_color Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Int
opt_intWidth Int -> Maybe String -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Maybe String
opt_hdlDir Int -> HdlSyn -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    HdlSyn
opt_hdlSyn Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_errorExtra Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_floatSupport Int -> [String] -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    [String]
opt_importPaths Int -> Maybe String -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Maybe String
opt_componentPrefix Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_newInlineStrat Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_escapedIds Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_ultra Int -> Maybe (Maybe Int) -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Maybe (Maybe Int)
opt_forceUndefined Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_checkIDir Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Bool
opt_aggressiveXOpt Int -> Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Word
opt_inlineWFCacheLimit
   where
    hashOverridingBool :: Int -> OverridingBool -> Int
    hashOverridingBool :: Int -> OverridingBool -> Int
hashOverridingBool Int
s1 OverridingBool
Auto = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
s1 (Int
0 :: Int)
    hashOverridingBool Int
s1 OverridingBool
Always = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
s1 (Int
1 :: Int)
    hashOverridingBool Int
s1 OverridingBool
Never = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
s1 (Int
2 :: Int)
    infixl 0 `hashOverridingBool`

    hashSet :: Hashable a => Int -> Set.Set a -> Int
    hashSet :: Int -> Set a -> Int
hashSet = (Int -> a -> Int) -> Int -> Set a -> Int
forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' Int -> a -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt
    infixl 0 `hashSet`

defClashOpts :: ClashOpts
defClashOpts :: ClashOpts
defClashOpts
  = ClashOpts :: Int
-> Int
-> Word
-> Word
-> DebugLevel
-> Set String
-> Int
-> Int
-> Bool
-> Bool
-> Bool
-> OverridingBool
-> Int
-> Maybe String
-> HdlSyn
-> Bool
-> Bool
-> [String]
-> Maybe String
-> Bool
-> Bool
-> Bool
-> Maybe (Maybe Int)
-> Bool
-> Bool
-> Word
-> ClashOpts
ClashOpts
  { opt_dbgLevel :: DebugLevel
opt_dbgLevel            = DebugLevel
DebugNone
  , opt_dbgTransformations :: Set String
opt_dbgTransformations  = Set String
forall a. Set a
Set.empty
  , opt_dbgTransformationsFrom :: Int
opt_dbgTransformationsFrom = Int
0
  , opt_dbgTransformationsLimit :: Int
opt_dbgTransformationsLimit = Int
forall a. Bounded a => a
maxBound
  , opt_inlineLimit :: Int
opt_inlineLimit         = Int
20
  , opt_specLimit :: Int
opt_specLimit           = Int
20
  , opt_inlineFunctionLimit :: Word
opt_inlineFunctionLimit = Word
15
  , opt_inlineConstantLimit :: Word
opt_inlineConstantLimit = Word
0
  , opt_cachehdl :: Bool
opt_cachehdl            = Bool
True
  , opt_cleanhdl :: Bool
opt_cleanhdl            = Bool
True
  , opt_primWarn :: Bool
opt_primWarn            = Bool
True
  , opt_color :: OverridingBool
opt_color               = OverridingBool
Auto
  , opt_intWidth :: Int
opt_intWidth            = WORD_SIZE_IN_BITS
  , opt_hdlDir :: Maybe String
opt_hdlDir              = Maybe String
forall a. Maybe a
Nothing
  , opt_hdlSyn :: HdlSyn
opt_hdlSyn              = HdlSyn
Other
  , opt_errorExtra :: Bool
opt_errorExtra          = Bool
False
  , opt_floatSupport :: Bool
opt_floatSupport        = Bool
False
  , opt_importPaths :: [String]
opt_importPaths         = []
  , opt_componentPrefix :: Maybe String
opt_componentPrefix     = Maybe String
forall a. Maybe a
Nothing
  , opt_newInlineStrat :: Bool
opt_newInlineStrat      = Bool
True
  , opt_escapedIds :: Bool
opt_escapedIds          = Bool
True
  , opt_ultra :: Bool
opt_ultra               = Bool
False
  , opt_forceUndefined :: Maybe (Maybe Int)
opt_forceUndefined      = Maybe (Maybe Int)
forall a. Maybe a
Nothing
  , opt_checkIDir :: Bool
opt_checkIDir           = Bool
True
  , opt_aggressiveXOpt :: Bool
opt_aggressiveXOpt      = Bool
False
  , opt_inlineWFCacheLimit :: Word
opt_inlineWFCacheLimit  = Word
10 -- TODO: find "optimal" value
  }

-- | Information about the generated HDL between (sub)runs of the compiler
data Manifest
  = Manifest
  { Manifest -> (Int, Maybe Int)
manifestHash :: (Int,Maybe Int)
    -- ^ Hash of the TopEntity and all its dependencies
    --   + (maybe) Hash of the TestBench and all its dependencies
  , Manifest -> (Int, Int, Bool)
successFlags  :: (Int,Int,Bool)
    -- ^ Compiler flags used to achieve successful compilation:
    --
    --   * opt_inlineLimit
    --   * opt_specLimit
    --   * opt_floatSupport
  , Manifest -> [Text]
portInNames  :: [Text]
  , Manifest -> [Text]
portInTypes  :: [Text]
    -- ^ The rendered versions of the types of the input ports of the TopEntity
    --
    -- Used when dealing with multiple @TopEntity@s who have different names
    -- for types which are structurally equal
  , Manifest -> [Text]
portOutNames :: [Text]
  , Manifest -> [Text]
portOutTypes :: [Text]
    -- ^ The rendered versions of the types of the output ports of the TopEntity
    --
    -- Used when dealing with multiple @TopEntity@s who have different names
    -- for types which are structurally equal
  , Manifest -> [Text]
componentNames :: [Text]
    -- ^ Names of all the generated components for the @TopEntity@ (does not
    -- include the names of the components of the @TestBench@ accompanying
    -- the @TopEntity@).
  }
  deriving (Int -> Manifest -> ShowS
[Manifest] -> ShowS
Manifest -> String
(Int -> Manifest -> ShowS)
-> (Manifest -> String) -> ([Manifest] -> ShowS) -> Show Manifest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Manifest] -> ShowS
$cshowList :: [Manifest] -> ShowS
show :: Manifest -> String
$cshow :: Manifest -> String
showsPrec :: Int -> Manifest -> ShowS
$cshowsPrec :: Int -> Manifest -> ShowS
Show,ReadPrec [Manifest]
ReadPrec Manifest
Int -> ReadS Manifest
ReadS [Manifest]
(Int -> ReadS Manifest)
-> ReadS [Manifest]
-> ReadPrec Manifest
-> ReadPrec [Manifest]
-> Read Manifest
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Manifest]
$creadListPrec :: ReadPrec [Manifest]
readPrec :: ReadPrec Manifest
$creadPrec :: ReadPrec Manifest
readList :: ReadS [Manifest]
$creadList :: ReadS [Manifest]
readsPrec :: Int -> ReadS Manifest
$creadsPrec :: Int -> ReadS Manifest
Read)