{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RecordWildCards #-}
module Clash.Driver.Types where
#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 (..))
data Binding = Binding
{ bindingId :: Id
, bindingLoc :: SrcSpan
, bindingSpec :: InlineSpec
, bindingTerm :: Term
} deriving (Binary, Generic, NFData, Show)
type BindingMap = VarEnv Binding
data DebugLevel
= DebugNone
| DebugSilent
| DebugFinal
| DebugName
| DebugTry
| DebugApplied
| DebugAll
deriving (Eq,Ord,Read,Enum,Generic,Hashable)
data ClashOpts = ClashOpts { opt_inlineLimit :: Int
, opt_specLimit :: Int
, opt_inlineFunctionLimit :: Word
, opt_inlineConstantLimit :: Word
, opt_dbgLevel :: DebugLevel
, opt_dbgTransformations :: Set.Set String
, opt_dbgTransformationsFrom :: Int
, opt_dbgTransformationsLimit :: Int
, opt_cachehdl :: Bool
, opt_cleanhdl :: Bool
, opt_primWarn :: Bool
, opt_color :: OverridingBool
, opt_intWidth :: Int
, opt_hdlDir :: Maybe String
, opt_hdlSyn :: HdlSyn
, opt_errorExtra :: Bool
, opt_floatSupport :: Bool
, opt_importPaths :: [FilePath]
, opt_componentPrefix :: Maybe String
, opt_newInlineStrat :: Bool
, opt_escapedIds :: Bool
, opt_ultra :: Bool
, opt_forceUndefined :: Maybe (Maybe Int)
, opt_checkIDir :: Bool
, opt_aggressiveXOpt :: Bool
, opt_inlineWFCacheLimit :: Word
}
instance Hashable ClashOpts where
hashWithSalt s ClashOpts {..} =
s `hashWithSalt`
opt_inlineLimit `hashWithSalt`
opt_specLimit `hashWithSalt`
opt_inlineFunctionLimit `hashWithSalt`
opt_inlineConstantLimit `hashWithSalt`
opt_dbgLevel `hashSet`
opt_dbgTransformations `hashWithSalt`
opt_dbgTransformationsFrom `hashWithSalt`
opt_dbgTransformationsLimit `hashWithSalt`
opt_cachehdl `hashWithSalt`
opt_cleanhdl `hashWithSalt`
opt_primWarn `hashWithSalt`
opt_cleanhdl `hashOverridingBool`
opt_color `hashWithSalt`
opt_intWidth `hashWithSalt`
opt_hdlDir `hashWithSalt`
opt_hdlSyn `hashWithSalt`
opt_errorExtra `hashWithSalt`
opt_floatSupport `hashWithSalt`
opt_importPaths `hashWithSalt`
opt_componentPrefix `hashWithSalt`
opt_newInlineStrat `hashWithSalt`
opt_escapedIds `hashWithSalt`
opt_ultra `hashWithSalt`
opt_forceUndefined `hashWithSalt`
opt_checkIDir `hashWithSalt`
opt_aggressiveXOpt `hashWithSalt`
opt_inlineWFCacheLimit
where
hashOverridingBool :: Int -> OverridingBool -> Int
hashOverridingBool s1 Auto = hashWithSalt s1 (0 :: Int)
hashOverridingBool s1 Always = hashWithSalt s1 (1 :: Int)
hashOverridingBool s1 Never = hashWithSalt s1 (2 :: Int)
infixl 0 `hashOverridingBool`
hashSet :: Hashable a => Int -> Set.Set a -> Int
hashSet = Set.foldl' hashWithSalt
infixl 0 `hashSet`
defClashOpts :: ClashOpts
defClashOpts
= ClashOpts
{ opt_dbgLevel = DebugNone
, opt_dbgTransformations = Set.empty
, opt_dbgTransformationsFrom = 0
, opt_dbgTransformationsLimit = maxBound
, opt_inlineLimit = 20
, opt_specLimit = 20
, opt_inlineFunctionLimit = 15
, opt_inlineConstantLimit = 0
, opt_cachehdl = True
, opt_cleanhdl = True
, opt_primWarn = True
, opt_color = Auto
, opt_intWidth = WORD_SIZE_IN_BITS
, opt_hdlDir = Nothing
, opt_hdlSyn = Other
, opt_errorExtra = False
, opt_floatSupport = False
, opt_importPaths = []
, opt_componentPrefix = Nothing
, opt_newInlineStrat = True
, opt_escapedIds = True
, opt_ultra = False
, opt_forceUndefined = Nothing
, opt_checkIDir = True
, opt_aggressiveXOpt = False
, opt_inlineWFCacheLimit = 10
}
data Manifest
= Manifest
{ manifestHash :: (Int,Maybe Int)
, successFlags :: (Int,Int,Bool)
, portInNames :: [Text]
, portInTypes :: [Text]
, portOutNames :: [Text]
, portOutTypes :: [Text]
, componentNames :: [Text]
}
deriving (Show,Read)