{-# LANGUAGE CPP #-}
module Clash.Driver.Types where
#include "MachDeps.h"
import Data.Text         (Text)
import BasicTypes        (InlineSpec)
import SrcLoc            (SrcSpan)
import Clash.Core.Term   (Term)
import Clash.Core.Var    (Id)
import Clash.Core.VarEnv (VarEnv)
import Clash.Netlist.BlackBox.Types (HdlSyn (..))
import Util (OverridingBool(..))
type BindingMap = VarEnv (Id,SrcSpan,InlineSpec,Term)
data DebugLevel
  = DebugNone
  
  | DebugSilent
  
  | DebugFinal
  
  | DebugName
  
  | DebugApplied
  
  | DebugAll
  
  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)
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 -> 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
                           
                           
                           , ClashOpts -> HdlSyn
opt_hdlSyn      :: HdlSyn
                           ,   :: 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
                           
                           
                           
                           
                           
                           
                           , ClashOpts -> Maybe (Maybe Int)
opt_forceUndefined :: Maybe (Maybe Int)
                           
                           
                           
                           
                           
                           
                           
                           
                           
                           , ClashOpts -> Bool
opt_checkIDir   :: Bool
                           }
defClashOpts :: ClashOpts
defClashOpts :: ClashOpts
defClashOpts
  = ClashOpts :: Int
-> Int
-> Word
-> Word
-> DebugLevel
-> Bool
-> Bool
-> Bool
-> OverridingBool
-> Int
-> Maybe String
-> HdlSyn
-> Bool
-> Bool
-> [String]
-> Maybe String
-> Bool
-> Bool
-> Bool
-> Maybe (Maybe Int)
-> Bool
-> ClashOpts
ClashOpts
  { opt_dbgLevel :: DebugLevel
opt_dbgLevel            = DebugLevel
DebugNone
  , opt_inlineLimit :: Int
opt_inlineLimit         = 20
  , opt_specLimit :: Int
opt_specLimit           = 20
  , opt_inlineFunctionLimit :: Word
opt_inlineFunctionLimit = 15
  , opt_inlineConstantLimit :: Word
opt_inlineConstantLimit = 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
  }
data Manifest
  = Manifest
  { Manifest -> (Int, Maybe Int)
manifestHash :: (Int,Maybe Int)
    
    
  , Manifest -> [Text]
portInNames  :: [Text]
  , Manifest -> [Text]
portInTypes  :: [Text]
    
    
    
    
  , Manifest -> [Text]
portOutNames :: [Text]
  , Manifest -> [Text]
portOutTypes :: [Text]
    
    
    
    
  , Manifest -> [Text]
componentNames :: [Text]
    
    
    
  }
  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)