{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Clash.Driver.Types where
#include "MachDeps.h"
import Control.DeepSeq (NFData(rnf), deepseq)
import Data.Binary (Binary)
import Data.Fixed
import Data.Hashable
import Data.HashMap.Strict (HashMap)
import Data.IntMap.Strict (IntMap)
import Data.Maybe (isJust)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as Text (dropAround)
#if MIN_VERSION_prettyprinter(1,7,0)
import Prettyprinter
#else
import Data.Text.Prettyprint.Doc
#endif
import GHC.Generics (Generic)
#if MIN_VERSION_ghc(9,0,0)
import GHC.Types.Basic (InlineSpec)
import GHC.Types.SrcLoc (SrcSpan)
import GHC.Utils.Misc (OverridingBool(..))
#else
import BasicTypes (InlineSpec)
import SrcLoc (SrcSpan)
import Util (OverridingBool(..))
#endif
import Clash.Annotations.BitRepresentation.Internal (CustomReprs)
import Clash.Signal.Internal
import Clash.Core.Term (Term)
import Clash.Core.TyCon (TyConMap, TyConName)
import Clash.Core.Var (Id)
import Clash.Core.VarEnv (VarEnv)
import Clash.Netlist.BlackBox.Types (HdlSyn (..))
import {-# SOURCE #-} Clash.Netlist.Types (PreserveCase(..), TopEntityT)
import Clash.Primitives.Types (CompiledPrimMap)
data ClashEnv = ClashEnv
{ ClashEnv -> ClashOpts
envOpts :: ClashOpts
, ClashEnv -> TyConMap
envTyConMap :: TyConMap
, ClashEnv -> IntMap TyConName
envTupleTyCons :: IntMap TyConName
, ClashEnv -> CompiledPrimMap
envPrimitives :: CompiledPrimMap
, ClashEnv -> CustomReprs
envCustomReprs :: CustomReprs
} deriving ((forall x. ClashEnv -> Rep ClashEnv x)
-> (forall x. Rep ClashEnv x -> ClashEnv) -> Generic ClashEnv
forall x. Rep ClashEnv x -> ClashEnv
forall x. ClashEnv -> Rep ClashEnv x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClashEnv x -> ClashEnv
$cfrom :: forall x. ClashEnv -> Rep ClashEnv x
Generic, ClashEnv -> ()
(ClashEnv -> ()) -> NFData ClashEnv
forall a. (a -> ()) -> NFData a
rnf :: ClashEnv -> ()
$crnf :: ClashEnv -> ()
NFData)
data ClashDesign = ClashDesign
{ ClashDesign -> [TopEntityT]
designEntities :: [TopEntityT]
, ClashDesign -> DomainMap
designDomains :: DomainMap
, ClashDesign -> BindingMap
designBindings :: BindingMap
}
instance NFData ClashDesign where
rnf :: ClashDesign -> ()
rnf ClashDesign
design =
ClashDesign -> [TopEntityT]
designEntities ClashDesign
design [TopEntityT] -> () -> ()
`seq`
ClashDesign -> DomainMap
designDomains ClashDesign
design DomainMap -> BindingMap -> BindingMap
forall a b. NFData a => a -> b -> b
`deepseq`
ClashDesign -> BindingMap
designBindings ClashDesign
design BindingMap -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
()
data IsPrim
= IsPrim
| IsFun
deriving (Get IsPrim
[IsPrim] -> Put
IsPrim -> Put
(IsPrim -> Put) -> Get IsPrim -> ([IsPrim] -> Put) -> Binary IsPrim
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [IsPrim] -> Put
$cputList :: [IsPrim] -> Put
get :: Get IsPrim
$cget :: Get IsPrim
put :: IsPrim -> Put
$cput :: IsPrim -> Put
Binary, IsPrim -> IsPrim -> Bool
(IsPrim -> IsPrim -> Bool)
-> (IsPrim -> IsPrim -> Bool) -> Eq IsPrim
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsPrim -> IsPrim -> Bool
$c/= :: IsPrim -> IsPrim -> Bool
== :: IsPrim -> IsPrim -> Bool
$c== :: IsPrim -> IsPrim -> Bool
Eq, (forall x. IsPrim -> Rep IsPrim x)
-> (forall x. Rep IsPrim x -> IsPrim) -> Generic IsPrim
forall x. Rep IsPrim x -> IsPrim
forall x. IsPrim -> Rep IsPrim x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IsPrim x -> IsPrim
$cfrom :: forall x. IsPrim -> Rep IsPrim x
Generic, IsPrim -> ()
(IsPrim -> ()) -> NFData IsPrim
forall a. (a -> ()) -> NFData a
rnf :: IsPrim -> ()
$crnf :: IsPrim -> ()
NFData, Int -> IsPrim -> ShowS
[IsPrim] -> ShowS
IsPrim -> String
(Int -> IsPrim -> ShowS)
-> (IsPrim -> String) -> ([IsPrim] -> ShowS) -> Show IsPrim
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsPrim] -> ShowS
$cshowList :: [IsPrim] -> ShowS
show :: IsPrim -> String
$cshow :: IsPrim -> String
showsPrec :: Int -> IsPrim -> ShowS
$cshowsPrec :: Int -> IsPrim -> ShowS
Show)
data Binding a = Binding
{ Binding a -> Id
bindingId :: Id
, Binding a -> SrcSpan
bindingLoc :: SrcSpan
, Binding a -> InlineSpec
bindingSpec :: InlineSpec
, Binding a -> IsPrim
bindingIsPrim :: IsPrim
, Binding a -> a
bindingTerm :: a
, Binding a -> Bool
bindingRecursive :: Bool
} deriving (Get (Binding a)
[Binding a] -> Put
Binding a -> Put
(Binding a -> Put)
-> Get (Binding a) -> ([Binding a] -> Put) -> Binary (Binding a)
forall a. Binary a => Get (Binding a)
forall a. Binary a => [Binding a] -> Put
forall a. Binary a => Binding a -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Binding a] -> Put
$cputList :: forall a. Binary a => [Binding a] -> Put
get :: Get (Binding a)
$cget :: forall a. Binary a => Get (Binding a)
put :: Binding a -> Put
$cput :: forall a. Binary a => Binding a -> Put
Binary, a -> Binding b -> Binding a
(a -> b) -> Binding a -> Binding b
(forall a b. (a -> b) -> Binding a -> Binding b)
-> (forall a b. a -> Binding b -> Binding a) -> Functor Binding
forall a b. a -> Binding b -> Binding a
forall a b. (a -> b) -> Binding a -> Binding b
forall (f :: Type -> Type).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Binding b -> Binding a
$c<$ :: forall a b. a -> Binding b -> Binding a
fmap :: (a -> b) -> Binding a -> Binding b
$cfmap :: forall a b. (a -> b) -> Binding a -> Binding b
Functor, (forall x. Binding a -> Rep (Binding a) x)
-> (forall x. Rep (Binding a) x -> Binding a)
-> Generic (Binding a)
forall x. Rep (Binding a) x -> Binding a
forall x. Binding a -> Rep (Binding a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Binding a) x -> Binding a
forall a x. Binding a -> Rep (Binding a) x
$cto :: forall a x. Rep (Binding a) x -> Binding a
$cfrom :: forall a x. Binding a -> Rep (Binding a) x
Generic, Binding a -> ()
(Binding a -> ()) -> NFData (Binding a)
forall a. NFData a => Binding a -> ()
forall a. (a -> ()) -> NFData a
rnf :: Binding a -> ()
$crnf :: forall a. NFData a => Binding a -> ()
NFData, Int -> Binding a -> ShowS
[Binding a] -> ShowS
Binding a -> String
(Int -> Binding a -> ShowS)
-> (Binding a -> String)
-> ([Binding a] -> ShowS)
-> Show (Binding a)
forall a. Show a => Int -> Binding a -> ShowS
forall a. Show a => [Binding a] -> ShowS
forall a. Show a => Binding a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Binding a] -> ShowS
$cshowList :: forall a. Show a => [Binding a] -> ShowS
show :: Binding a -> String
$cshow :: forall a. Show a => Binding a -> String
showsPrec :: Int -> Binding a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Binding a -> ShowS
Show)
type BindingMap = VarEnv (Binding Term)
type DomainMap = HashMap Text VDomainConfiguration
data TransformationInfo
= None
| FinalTerm
| AppliedName
| AppliedTerm
| TryName
| TryTerm
deriving (TransformationInfo -> TransformationInfo -> Bool
(TransformationInfo -> TransformationInfo -> Bool)
-> (TransformationInfo -> TransformationInfo -> Bool)
-> Eq TransformationInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransformationInfo -> TransformationInfo -> Bool
$c/= :: TransformationInfo -> TransformationInfo -> Bool
== :: TransformationInfo -> TransformationInfo -> Bool
$c== :: TransformationInfo -> TransformationInfo -> Bool
Eq, (forall x. TransformationInfo -> Rep TransformationInfo x)
-> (forall x. Rep TransformationInfo x -> TransformationInfo)
-> Generic TransformationInfo
forall x. Rep TransformationInfo x -> TransformationInfo
forall x. TransformationInfo -> Rep TransformationInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransformationInfo x -> TransformationInfo
$cfrom :: forall x. TransformationInfo -> Rep TransformationInfo x
Generic, Eq TransformationInfo
Eq TransformationInfo
-> (Int -> TransformationInfo -> Int)
-> (TransformationInfo -> Int)
-> Hashable TransformationInfo
Int -> TransformationInfo -> Int
TransformationInfo -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TransformationInfo -> Int
$chash :: TransformationInfo -> Int
hashWithSalt :: Int -> TransformationInfo -> Int
$chashWithSalt :: Int -> TransformationInfo -> Int
$cp1Hashable :: Eq TransformationInfo
Hashable, Eq TransformationInfo
Eq TransformationInfo
-> (TransformationInfo -> TransformationInfo -> Ordering)
-> (TransformationInfo -> TransformationInfo -> Bool)
-> (TransformationInfo -> TransformationInfo -> Bool)
-> (TransformationInfo -> TransformationInfo -> Bool)
-> (TransformationInfo -> TransformationInfo -> Bool)
-> (TransformationInfo -> TransformationInfo -> TransformationInfo)
-> (TransformationInfo -> TransformationInfo -> TransformationInfo)
-> Ord TransformationInfo
TransformationInfo -> TransformationInfo -> Bool
TransformationInfo -> TransformationInfo -> Ordering
TransformationInfo -> TransformationInfo -> TransformationInfo
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 :: TransformationInfo -> TransformationInfo -> TransformationInfo
$cmin :: TransformationInfo -> TransformationInfo -> TransformationInfo
max :: TransformationInfo -> TransformationInfo -> TransformationInfo
$cmax :: TransformationInfo -> TransformationInfo -> TransformationInfo
>= :: TransformationInfo -> TransformationInfo -> Bool
$c>= :: TransformationInfo -> TransformationInfo -> Bool
> :: TransformationInfo -> TransformationInfo -> Bool
$c> :: TransformationInfo -> TransformationInfo -> Bool
<= :: TransformationInfo -> TransformationInfo -> Bool
$c<= :: TransformationInfo -> TransformationInfo -> Bool
< :: TransformationInfo -> TransformationInfo -> Bool
$c< :: TransformationInfo -> TransformationInfo -> Bool
compare :: TransformationInfo -> TransformationInfo -> Ordering
$ccompare :: TransformationInfo -> TransformationInfo -> Ordering
$cp1Ord :: Eq TransformationInfo
Ord, ReadPrec [TransformationInfo]
ReadPrec TransformationInfo
Int -> ReadS TransformationInfo
ReadS [TransformationInfo]
(Int -> ReadS TransformationInfo)
-> ReadS [TransformationInfo]
-> ReadPrec TransformationInfo
-> ReadPrec [TransformationInfo]
-> Read TransformationInfo
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TransformationInfo]
$creadListPrec :: ReadPrec [TransformationInfo]
readPrec :: ReadPrec TransformationInfo
$creadPrec :: ReadPrec TransformationInfo
readList :: ReadS [TransformationInfo]
$creadList :: ReadS [TransformationInfo]
readsPrec :: Int -> ReadS TransformationInfo
$creadsPrec :: Int -> ReadS TransformationInfo
Read, Int -> TransformationInfo -> ShowS
[TransformationInfo] -> ShowS
TransformationInfo -> String
(Int -> TransformationInfo -> ShowS)
-> (TransformationInfo -> String)
-> ([TransformationInfo] -> ShowS)
-> Show TransformationInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransformationInfo] -> ShowS
$cshowList :: [TransformationInfo] -> ShowS
show :: TransformationInfo -> String
$cshow :: TransformationInfo -> String
showsPrec :: Int -> TransformationInfo -> ShowS
$cshowsPrec :: Int -> TransformationInfo -> ShowS
Show, TransformationInfo -> ()
(TransformationInfo -> ()) -> NFData TransformationInfo
forall a. (a -> ()) -> NFData a
rnf :: TransformationInfo -> ()
$crnf :: TransformationInfo -> ()
NFData)
data DebugOpts = DebugOpts
{ DebugOpts -> Bool
dbg_invariants :: Bool
, DebugOpts -> TransformationInfo
dbg_transformationInfo :: TransformationInfo
, DebugOpts -> Set String
dbg_transformations :: Set String
, DebugOpts -> Bool
dbg_countTransformations :: Bool
, DebugOpts -> Maybe Word
dbg_transformationsFrom :: Maybe Word
, DebugOpts -> Maybe Word
dbg_transformationsLimit :: Maybe Word
, DebugOpts -> Maybe String
dbg_historyFile :: Maybe FilePath
} deriving ((forall x. DebugOpts -> Rep DebugOpts x)
-> (forall x. Rep DebugOpts x -> DebugOpts) -> Generic DebugOpts
forall x. Rep DebugOpts x -> DebugOpts
forall x. DebugOpts -> Rep DebugOpts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DebugOpts x -> DebugOpts
$cfrom :: forall x. DebugOpts -> Rep DebugOpts x
Generic, DebugOpts -> ()
(DebugOpts -> ()) -> NFData DebugOpts
forall a. (a -> ()) -> NFData a
rnf :: DebugOpts -> ()
$crnf :: DebugOpts -> ()
NFData, Int -> DebugOpts -> ShowS
[DebugOpts] -> ShowS
DebugOpts -> String
(Int -> DebugOpts -> ShowS)
-> (DebugOpts -> String)
-> ([DebugOpts] -> ShowS)
-> Show DebugOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DebugOpts] -> ShowS
$cshowList :: [DebugOpts] -> ShowS
show :: DebugOpts -> String
$cshow :: DebugOpts -> String
showsPrec :: Int -> DebugOpts -> ShowS
$cshowsPrec :: Int -> DebugOpts -> ShowS
Show, DebugOpts -> DebugOpts -> Bool
(DebugOpts -> DebugOpts -> Bool)
-> (DebugOpts -> DebugOpts -> Bool) -> Eq DebugOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugOpts -> DebugOpts -> Bool
$c/= :: DebugOpts -> DebugOpts -> Bool
== :: DebugOpts -> DebugOpts -> Bool
$c== :: DebugOpts -> DebugOpts -> Bool
Eq)
instance Hashable DebugOpts where
hashWithSalt :: Int -> DebugOpts -> Int
hashWithSalt Int
s DebugOpts{Bool
Maybe String
Maybe Word
Set String
TransformationInfo
dbg_historyFile :: Maybe String
dbg_transformationsLimit :: Maybe Word
dbg_transformationsFrom :: Maybe Word
dbg_countTransformations :: Bool
dbg_transformations :: Set String
dbg_transformationInfo :: TransformationInfo
dbg_invariants :: Bool
dbg_historyFile :: DebugOpts -> Maybe String
dbg_transformationsLimit :: DebugOpts -> Maybe Word
dbg_transformationsFrom :: DebugOpts -> Maybe Word
dbg_countTransformations :: DebugOpts -> Bool
dbg_transformations :: DebugOpts -> Set String
dbg_transformationInfo :: DebugOpts -> TransformationInfo
dbg_invariants :: DebugOpts -> Bool
..} =
Int
s Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Bool
dbg_invariants Int -> TransformationInfo -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
TransformationInfo
dbg_transformationInfo Int -> Set String -> Int
`hashSet`
Set String
dbg_transformations Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Bool
dbg_countTransformations Int -> Maybe Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Maybe Word
dbg_transformationsFrom Int -> Maybe Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Maybe Word
dbg_transformationsLimit Int -> Maybe String -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Maybe String
dbg_historyFile
where
hashSet :: Int -> Set String -> Int
hashSet = (Int -> String -> Int) -> Int -> Set String -> Int
forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' Int -> String -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt
infixl 0 `hashSet`
isDebugging :: DebugOpts -> Bool
isDebugging :: DebugOpts -> Bool
isDebugging DebugOpts
opts = [Bool] -> Bool
forall (t :: Type -> Type). Foldable t => t Bool -> Bool
or
[ DebugOpts -> Bool
dbg_invariants DebugOpts
opts
, DebugOpts -> TransformationInfo
dbg_transformationInfo DebugOpts
opts TransformationInfo -> TransformationInfo -> Bool
forall a. Ord a => a -> a -> Bool
> TransformationInfo
None
, DebugOpts -> Bool
dbg_countTransformations DebugOpts
opts
, Maybe Word -> Bool
forall a. Maybe a -> Bool
isJust (DebugOpts -> Maybe Word
dbg_transformationsLimit DebugOpts
opts)
]
hasDebugInfo :: TransformationInfo -> String -> DebugOpts -> Bool
hasDebugInfo :: TransformationInfo -> String -> DebugOpts -> Bool
hasDebugInfo TransformationInfo
info String
name DebugOpts
opts =
String -> Bool
isDebugged String
name Bool -> Bool -> Bool
&& TransformationInfo -> DebugOpts -> Bool
hasTransformationInfo TransformationInfo
info DebugOpts
opts
where
isDebugged :: String -> Bool
isDebugged String
n =
let set :: Set String
set = DebugOpts -> Set String
dbg_transformations DebugOpts
opts
in Set String -> Bool
forall a. Set a -> Bool
Set.null Set String
set Bool -> Bool -> Bool
|| String -> Set String -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member String
n Set String
set
hasTransformationInfo :: TransformationInfo -> DebugOpts -> Bool
hasTransformationInfo :: TransformationInfo -> DebugOpts -> Bool
hasTransformationInfo TransformationInfo
info DebugOpts
opts =
TransformationInfo
info TransformationInfo -> TransformationInfo -> Bool
forall a. Ord a => a -> a -> Bool
<= DebugOpts -> TransformationInfo
dbg_transformationInfo DebugOpts
opts
debugNone :: DebugOpts
debugNone :: DebugOpts
debugNone = DebugOpts :: Bool
-> TransformationInfo
-> Set String
-> Bool
-> Maybe Word
-> Maybe Word
-> Maybe String
-> DebugOpts
DebugOpts
{ dbg_invariants :: Bool
dbg_invariants = Bool
False
, dbg_transformationInfo :: TransformationInfo
dbg_transformationInfo = TransformationInfo
None
, dbg_transformations :: Set String
dbg_transformations = Set String
forall a. Set a
Set.empty
, dbg_countTransformations :: Bool
dbg_countTransformations = Bool
False
, dbg_transformationsFrom :: Maybe Word
dbg_transformationsFrom = Maybe Word
forall a. Maybe a
Nothing
, dbg_transformationsLimit :: Maybe Word
dbg_transformationsLimit = Maybe Word
forall a. Maybe a
Nothing
, dbg_historyFile :: Maybe String
dbg_historyFile = Maybe String
forall a. Maybe a
Nothing
}
debugSilent :: DebugOpts
debugSilent :: DebugOpts
debugSilent = DebugOpts
debugNone { dbg_invariants :: Bool
dbg_invariants = Bool
True }
debugFinal :: DebugOpts
debugFinal :: DebugOpts
debugFinal = DebugOpts
debugSilent { dbg_transformationInfo :: TransformationInfo
dbg_transformationInfo = TransformationInfo
FinalTerm }
debugCount :: DebugOpts
debugCount :: DebugOpts
debugCount = DebugOpts
debugFinal { dbg_countTransformations :: Bool
dbg_countTransformations = Bool
True }
debugName :: DebugOpts
debugName :: DebugOpts
debugName = DebugOpts
debugCount { dbg_transformationInfo :: TransformationInfo
dbg_transformationInfo = TransformationInfo
AppliedName }
debugTry :: DebugOpts
debugTry :: DebugOpts
debugTry = DebugOpts
debugName { dbg_transformationInfo :: TransformationInfo
dbg_transformationInfo = TransformationInfo
TryName }
debugApplied :: DebugOpts
debugApplied :: DebugOpts
debugApplied = DebugOpts
debugTry { dbg_transformationInfo :: TransformationInfo
dbg_transformationInfo = TransformationInfo
AppliedTerm }
debugAll :: DebugOpts
debugAll :: DebugOpts
debugAll = DebugOpts
debugApplied { dbg_transformationInfo :: TransformationInfo
dbg_transformationInfo = TransformationInfo
TryTerm }
data ClashOpts = ClashOpts
{ ClashOpts -> Bool
opt_werror :: Bool
, ClashOpts -> Int
opt_inlineLimit :: Int
, ClashOpts -> Int
opt_specLimit :: Int
, ClashOpts -> Word
opt_inlineFunctionLimit :: Word
, ClashOpts -> Word
opt_inlineConstantLimit :: Word
, ClashOpts -> Word
opt_evaluatorFuelLimit :: Word
, ClashOpts -> DebugOpts
opt_debug :: DebugOpts
, ClashOpts -> Bool
opt_cachehdl :: Bool
, ClashOpts -> Bool
opt_clear :: 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 -> [String]
opt_importPaths :: [FilePath]
, ClashOpts -> Maybe Text
opt_componentPrefix :: Maybe Text
, ClashOpts -> Bool
opt_newInlineStrat :: Bool
, ClashOpts -> Bool
opt_escapedIds :: Bool
, ClashOpts -> PreserveCase
opt_lowerCaseBasicIds :: PreserveCase
, ClashOpts -> Bool
opt_ultra :: Bool
, ClashOpts -> Maybe (Maybe Int)
opt_forceUndefined :: Maybe (Maybe Int)
, ClashOpts -> Bool
opt_checkIDir :: Bool
, ClashOpts -> Bool
opt_aggressiveXOpt :: Bool
, ClashOpts -> Bool
opt_aggressiveXOptBB :: Bool
, ClashOpts -> Word
opt_inlineWFCacheLimit :: Word
, ClashOpts -> Bool
opt_edalize :: Bool
, ClashOpts -> Bool
opt_renderEnums :: Bool
}
deriving (Int -> ClashOpts -> ShowS
[ClashOpts] -> ShowS
ClashOpts -> String
(Int -> ClashOpts -> ShowS)
-> (ClashOpts -> String)
-> ([ClashOpts] -> ShowS)
-> Show ClashOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClashOpts] -> ShowS
$cshowList :: [ClashOpts] -> ShowS
show :: ClashOpts -> String
$cshow :: ClashOpts -> String
showsPrec :: Int -> ClashOpts -> ShowS
$cshowsPrec :: Int -> ClashOpts -> ShowS
Show)
instance NFData ClashOpts where
rnf :: ClashOpts -> ()
rnf ClashOpts
o =
ClashOpts -> Bool
opt_werror ClashOpts
o Bool -> Int -> Int
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Int
opt_inlineLimit ClashOpts
o Int -> Int -> Int
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Int
opt_specLimit ClashOpts
o Int -> Word -> Word
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Word
opt_inlineFunctionLimit ClashOpts
o Word -> Word -> Word
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Word
opt_inlineConstantLimit ClashOpts
o Word -> Word -> Word
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Word
opt_evaluatorFuelLimit ClashOpts
o Word -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_cachehdl ClashOpts
o Bool -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_clear ClashOpts
o Bool -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_primWarn ClashOpts
o Bool -> OverridingBool -> OverridingBool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> OverridingBool
opt_color ClashOpts
o OverridingBool -> () -> ()
`seq`
ClashOpts -> Int
opt_intWidth ClashOpts
o Int -> Maybe String -> Maybe String
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Maybe String
opt_hdlDir ClashOpts
o Maybe String -> HdlSyn -> HdlSyn
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> HdlSyn
opt_hdlSyn ClashOpts
o HdlSyn -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_errorExtra ClashOpts
o Bool -> [String] -> [String]
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> [String]
opt_importPaths ClashOpts
o [String] -> Maybe Text -> Maybe Text
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Maybe Text
opt_componentPrefix ClashOpts
o Maybe Text -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_newInlineStrat ClashOpts
o Bool -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_escapedIds ClashOpts
o Bool -> PreserveCase -> PreserveCase
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> PreserveCase
opt_lowerCaseBasicIds ClashOpts
o PreserveCase -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_ultra ClashOpts
o Bool -> Maybe (Maybe Int) -> Maybe (Maybe Int)
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Maybe (Maybe Int)
opt_forceUndefined ClashOpts
o Maybe (Maybe Int) -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_checkIDir ClashOpts
o Bool -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_aggressiveXOpt ClashOpts
o Bool -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_aggressiveXOptBB ClashOpts
o Bool -> Word -> Word
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Word
opt_inlineWFCacheLimit ClashOpts
o Word -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_edalize ClashOpts
o Bool -> Bool -> Bool
forall a b. NFData a => a -> b -> b
`deepseq`
ClashOpts -> Bool
opt_renderEnums ClashOpts
o Bool -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
()
instance Eq ClashOpts where
ClashOpts
s0 == :: ClashOpts -> ClashOpts -> Bool
== ClashOpts
s1 =
ClashOpts -> Bool
opt_werror ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_werror ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Int
opt_inlineLimit ClashOpts
s0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Int
opt_inlineLimit ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Int
opt_specLimit ClashOpts
s0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Int
opt_specLimit ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Word
opt_inlineFunctionLimit ClashOpts
s0 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Word
opt_inlineFunctionLimit ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Word
opt_inlineConstantLimit ClashOpts
s0 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Word
opt_inlineConstantLimit ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Word
opt_evaluatorFuelLimit ClashOpts
s0 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Word
opt_evaluatorFuelLimit ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_cachehdl ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_cachehdl ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_clear ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_clear ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_primWarn ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_primWarn ClashOpts
s1 Bool -> Bool -> Bool
&&
(ClashOpts -> OverridingBool
opt_color ClashOpts
s0 OverridingBool -> OverridingBool -> Bool
`eqOverridingBool` ClashOpts -> OverridingBool
opt_color ClashOpts
s1) Bool -> Bool -> Bool
&&
ClashOpts -> Int
opt_intWidth ClashOpts
s0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Int
opt_intWidth ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Maybe String
opt_hdlDir ClashOpts
s0 Maybe String -> Maybe String -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Maybe String
opt_hdlDir ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> HdlSyn
opt_hdlSyn ClashOpts
s0 HdlSyn -> HdlSyn -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> HdlSyn
opt_hdlSyn ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_errorExtra ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_errorExtra ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> [String]
opt_importPaths ClashOpts
s0 [String] -> [String] -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> [String]
opt_importPaths ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Maybe Text
opt_componentPrefix ClashOpts
s0 Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Maybe Text
opt_componentPrefix ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_newInlineStrat ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_newInlineStrat ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_escapedIds ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_escapedIds ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> PreserveCase
opt_lowerCaseBasicIds ClashOpts
s0 PreserveCase -> PreserveCase -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> PreserveCase
opt_lowerCaseBasicIds ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_ultra ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_ultra ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Maybe (Maybe Int)
opt_forceUndefined ClashOpts
s0 Maybe (Maybe Int) -> Maybe (Maybe Int) -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Maybe (Maybe Int)
opt_forceUndefined ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_checkIDir ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_checkIDir ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_aggressiveXOpt ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_aggressiveXOpt ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_aggressiveXOptBB ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_aggressiveXOptBB ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Word
opt_inlineWFCacheLimit ClashOpts
s0 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Word
opt_inlineWFCacheLimit ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_edalize ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_edalize ClashOpts
s1 Bool -> Bool -> Bool
&&
ClashOpts -> Bool
opt_renderEnums ClashOpts
s0 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== ClashOpts -> Bool
opt_renderEnums ClashOpts
s1
where
eqOverridingBool :: OverridingBool -> OverridingBool -> Bool
eqOverridingBool :: OverridingBool -> OverridingBool -> Bool
eqOverridingBool OverridingBool
Auto OverridingBool
Auto = Bool
True
eqOverridingBool OverridingBool
Always OverridingBool
Always = Bool
True
eqOverridingBool OverridingBool
Never OverridingBool
Never = Bool
True
eqOverridingBool OverridingBool
_ OverridingBool
_ = Bool
False
instance Hashable ClashOpts where
hashWithSalt :: Int -> ClashOpts -> Int
hashWithSalt Int
s ClashOpts {Bool
Int
[String]
Maybe String
Maybe (Maybe Int)
Maybe Text
Word
OverridingBool
PreserveCase
HdlSyn
DebugOpts
opt_renderEnums :: Bool
opt_edalize :: Bool
opt_inlineWFCacheLimit :: Word
opt_aggressiveXOptBB :: Bool
opt_aggressiveXOpt :: Bool
opt_checkIDir :: Bool
opt_forceUndefined :: Maybe (Maybe Int)
opt_ultra :: Bool
opt_lowerCaseBasicIds :: PreserveCase
opt_escapedIds :: Bool
opt_newInlineStrat :: Bool
opt_componentPrefix :: Maybe Text
opt_importPaths :: [String]
opt_errorExtra :: Bool
opt_hdlSyn :: HdlSyn
opt_hdlDir :: Maybe String
opt_intWidth :: Int
opt_color :: OverridingBool
opt_primWarn :: Bool
opt_clear :: Bool
opt_cachehdl :: Bool
opt_debug :: DebugOpts
opt_evaluatorFuelLimit :: Word
opt_inlineConstantLimit :: Word
opt_inlineFunctionLimit :: Word
opt_specLimit :: Int
opt_inlineLimit :: Int
opt_werror :: Bool
opt_renderEnums :: ClashOpts -> Bool
opt_edalize :: ClashOpts -> Bool
opt_inlineWFCacheLimit :: ClashOpts -> Word
opt_aggressiveXOptBB :: ClashOpts -> Bool
opt_aggressiveXOpt :: ClashOpts -> Bool
opt_checkIDir :: ClashOpts -> Bool
opt_forceUndefined :: ClashOpts -> Maybe (Maybe Int)
opt_ultra :: ClashOpts -> Bool
opt_lowerCaseBasicIds :: ClashOpts -> PreserveCase
opt_escapedIds :: ClashOpts -> Bool
opt_newInlineStrat :: ClashOpts -> Bool
opt_componentPrefix :: ClashOpts -> Maybe Text
opt_importPaths :: ClashOpts -> [String]
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_clear :: ClashOpts -> Bool
opt_cachehdl :: ClashOpts -> Bool
opt_debug :: ClashOpts -> DebugOpts
opt_evaluatorFuelLimit :: ClashOpts -> Word
opt_inlineConstantLimit :: ClashOpts -> Word
opt_inlineFunctionLimit :: ClashOpts -> Word
opt_specLimit :: ClashOpts -> Int
opt_inlineLimit :: ClashOpts -> Int
opt_werror :: ClashOpts -> Bool
..} =
Int
s Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Bool
opt_werror 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 -> Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Word
opt_evaluatorFuelLimit 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_clear Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Bool
opt_primWarn 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 -> [String] -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
[String]
opt_importPaths Int -> Maybe Text -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Maybe Text
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 -> PreserveCase -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
PreserveCase
opt_lowerCaseBasicIds 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 -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Bool
opt_aggressiveXOptBB Int -> Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Word
opt_inlineWFCacheLimit Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Bool
opt_edalize Int -> Bool -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
Bool
opt_renderEnums
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`
defClashOpts :: ClashOpts
defClashOpts :: ClashOpts
defClashOpts
= ClashOpts :: Bool
-> Int
-> Int
-> Word
-> Word
-> Word
-> DebugOpts
-> Bool
-> Bool
-> Bool
-> OverridingBool
-> Int
-> Maybe String
-> HdlSyn
-> Bool
-> [String]
-> Maybe Text
-> Bool
-> Bool
-> PreserveCase
-> Bool
-> Maybe (Maybe Int)
-> Bool
-> Bool
-> Bool
-> Word
-> Bool
-> Bool
-> ClashOpts
ClashOpts
{ opt_werror :: Bool
opt_werror = Bool
False
, 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_evaluatorFuelLimit :: Word
opt_evaluatorFuelLimit = Word
20
, opt_debug :: DebugOpts
opt_debug = DebugOpts
debugNone
, opt_cachehdl :: Bool
opt_cachehdl = Bool
True
, opt_clear :: Bool
opt_clear = Bool
False
, 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_importPaths :: [String]
opt_importPaths = []
, opt_componentPrefix :: Maybe Text
opt_componentPrefix = Maybe Text
forall a. Maybe a
Nothing
, opt_newInlineStrat :: Bool
opt_newInlineStrat = Bool
True
, opt_escapedIds :: Bool
opt_escapedIds = Bool
True
, opt_lowerCaseBasicIds :: PreserveCase
opt_lowerCaseBasicIds = PreserveCase
PreserveCase
, 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_aggressiveXOptBB :: Bool
opt_aggressiveXOptBB = Bool
False
, opt_inlineWFCacheLimit :: Word
opt_inlineWFCacheLimit = Word
10
, opt_edalize :: Bool
opt_edalize = Bool
False
, opt_renderEnums :: Bool
opt_renderEnums = Bool
True
}
newtype SdcInfo = SdcInfo
{ SdcInfo -> [(Text, VDomainConfiguration)]
sdcClock :: [(Text, VDomainConfiguration)]
}
pprSDC :: SdcInfo -> Doc ()
pprSDC :: SdcInfo -> Doc ()
pprSDC = [Doc ()] -> Doc ()
forall ann. [Doc ann] -> Doc ann
vcat ([Doc ()] -> Doc ()) -> (SdcInfo -> [Doc ()]) -> SdcInfo -> Doc ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, VDomainConfiguration) -> Doc ())
-> [(Text, VDomainConfiguration)] -> [Doc ()]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, VDomainConfiguration) -> Doc ()
forall ann. (Text, VDomainConfiguration) -> Doc ann
go ([(Text, VDomainConfiguration)] -> [Doc ()])
-> (SdcInfo -> [(Text, VDomainConfiguration)])
-> SdcInfo
-> [Doc ()]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SdcInfo -> [(Text, VDomainConfiguration)]
sdcClock
where
go :: (Text, VDomainConfiguration) -> Doc ann
go (Text
i, VDomainConfiguration
dom) =
let p :: Fixed E3
p = Integer -> Fixed E3
forall k (a :: k). Integer -> Fixed a
MkFixed (Natural -> Integer
forall a. Integral a => a -> Integer
toInteger (Natural -> Integer) -> Natural -> Integer
forall a b. (a -> b) -> a -> b
$ VDomainConfiguration -> Natural
vPeriod VDomainConfiguration
dom) :: Fixed E3
name :: Doc ann
name = Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
braces (Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ((Char -> Bool) -> Text -> Text
Text.dropAround (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\\') Text
i))
period :: Doc ann
period = Fixed E3 -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow Fixed E3
p
waveform :: Doc ann
waveform = Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
braces (Doc ann
"0.000" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Fixed E3 -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow (Fixed E3
p Fixed E3 -> Fixed E3 -> Fixed E3
forall a. Fractional a => a -> a -> a
/ Fixed E3
2))
targets :: Doc ann
targets = Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann
brackets (Doc ann
"get_ports" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
forall ann. Doc ann
name)
in [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
hsep
[ Doc ann
"create_clock"
, Doc ann
"-name" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
forall ann. Doc ann
name
, Doc ann
"-period" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
forall ann. Doc ann
period
, Doc ann
"-waveform" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
forall ann. Doc ann
waveform
, Doc ann
forall ann. Doc ann
targets
]