{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Clash.Driver.Types where
#include "MachDeps.h"
import           Control.DeepSeq                (NFData)
import           Data.Binary                    (Binary)
import           Data.Fixed
import           Data.Hashable
import qualified Data.Set                       as Set
import           Data.Text                      (Text)
#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.Signal.Internal
import           Clash.Core.Term                (Term)
import           Clash.Core.Var                 (Id)
import           Clash.Core.VarEnv              (VarEnv)
import           Clash.Netlist.BlackBox.Types   (HdlSyn (..))
import {-# SOURCE #-} Clash.Netlist.Types       (PreserveCase(..))
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
    
    
    
  } 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)
data DebugLevel
  = DebugNone
  
  | DebugSilent
  
  | DebugFinal
  
  | DebugName
  
  | DebugTry
  
  | 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,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 -> Word
opt_evaluatorFuelLimit :: Word
  
  
  
  
  , ClashOpts -> DebugLevel
opt_dbgLevel :: DebugLevel
  
  
  
  
  , ClashOpts -> Set String
opt_dbgTransformations :: Set.Set String
  
  
  
  , ClashOpts -> Int
opt_dbgTransformationsFrom :: Int
  
  
  
  , ClashOpts -> Int
opt_dbgTransformationsLimit :: Int
  
  
  
  
  , ClashOpts -> Maybe String
opt_dbgRewriteHistoryFile :: Maybe FilePath
  
  
  
  , 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 -> Bool
opt_floatSupport :: 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
  
  }
instance Hashable ClashOpts where
  hashWithSalt :: Int -> ClashOpts -> Int
hashWithSalt Int
s ClashOpts {Bool
Int
[String]
Maybe String
Maybe (Maybe Int)
Maybe Text
Word
Set String
OverridingBool
PreserveCase
HdlSyn
DebugLevel
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_floatSupport :: Bool
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_dbgRewriteHistoryFile :: Maybe String
opt_dbgTransformationsLimit :: Int
opt_dbgTransformationsFrom :: Int
opt_dbgTransformations :: Set String
opt_dbgLevel :: DebugLevel
opt_evaluatorFuelLimit :: Word
opt_inlineConstantLimit :: Word
opt_inlineFunctionLimit :: Word
opt_specLimit :: Int
opt_inlineLimit :: Int
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_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_clear :: ClashOpts -> Bool
opt_cachehdl :: ClashOpts -> Bool
opt_dbgRewriteHistoryFile :: ClashOpts -> Maybe String
opt_dbgTransformationsLimit :: ClashOpts -> Int
opt_dbgTransformationsFrom :: ClashOpts -> Int
opt_dbgTransformations :: ClashOpts -> Set String
opt_dbgLevel :: ClashOpts -> DebugLevel
opt_evaluatorFuelLimit :: ClashOpts -> Word
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 -> Word -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Word
opt_evaluatorFuelLimit 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 -> Maybe String -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
    Maybe String
opt_dbgRewriteHistoryFile 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 -> 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 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
   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
-> Word
-> DebugLevel
-> Set String
-> Int
-> Int
-> Maybe String
-> Bool
-> Bool
-> Bool
-> OverridingBool
-> Int
-> Maybe String
-> HdlSyn
-> Bool
-> Bool
-> [String]
-> Maybe Text
-> Bool
-> Bool
-> PreserveCase
-> Bool
-> Maybe (Maybe Int)
-> Bool
-> Bool
-> Bool
-> Word
-> Bool
-> ClashOpts
ClashOpts
  { opt_dbgLevel :: DebugLevel
opt_dbgLevel            = DebugLevel
DebugNone
  , opt_dbgRewriteHistoryFile :: Maybe String
opt_dbgRewriteHistoryFile = Maybe String
forall a. Maybe a
Nothing
  , 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_evaluatorFuelLimit :: Word
opt_evaluatorFuelLimit  = Word
20
  , 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_floatSupport :: Bool
opt_floatSupport        = 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
  }
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 a ann. Pretty a => (a, 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 :: (a, VDomainConfiguration) -> Doc ann
go (a
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 (a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty a
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
          ]