-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Clash: a functional hardware description language - As a library -- -- Clash is a functional hardware description language that borrows both -- its syntax and semantics from the functional programming language -- Haskell. The Clash compiler transforms these high-level descriptions -- to low-level synthesizable VHDL, Verilog, or SystemVerilog. -- -- Features of Clash: -- -- -- -- This package provides: -- -- -- -- Front-ends (for: parsing, typecheck, etc.) are provided by separate -- packages: -- -- -- -- Prelude library: -- https://hackage.haskell.org/package/clash-prelude @package clash-lib @version 1.9.0 -- | Utilities and definitions to deal with Verilog's time unit. These -- definitions are here mostly to deal with varying `timescale -- defintions, see: -- -- https://www.chipverify.com/verilog/verilog-timescale module Clash.Backend.Verilog.Time -- | Verilog time units data Unit Fs :: Unit Ps :: Unit Ns :: Unit Us :: Unit Ms :: Unit S :: Unit -- | Verilog time period. A combination of a length and a unit. data Period Period :: Word64 -> Unit -> Period -- | Verilog timescale. Influences simulation precision. data Scale Scale :: Period -> Period -> Scale -- | Time step in wait statements, e.g. `#1`. [step] :: Scale -> Period -- | Simulator precision - all units will get rounded to this period. [precision] :: Scale -> Period -- | Pretty print Scale to Verilog `timescale -- --
--   >>> scaleToString (Scale (Period 100 Ps) (Period 10 Fs))
--   "`timescale 100ps/10fs"
--   
scaleToString :: Scale -> String -- | Convert Unit to Verilog time unit -- --
--   >>> periodToString (Period 100 Fs)
--   "100fs"
--   
periodToString :: Period -> String -- | Convert Unit to Verilog time unit -- --
--   >>> unitToString Ms
--   "ms"
--   
unitToString :: Unit -> String -- | Parse string representing a Verilog time unit to Unit. -- --
--   >>> parseUnit "ms"
--   Just Ms
--   
--   >>> parseUnit "xs"
--   Nothing
--   
parseUnit :: String -> Maybe Unit -- | Parse a Verilog -- --
--   >>> parsePeriod "100ms"
--   Just (Period 100 Ms)
--   
--   >>> parsePeriod "100xs"
--   Nothing
--   
--   >>> parsePeriod "100"
--   Nothing
--   
--   >>> parsePeriod "ms"
--   Nothing
--   
parsePeriod :: String -> Maybe Period -- | Convert a period to a specific time unit. Will always output a minimum -- of 1, even if the given Period is already of the right -- Unit. -- --
--   >>> convertUnit Ps (Period 100 Ps)
--   100
--   
--   >>> convertUnit Fs (Period 100 Ps)
--   100000
--   
--   >>> convertUnit Ns (Period 100 Ps)
--   1
--   
--   >>> convertUnit Ms (Period 0 Ms)
--   1
--   
convertUnit :: Unit -> Period -> Word64 instance Control.DeepSeq.NFData Clash.Backend.Verilog.Time.Unit instance Data.Hashable.Class.Hashable Clash.Backend.Verilog.Time.Unit instance GHC.Generics.Generic Clash.Backend.Verilog.Time.Unit instance GHC.Classes.Ord Clash.Backend.Verilog.Time.Unit instance GHC.Classes.Eq Clash.Backend.Verilog.Time.Unit instance GHC.Enum.Bounded Clash.Backend.Verilog.Time.Unit instance GHC.Enum.Enum Clash.Backend.Verilog.Time.Unit instance GHC.Show.Show Clash.Backend.Verilog.Time.Unit instance Control.DeepSeq.NFData Clash.Backend.Verilog.Time.Period instance GHC.Classes.Eq Clash.Backend.Verilog.Time.Period instance Data.Hashable.Class.Hashable Clash.Backend.Verilog.Time.Period instance GHC.Generics.Generic Clash.Backend.Verilog.Time.Period instance GHC.Show.Show Clash.Backend.Verilog.Time.Period instance Control.DeepSeq.NFData Clash.Backend.Verilog.Time.Scale instance GHC.Classes.Eq Clash.Backend.Verilog.Time.Scale instance Data.Hashable.Class.Hashable Clash.Backend.Verilog.Time.Scale instance GHC.Generics.Generic Clash.Backend.Verilog.Time.Scale instance GHC.Show.Show Clash.Backend.Verilog.Time.Scale module Clash.Debug debugIsOn :: Bool -- | Performs trace when first argument evaluates to True traceIf :: Bool -> String -> a -> a module Clash.Driver.Bool data OverridingBool Auto :: OverridingBool Never :: OverridingBool Always :: OverridingBool toGhcOverridingBool :: OverridingBool -> OverridingBool fromGhcOverridingBool :: OverridingBool -> OverridingBool instance Control.DeepSeq.NFData Clash.Driver.Bool.OverridingBool instance GHC.Generics.Generic Clash.Driver.Bool.OverridingBool instance Data.Hashable.Class.Hashable Clash.Driver.Bool.OverridingBool instance GHC.Enum.Bounded Clash.Driver.Bool.OverridingBool instance GHC.Enum.Enum Clash.Driver.Bool.OverridingBool instance GHC.Classes.Ord Clash.Driver.Bool.OverridingBool instance GHC.Classes.Eq Clash.Driver.Bool.OverridingBool instance GHC.Read.Read Clash.Driver.Bool.OverridingBool instance GHC.Show.Show Clash.Driver.Bool.OverridingBool -- | Data types and rendering for Edalize Metadata files (EDAM). module Clash.Edalize.Edam -- | EDAM data structure to be given to an Edalize backend. This contains -- all information needed to generate a project scaffolding. Note that -- hooks and VPI modules are currently not specified by clash. data Edam Edam :: Text -> Text -> [EdamFile] -> EdamTools -> Edam [edamProjectName] :: Edam -> Text [edamTopEntity] :: Edam -> Text [edamFiles] :: Edam -> [EdamFile] [edamToolOptions] :: Edam -> EdamTools -- | Information about each file in the project. This does not include -- is_include_file or include_path, as these are not currently used by -- Clash. data EdamFile EdamFile :: FilePath -> EdamFileType -> Text -> EdamFile [efName] :: EdamFile -> FilePath [efType] :: EdamFile -> EdamFileType [efLogicalName] :: EdamFile -> Text -- | A subset of the file types recognized by Edalize. The supported -- formats are largely from IP-XACT 2014 (IEEE 1685-2014), although -- Edalize extends this with other types, e.g. QSYS. -- -- Only file types which are generated by Clash are listed. data EdamFileType -- | Unknown file type. Unknown :: EdamFileType -- | VHDL source. VhdlSource :: EdamFileType -- | Verilog source. VerilogSource :: EdamFileType -- | SystemVerilog source. SystemVerilogSource :: EdamFileType -- | Tool Command Language source. TclSource :: EdamFileType -- | QSys system source. QSYS :: EdamFileType -- | Synopsys Design Constraints source. SDC :: EdamFileType -- | Tool-specific configuration used by Edalize. Currently only tools -- which are supported by Clash are provided. data EdamTools EdamTools :: Maybe GhdlOptions -> Maybe IcarusOptions -> Maybe ModelsimOptions -> Maybe QuartusOptions -> Maybe VivadoOptions -> EdamTools [etGhdl] :: EdamTools -> Maybe GhdlOptions [etIcarus] :: EdamTools -> Maybe IcarusOptions [etModelsim] :: EdamTools -> Maybe ModelsimOptions [etQuartus] :: EdamTools -> Maybe QuartusOptions [etVivado] :: EdamTools -> Maybe VivadoOptions data GhdlOptions GhdlOptions :: [Text] -> [Text] -> GhdlOptions [ghdlAnalyseOpts] :: GhdlOptions -> [Text] [ghdlRunOpts] :: GhdlOptions -> [Text] data IcarusOptions IcarusOptions :: [Text] -> Text -> IcarusOptions [icarusOpts] :: IcarusOptions -> [Text] [icarusTimeScale] :: IcarusOptions -> Text data ModelsimOptions ModelsimOptions :: [Text] -> [Text] -> ModelsimOptions [msVlogOpts] :: ModelsimOptions -> [Text] [msVsimOpts] :: ModelsimOptions -> [Text] data QuartusOptions QuartusOptions :: Int -> Text -> Text -> [Text] -> [Text] -> QuartusOptions [quartusBoardDevIndex] :: QuartusOptions -> Int [quartusFamily] :: QuartusOptions -> Text [quartusDevice] :: QuartusOptions -> Text [quartusOpts] :: QuartusOptions -> [Text] [quartusDseOpts] :: QuartusOptions -> [Text] data VivadoOptions VivadoOptions :: Text -> VivadoOptions [vivadoPart] :: VivadoOptions -> Text pprEdam :: Edam -> Doc ann instance GHC.Show.Show Clash.Edalize.Edam.EdamFileType instance GHC.Classes.Eq Clash.Edalize.Edam.EdamFileType instance Data.Default.Class.Default Clash.Edalize.Edam.EdamTools instance Data.Default.Class.Default Clash.Edalize.Edam.VivadoOptions instance Data.Default.Class.Default Clash.Edalize.Edam.QuartusOptions instance Data.Default.Class.Default Clash.Edalize.Edam.ModelsimOptions instance Data.Default.Class.Default Clash.Edalize.Edam.IcarusOptions instance Data.Default.Class.Default Clash.Edalize.Edam.GhdlOptions module Clash.Unique type Unique = Int class Uniquable a getUnique :: Uniquable a => a -> Unique setUnique :: Uniquable a => a -> Unique -> a fromGhcUnique :: Unique -> Unique instance Clash.Unique.Uniquable Clash.Unique.Unique instance Clash.Unique.Uniquable GHC.Word.Word64 -- | Utilities related to the Eq type class. module Clash.Util.Eq -- | Compare two values using pointer equality. If that fails, use -- Eq to determine equality. Note that this function will only -- shortcut for values that are the same, but will always use Eq -- for values that differ. -- -- Values are evaluated to WHNF before comparison. This function can -- therefore not be used if any of its arguments is expected to be -- bottom. fastEq :: Eq a => a -> a -> Bool -- | Compare two values using pointer equality. If that fails, use given -- function to determine equality. Note that this function will only -- shortcut for values that are the same, but will always use the given -- function for values that differ. -- -- Values are evaluated to WHNF before comparison. This function can -- therefore not be used if any of its arguments is expected to be -- bottom. fastEqBy :: (a -> a -> Bool) -> a -> a -> Bool module Clash.Util.Interpolate -- | i will reflow the quasi-quoted text to 90 columns wide. If an -- interpolation variable is on its own line and expands to a multi-line -- string, the interpolated text will be indented the same as the -- interpolation variable was: -- --
--   :set -XQuasiQuotes
--   :{
--   a = "Multi\nLine\nString"
--   b = [i|
--       This line will be reflowed
--       and the interpolated
--       multi-line string here:
--           #{a}
--       will be indented. This
--       text is outdented again.
--     |]
--   :}
--   putStrLn b
--   
-- -- This line will be reflowed and the interpolated multi-line string -- here: Multi Line String will be indented. This text is outdented -- again. i :: QuasiQuoter format :: [Node] -> String toString :: Show a => a -> String instance GHC.Show.Show Clash.Util.Interpolate.Node instance GHC.Show.Show Clash.Util.Interpolate.Line module Clash.Pretty unsafeLookupEnvWord :: HasCallStack => String -> Word -> Word defaultPprWidth :: Int showDoc :: Doc ann -> String removeAnnotations :: Doc ann -> Doc () -- | A variant of Pretty that is not polymorphic on the type of -- annotations. This is needed to derive instances from Clash's pretty -- printer (PrettyPrec), which annotates documents with Clash-specific -- information and, therefore, fixes the type of annotations. class ClashPretty a clashPretty :: ClashPretty a => a -> Doc () fromPretty :: Pretty a => a -> Doc () module Clash.Data.UniqMap -- | A map indexed by a Unique. Typically the elements of this map -- are also uniqueable and provide their own key, however a unique can be -- associated with any value. newtype UniqMap a UniqMap :: IntMap a -> UniqMap a [uniqMapToIntMap] :: UniqMap a -> IntMap a -- | An empty map. empty :: UniqMap a -- | A map containing a single value indexed by the given key's unique. singleton :: Uniquable a => a -> b -> UniqMap b -- | A map containing a single value indexed by the value's unique. singletonUnique :: Uniquable a => a -> UniqMap a -- | Check if the map is empty. null :: UniqMap a -> Bool -- | Insert a new key-value pair into the map. insert :: Uniquable a => a -> b -> UniqMap b -> UniqMap b -- | Insert a new value into the map, using the unique of the value as the -- key. insertUnique :: Uniquable a => a -> UniqMap a -> UniqMap a -- | Insert a new key-value pair into the map, using the given combining -- function if there is already an entry with the same unique in the map. insertWith :: Uniquable a => (b -> b -> b) -> a -> b -> UniqMap b -> UniqMap b -- | Insert a list of key-value pairs into the map. insertMany :: Uniquable a => [(a, b)] -> UniqMap b -> UniqMap b -- | Lookup an item in the map, using the unique of the given key. lookup :: Uniquable a => a -> UniqMap b -> Maybe b -- | Lookup and item in the map, using the unique of the given key. If the -- item is not found in the map an error is raised. find :: Uniquable a => a -> UniqMap b -> b -- | Check if there is an entry in the map for the unique of the given -- value. elem :: Uniquable a => a -> UniqMap b -> Bool -- | Check if there is not an entry in the map for the unique of the given -- value. notElem :: Uniquable a => a -> UniqMap b -> Bool -- | Filter all elements in the map according to some predicate. filter :: (b -> Bool) -> UniqMap b -> UniqMap b -- | Apply a function to all elements in the map, keeping those where the -- result is not Nothing. mapMaybe :: (a -> Maybe b) -> UniqMap a -> UniqMap b -- | Lazily right-fold over the map using the given function. foldrWithUnique :: (Unique -> a -> b -> b) -> b -> UniqMap a -> b -- | Strictly left-fold over the map using the given function. foldlWithUnique' :: (b -> Unique -> a -> b) -> b -> UniqMap a -> b -- | Delete the entry in the map indexed by the unique of the given value. delete :: Uniquable a => a -> UniqMap b -> UniqMap b -- | Delete all entries in the map indexed by the uniques of the given -- values. deleteMany :: Uniquable a => [a] -> UniqMap b -> UniqMap b -- | Merge two unique maps, using the given combining funcion if a value -- with the same unique key exists in both maps. unionWith :: (b -> b -> b) -> UniqMap b -> UniqMap b -> UniqMap b -- | Filter the first map to only contain keys which are not in the second -- map. difference :: UniqMap b -> UniqMap b -> UniqMap b -- | Check if there are no common keys between two maps. disjoint :: UniqMap b -> UniqMap b -> Bool -- | Check if one map is a submap of another. submap :: UniqMap b -> UniqMap b -> Bool -- | Convert a list of key-value pairs to a map. fromList :: Uniquable a => [(a, b)] -> UniqMap b -- | Convert a map to a list of unique-value pairs. toList :: UniqMap b -> [(Unique, b)] -- | Get the unique keys of a map. keys :: UniqMap b -> [Unique] -- | Get the values of a map. elems :: UniqMap b -> [b] instance GHC.Show.Show a => GHC.Show.Show (Clash.Data.UniqMap.UniqMap a) instance GHC.Base.Semigroup (Clash.Data.UniqMap.UniqMap a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Data.UniqMap.UniqMap a) instance GHC.Base.Monoid (Clash.Data.UniqMap.UniqMap a) instance GHC.Base.Functor Clash.Data.UniqMap.UniqMap instance Data.Foldable.Foldable Clash.Data.UniqMap.UniqMap instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Data.UniqMap.UniqMap a) instance Data.Traversable.Traversable Clash.Data.UniqMap.UniqMap instance Clash.Pretty.ClashPretty a => Clash.Pretty.ClashPretty (Clash.Data.UniqMap.UniqMap a) -- | Utilities to detect and report GHC / operating system combinations -- that are known to be buggy. module Clash.Driver.BrokenGhcs fullCompilerVersion :: Version -- | Current OS. Currently only recognizes Linux, Windows, and macOS. os :: OS -- | What OS GHC is broken on (or all) data BrokenOn All :: BrokenOn SomeOs :: OS -> BrokenOn data GhcVersion Ghc :: Int -> Int -> Int -> GhcVersion [major0] :: GhcVersion -> Int [major1] :: GhcVersion -> Int [patch] :: GhcVersion -> Int data GhcRange GhcRange :: GhcVersion -> GhcVersion -> GhcRange -- | Start of range, inclusive [from] :: GhcRange -> GhcVersion -- | End of range, exclusive [to] :: GhcRange -> GhcVersion -- | Check if a GhcVersion is within a GhcRange ghcInRange :: GhcVersion -> GhcRange -> Bool -- | Construct a range of all GHC versions matching a major version ghcMajor :: Int -> Int -> GhcRange data Why Why :: String -> String -> String -> [(BrokenOn, GhcRange)] -> Why -- | What is broken [what] :: Why -> String -- | What can be done to work around or solve the issue [solution] :: Why -> String -- | Link to issue [issue] :: Why -> String -- | What operation systems are affected [brokenOn] :: Why -> [(BrokenOn, GhcRange)] -- | Get current GHC version expressed as a triple. It probably does -- something non-sensible on unreleased GHCs. ghcVersion :: GhcVersion -- | Pretty print Why into an error message whyPp :: Why -> String -- | Which GHCs are broken and why brokenGhcs :: [Why] -- | Given a BrokenOn, determine whether current OS matches matchOs :: BrokenOn -> Bool -- | Given a BrokenOn and GhcVersion, determine whether it -- matches current OS and GHC matchBroken :: (BrokenOn, GhcRange) -> Bool -- | Get first reason for GHC/OS being broken, if any broken :: Maybe Why -- | Throw an error if current OS / GHC version is known to be buggy assertWorking :: IO () instance GHC.Classes.Ord Clash.Driver.BrokenGhcs.GhcVersion instance GHC.Classes.Eq Clash.Driver.BrokenGhcs.GhcVersion -- | Term Literal module Clash.Core.Literal -- | Term Literal data Literal IntegerLiteral :: !Integer -> Literal IntLiteral :: !Integer -> Literal WordLiteral :: !Integer -> Literal Int64Literal :: !Integer -> Literal Word64Literal :: !Integer -> Literal Int8Literal :: !Integer -> Literal Int16Literal :: !Integer -> Literal Int32Literal :: !Integer -> Literal Word8Literal :: !Integer -> Literal Word16Literal :: !Integer -> Literal Word32Literal :: !Integer -> Literal StringLiteral :: !String -> Literal FloatLiteral :: !Word32 -> Literal DoubleLiteral :: !Word64 -> Literal CharLiteral :: !Char -> Literal NaturalLiteral :: !Integer -> Literal ByteArrayLiteral :: !ByteArray -> Literal instance Data.Binary.Class.Binary Clash.Core.Literal.Literal instance Data.Hashable.Class.Hashable Clash.Core.Literal.Literal instance Control.DeepSeq.NFData Clash.Core.Literal.Literal instance GHC.Generics.Generic Clash.Core.Literal.Literal instance GHC.Show.Show Clash.Core.Literal.Literal instance GHC.Classes.Ord Clash.Core.Literal.Literal instance GHC.Classes.Eq Clash.Core.Literal.Literal module Clash.Netlist.Id.Common parseWhiteSpace :: Text -> Maybe Text isWhiteSpace :: Char -> Bool parsePrintable :: Text -> Maybe Text parseSingle :: (Char -> Bool) -> Text -> Maybe Text parseMaybeSingle :: (Char -> Bool) -> Text -> Maybe Text parseLetter :: Text -> Maybe Text parseDigit :: Text -> Maybe Text parseLetterOrDigit :: Text -> Maybe Text parseUnderscore :: Text -> Maybe Text parseDollar :: Text -> Maybe Text parseTab :: Text -> Maybe Text parseBackslash :: Text -> Maybe Text failNonEmpty :: Text -> Maybe Text repeatParseN :: (Text -> Maybe Text) -> Text -> Maybe (Int, Text) repeatParse :: (Text -> Maybe Text) -> Text -> Maybe Text -- | Encodes tuples as TupN and removes all characters not matching -- a predicate. zEncode :: (Char -> Bool) -> Text -> Text prettyName :: Text -> Text maybeTuple :: Text -> Maybe (Text, Text) parseTuple :: Text -> Maybe (Int, Text) module Data.Text.Prettyprint.Doc.Extra type Doc = Doc () layoutOneLine :: Doc ann -> SimpleDocStream ann renderOneLine :: Doc ann -> Text int :: Applicative f => Int -> f Doc integer :: Applicative f => Integer -> f Doc char :: Applicative f => Char -> f Doc lbrace :: Applicative f => f Doc rbrace :: Applicative f => f Doc colon :: Applicative f => f Doc semi :: Applicative f => f Doc equals :: Applicative f => f Doc comma :: Applicative f => f Doc dot :: Applicative f => f Doc lparen :: Applicative f => f Doc rparen :: Applicative f => f Doc space :: Applicative f => f Doc brackets :: Functor f => f Doc -> f Doc braces :: Functor f => f Doc -> f Doc tupled :: Functor f => f [Doc] -> f Doc (<+>) :: Applicative f => f Doc -> f Doc -> f Doc infixr 6 <+> vcat :: Functor f => f [Doc] -> f Doc hcat :: Functor f => f [Doc] -> f Doc nest :: Functor f => Int -> f Doc -> f Doc indent :: Functor f => Int -> f Doc -> f Doc parens :: Functor f => f Doc -> f Doc emptyDoc :: Applicative f => f Doc punctuate :: Applicative f => f Doc -> f [Doc] -> f [Doc] encloseSep :: Applicative f => f Doc -> f Doc -> f Doc -> f [Doc] -> f Doc enclose :: Applicative f => f Doc -> f Doc -> f Doc -> f Doc line :: Applicative f => f Doc line' :: Applicative f => f Doc softline :: Applicative f => f Doc softline' :: Applicative f => f Doc pretty :: (Applicative f, Pretty a) => a -> f Doc stringS :: Applicative f => Text -> f Doc string :: Applicative f => Text -> f Doc squotes :: Applicative f => f Doc -> f Doc dquotes :: Functor f => f Doc -> f Doc align :: Functor f => f Doc -> f Doc hsep :: Functor f => f [Doc] -> f Doc vsep :: Functor f => f [Doc] -> f Doc isEmpty :: Doc -> Bool fill :: Applicative f => Int -> f Doc -> f Doc column :: Functor f => f (Int -> Doc) -> f Doc nesting :: Functor f => f (Int -> Doc) -> f Doc flatAlt :: Applicative f => f Doc -> f Doc -> f Doc comment :: Applicative f => Text -> Text -> f Doc squote :: Applicative f => f Doc -- | Options to influence the layout algorithms. newtype LayoutOptions LayoutOptions :: PageWidth -> LayoutOptions [layoutPageWidth] :: LayoutOptions -> PageWidth -- | Maximum number of characters that fit in one line. The layout -- algorithms will try not to exceed the set limit by inserting line -- breaks when applicable (e.g. via softline'). data PageWidth -- | Layouters should not exceed the specified space per line. -- -- AvailablePerLine :: !Int -> !Double -> PageWidth -- | Layouters should not introduce line breaks on their own. Unbounded :: PageWidth -- | (layoutCompact x) lays out the document x without -- adding any indentation and without preserving annotations. Since no -- 'pretty' printing is involved, this layouter is very fast. The -- resulting output contains fewer characters than a prettyprinted -- version and can be used for output that is read by other programs. -- --
--   >>> let doc = hang 4 (vsep ["lorem", "ipsum", hang 4 (vsep ["dolor", "sit"])])
--   
--   >>> doc
--   lorem
--       ipsum
--       dolor
--           sit
--   
-- --
--   >>> let putDocCompact = renderIO System.IO.stdout . layoutCompact
--   
--   >>> putDocCompact doc
--   lorem
--   ipsum
--   dolor
--   sit
--   
layoutCompact :: Doc ann1 -> SimpleDocStream ann2 -- | This is the default layout algorithm, and it is used by show, -- putDoc and hPutDoc. -- -- layoutPretty commits to rendering something in a -- certain way if the next element fits the layout constraints; in other -- words, it has one SimpleDocStream element lookahead when -- rendering. Consider using the smarter, but a bit less performant, -- layoutSmart algorithm if the results seem to run off -- to the right before having lots of line breaks. layoutPretty :: LayoutOptions -> Doc ann -> SimpleDocStream ann -- | (renderLazy sdoc) takes the output sdoc from -- a rendering function and transforms it to lazy text. -- --
--   >>> let render = TL.putStrLn . renderLazy . layoutPretty defaultLayoutOptions
--   
--   >>> let doc = "lorem" <+> align (vsep ["ipsum dolor", parens "foo bar", "sit amet"])
--   
--   >>> render doc
--   lorem ipsum dolor
--         (foo bar)
--         sit amet
--   
renderLazy :: SimpleDocStream ann -> Text instance GHC.Base.Applicative f => Data.String.IsString (f Data.Text.Prettyprint.Doc.Extra.Doc) module GHC.BasicTypes.Extra -- | Determine whether given InlineSpec is NOINLINE or more strict -- (OPAQUE) isNoInline :: InlineSpec -> Bool -- | Determine whether given InlineSpec is OPAQUE. If this function -- is used on a GHC that does not support OPAQUE yet (<9.4), it will -- return True if given InlineSpec is NOINLINE instead. isOpaque :: InlineSpec -> Bool instance GHC.Generics.Generic BasicTypes.InlineSpec instance Control.DeepSeq.NFData BasicTypes.InlineSpec instance Data.Binary.Class.Binary BasicTypes.InlineSpec -- | Names module Clash.Core.Name data NameSort User :: NameSort System :: NameSort Internal :: NameSort type OccName = Text data Name a Name :: NameSort -> !OccName -> {-# UNPACK #-} !Unique -> !SrcSpan -> Name a [nameSort] :: Name a -> NameSort [nameOcc] :: Name a -> !OccName [nameUniq] :: Name a -> {-# UNPACK #-} !Unique [nameLoc] :: Name a -> !SrcSpan mkUnsafeName :: NameSort -> Text -> Unique -> Name a mkUnsafeSystemName :: Text -> Unique -> Name a mkUnsafeInternalName :: Text -> Unique -> Name a appendToName :: Name a -> Text -> Name a -- | Built-in "bad" SrcSpans for common sources of location -- uncertainty noSrcSpan :: SrcSpan instance Data.Binary.Class.Binary Clash.Core.Name.NameSort instance Data.Hashable.Class.Hashable Clash.Core.Name.NameSort instance Control.DeepSeq.NFData Clash.Core.Name.NameSort instance GHC.Generics.Generic Clash.Core.Name.NameSort instance GHC.Show.Show Clash.Core.Name.NameSort instance GHC.Classes.Ord Clash.Core.Name.NameSort instance GHC.Classes.Eq Clash.Core.Name.NameSort instance Data.Binary.Class.Binary (Clash.Core.Name.Name a) instance Control.DeepSeq.NFData (Clash.Core.Name.Name a) instance GHC.Generics.Generic (Clash.Core.Name.Name a) instance GHC.Show.Show (Clash.Core.Name.Name a) instance GHC.Classes.Eq (Clash.Core.Name.Name a) instance GHC.Classes.Ord (Clash.Core.Name.Name a) instance Data.Hashable.Class.Hashable (Clash.Core.Name.Name a) instance Clash.Unique.Uniquable (Clash.Core.Name.Name a) -- | Variables in CoreHW module Clash.Core.Var -- | Variables in CoreHW data Var a -- | Constructor for type variables TyVar :: !Name a -> {-# UNPACK #-} !Unique -> Kind -> Var a [varName] :: Var a -> !Name a -- | Invariant: forall x . varUniq x ~ nameUniq (varName x) [varUniq] :: Var a -> {-# UNPACK #-} !Unique [varType] :: Var a -> Kind -- | Constructor for term variables Id :: !Name a -> {-# UNPACK #-} !Unique -> Type -> IdScope -> Var a [varName] :: Var a -> !Name a -- | Invariant: forall x . varUniq x ~ nameUniq (varName x) [varUniq] :: Var a -> {-# UNPACK #-} !Unique [varType] :: Var a -> Type [idScope] :: Var a -> IdScope data IdScope GlobalId :: IdScope LocalId :: IdScope -- | Term variable type Id = Var Term -- | Type variable type TyVar = Var Type -- | Make a term variable mkId :: Type -> IdScope -> TmName -> Id mkLocalId :: Type -> TmName -> Id mkGlobalId :: Type -> TmName -> Id -- | Make a type variable mkTyVar :: Kind -> TyName -> TyVar setIdScope :: IdScope -> Var a -> Var a -- | Change the name of a variable modifyVarName :: (Name a -> Name a) -> Var a -> Var a isGlobalId :: Var a -> Bool isLocalId :: Var a -> Bool instance GHC.Classes.Ord Clash.Core.Var.IdScope instance GHC.Classes.Eq Clash.Core.Var.IdScope instance Data.Binary.Class.Binary Clash.Core.Var.IdScope instance Data.Hashable.Class.Hashable Clash.Core.Var.IdScope instance Control.DeepSeq.NFData Clash.Core.Var.IdScope instance GHC.Generics.Generic Clash.Core.Var.IdScope instance GHC.Show.Show Clash.Core.Var.IdScope instance Data.Binary.Class.Binary (Clash.Core.Var.Var a) instance Control.DeepSeq.NFData (Clash.Core.Var.Var a) instance GHC.Generics.Generic (Clash.Core.Var.Var a) instance GHC.Show.Show (Clash.Core.Var.Var a) instance Data.Hashable.Class.Hashable (Clash.Core.Var.Var a) instance GHC.Classes.Eq (Clash.Core.Var.Var a) instance GHC.Classes.Ord (Clash.Core.Var.Var a) instance Clash.Unique.Uniquable (Clash.Core.Var.Var a) -- | Data Constructors in CoreHW module Clash.Core.DataCon -- | Data Constructor data DataCon MkData :: !DcName -> {-# UNPACK #-} !Unique -> !ConTag -> !Type -> [TyVar] -> [TyVar] -> [Type] -> [DcStrictness] -> [Text] -> DataCon -- | Name of the DataCon [dcName] :: DataCon -> !DcName -- | Invariant: forall x . dcUniq x ~ nameUniq (dcName x) [dcUniq] :: DataCon -> {-# UNPACK #-} !Unique -- | Syntactical position in the type definition [dcTag] :: DataCon -> !ConTag -- | Type of the 'DataCon [dcType] :: DataCon -> !Type -- | Universally quantified type-variables, these type variables are also -- part of the result type of the DataCon [dcUnivTyVars] :: DataCon -> [TyVar] -- | Existentially quantified type-variables, these type variables are not -- part of the result of the DataCon, but only of the arguments. [dcExtTyVars] :: DataCon -> [TyVar] -- | Argument types [dcArgTys] :: DataCon -> [Type] -- | Argument strictness [dcArgStrict] :: DataCon -> [DcStrictness] -- | Names of fields. Used when data constructor is referring to a record -- type. [dcFieldLabels] :: DataCon -> [Text] -- | DataCon reference type DcName = Name DataCon -- | Syntactical position of the DataCon in the type definition type ConTag = Int data DcStrictness Strict :: DcStrictness Lazy :: DcStrictness instance Data.Binary.Class.Binary Clash.Core.DataCon.DcStrictness instance Data.Hashable.Class.Hashable Clash.Core.DataCon.DcStrictness instance GHC.Classes.Eq Clash.Core.DataCon.DcStrictness instance Control.DeepSeq.NFData Clash.Core.DataCon.DcStrictness instance GHC.Generics.Generic Clash.Core.DataCon.DcStrictness instance Data.Binary.Class.Binary Clash.Core.DataCon.DataCon instance Control.DeepSeq.NFData Clash.Core.DataCon.DataCon instance GHC.Generics.Generic Clash.Core.DataCon.DataCon instance GHC.Show.Show Clash.Core.DataCon.DataCon instance GHC.Classes.Eq Clash.Core.DataCon.DataCon instance GHC.Classes.Ord Clash.Core.DataCon.DataCon instance Clash.Unique.Uniquable Clash.Core.DataCon.DataCon -- | Type Constructors in CoreHW module Clash.Core.TyCon -- | Type Constructor data TyCon -- | Algorithmic DataCons AlgTyCon :: {-# UNPACK #-} !Unique -> !TyConName -> !Kind -> !Int -> !AlgTyConRhs -> !Bool -> TyCon [tyConUniq] :: TyCon -> {-# UNPACK #-} !Unique -- | Name of the TyCon [tyConName] :: TyCon -> !TyConName -- | Kind of the TyCon [tyConKind] :: TyCon -> !Kind -- | Number of type arguments [tyConArity] :: TyCon -> !Int -- | DataCon definitions [algTcRhs] :: TyCon -> !AlgTyConRhs -- | Is this a class dictionary? [isClassTc] :: TyCon -> !Bool PromotedDataCon :: {-# UNPACK #-} !Unique -> !TyConName -> !Kind -> !Int -> !DataCon -> TyCon [tyConUniq] :: TyCon -> {-# UNPACK #-} !Unique -- | Name of the TyCon [tyConName] :: TyCon -> !TyConName -- | Kind of the TyCon [tyConKind] :: TyCon -> !Kind -- | Number of type arguments [tyConArity] :: TyCon -> !Int -- | DataCon which is promoted [tyConData] :: TyCon -> !DataCon -- | Function TyCons (e.g. type families) FunTyCon :: {-# UNPACK #-} !Unique -> !TyConName -> !Kind -> !Int -> [([Type], Type)] -> TyCon [tyConUniq] :: TyCon -> {-# UNPACK #-} !Unique -- | Name of the TyCon [tyConName] :: TyCon -> !TyConName -- | Kind of the TyCon [tyConKind] :: TyCon -> !Kind -- | Number of type arguments [tyConArity] :: TyCon -> !Int -- | List of: ([LHS match types], RHS type) [tyConSubst] :: TyCon -> [([Type], Type)] -- | Primitive TyCons PrimTyCon :: {-# UNPACK #-} !Unique -> !TyConName -> !Kind -> !Int -> TyCon [tyConUniq] :: TyCon -> {-# UNPACK #-} !Unique -- | Name of the TyCon [tyConName] :: TyCon -> !TyConName -- | Kind of the TyCon [tyConKind] :: TyCon -> !Kind -- | Number of type arguments [tyConArity] :: TyCon -> !Int -- | TyCon reference type TyConName = Name TyCon type TyConMap = UniqMap TyCon -- | The RHS of an Algebraic Datatype data AlgTyConRhs DataTyCon :: [DataCon] -> AlgTyConRhs -- | The DataCons of a TyCon [dataCons] :: AlgTyConRhs -> [DataCon] NewTyCon :: !DataCon -> ([TyVar], Type) -> AlgTyConRhs -- | The newtype DataCon [dataCon] :: AlgTyConRhs -> !DataCon -- | The argument type of the newtype DataCon in eta-reduced form, which is -- just the representation of the TyCon. The TyName's are the -- type-variables from the corresponding TyCon. [ntEtadRhs] :: AlgTyConRhs -> ([TyVar], Type) -- | Create a Kind out of a TyConName mkKindTyCon :: TyConName -> Kind -> TyCon -- | Does the TyCon look like a tuple TyCon isTupleTyConLike :: TyConName -> Bool isPrimTc :: TyCon -> Bool isNewTypeTc :: TyCon -> Bool isPromotedDc :: TyCon -> Bool -- | Get the DataCons belonging to a TyCon tyConDataCons :: TyCon -> [DataCon] instance Data.Binary.Class.Binary Clash.Core.TyCon.AlgTyConRhs instance Control.DeepSeq.NFData Clash.Core.TyCon.AlgTyConRhs instance GHC.Generics.Generic Clash.Core.TyCon.AlgTyConRhs instance GHC.Show.Show Clash.Core.TyCon.AlgTyConRhs instance Data.Binary.Class.Binary Clash.Core.TyCon.TyCon instance Control.DeepSeq.NFData Clash.Core.TyCon.TyCon instance GHC.Generics.Generic Clash.Core.TyCon.TyCon instance GHC.Show.Show Clash.Core.TyCon.TyCon instance GHC.Classes.Eq Clash.Core.TyCon.TyCon instance Clash.Unique.Uniquable Clash.Core.TyCon.TyCon -- | Assortment of utility function used in the Clash library module Clash.Util -- | A class that can generate unique numbers class Monad m => MonadUnique m -- | Get a new unique getUniqueM :: MonadUnique m => m Int data ClashException ClashException :: SrcSpan -> String -> Maybe String -> ClashException assertPanic :: String -> Int -> a assertPprPanic :: HasCallStack => String -> Int -> Doc ann -> a pprPanic :: String -> Doc ann -> a callStackDoc :: HasCallStack => Doc ann warnPprTrace :: HasCallStack => Bool -> String -> Int -> Doc ann -> a -> a pprTrace :: String -> Doc ann -> a -> a pprTraceDebug :: String -> Doc ann -> a -> a pprDebugAndThen :: (String -> a) -> Doc ann -> Doc ann -> a -- | Create a TH expression that returns the a formatted string containing -- the name of the module curLoc is spliced into, and the line -- where it was spliced. curLoc :: Q Exp -- | Cache the result of a monadic action makeCached :: (MonadState s m, Hashable k, Eq k) => k -> Lens' s (HashMap k v) -> m v -> m v -- | Cache the result of a monadic action using a UniqMap makeCachedU :: (MonadState s m, Uniquable k) => k -> Lens' s (UniqMap v) -> m v -> m v -- | Cache the result of a monadic action using a OMap makeCachedO :: (MonadState s m, Uniquable k) => k -> Lens' s (OMap Unique v) -> m v -> m v -- | Same as indexNote with last two arguments swapped indexNote' :: HasCallStack => String -> Int -> [a] -> a -- | Unsafe indexing, return a custom error message when indexing fails indexNote :: HasCallStack => String -> [a] -> Int -> a clashLibVersion :: Version -- | x y -> floor (logBase x y), x > 1 && y > 0 flogBase :: Integer -> Integer -> Maybe Int -- | x y -> ceiling (logBase x y), x > 1 && y > 0 clogBase :: Integer -> Integer -> Maybe Int -- | Get the package id of the type of a value -- --
--   >>> pkgIdFromTypeable (0 :: Unsigned 32)
--   "clash-prelude-...
--   
pkgIdFromTypeable :: Typeable a => a -> String reportTimeDiff :: UTCTime -> UTCTime -> String -- | Left-biased choice on maybes orElses :: [Maybe a] -> Maybe a wantedLanguageExtensions :: [Extension] unwantedLanguageExtensions :: [Extension] thenCompare :: Ordering -> Ordering -> Ordering hoistMaybe :: Applicative m => Maybe b -> MaybeT m b -- | Source Span -- -- A SrcSpan identifies either a specific portion of a text file -- or a human-readable description of a location. data SrcSpan -- | Built-in "bad" SrcSpans for common sources of location -- uncertainty noSrcSpan :: SrcSpan instance GHC.Base.Monad m => Clash.Util.MonadUnique (Control.Monad.Trans.State.Lazy.StateT GHC.Types.Int m) instance GHC.Show.Show Clash.Util.ClashException instance GHC.Exception.Type.Exception Clash.Util.ClashException -- | Types in CoreHW module Clash.Core.Type -- | Types in CoreHW: function and polymorphic types data Type -- | Type variable VarTy :: !TyVar -> Type -- | Type constant ConstTy :: !ConstTy -> Type -- | Polymorphic Type ForAllTy :: !TyVar -> !Type -> Type -- | Type Application AppTy :: !Type -> !Type -> Type -- | Type literal LitTy :: !LitTy -> Type -- | Annotated type, see Clash.Annotations.SynthesisAttributes AnnType :: [Attr Text] -> !Type -> Type -- | An easier view on types data TypeView -- | Function type FunTy :: !Type -> !Type -> TypeView -- | Applied TyCon TyConApp :: !TyConName -> [Type] -> TypeView -- | Neither of the above OtherType :: !Type -> TypeView -- | Type Constants data ConstTy -- | TyCon type TyCon :: !TyConName -> ConstTy -- | Function type Arrow :: ConstTy -- | Literal Types data LitTy NumTy :: !Integer -> LitTy SymTy :: !String -> LitTy CharTy :: !Char -> LitTy -- | The level above types type Kind = Type -- | Either a Kind or a Type type KindOrType = Type -- | Reference to a Kind type KiName = Name Kind -- | Reference to a Type type TyName = Name Type -- | Type variable type TyVar = Var Type -- | An easier view on types -- -- Note [Arrow arguments] -- -- Clash' Arrow type can either have 2 or 4 arguments, depending on who -- created it. By default it has two arguments: the argument type of a -- function, and the result type of a function. -- -- So when do we have 4 arguments? When in Haskell/GHC land the arrow was -- unsaturated. This can happen in instance heads, or in the eta-reduced -- representation of newtypes. So what are those additional 2 arguments -- compared to the "normal" function type? They're the kinds of argument -- and result type. tyView :: Type -> TypeView -- | A view on types in which newtypes are transparent, the Signal type is -- transparent, and type functions are evaluated to WHNF (when possible). -- -- Strips away ALL layers. If no layers are found it returns the given -- type. coreView :: TyConMap -> Type -> Type -- | A view on types in which newtypes are transparent, the Signal type is -- transparent, and type functions are evaluated to WHNF (when possible). -- -- Only strips away one "layer". coreView1 :: TyConMap -> Type -> Maybe Type -- | Make a Type out of a TyCon mkTyConTy :: TyConName -> Type -- | Make a function type of an argument and result type mkFunTy :: Type -> Type -> Type -- | Make a polymorphic function type out of a result type and a list of -- quantifiers and function argument types mkPolyFunTy :: Type -> [Either TyVar Type] -> Type -- | Make a TyCon Application out of a TyCon and a list of argument types mkTyConApp :: TyConName -> [Type] -> Type -- | Split a function type in an argument and result type splitFunTy :: TyConMap -> Type -> Maybe (Type, Type) splitFunTys :: TyConMap -> Type -> ([Type], Type) -- | Split a poly-function type in a: list of type-binders and argument -- types, and the result type splitFunForallTy :: Type -> ([Either TyVar Type], Type) -- | Split a poly-function type in a: list of type-binders and argument -- types, and the result type. Looks through Signal and type -- functions. splitCoreFunForallTy :: TyConMap -> Type -> ([Either TyVar Type], Type) -- | Split a TyCon Application in a TyCon and its arguments splitTyConAppM :: Type -> Maybe (TyConName, [Type]) -- | Is a type a polymorphic or function type? isPolyFunTy :: Type -> Bool -- | Is a type a polymorphic or function type under coreView1? isPolyFunCoreTy :: TyConMap -> Type -> Bool -- | Is a type polymorphic? isPolyTy :: Type -> Bool isTypeFamilyApplication :: TyConMap -> Type -> Bool -- | Is a type a function type? isFunTy :: TyConMap -> Type -> Bool isClassTy :: TyConMap -> Type -> Bool -- | Apply a function type to an argument type and get the result type applyFunTy :: TyConMap -> Type -> Type -> Type findFunSubst :: TyConMap -> [([Type], Type)] -> [Type] -> Maybe Type reduceTypeFamily :: TyConMap -> Type -> Maybe Type isIntegerTy :: Type -> Bool -- | Normalize a type, looking through Signals and newtypes -- -- For example: Signal a (Vec (6-1) (Unsigned (3+1))) normalizes -- to Vec 5 (Unsigned 4) normalizeType :: TyConMap -> Type -> Type varAttrs :: Var a -> [Attr Text] -- | Extract attributes from type. Will return an empty list if this is an -- AnnType with an empty list AND if this is not an AnnType at all. typeAttrs :: Type -> [Attr Text] instance Data.Binary.Class.Binary Clash.Core.Type.ConstTy instance Data.Hashable.Class.Hashable Clash.Core.Type.ConstTy instance Control.DeepSeq.NFData Clash.Core.Type.ConstTy instance GHC.Generics.Generic Clash.Core.Type.ConstTy instance GHC.Show.Show Clash.Core.Type.ConstTy instance GHC.Classes.Ord Clash.Core.Type.ConstTy instance GHC.Classes.Eq Clash.Core.Type.ConstTy instance Data.Binary.Class.Binary Clash.Core.Type.LitTy instance Data.Hashable.Class.Hashable Clash.Core.Type.LitTy instance Control.DeepSeq.NFData Clash.Core.Type.LitTy instance GHC.Generics.Generic Clash.Core.Type.LitTy instance GHC.Show.Show Clash.Core.Type.LitTy instance GHC.Classes.Ord Clash.Core.Type.LitTy instance GHC.Classes.Eq Clash.Core.Type.LitTy instance Data.Binary.Class.Binary Clash.Core.Type.Type instance Control.DeepSeq.NFData Clash.Core.Type.Type instance GHC.Generics.Generic Clash.Core.Type.Type instance GHC.Show.Show Clash.Core.Type.Type instance GHC.Show.Show Clash.Core.Type.TypeView instance (TypeError ...) => Data.Hashable.Class.Hashable Clash.Core.Type.Type -- | Builtin Type and Kind definitions module Clash.Core.TysPrim liftedTypeKind :: Type typeNatKind :: Type typeSymbolKind :: Type intPrimTy :: Type integerPrimTy :: Type charPrimTy :: Type stringPrimTy :: Type voidPrimTy :: Type wordPrimTy :: Type int64PrimTy :: Type word64PrimTy :: Type int8PrimTy :: Type int16PrimTy :: Type int32PrimTy :: Type word8PrimTy :: Type word16PrimTy :: Type word32PrimTy :: Type floatPrimTy :: Type doublePrimTy :: Type naturalPrimTy :: Type byteArrayPrimTy :: Type eqPrimTy :: Type tysPrimMap :: TyConMap -- | Term representation in the CoreHW language: System F + LetRec + Case module Clash.Core.Term -- | Term representation in the CoreHW language: System F + LetRec + Case data Term -- | Variable reference Var :: !Id -> Term -- | Datatype constructor Data :: !DataCon -> Term -- | Literal Literal :: !Literal -> Term -- | Primitive Prim :: !PrimInfo -> Term -- | Term-abstraction Lam :: !Id -> Term -> Term -- | Type-abstraction TyLam :: !TyVar -> Term -> Term -- | Application App :: !Term -> !Term -> Term -- | Type-application TyApp :: !Term -> !Type -> Term -- | Recursive let-binding Let :: !Bind Term -> Term -> Term -- | Case-expression: subject, type of alternatives, list of alternatives Case :: !Term -> !Type -> [Alt] -> Term -- | Cast a term from one type to another Cast :: !Term -> !Type -> !Type -> Term -- | Annotated term Tick :: !TickInfo -> !Term -> Term pattern Letrec :: [LetBinding] -> Term -> Term -- | Abstract a term over a list of term and type variables mkAbstraction :: Term -> [Either Id TyVar] -> Term -- | Abstract a term over a list of type variables mkTyLams :: Term -> [TyVar] -> Term -- | Abstract a term over a list of variables mkLams :: Term -> [Id] -> Term -- | Apply a list of types and terms to a term mkApps :: Term -> [Either Term Type] -> Term -- | Apply a list of types to a term mkTyApps :: Term -> [Type] -> Term -- | Apply a list of terms to a term mkTmApps :: Term -> [Term] -> Term mkTicks :: Term -> [TickInfo] -> Term -- | Term reference type TmName = Name Term -- | Make a term variable out of a variable reference or ticked variable -- reference varToId :: Term -> Id data Bind a NonRec :: Id -> a -> Bind a Rec :: [(Id, a)] -> Bind a -- | Binding in a LetRec construct type LetBinding = (Id, Term) -- | Patterns in the LHS of a case-decomposition data Pat -- | Datatype pattern, '[TyVar]' bind existentially-quantified -- type-variables of a DataCon DataPat :: !DataCon -> [TyVar] -> [Id] -> Pat -- | Literal pattern LitPat :: !Literal -> Pat -- | Default pattern DefaultPat :: Pat -- | Get the list of term-binders out of a DataType pattern patIds :: Pat -> ([TyVar], [Id]) patVars :: Pat -> [Var a] type Alt = (Pat, Term) data TickInfo -- | Source tick, will get added by GHC by running clash with `-g` SrcSpan :: !SrcSpan -> TickInfo -- | Modifier for naming module instantiations and registers, are added by -- the user by using the functions -- Clash.Magic.[prefixName,suffixName,setName] NameMod :: !NameMod -> !Type -> TickInfo -- | Deduplicate, i.e. try to share expressions between multiple branches. DeDup :: TickInfo -- | Do not deduplicate, i.e. keep, an expression inside a -- case-alternative; do not try to share expressions between multiple -- branches. NoDeDup :: TickInfo stripTicks :: Term -> Term -- | Like stripTicks but removes all ticks from subexpressions. stripAllTicks :: Term -> Term -- | Partition ticks in source ticks and nameMod ticks partitionTicks :: [TickInfo] -> ([TickInfo], [TickInfo]) -- | Tag to indicate which instance/register name modifier was used data NameMod -- |
--   Clash.Magic.prefixName
--   
PrefixName :: NameMod -- |
--   Clash.Magic.suffixName
--   
SuffixName :: NameMod -- |
--   Clash.Magic.suffixNameP
--   
SuffixNameP :: NameMod -- |
--   Clash.Magic.setName
--   
SetName :: NameMod data PrimInfo PrimInfo :: !Text -> !Type -> !WorkInfo -> !IsMultiPrim -> !PrimUnfolding -> PrimInfo [primName] :: PrimInfo -> !Text [primType] :: PrimInfo -> !Type [primWorkInfo] :: PrimInfo -> !WorkInfo -- | Primitive with multiple return values. Useful for primitives that -- cannot return their results as a single product type, due to -- limitation of synthesis tooling. It will be applied to its normal -- arguments, followed by the variables it should assign its results to. -- -- See: setupMultiResultPrim [primMultiResult] :: PrimInfo -> !IsMultiPrim [primUnfolding] :: PrimInfo -> !PrimUnfolding data PrimUnfolding NoUnfolding :: PrimUnfolding Unfolding :: !Id -> PrimUnfolding data IsMultiPrim SingleResult :: IsMultiPrim MultiResult :: IsMultiPrim data MultiPrimInfo MultiPrimInfo :: PrimInfo -> DataCon -> [Type] -> MultiPrimInfo [mpi_primInfo] :: MultiPrimInfo -> PrimInfo [mpi_resultDc] :: MultiPrimInfo -> DataCon [mpi_resultTypes] :: MultiPrimInfo -> [Type] data WorkInfo -- | Ignores its arguments, and outputs a constant WorkConstant :: WorkInfo -- | Never adds any work WorkNever :: WorkInfo -- | Does work when the arguments are variable WorkVariable :: WorkInfo -- | Performs work regardless of whether the variables are constant or -- variable; these are things like clock or reset generators WorkAlways :: WorkInfo -- | A more restrictive version of WorkNever, where the value is the -- argument at the given position if all arguments for the given list of -- positions are also WorkIdentity WorkIdentity :: Int -> [Int] -> WorkInfo -- | Context in which a term appears data CoreContext -- | Function position of an application AppFun :: CoreContext -- | Argument position of an application. If this is an argument applied to -- a primitive, a tuple is defined containing (name of the primitive, -- #type args, #term args) AppArg :: Maybe (Text, Int, Int) -> CoreContext -- | Function position of a type application TyAppC :: CoreContext -- | RHS of a Let-binder with the sibling LHS' LetBinding :: Id -> [Id] -> CoreContext -- | Body of a Let-binding with the bound LHS' LetBody :: [LetBinding] -> CoreContext -- | Body of a lambda-term with the abstracted variable LamBody :: Id -> CoreContext -- | Body of a TyLambda-term with the abstracted type-variable TyLamBody :: TyVar -> CoreContext -- | RHS of a case-alternative with the bound pattern on the LHS CaseAlt :: Pat -> CoreContext -- | Subject of a case-decomposition CaseScrut :: CoreContext -- | Body of a Cast CastBody :: CoreContext -- | Body of a Tick TickC :: TickInfo -> CoreContext -- | A list of CoreContext describes the complete navigation path -- from the top-level to a specific sub-expression. type Context = [CoreContext] -- | Is the Context a Lambda/Term-abstraction context? isLambdaBodyCtx :: CoreContext -> Bool -- | Is the Context a Tick context? isTickCtx :: CoreContext -> Bool -- | Visit all terms in a term, testing it with a predicate, and returning -- a list of predicate yields. walkTerm :: forall a. (Term -> Maybe a) -> Term -> [a] -- | Split a (Type)Application in the applied term and it arguments collectArgs :: Term -> (Term, [Either Term Type]) collectArgsTicks :: Term -> (Term, [Either Term Type], [TickInfo]) collectTicks :: Term -> (Term, [TickInfo]) collectTermIds :: Term -> [Id] -- | Split a (Type)Abstraction in the bound variables and the abstracted -- term collectBndrs :: Term -> ([Either Id TyVar], Term) -- | Given a function application, find the primitive it's applied. Yields -- Nothing if given term is not an application or if it is not a -- primitive. primArg :: Term -> Maybe (Text, Int, Int) instance Data.Binary.Class.Binary Clash.Core.Term.NameMod instance Data.Hashable.Class.Hashable Clash.Core.Term.NameMod instance Control.DeepSeq.NFData Clash.Core.Term.NameMod instance GHC.Generics.Generic Clash.Core.Term.NameMod instance GHC.Show.Show Clash.Core.Term.NameMod instance GHC.Classes.Ord Clash.Core.Term.NameMod instance GHC.Classes.Eq Clash.Core.Term.NameMod instance Data.Binary.Class.Binary Clash.Core.Term.TickInfo instance Control.DeepSeq.NFData Clash.Core.Term.TickInfo instance GHC.Generics.Generic Clash.Core.Term.TickInfo instance GHC.Show.Show Clash.Core.Term.TickInfo instance GHC.Classes.Eq Clash.Core.Term.TickInfo instance Data.Binary.Class.Binary Clash.Core.Term.IsMultiPrim instance Data.Hashable.Class.Hashable Clash.Core.Term.IsMultiPrim instance GHC.Classes.Eq Clash.Core.Term.IsMultiPrim instance Control.DeepSeq.NFData Clash.Core.Term.IsMultiPrim instance GHC.Generics.Generic Clash.Core.Term.IsMultiPrim instance GHC.Show.Show Clash.Core.Term.IsMultiPrim instance Data.Binary.Class.Binary Clash.Core.Term.PrimUnfolding instance Data.Hashable.Class.Hashable Clash.Core.Term.PrimUnfolding instance GHC.Classes.Eq Clash.Core.Term.PrimUnfolding instance Control.DeepSeq.NFData Clash.Core.Term.PrimUnfolding instance GHC.Generics.Generic Clash.Core.Term.PrimUnfolding instance GHC.Show.Show Clash.Core.Term.PrimUnfolding instance Data.Binary.Class.Binary Clash.Core.Term.WorkInfo instance Data.Hashable.Class.Hashable Clash.Core.Term.WorkInfo instance Control.DeepSeq.NFData Clash.Core.Term.WorkInfo instance GHC.Generics.Generic Clash.Core.Term.WorkInfo instance GHC.Show.Show Clash.Core.Term.WorkInfo instance GHC.Classes.Eq Clash.Core.Term.WorkInfo instance Data.Binary.Class.Binary Clash.Core.Term.PrimInfo instance Control.DeepSeq.NFData Clash.Core.Term.PrimInfo instance GHC.Generics.Generic Clash.Core.Term.PrimInfo instance GHC.Show.Show Clash.Core.Term.PrimInfo instance GHC.Base.Functor Clash.Core.Term.Bind instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Core.Term.Bind a) instance Data.Hashable.Class.Hashable a => Data.Hashable.Class.Hashable (Clash.Core.Term.Bind a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Core.Term.Bind a) instance GHC.Generics.Generic (Clash.Core.Term.Bind a) instance GHC.Show.Show a => GHC.Show.Show (Clash.Core.Term.Bind a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Core.Term.Bind a) instance Data.Binary.Class.Binary Clash.Core.Term.Pat instance Control.DeepSeq.NFData Clash.Core.Term.Pat instance GHC.Generics.Generic Clash.Core.Term.Pat instance GHC.Show.Show Clash.Core.Term.Pat instance GHC.Classes.Ord Clash.Core.Term.Pat instance GHC.Classes.Eq Clash.Core.Term.Pat instance Data.Binary.Class.Binary Clash.Core.Term.Term instance Control.DeepSeq.NFData Clash.Core.Term.Term instance GHC.Generics.Generic Clash.Core.Term.Term instance GHC.Show.Show Clash.Core.Term.Term instance Data.Binary.Class.Binary Clash.Core.Term.CoreContext instance Control.DeepSeq.NFData Clash.Core.Term.CoreContext instance GHC.Generics.Generic Clash.Core.Term.CoreContext instance GHC.Show.Show Clash.Core.Term.CoreContext instance GHC.Classes.Eq Clash.Core.Term.CoreContext instance GHC.Classes.Ord Clash.Core.Term.TickInfo -- | Types used in BlackBox modules module Clash.Netlist.BlackBox.Types -- | See BlackBox for documentation on this record's fields. (They -- are intentionally renamed to prevent name clashes.) data BlackBoxMeta BlackBoxMeta :: Usage -> TemplateKind -> [BlackBoxTemplate] -> [BlackBoxTemplate] -> [(Int, Int)] -> [((Text, Text), BlackBox)] -> RenderVoid -> [BlackBox] -> [BlackBox] -> BlackBoxMeta [bbOutputUsage] :: BlackBoxMeta -> Usage [bbKind] :: BlackBoxMeta -> TemplateKind [bbLibrary] :: BlackBoxMeta -> [BlackBoxTemplate] [bbImports] :: BlackBoxMeta -> [BlackBoxTemplate] [bbFunctionPlurality] :: BlackBoxMeta -> [(Int, Int)] [bbIncludes] :: BlackBoxMeta -> [((Text, Text), BlackBox)] [bbRenderVoid] :: BlackBoxMeta -> RenderVoid [bbResultNames] :: BlackBoxMeta -> [BlackBox] [bbResultInits] :: BlackBoxMeta -> [BlackBox] -- | Use this value in your blackbox template function if you do want to -- accept the defaults as documented in BlackBox. emptyBlackBoxMeta :: BlackBoxMeta -- | A BlackBox function generates a blackbox template, given the inputs -- and result type of the function it should provide a blackbox for. This -- is useful when having a need for blackbox functions, ... TODO: docs type BlackBoxFunction = Bool " Indicates whether caller needs a declaration. If set, the function is still free to return an expression, but the caller will convert it to a declaration." -> Text " Name of primitive" -> [Either Term Type] " Arguments" -> [Type] " Result types" -> NetlistMonad (Either String (BlackBoxMeta, BlackBox)) -- | A BlackBox Template is a List of Elements TODO: Add name of function -- for better error messages type BlackBoxTemplate = [Element] data TemplateKind TDecl :: TemplateKind TExpr :: TemplateKind -- | Elements of a blackbox context. If you extend this list, make sure to -- update the following functions: -- -- data Element -- | Dumps given text without processing in HDL Text :: !Text -> Element -- | Component instantiation hole Component :: !Decl -> Element -- | Output hole; Result :: Element -- | Input hole Arg :: !Int -> Element -- | Like Arg, but its first argument is the scoping level. For use in in -- generated code only. ArgGen :: !Int -> !Int -> Element -- | Like Arg, but input hole must be a constant. Const :: !Int -> Element -- | Like Arg, but input hole must be a literal Lit :: !Int -> Element -- | Name hole Name :: !Int -> Element -- | Like Arg but only insert variable reference (creating an assignment -- elsewhere if necessary). ToVar :: [Element] -> !Int -> Element -- | Symbol hole Sym :: !Text -> !Int -> Element -- | Type declaration hole Typ :: !Maybe Int -> Element -- | Type root hole TypM :: !Maybe Int -> Element -- | Error value hole Err :: !Maybe Int -> Element -- | Select element type from a vector-like type TypElem :: !Element -> Element -- | Hole for the name of the component in which the blackbox is -- instantiated CompName :: Element IncludeName :: !Int -> Element -- | Index data type hole, the field is the (exclusive) maximum index IndexType :: !Element -> Element -- | Size of a type hole Size :: !Element -> Element -- | Length of a vector-like hole Length :: !Element -> Element -- | Depth of a tree hole Depth :: !Element -> Element -- | Max index into a vector-like type MaxIndex :: !Element -> Element -- | Hole containing a filepath for a data file FilePath :: !Element -> Element -- | Create data file HOLE0 with contents HOLE1 Template :: [Element] -> [Element] -> Element -- | Hole marking beginning (True) or end (False) of a generative construct Gen :: !Bool -> Element IF :: !Element -> [Element] -> [Element] -> Element And :: [Element] -> Element -- | Hole indicating whether IntWordInteger are 64-Bit IW64 :: Element -- | Compare less-or-equal CmpLE :: !Element -> !Element -> Element -- | Hole indicating which synthesis tool we're generating HDL for HdlSyn :: HdlSyn -> Element -- | Convert to (True)/from(False) a bit-vector BV :: !Bool -> [Element] -> !Element -> Element -- | Record selector of a type Sel :: !Element -> !Int -> Element IsLit :: !Int -> Element IsVar :: !Int -> Element -- | Whether element is scalar IsScalar :: !Int -> Element -- | Whether a domain's reset lines are active high. Errors if not applied -- to a KnownDomain or KnownConfiguration. IsActiveHigh :: !Int -> Element -- | Tag of a domain. Tag :: !Int -> Element -- | Period of a domain. Errors if not applied to a KnownDomain or -- KnownConfiguration. Period :: !Int -> Element -- | Longest period of all known domains. The minimum duration returned is -- 100 ns, see -- https://github.com/clash-lang/clash-compiler/issues/2455. LongestPeriod :: Element -- | Test active edge of memory elements in a certain domain. Errors if not -- applied to a KnownDomain or KnownConfiguration. ActiveEdge :: !ActiveEdge -> !Int -> Element -- | Whether a domain's reset lines are synchronous. Errors if not applied -- to a KnownDomain or KnownConfiguration. IsSync :: !Int -> Element -- | Whether the initial (or "power up") value of memory elements in a -- domain are configurable to a specific value rather than -- unknown/undefined. Errors if not applied to a KnownDomain or -- KnownConfiguration. IsInitDefined :: !Int -> Element -- | Whether given enable line is active. More specifically, whether the -- enable line is NOT set to a constant True. IsActiveEnable :: !Int -> Element -- | Whether argument is undefined. E.g., an XException, error call, -- removed argument, or primitive that is undefined. This template tag -- will always return 0 (False) if -- `-fclash-aggressive-x-optimization-blackboxes` is NOT set. IsUndefined :: !Int -> Element StrCmp :: [Element] -> !Int -> Element OutputUsage :: !Int -> Element Vars :: !Int -> Element GenSym :: [Element] -> !Int -> Element -- | Repeat hole n times Repeat :: [Element] -> [Element] -> Element -- | Evaluate hole but swallow output DevNull :: [Element] -> Element SigD :: [Element] -> !Maybe Int -> Element -- | The "context name", name set by setName, defaults to the name -- of the closest binder CtxName :: Element -- | Component instantiation hole. First argument indicates which function -- argument to instantiate. Third argument corresponds to output and -- input assignments, where the first element is the output assignment, -- and the subsequent elements are the consecutive input assignments. -- -- The LHS of the tuple is the name of the signal, while the RHS of the -- tuple is the type of the signal data Decl Decl :: !Int -> !Int -> [(BlackBoxTemplate, BlackBoxTemplate)] -> Decl data HdlSyn Vivado :: HdlSyn Quartus :: HdlSyn Other :: HdlSyn -- | Whether this primitive should be rendered when its result type is -- void. Defaults to NoRenderVoid. data RenderVoid -- | Render blackbox, even if result type is void RenderVoid :: RenderVoid -- | Don't render blackbox result type is void. Default for all blackboxes. NoRenderVoid :: RenderVoid instance Data.Aeson.Types.FromJSON.FromJSON Clash.Netlist.BlackBox.Types.RenderVoid instance Data.Hashable.Class.Hashable Clash.Netlist.BlackBox.Types.RenderVoid instance GHC.Classes.Eq Clash.Netlist.BlackBox.Types.RenderVoid instance Data.Binary.Class.Binary Clash.Netlist.BlackBox.Types.RenderVoid instance Control.DeepSeq.NFData Clash.Netlist.BlackBox.Types.RenderVoid instance GHC.Generics.Generic Clash.Netlist.BlackBox.Types.RenderVoid instance GHC.Show.Show Clash.Netlist.BlackBox.Types.RenderVoid instance Data.Hashable.Class.Hashable Clash.Netlist.BlackBox.Types.TemplateKind instance Data.Binary.Class.Binary Clash.Netlist.BlackBox.Types.TemplateKind instance Control.DeepSeq.NFData Clash.Netlist.BlackBox.Types.TemplateKind instance GHC.Generics.Generic Clash.Netlist.BlackBox.Types.TemplateKind instance GHC.Classes.Eq Clash.Netlist.BlackBox.Types.TemplateKind instance GHC.Show.Show Clash.Netlist.BlackBox.Types.TemplateKind instance Data.Hashable.Class.Hashable Clash.Netlist.BlackBox.Types.HdlSyn instance Data.Binary.Class.Binary Clash.Netlist.BlackBox.Types.HdlSyn instance Control.DeepSeq.NFData Clash.Netlist.BlackBox.Types.HdlSyn instance GHC.Generics.Generic Clash.Netlist.BlackBox.Types.HdlSyn instance GHC.Read.Read Clash.Netlist.BlackBox.Types.HdlSyn instance GHC.Show.Show Clash.Netlist.BlackBox.Types.HdlSyn instance GHC.Classes.Eq Clash.Netlist.BlackBox.Types.HdlSyn instance Data.Hashable.Class.Hashable Clash.Netlist.BlackBox.Types.Decl instance GHC.Classes.Eq Clash.Netlist.BlackBox.Types.Decl instance Data.Binary.Class.Binary Clash.Netlist.BlackBox.Types.Decl instance Control.DeepSeq.NFData Clash.Netlist.BlackBox.Types.Decl instance GHC.Generics.Generic Clash.Netlist.BlackBox.Types.Decl instance GHC.Show.Show Clash.Netlist.BlackBox.Types.Decl instance Data.Hashable.Class.Hashable Clash.Netlist.BlackBox.Types.Element instance GHC.Classes.Eq Clash.Netlist.BlackBox.Types.Element instance Data.Binary.Class.Binary Clash.Netlist.BlackBox.Types.Element instance Control.DeepSeq.NFData Clash.Netlist.BlackBox.Types.Element instance GHC.Generics.Generic Clash.Netlist.BlackBox.Types.Element instance GHC.Show.Show Clash.Netlist.BlackBox.Types.Element -- | Type and instance definitions for Primitive module Clash.Primitives.Types data TemplateSource -- | Template source stored in file on filesystem TFile :: FilePath -> TemplateSource -- | Template stored inline TInline :: Text -> TemplateSource data TemplateKind TDecl :: TemplateKind TExpr :: TemplateKind data TemplateFormat TTemplate :: TemplateFormat THaskell :: TemplateFormat -- | A BBFN is a parsed version of a fully qualified function name. It is -- guaranteed to have at least one module name which is not Main. data BlackBoxFunctionName BlackBoxFunctionName :: [String] -> String -> BlackBoxFunctionName -- | Externally defined primitive data Primitive a b c d -- | Primitive template written in a Clash specific templating language BlackBox :: !Text -> WorkInfo -> RenderVoid -> Bool -> TemplateKind -> c -> Usage -> [a] -> [a] -> [(Int, Int)] -> [((Text, Text), b)] -> [b] -> [b] -> b -> Primitive a b c d -- | Name of the primitive [name] :: Primitive a b c d -> !Text -- | Whether the primitive does any work, i.e. takes chip area [workInfo] :: Primitive a b c d -> WorkInfo -- | Whether this primitive should be rendered when its result type is -- void. Defaults to NoRenderVoid. [renderVoid] :: Primitive a b c d -> RenderVoid -- | Wether this blackbox assigns its results to multiple variables. See -- setupMultiResultPrim [multiResult] :: Primitive a b c d -> Bool -- | Whether this results in an expression or a declaration [kind] :: Primitive a b c d -> TemplateKind -- | A warning to be outputted when the primitive is instantiated. This is -- intended to be used as a warning for primitives that are not -- synthesizable, but may also be used for other purposes. [warning] :: Primitive a b c d -> c -- | How the result is assigned in HDL. This is used to determine the type -- of declaration used to render the result (wire/reg or -- signal/variable). The default usage is continuous assignment. [outputUsage] :: Primitive a b c d -> Usage -- | VHDL only: add library declarations for the given names [libraries] :: Primitive a b c d -> [a] -- | VHDL only: add use declarations for the given names [imports] :: Primitive a b c d -> [a] -- | Indicates how often a function will be instantiated in a blackbox. For -- example, consider the following higher-order function that creates a -- tree structure: -- -- fold :: (a -> a -> a) -> Vec n a -> a -- -- In order to generate HDL for an instance of fold we need log2(n) calls -- to the first argument, `a -> a -> a` (plus a few more if n is -- not a power of two). Note that this only targets multiple textual -- instances of the function. If you can generate the HDL using a -- for-loop and only need to call ~INST once, you don't have to worry -- about this option. See the blackbox for map for an example of -- this. -- -- Right now, option can only be generated by BlackBoxHaskell. It cannot -- be used within JSON primitives. To see how to use this, see the -- Haskell blackbox for fold. [functionPlurality] :: Primitive a b c d -> [(Int, Int)] -- | Create files to be included with the generated primitive. The fields -- are ((name, extension), content), where content is a template of the -- file Defaults to [] when not specified in the -- .primitives file [includes] :: Primitive a b c d -> [((Text, Text), b)] -- | (Maybe) Control the generated name of the result [resultNames] :: Primitive a b c d -> [b] -- | (Maybe) Control the initial/power-up value of the result [resultInits] :: Primitive a b c d -> [b] -- | Used to indiciate type of template (declaration or expression). Will -- be filled with Template or an Either decl expr. [template] :: Primitive a b c d -> b -- | Primitive template rendered by a Haskell function (given as raw source -- code) BlackBoxHaskell :: !Text -> WorkInfo -> UsedArguments -> Bool -> BlackBoxFunctionName -> d -> Primitive a b c d -- | Name of the primitive [name] :: Primitive a b c d -> !Text -- | Whether the primitive does any work, i.e. takes chip area [workInfo] :: Primitive a b c d -> WorkInfo -- | Arguments used by blackbox. Used to remove arguments during -- normalization. [usedArguments] :: Primitive a b c d -> UsedArguments -- | Wether this blackbox assigns its results to multiple variables. See -- setupMultiResultPrim [multiResult] :: Primitive a b c d -> Bool [functionName] :: Primitive a b c d -> BlackBoxFunctionName -- | Holds blackbox function and its hash, (Int, BlackBoxFunction), in a -- CompiledPrimitive. [function] :: Primitive a b c d -> d -- | A primitive that carries additional information. These are "real" -- primitives, hardcoded in the compiler. For example: mapSignal -- in GHC2Core.coreToTerm. Primitive :: !Text -> WorkInfo -> !Text -> Primitive a b c d -- | Name of the primitive [name] :: Primitive a b c d -> !Text -- | Whether the primitive does any work, i.e. takes chip area [workInfo] :: Primitive a b c d -> WorkInfo -- | Additional information [primSort] :: Primitive a b c d -> !Text -- | Data type to indicate what arguments are in use by a BlackBox data UsedArguments -- | Only these are used UsedArguments :: [Int] -> UsedArguments -- | All but these are used IgnoredArguments :: [Int] -> UsedArguments type GuardedCompiledPrimitive = PrimitiveGuard CompiledPrimitive type GuardedResolvedPrimitive = PrimitiveGuard ResolvedPrimitive -- | A PrimMap maps primitive names to a Primitive type PrimMap a = HashMap Text a -- | An unresolved primitive still contains pointers to files. type UnresolvedPrimitive = Primitive Text ((TemplateFormat, BlackBoxFunctionName), Maybe TemplateSource) (Maybe Text) (Maybe TemplateSource) -- | A parsed primitive does not contain pointers to filesystem files -- anymore, but holds uncompiled BlackBoxTemplates and -- BlackBoxFunctions. type ResolvedPrimitive = Primitive Text ((TemplateFormat, BlackBoxFunctionName), Maybe Text) () (Maybe Text) type ResolvedPrimMap = PrimMap GuardedResolvedPrimitive -- | A compiled primitive has compiled all templates and functions from its -- ResolvedPrimitive counterpart. The Int in the tuple is a hash -- of the (uncompiled) BlackBoxFunction. type CompiledPrimitive = Primitive BlackBoxTemplate BlackBox () (Int, BlackBoxFunction) type CompiledPrimMap = PrimMap GuardedCompiledPrimitive instance Data.Hashable.Class.Hashable Clash.Primitives.Types.BlackBoxFunctionName instance Data.Binary.Class.Binary Clash.Primitives.Types.BlackBoxFunctionName instance Control.DeepSeq.NFData Clash.Primitives.Types.BlackBoxFunctionName instance GHC.Generics.Generic Clash.Primitives.Types.BlackBoxFunctionName instance GHC.Classes.Eq Clash.Primitives.Types.BlackBoxFunctionName instance Control.DeepSeq.NFData Clash.Primitives.Types.TemplateSource instance GHC.Generics.Generic Clash.Primitives.Types.TemplateSource instance Data.Hashable.Class.Hashable Clash.Primitives.Types.TemplateSource instance GHC.Classes.Eq Clash.Primitives.Types.TemplateSource instance GHC.Show.Show Clash.Primitives.Types.TemplateSource instance Control.DeepSeq.NFData Clash.Primitives.Types.TemplateFormat instance Data.Hashable.Class.Hashable Clash.Primitives.Types.TemplateFormat instance GHC.Classes.Eq Clash.Primitives.Types.TemplateFormat instance GHC.Generics.Generic Clash.Primitives.Types.TemplateFormat instance GHC.Show.Show Clash.Primitives.Types.TemplateFormat instance Data.Binary.Class.Binary Clash.Primitives.Types.UsedArguments instance Control.DeepSeq.NFData Clash.Primitives.Types.UsedArguments instance Data.Hashable.Class.Hashable Clash.Primitives.Types.UsedArguments instance GHC.Classes.Eq Clash.Primitives.Types.UsedArguments instance GHC.Generics.Generic Clash.Primitives.Types.UsedArguments instance GHC.Show.Show Clash.Primitives.Types.UsedArguments instance GHC.Base.Functor (Clash.Primitives.Types.Primitive a b c) instance (Data.Hashable.Class.Hashable c, Data.Hashable.Class.Hashable a, Data.Hashable.Class.Hashable b, Data.Hashable.Class.Hashable d) => Data.Hashable.Class.Hashable (Clash.Primitives.Types.Primitive a b c d) instance (GHC.Classes.Eq c, GHC.Classes.Eq a, GHC.Classes.Eq b, GHC.Classes.Eq d) => GHC.Classes.Eq (Clash.Primitives.Types.Primitive a b c d) instance (Data.Binary.Class.Binary c, Data.Binary.Class.Binary a, Data.Binary.Class.Binary b, Data.Binary.Class.Binary d) => Data.Binary.Class.Binary (Clash.Primitives.Types.Primitive a b c d) instance (Control.DeepSeq.NFData c, Control.DeepSeq.NFData a, Control.DeepSeq.NFData b, Control.DeepSeq.NFData d) => Control.DeepSeq.NFData (Clash.Primitives.Types.Primitive a b c d) instance GHC.Generics.Generic (Clash.Primitives.Types.Primitive a b c d) instance (GHC.Show.Show c, GHC.Show.Show a, GHC.Show.Show b, GHC.Show.Show d) => GHC.Show.Show (Clash.Primitives.Types.Primitive a b c d) instance Data.Aeson.Types.FromJSON.FromJSON Clash.Primitives.Types.UnresolvedPrimitive instance GHC.Show.Show Clash.Primitives.Types.BlackBoxFunctionName -- | Parser definitions for BlackBox templates module Clash.Netlist.BlackBox.Parser -- | Parse a text as a BlackBoxTemplate, returns a list of errors in case -- parsing fails runParse :: Text -> Result BlackBoxTemplate -- | PrettyPrec printing class and instances for CoreHW module Clash.Core.Pretty -- | PrettyPrec printing Show-like typeclass class PrettyPrec p pprPrec :: (PrettyPrec p, Monad m) => Rational -> p -> m ClashDoc pprPrec' :: (PrettyPrec p, Monad m) => PrettyOptions -> Rational -> p -> m ClashDoc -- | Options for the pretty-printer, controlling which elements to hide. data PrettyOptions PrettyOptions :: Bool -> Bool -> Bool -> Bool -> PrettyOptions -- | whether to display unique identifiers [displayUniques] :: PrettyOptions -> Bool -- | whether to display type information [displayTypes] :: PrettyOptions -> Bool -- | whether to display module qualifiers [displayQualifiers] :: PrettyOptions -> Bool -- | whether to display ticks [displayTicks] :: PrettyOptions -> Bool -- | Clash's specialized Doc type holds metadata of type -- ClashAnnotation. type ClashDoc = Doc ClashAnnotation -- | Annotations carried on pretty-printed code. data ClashAnnotation -- | marking navigation to a different context AnnContext :: CoreContext -> ClashAnnotation -- | marking a specific sort of syntax AnnSyntax :: SyntaxElement -> ClashAnnotation -- | Specific places in the program syntax. data SyntaxElement Keyword :: SyntaxElement LitS :: SyntaxElement Type :: SyntaxElement Unique :: SyntaxElement Qualifier :: SyntaxElement Ticky :: SyntaxElement ppr :: PrettyPrec p => p -> ClashDoc ppr' :: PrettyPrec p => PrettyOptions -> p -> ClashDoc -- | Print a PrettyPrec thing to a String showPpr :: PrettyPrec p => p -> String showPpr' :: PrettyPrec p => PrettyOptions -> p -> String tracePprId :: PrettyPrec p => p -> p tracePpr :: PrettyPrec p => p -> a -> a fromPpr :: PrettyPrec a => a -> Doc () unsafeLookupEnvBool :: HasCallStack => String -> Bool -> Bool instance GHC.Show.Show Clash.Core.Pretty.SyntaxElement instance GHC.Classes.Eq Clash.Core.Pretty.SyntaxElement instance GHC.Classes.Eq Clash.Core.Pretty.ClashAnnotation instance GHC.Classes.Ord Clash.Core.Pretty.TypePrec instance GHC.Classes.Eq Clash.Core.Pretty.TypePrec instance Clash.Core.Pretty.PrettyPrec Clash.Core.Term.Pat instance Clash.Core.Pretty.PrettyPrec (Clash.Core.Name.Name a) instance Clash.Core.Pretty.PrettyPrec a => Clash.Core.Pretty.PrettyPrec [a] instance Clash.Core.Pretty.PrettyPrec (Clash.Core.Var.Id, Clash.Core.Term.Term) instance Clash.Core.Pretty.PrettyPrec Data.Text.Internal.Text instance Clash.Core.Pretty.PrettyPrec Clash.Core.Type.Type instance Clash.Core.Pretty.PrettyPrec Clash.Core.TyCon.TyCon instance Clash.Core.Pretty.PrettyPrec Clash.Core.Type.LitTy instance Clash.Core.Pretty.PrettyPrec Clash.Core.Term.Term instance Clash.Core.Pretty.PrettyPrec Clash.Core.Term.TickInfo instance Clash.Core.Pretty.PrettyPrec SrcLoc.SrcSpan instance Clash.Core.Pretty.PrettyPrec (Clash.Core.Var.Var a) instance Clash.Core.Pretty.PrettyPrec Clash.Core.DataCon.DataCon instance Clash.Core.Pretty.PrettyPrec Clash.Core.Literal.Literal instance Data.Default.Class.Default Clash.Core.Pretty.PrettyOptions instance Clash.Pretty.ClashPretty (Clash.Core.Name.Name a) instance Clash.Pretty.ClashPretty Clash.Core.Type.Type instance Prettyprinter.Internal.Pretty Clash.Core.Type.LitTy instance Clash.Pretty.ClashPretty Clash.Core.Term.Term instance Clash.Pretty.ClashPretty (Clash.Core.Var.Var a) module Clash.Core.VarEnv -- | Map indexed by variables type VarEnv a = UniqMap a -- | Is the environment empty nullVarEnv :: VarEnv a -> Bool -- | Look up a value based on the variable lookupVarEnv :: Var b -> VarEnv a -> Maybe a -- | Lookup a value based on the variable -- -- Errors out when the variable is not present lookupVarEnv' :: HasCallStack => VarEnv a -> Var b -> a -- | Lookup a value based on the unique of a variable lookupVarEnvDirectly :: Unique -> VarEnv a -> Maybe a -- | Empty map emptyVarEnv :: VarEnv a -- | Environment containing a single variable-value pair unitVarEnv :: Var b -> a -> VarEnv a -- | Create an environment given a list of var-value pairs mkVarEnv :: [(Var a, b)] -> VarEnv b -- | Add a variable-value pair to the environment; overwrites the value if -- the variable already exists extendVarEnv :: Var b -> a -> VarEnv a -> VarEnv a -- | Add a list of variable-value pairs; the values of existing keys will -- be overwritten extendVarEnvList :: VarEnv a -> [(Var b, a)] -> VarEnv a -- | Add a variable-value pair to the environment; if the variable already -- exists, the two values are merged with the given function extendVarEnvWith :: Var b -> a -> (a -> a -> a) -> VarEnv a -> VarEnv a -- | Remove a variable-value pair from the environment delVarEnv :: VarEnv a -> Var b -> VarEnv a -- | Remove a list of variable-value pairs from the environment delVarEnvList :: VarEnv a -> [Var b] -> VarEnv a -- | Get the (left-biased) union of two environments unionVarEnv :: VarEnv a -> VarEnv a -> VarEnv a -- | Get the union of two environments, mapped values existing in both -- environments will be merged with the given function. unionVarEnvWith :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a -- | Filter the first varenv to only contain keys which are not in the -- second varenv. differenceVarEnv :: VarEnv a -> VarEnv a -> VarEnv a -- | Apply a function to every element in the environment mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b -- | Apply a function to every element in the environment; values for which -- the function returns Nothing are removed from the environment mapMaybeVarEnv :: (a -> Maybe b) -> VarEnv a -> VarEnv b -- | Strict left-fold over an environment using both the unique of the the -- variable and the value foldlWithUniqueVarEnv' :: (a -> Unique -> b -> a) -> a -> VarEnv b -> a -- | Does the variable exist in the environment elemVarEnv :: Var a -> VarEnv b -> Bool -- | Does the variable not exist in the environment notElemVarEnv :: Var a -> VarEnv b -> Bool -- | Extract the elements eltsVarEnv :: VarEnv a -> [a] -- | Set of variables type VarSet = UniqMap (Var Any) -- | The empty set emptyVarSet :: VarSet -- | The set of a single variable unitVarSet :: Var a -> VarSet -- | Remove a variable from the set based on its Unique delVarSetByKey :: Unique -> VarSet -> VarSet -- | Union two sets unionVarSet :: VarSet -> VarSet -> VarSet -- | Take the difference of two sets differenceVarSet :: VarSet -> VarSet -> VarSet -- | Check whether a varset is empty nullVarSet :: VarSet -> Bool -- | Is the variable an element in the set elemVarSet :: Var a -> VarSet -> Bool -- | Is the variable not an element in the set notElemVarSet :: Var a -> VarSet -> Bool -- | Is the set of variables A a subset of the variables B subsetVarSet :: VarSet -> VarSet -> Bool -- | Are the sets of variables disjoint disjointVarSet :: VarSet -> VarSet -> Bool -- | Create a set from a list of variables mkVarSet :: [Var a] -> VarSet eltsVarSet :: VarSet -> [Var Any] -- | Set of variables that is in scope at some point -- -- The Int is a kind of hash-value used to generate new uniques. -- It should never be zero -- -- See "Secrets of the Glasgow Haskell Compiler inliner" Section 3.2 for -- the motivation data InScopeSet -- | The empty set emptyInScopeSet :: InScopeSet -- | Look up a variable in the InScopeSet. This gives you the -- canonical version of the variable lookupInScope :: InScopeSet -> Var a -> Maybe (Var Any) -- | Create a set of variables in scope mkInScopeSet :: VarSet -> InScopeSet -- | The empty set extendInScopeSet :: InScopeSet -> Var a -> InScopeSet -- | Add a list of variables in scope extendInScopeSetList :: InScopeSet -> [Var a] -> InScopeSet -- | Union two sets of in scope variables unionInScope :: InScopeSet -> InScopeSet -> InScopeSet -- | Is the variable in scope elemInScopeSet :: Var a -> InScopeSet -> Bool -- | Check whether an element exists in the set based on the Unique -- contained in that element elemUniqInScopeSet :: Unique -> InScopeSet -> Bool -- | Is the variable not in scope notElemInScopeSet :: Var a -> InScopeSet -> Bool -- | Is the set of variables in scope varSetInScope :: VarSet -> InScopeSet -> Bool -- | Ensure that the Unique of a variable does not occur in the -- InScopeSet uniqAway :: (Uniquable a, ClashPretty a) => InScopeSet -> a -> a uniqAway' :: (Uniquable a, ClashPretty a) => (Unique -> Bool) -> Int -> a -> a -- | Rename environment for e.g. alpha equivalence -- -- When going under binders for e.g. -- --
--   x -> e1  aeq y -> e2
--   
-- -- We want to rename [x -> y] or [y -> x], but we -- have to pick a binder that is neither free in e1 nor -- e2 or we risk accidental capture. -- -- So we must maintain: -- --
    --
  1. A renaming for the left term
  2. --
  3. A renaming for the right term
  4. --
  5. A set of in scope variables
  6. --
data RnEnv -- | Create an empty renaming environment mkRnEnv :: InScopeSet -> RnEnv -- | Simultaneously go under the binder bL and binder bR, -- finds a new binder newTvB, and return an environment mapping -- [bL -> newB] and [bR -> newB] rnTmBndr :: RnEnv -> Id -> Id -> RnEnv -- | Simultaneously go under the type-variable binder bTvL and -- type-variable binder bTvR, finds a new binder newTvB, -- and return an environment mapping [bTvL -> newB] and -- [bTvR -> newB] rnTyBndr :: RnEnv -> TyVar -> TyVar -> RnEnv -- | Applies rnTmBndr to several variables: the two variable lists -- must be of equal length. rnTmBndrs :: RnEnv -> [Id] -> [Id] -> RnEnv -- | Applies rnTyBndr to several variables: the two variable lists -- must be of equal length. rnTyBndrs :: RnEnv -> [TyVar] -> [TyVar] -> RnEnv -- | Look up the renaming of an occurrence in the left term rnOccLId :: RnEnv -> Id -> Id -- | Look up the renaming of an occurrence in the left term rnOccRId :: RnEnv -> Id -> Id -- | Look up the renaming of an type-variable occurrence in the left term rnOccLTy :: RnEnv -> TyVar -> TyVar -- | Look up the renaming of an type-variable occurrence in the right term rnOccRTy :: RnEnv -> TyVar -> TyVar instance Data.Binary.Class.Binary Clash.Core.VarEnv.InScopeSet instance Control.DeepSeq.NFData Clash.Core.VarEnv.InScopeSet instance GHC.Generics.Generic Clash.Core.VarEnv.InScopeSet instance Clash.Pretty.ClashPretty Clash.Core.VarEnv.InScopeSet -- | Type definitions used by the Driver module module Clash.Driver.Types data ClashEnv ClashEnv :: ClashOpts -> TyConMap -> IntMap TyConName -> CompiledPrimMap -> CustomReprs -> DomainMap -> ClashEnv [envOpts] :: ClashEnv -> ClashOpts [envTyConMap] :: ClashEnv -> TyConMap [envTupleTyCons] :: ClashEnv -> IntMap TyConName [envPrimitives] :: ClashEnv -> CompiledPrimMap [envCustomReprs] :: ClashEnv -> CustomReprs [envDomains] :: ClashEnv -> DomainMap data ClashDesign ClashDesign :: [TopEntityT] -> BindingMap -> ClashDesign [designEntities] :: ClashDesign -> [TopEntityT] [designBindings] :: ClashDesign -> BindingMap data IsPrim -- | The binding is the unfolding for a primitive. IsPrim :: IsPrim -- | The binding is an ordinary function. IsFun :: IsPrim data Binding a Binding :: Id -> SrcSpan -> InlineSpec -> IsPrim -> a -> Bool -> Binding a -- | The core identifier for this binding. [bindingId] :: Binding a -> Id -- | The source location of this binding in the original source code. [bindingLoc] :: Binding a -> SrcSpan -- | the inline specification for this binding, in the original source -- code. [bindingSpec] :: Binding a -> InlineSpec -- | Is the binding a core term corresponding to a primitive with a known -- implementation? If so, it can potentially be inlined despite being -- marked as NOINLINE in source. [bindingIsPrim] :: Binding a -> IsPrim -- | The term representation for this binding. This is polymorphic so -- alternate representations can be used if more appropriate (i.e. in the -- evaluator this can be Value for evaluated bindings). [bindingTerm] :: Binding a -> a -- | Whether the binding is recursive. -- -- TODO Ideally the BindingMap would store recursive and non-recursive -- bindings in a way similar to Let / Letrec. GHC also does this. [bindingRecursive] :: Binding a -> Bool -- | Global function binders -- -- Global functions cannot be mutually recursive, only self-recursive. type BindingMap = VarEnv (Binding Term) type DomainMap = HashMap Text VDomainConfiguration -- | Information to show about transformations during compilation. -- -- NB: The Ord instance compares by amount of -- information. data TransformationInfo -- | Show no information about transformations. None :: TransformationInfo -- | Show the final term after all applied transformations. FinalTerm :: TransformationInfo -- | Show the name of every transformation that is applied. AppliedName :: TransformationInfo -- | Show the name and result of every transformation that is applied. AppliedTerm :: TransformationInfo -- | Show the name of every transformation that is attempted, and the -- result of every transformation that is applied. TryName :: TransformationInfo -- | Show the name and input to every transformation that is applied, and -- the result of every transformation that is applied. TryTerm :: TransformationInfo -- | Options related to debugging. See ClashOpts data DebugOpts DebugOpts :: Bool -> TransformationInfo -> Set String -> Bool -> Maybe Word -> Maybe Word -> Maybe FilePath -> DebugOpts -- | Check that the results of applied transformations do not violate the -- invariants for rewriting (e.g. no accidental shadowing, or type -- changes). -- -- Command line flag: -fclash-debug-invariants [dbg_invariants] :: DebugOpts -> Bool -- | The information to show when debugging a transformation. See the -- TransformationInfo type for different configurations. -- -- Command line flag: -fclash-debug-info -- (None|FinalTerm|AppliedName|AppliedTerm|TryName|TryTerm) [dbg_transformationInfo] :: DebugOpts -> TransformationInfo -- | List the transformations that are being debugged. When the set is -- empty, all transformations are debugged. -- -- Command line flag: -fclash-debug-transformations t1[,t2...] [dbg_transformations] :: DebugOpts -> Set String -- | Count how many times transformations are applied and provide a summary -- at the end of normalization. This includes all transformations, not -- just those in dbg_transformations. -- -- Command line flag: -fclash-debug-count-transformations [dbg_countTransformations] :: DebugOpts -> Bool -- | Debug transformations applied after the nth transformation applied. -- This includes all transformations, not just those in -- dbg_transformations. -- -- Command line flag: -fclash-debug-transformations-from=N [dbg_transformationsFrom] :: DebugOpts -> Maybe Word -- | Debug up to the nth applied transformation. If this limit is exceeded -- then Clash will error. This includes all transformations, not just -- those in dbg_transformations. -- -- Command line flag: -fclash-debug-transformations-limit=N [dbg_transformationsLimit] :: DebugOpts -> Maybe Word -- | Save information about all applied transformations to a history file -- for use with clash-term. -- -- Command line flag: -fclash-debug-history[=FILE] [dbg_historyFile] :: DebugOpts -> Maybe FilePath -- | Check whether the debugging options mean the compiler is debugging. -- This is true only if at least one debugging feature is enabled, namely -- one of -- -- -- -- Other flags, such as writing to a history file or offsetting which -- applied transformation to show information from do not affect the -- result, as it is possible to enable these but still not perform any -- debugging checks in functions like applyDebug. If this is no -- longer the case, this function will need to be changed. isDebugging :: DebugOpts -> Bool -- | Check whether the requested information is available to the specified -- transformation according to the options. e.g. -- --
--   traceIf (hasDebugInfo AppliedName name opts) ("Trace something using: " <> show name)
--   
-- -- This accounts for the set of transformations which are being debugged. -- For a check which is agnostic to the a transformation, see -- hasTransformationInfo. hasDebugInfo :: TransformationInfo -> String -> DebugOpts -> Bool -- | Check that the transformation info shown supports the requested info. -- If the call-site is in the context of a particular transformation, -- hasDebugInfo should be used instead. hasTransformationInfo :: TransformationInfo -> DebugOpts -> Bool -- | debugNone :: DebugOpts -- | debugSilent :: DebugOpts -- | debugFinal :: DebugOpts -- | debugCount :: DebugOpts -- | debugName :: DebugOpts -- | debugTry :: DebugOpts -- | debugApplied :: DebugOpts -- | debugAll :: DebugOpts -- | Options passed to Clash compiler data ClashOpts ClashOpts :: Bool -> Int -> Int -> Word -> Word -> Word -> DebugOpts -> Bool -> Bool -> Bool -> OverridingBool -> Int -> Maybe String -> HdlSyn -> Bool -> [FilePath] -> Maybe Text -> Bool -> Bool -> PreserveCase -> Bool -> Maybe (Maybe Int) -> Bool -> Bool -> Bool -> Word -> Bool -> Bool -> Period -> Bool -> ClashOpts -- | Are warnings treated as errors. -- -- Command line flag: -Werror [opt_werror] :: ClashOpts -> Bool -- | Change the number of times a function f can undergo inlining inside -- some other function g. This prevents the size of g growing -- dramatically. -- -- Command line flag: -fclash-inline-limit [opt_inlineLimit] :: ClashOpts -> Int -- | Change the number of times a function can undergo specialization. -- -- Command line flag: -fclash-spec-limit [opt_specLimit] :: ClashOpts -> Int -- | Set the threshold for function size. Below this threshold functions -- are always inlined (if it is not recursive). -- -- Command line flag: -fclash-inline-function-limit [opt_inlineFunctionLimit] :: ClashOpts -> Word -- | Set the threshold for constant size. Below this threshold constants -- are always inlined. A value of 0 inlines all constants. -- -- Command line flag: -fclash-inline-constant-limit [opt_inlineConstantLimit] :: ClashOpts -> Word -- | Set the threshold for maximum unfolding depth in the evaluator. A -- value of zero means no potentially non-terminating binding is -- unfolded. -- -- Command line flag: -fclash-evaluator-fuel-limit [opt_evaluatorFuelLimit] :: ClashOpts -> Word -- | Options which control debugging. See DebugOpts. [opt_debug] :: ClashOpts -> DebugOpts -- | Reuse previously generated output from Clash. Only caches topentities. -- -- Command line flag: -fclash-no-cache [opt_cachehdl] :: ClashOpts -> Bool -- | Remove HDL directories before writing to them. By default, Clash will -- only write to non-empty directories if it can prove all files in it -- are generated by a previous run. This option applies to directories of -- the various top entities, i.e., the subdirectories made in the -- directory passed in with -fclash-hdldir. Note that Clash will -- still use a cache if it can. -- -- Command line flag: -fclash-clear [opt_clear] :: ClashOpts -> Bool -- | Disable warnings for primitives -- -- Command line flag: -fclash-no-prim-warn [opt_primWarn] :: ClashOpts -> Bool -- | Show colors in debug output -- -- Command line flag: -fdiagnostics-color [opt_color] :: ClashOpts -> OverridingBool -- | Set the bit width for the Int/Word/Integer types. The only allowed -- values are 32 or 64. [opt_intWidth] :: ClashOpts -> Int -- | Directory to save HDL files to [opt_hdlDir] :: ClashOpts -> Maybe String -- | Synthesis target. See HdlSyn for available options. [opt_hdlSyn] :: ClashOpts -> HdlSyn -- | Show additional information in error messages [opt_errorExtra] :: ClashOpts -> Bool -- | Paths where Clash should look for modules [opt_importPaths] :: ClashOpts -> [FilePath] -- | Prefix components with given string [opt_componentPrefix] :: ClashOpts -> Maybe Text -- | Use new inline strategy. Functions marked NOINLINE will get their own -- HDL module. [opt_newInlineStrat] :: ClashOpts -> Bool -- | Use escaped identifiers in HDL. See: -- -- [opt_escapedIds] :: ClashOpts -> Bool -- | Force all generated basic identifiers to lowercase. Among others, this -- affects module and file names. [opt_lowerCaseBasicIds] :: ClashOpts -> PreserveCase -- | Perform a high-effort compile, trading improved performance for -- potentially much longer compile times. -- -- Name inspired by Design Compiler's compile_ultra flag. [opt_ultra] :: ClashOpts -> Bool -- | [opt_forceUndefined] :: ClashOpts -> Maybe (Maybe Int) -- | Check whether paths specified in opt_importPaths exists on the -- filesystem. [opt_checkIDir] :: ClashOpts -> Bool -- | Enable aggressive X optimization, which may remove undefineds from -- generated HDL by replaced with defined alternatives. [opt_aggressiveXOpt] :: ClashOpts -> Bool -- | Enable aggressive X optimization, which may remove undefineds from HDL -- generated by blackboxes. This enables the ~ISUNDEFINED template tag. [opt_aggressiveXOptBB] :: ClashOpts -> Bool -- | At what size do we cache normalized work-free top-level binders. [opt_inlineWFCacheLimit] :: ClashOpts -> Word -- | Generate an EDAM file for use with Edalize. [opt_edalize] :: ClashOpts -> Bool -- | Render sum types with all zero-width fields as enums where supported, -- as opposed to rendering them as bitvectors. [opt_renderEnums] :: ClashOpts -> Bool -- | Timescale precision set in Verilog files. E.g., setting this would -- sets the second part of `timescale 100fs/100fs. [opt_timescalePrecision] :: ClashOpts -> Period -- | Don't error if we see a (potentially) broken GHC / platform -- combination. See the project's README.md for more -- information. [opt_ignoreBrokenGhcs] :: ClashOpts -> Bool defClashOpts :: ClashOpts -- | Synopsys Design Constraint (SDC) information for a component. -- Currently this limited to the names and periods of clocks for -- create_clock. newtype SdcInfo SdcInfo :: [(Text, VDomainConfiguration)] -> SdcInfo [sdcClock] :: SdcInfo -> [(Text, VDomainConfiguration)] -- | Render an SDC file from an SdcInfo. The clock periods, waveforms, and -- targets are all hardcoded. pprSDC :: SdcInfo -> Doc () instance GHC.Show.Show Clash.Driver.Types.IsPrim instance Control.DeepSeq.NFData Clash.Driver.Types.IsPrim instance GHC.Generics.Generic Clash.Driver.Types.IsPrim instance GHC.Classes.Eq Clash.Driver.Types.IsPrim instance Data.Binary.Class.Binary Clash.Driver.Types.IsPrim instance GHC.Show.Show a => GHC.Show.Show (Clash.Driver.Types.Binding a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Clash.Driver.Types.Binding a) instance GHC.Generics.Generic (Clash.Driver.Types.Binding a) instance GHC.Base.Functor Clash.Driver.Types.Binding instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Clash.Driver.Types.Binding a) instance Control.DeepSeq.NFData Clash.Driver.Types.TransformationInfo instance GHC.Show.Show Clash.Driver.Types.TransformationInfo instance GHC.Read.Read Clash.Driver.Types.TransformationInfo instance GHC.Classes.Ord Clash.Driver.Types.TransformationInfo instance Data.Hashable.Class.Hashable Clash.Driver.Types.TransformationInfo instance GHC.Generics.Generic Clash.Driver.Types.TransformationInfo instance GHC.Classes.Eq Clash.Driver.Types.TransformationInfo instance GHC.Classes.Eq Clash.Driver.Types.DebugOpts instance GHC.Show.Show Clash.Driver.Types.DebugOpts instance Control.DeepSeq.NFData Clash.Driver.Types.DebugOpts instance GHC.Generics.Generic Clash.Driver.Types.DebugOpts instance Data.Hashable.Class.Hashable Clash.Driver.Types.ClashOpts instance GHC.Generics.Generic Clash.Driver.Types.ClashOpts instance Control.DeepSeq.NFData Clash.Driver.Types.ClashOpts instance GHC.Classes.Eq Clash.Driver.Types.ClashOpts instance GHC.Show.Show Clash.Driver.Types.ClashOpts instance Control.DeepSeq.NFData Clash.Driver.Types.ClashEnv instance GHC.Generics.Generic Clash.Driver.Types.ClashEnv instance Data.Hashable.Class.Hashable Clash.Driver.Types.DebugOpts instance Control.DeepSeq.NFData Clash.Driver.Types.ClashDesign -- | Free variable calculations module Clash.Core.FreeVars -- | Gives the free type-variables in a Type, implemented as a Fold -- -- The Fold is closed over the types of its variables, so: -- --
--   foldMapOf typeFreeVars unitVarSet ((a:* -> k) Int) = {a, k}
--   
typeFreeVars :: Fold Type TyVar -- | Gives the free identifiers of a Term, implemented as a Fold freeIds :: Fold Term Id -- | Calculate the local free variable of an expression: the free -- type variables and the free identifiers that are not bound in the -- global environment. freeLocalVars :: Fold Term (Var a) -- | Calculate the local free identifiers of an expression: the free -- identifiers that are not bound in the global environment. freeLocalIds :: Fold Term Id -- | Calculate the global free identifiers of an expression: the -- free identifiers that are bound in the global environment. globalIds :: Fold Term Id -- | Gives the free type-variables of a Term, implemented as a Fold -- -- The Fold is closed over the types of variables, so: -- --
--   foldMapOf termFreeTyVars unitVarSet (case (x : (a:* -> k) Int)) of {}) = {a, k}
--   
termFreeTyVars :: Fold Term TyVar -- | Check whether a local identifier occurs free in a term globalIdOccursIn :: Id -> Term -> Bool -- | Check whether a set of variables does not occur free in a term localVarsDoNotOccurIn :: [Var a] -> Term -> Bool -- | Get the free variables of an expression and count the number of -- occurrences countFreeOccurances :: Term -> VarEnv Int -- | Gives the "interesting" free variables in a Type, implemented as a -- Fold -- -- The Fold is closed over the types of variables, so: -- --
--   foldMapOf (typeFreeVars' (const True) IntSet.empty) unitVarSet ((a:* -> k) Int) = {a, k}
--   
-- -- Note [Closing over kind variables] -- -- Consider the type -- --
--   forall k . b -> k
--   
-- -- where -- --
--   b :: k -> Type
--   
-- -- When we close over the free variables of forall k . b -> -- k, i.e. b, then the k in b :: k -> -- Type is most definitely not the k in forall k -- . b -> k. So when a type variable is free, i.e. not in the -- inScope set, its kind variables also aren´t; so in order to prevent -- collisions due to shadowing we close using an empty inScope set. -- -- See also: -- https://gitlab.haskell.org/ghc/ghc/-/commit/503514b94f8dc7bd9eab5392206649aee45f140b typeFreeVars' :: (Contravariant f, Applicative f) => (forall b. Var b -> Bool) -> IntSet -> (Var a -> f (Var a)) -> Type -> f Type -- | Gives the "interesting" free variables in a Term, implemented as a -- Fold -- -- The Fold is closed over the types of variables, so: -- --
--   foldMapOf (termFreeVars' (const True)) unitVarSet (case (x : (a:* -> k) Int)) of {}) = {x, a, k}
--   
-- -- Note [Closing over type variables] -- -- Consider the term -- --
--   /\(k :: Type) -> \(b :: k) -> a
--   
-- -- where -- --
--   a :: k
--   
-- -- When we close over the free variables of /k -> (b :: k) -> -- (a :: k), i.e. a, then the k in a :: k -- is most definitely not the k in introduced by the -- /k ->. So when a term variable is free, i.e. not in the -- inScope set, its type variables also aren´t; so in order to prevent -- collisions due to shadowing we close using an empty inScope set. -- -- See also: -- https://gitlab.haskell.org/ghc/ghc/-/commit/503514b94f8dc7bd9eab5392206649aee45f140b termFreeVars' :: (Contravariant f, Applicative f) => (forall b. Var b -> Bool) -> (Var a -> f (Var a)) -> Term -> f Term -- | Utility class to extract free variables from data which has variables. module Clash.Core.HasFreeVars class HasFreeVars a freeVarsOf :: HasFreeVars a => a -> VarSet -- | Something is closed if it has no free variables. This function may be -- replaced with a more efficient implementation. isClosed :: HasFreeVars a => a -> Bool -- | Check if a variable is free in the given value. This function may be -- replaced with a more efficient implementation. elemFreeVars :: HasFreeVars a => Var a -> a -> Bool -- | Check if a variable is not free in the given value. This function may -- be replaced with a more efficient implementation. notElemFreeVars :: HasFreeVars a => Var a -> a -> Bool -- | Check if all variables in a set are free in the given value. This -- function may be replaced with a more efficient implementation. subsetFreeVars :: HasFreeVars a => VarSet -> a -> Bool -- | Check if no variables in a set are free in the given value. This -- function may be replaced with a more efficient implementation. disjointFreeVars :: HasFreeVars a => VarSet -> a -> Bool instance Clash.Core.HasFreeVars.HasFreeVars Clash.Core.Term.Term instance Clash.Core.HasFreeVars.HasFreeVars Clash.Core.Type.Type instance (Data.Foldable.Foldable f, Clash.Core.HasFreeVars.HasFreeVars a) => Clash.Core.HasFreeVars.HasFreeVars (f a) module Clash.Core.EqSolver -- | Data type that indicates what kind of solution (if any) was found data TypeEqSolution -- | Solution was found. Variable equals some integer. Solution :: (TyVar, Type) -> TypeEqSolution -- | A solution was found, but it involved negative naturals. AbsurdSolution :: TypeEqSolution -- | Given type wasn't an equation, or it was unsolvable. NoSolution :: TypeEqSolution catSolutions :: [TypeEqSolution] -> [(TyVar, Type)] -- | Solve given equations and return all non-absurd solutions solveNonAbsurds :: TyConMap -> VarSet -> [(Type, Type)] -> [(TyVar, Type)] -- | Solve simple equalities such as: -- -- solveEq :: TyConMap -> VarSet -> (Type, Type) -> [TypeEqSolution] -- | Solve equations supported by normalizeAdd. See documentation -- of TypeEqSolution to understand the return value. solveAdd :: VarSet -> (Type, Type) -> TypeEqSolution -- | Given the left and right side of an equation, normalize it such that -- equations of the following forms: -- -- -- -- are returned as (5, 2, n) normalizeAdd :: (Type, Type) -> Maybe (Integer, Integer, Type) -- | Tests for nonsencical patterns due to types being "absurd". See -- isAbsurdEq for more info. isAbsurdPat :: TyConMap -> Pat -> Bool -- | Determines if an "equation" obtained through patEqs or -- typeEq is absurd. That is, it tests if two types that are -- definitely not equal are asserted to be equal OR if the computation of -- the types yield some absurd (intermediate) result such as -1. isAbsurdEq :: TyConMap -> VarSet -> (Type, Type) -> Bool -- | Get constraint equations patEqs :: TyConMap -> Pat -> [(Type, Type)] -- | If type is an equation, return LHS and RHS. typeEq :: TyConMap -> Type -> Maybe (Type, Type) instance GHC.Classes.Eq Clash.Core.EqSolver.TypeEqSolution instance GHC.Show.Show Clash.Core.EqSolver.TypeEqSolution -- | Capture-free substitution function for CoreHW module Clash.Core.Subst -- | Type substitution -- -- The following invariants must hold: -- --
    --
  1. The InScopeSet is needed only to guide the generation of -- fresh uniques
  2. --
  3. In particular, the kind of the type variables in the -- InScopeSet is not relevant.
  4. --
  5. The substitution is only applied once
  6. --
-- -- Note [Apply Once] -- -- We might instantiate forall a b. ty with the types [a, -- b] or [b, a]. So the substitution might go like [a -- -> b, b -> a]. A similar situation arises in terms when we -- find a redex like (a -> b -> e) b a. Then we -- also end up with a substitution that permutes variables. Other -- variations happen to; for example [a -> (a,b)]. -- -- SO A TvSubst MUST BE APPLIED PRECISELY ONCE, OR THINGS MIGHT LOOP -- -- Note [The substitution invariant] -- -- When calling (substTy subst ty) it should be the case that the -- InScopeSet is a superset of both: -- -- data TvSubst TvSubst :: InScopeSet -> TvSubstEnv -> TvSubst -- | A substitution of Types for TyVars -- -- Note [Extending the TvSubstEnv] See TvSubst for the invariants -- that must hold -- -- This invariant allows a short-cut when the subst env is empty: if the -- TvSubstEnv is empty, i.e. nullVarEnv TvSubstEnv holds, then -- (substTy subst ty) does nothing. -- -- For example, consider: -- -- (a -> b(a ~ Int) -> ... b ...) Int -- -- We substitute Int for a. The Unique of b does not -- change, but nevertheless we add b to the TvSubstEnv -- because b's kind does change -- -- This invariant has several consequences: -- -- type TvSubstEnv = VarEnv Type -- | Extend the substitution environment with a new TyVar -- substitution extendTvSubst :: Subst -> TyVar -> Type -> Subst -- | Extend the substitution environment with a list of TyVar -- substitutions extendTvSubstList :: Subst -> [(TyVar, Type)] -> Subst -- | Substitute within a Type -- -- The substitution has to satisfy the invariant described in -- TvSubsts Note [The substitution environment] substTy :: HasCallStack => Subst -> Type -> Type -- | Type substitution, see zipTvSubst -- -- Works only if the domain of the substitution is superset of the type -- being substituted into substTyWith :: HasCallStack => [TyVar] -> [Type] -> Type -> Type -- | Substitute within a TyVar. See substTy. substTyInVar :: HasCallStack => Subst -> Var a -> Var a substGlobalsInExistentials :: HasCallStack => InScopeSet -> [TyVar] -> [(TyVar, Type)] -> [TyVar] -- | Safely substitute a type variable in a list of existentials. This -- function will account for cases where existentials shadow each other. substInExistentials :: HasCallStack => InScopeSet -> [TyVar] -> (TyVar, Type) -> [TyVar] -- | Safely substitute type variables in a list of existentials. This -- function will account for cases where existentials shadow each other. substInExistentialsList :: HasCallStack => InScopeSet -> [TyVar] -> [(TyVar, Type)] -> [TyVar] -- | A substitution environment containing containing both Id and -- TyVar substitutions. -- -- Some invariants apply to how you use the substitution: -- --
    --
  1. The InScopeSet contains at least those Ids and -- TyVars that will be in scope after applying the -- substitution to a term. Precisely, the in-scope set must be a superset -- of the free variables of the substitution range that might possibly -- clash with locally-bound variables in the thing being substituted -- in.
  2. --
  3. You may only apply the substitution once. See TvSubst
  4. --
-- -- There are various ways of setting up the in-scope set such that the -- first of of these invariants holds: -- -- data Subst Subst :: InScopeSet -> IdSubstEnv -> TvSubstEnv -> IdSubstEnv -> Subst [substInScope] :: Subst -> InScopeSet [substTmEnv] :: Subst -> IdSubstEnv [substTyEnv] :: Subst -> TvSubstEnv [substGblEnv] :: Subst -> IdSubstEnv -- | An empty substitution, starting the variables currently in scope mkSubst :: InScopeSet -> Subst -- | Create a type substitution mkTvSubst :: InScopeSet -> VarEnv Type -> Subst -- | Add an Id to the in-scope set: as a side effect, remove any -- existing substitutions for it. extendInScopeId :: Subst -> Id -> Subst -- | Add Ids to the in-scope set. See also extendInScopeId extendInScopeIdList :: Subst -> [Id] -> Subst -- | Extend the substitution environment with a new Id substitution extendIdSubst :: Subst -> Id -> Term -> Subst -- | Extend the substitution environment with a list of Id -- substitutions extendIdSubstList :: Subst -> [(Id, Term)] -> Subst -- | Extend the substitution environment with a list of global Id -- substitutions extendGblSubstList :: Subst -> [(Id, Term)] -> Subst -- | Substitute within a Term substTm :: HasCallStack => Doc () -> Subst -> Term -> Term -- | Substitute within a Term. Just return original term if given -- substitution is Nothing. maybeSubstTm :: HasCallStack => Doc () -> Maybe Subst -> Term -> Term -- | Substitute within a case-alternative substAlt :: HasCallStack => Doc () -> Subst -> (Pat, Term) -> (Pat, Term) substId :: HasCallStack => Subst -> Id -> Id -- | Ensure that non of the binders in an expression shadow each-other, nor -- conflict with he in-scope set deShadowTerm :: HasCallStack => InScopeSet -> Term -> Term -- | Ensure that non of the binders in an alternative shadow each-other, -- nor conflict with the in-scope set deShadowAlt :: HasCallStack => InScopeSet -> (Pat, Term) -> (Pat, Term) -- | A much stronger variant of deShadowTerm that ensures that all -- bound variables are unique. -- -- Also returns an extended InScopeSet additionally containing the -- (renamed) unique bound variables of the term. freshenTm :: InScopeSet -> Term -> (InScopeSet, Term) -- | Ensure that non of the let-bindings of a let-expression shadow w.r.t -- the in-scope set deshadowLetExpr :: HasCallStack => InScopeSet -> Bind Term -> Term -> (Bind Term, Term) -- | Alpha equality for types aeqType :: Type -> Type -> Bool -- | Alpha equality for terms aeqTerm :: Term -> Term -> Bool -- | Structural equality on Term eqTerm :: Term -> Term -> Bool -- | Structural equality on Type eqType :: Type -> Type -> Bool instance Clash.Pretty.ClashPretty Clash.Core.Subst.TvSubst instance GHC.Classes.Eq Clash.Core.Type.Type instance GHC.Classes.Ord Clash.Core.Type.Type instance GHC.Classes.Eq Clash.Core.Term.Term instance (TypeError ...) => Data.Hashable.Class.Hashable Clash.Core.Term.Term instance GHC.Classes.Ord Clash.Core.Term.Term -- | Template Haskell utilities for Clash.Core.TermLiteral. module Clash.Core.TermLiteral.TH deriveTermToData :: Name -> Q Exp -- | For Maybe, constructs: -- --
--   showsTypePrec n _
--     = let
--         showSpace = showChar ' '
--         precCalls = [showsTypePrec 11 (Proxy @a)]
--         interspersedPrecCalls = intersperse showSpace precCalls
--         showType = foldl (.) (showString "Maybe") (showSpace : interspersedPrecCalls)
--       in
--         showParen (n > 10) showType
--   
deriveShowsTypePrec :: Name -> Q Dec -- | Derive a TermLiteral instance for given type deriveTermLiteral :: Name -> Q [Dec] dcName' :: DataCon -> String -- | Tools to convert a Term into its "real" representation module Clash.Core.TermLiteral -- | Tools to deal with literals encoded as a Term. class TermLiteral a -- | Pretty print the type of a term (for error messages). Its default -- implementation uses Typeable to print the type. Note that this -- method is there to allow an instance for SNat to exist (and -- other GADTs imposing KnownNat). Without it, GHC would ask for a -- KnownNat constraint on the instance, which would defeat the -- purpose of it. showsTypePrec :: TermLiteral a => Int -> Proxy a -> ShowS -- | Pretty print type a showType :: TermLiteral a => Proxy a -> String -- | Convert Term to the constant it represents. Will return an -- error if (one of the subterms) fail to translate. termToData :: (TermLiteral a, HasCallStack) => Term -> Either Term a -- | Same as termToData, but returns printable error message if it -- couldn't translate a term. termToDataError :: forall a. TermLiteral a => Term -> Either String a -- | Derive a TermLiteral instance for given type deriveTermLiteral :: Name -> Q [Dec] instance Clash.Core.TermLiteral.TermLiteral a => Clash.Core.TermLiteral.TermLiteral (Clash.Annotations.SynthesisAttributes.Attr a) instance Clash.Core.TermLiteral.TermLiteral a => Clash.Core.TermLiteral.TermLiteral (Clash.Verification.Internal.Property' a) instance Clash.Core.TermLiteral.TermLiteral a => Clash.Core.TermLiteral.TermLiteral (Clash.Verification.Internal.Assertion' a) instance Clash.Core.TermLiteral.TermLiteral Clash.Verification.Internal.RenderAs instance (Clash.Core.TermLiteral.TermLiteral a, Clash.Core.TermLiteral.TermLiteral b) => Clash.Core.TermLiteral.TermLiteral (Data.Either.Either a b) instance Clash.Core.TermLiteral.TermLiteral a => Clash.Core.TermLiteral.TermLiteral (GHC.Maybe.Maybe a) instance Clash.Core.TermLiteral.TermLiteral GHC.Types.Bool instance Clash.Core.TermLiteral.TermLiteral Clash.Core.Term.Term instance Clash.Core.TermLiteral.TermLiteral GHC.Base.String instance Clash.Core.TermLiteral.TermLiteral Data.Text.Internal.Text instance GHC.TypeNats.KnownNat n => Clash.Core.TermLiteral.TermLiteral (Clash.Sized.Internal.Index.Index n) instance Clash.Core.TermLiteral.TermLiteral GHC.Types.Int instance Clash.Core.TermLiteral.TermLiteral GHC.Types.Word instance Clash.Core.TermLiteral.TermLiteral GHC.Integer.Type.Integer instance Clash.Core.TermLiteral.TermLiteral GHC.Types.Char instance Clash.Core.TermLiteral.TermLiteral GHC.Natural.Natural instance Clash.Core.TermLiteral.TermLiteral (Clash.Promoted.Nat.SNat n) instance (Clash.Core.TermLiteral.TermLiteral a, Clash.Core.TermLiteral.TermLiteral b) => Clash.Core.TermLiteral.TermLiteral (a, b) instance (Clash.Core.TermLiteral.TermLiteral a, GHC.TypeNats.KnownNat n) => Clash.Core.TermLiteral.TermLiteral (Clash.Sized.Vector.Vec n a) -- | Utility class to extract type information from data which has a type. module Clash.Core.HasType class HasType a coreTypeOf :: HasType a => a -> Type coreKindOf :: HasType a => a -> Kind class InferType a inferCoreTypeOf :: InferType a => TyConMap -> a -> Type inferCoreKindOf :: InferType a => TyConMap -> a -> Kind -- | Get the result type of a polymorphic function given a list of -- arguments applyTypeToArgs :: Term -> TyConMap -> Type -> [Either Term Type] -> Type -- | Like piResultTys, but only applies a single type. If multiple -- types are being applied use piResultTys, as it is more -- efficient to only substitute once with many types. piResultTy :: HasCallStack => TyConMap -> Type -> Type -> Type -- | (piResultTys f_ty [ty1, ..., tyn]) gives the type of (f -- ty1 .. tyn) where f :: f_ty -- -- piResultTys is interesting because: -- --
    --
  1. f_ty may have more foralls than there are args
  2. --
  3. Less obviously, it may have fewer foralls
  4. --
-- -- Fore case 2. think of: -- -- piResultTys (forall a . a) [forall b.b, Int] -- -- This really can happen, such as situations involving undefineds -- type: -- -- undefined :: forall a. a -- -- undefined (forall b. b -> b) Int -- -- This term should have the type (Int -> Int), but notice -- that there are more type args than foralls in undefineds type. -- -- For efficiency reasons, when there are no foralls, we simply drop -- arrows from a function type/kind. piResultTys :: HasCallStack => TyConMap -> Type -> [Type] -> Type instance Clash.Core.HasType.InferType Clash.Core.Type.Type instance Clash.Core.HasType.InferType Clash.Core.Term.Term instance Clash.Core.HasType.HasType Clash.Core.DataCon.DataCon instance Clash.Core.HasType.HasType Clash.Core.Literal.Literal instance Clash.Core.HasType.HasType Clash.Core.Term.PrimInfo instance Clash.Core.HasType.HasType Clash.Core.TyCon.TyCon instance Clash.Core.HasType.HasType Clash.Core.Type.Type instance Clash.Core.HasType.HasType (Clash.Core.Var.Var a) -- | Smart constructor and destructor functions for CoreHW module Clash.Core.Util -- | Rebuild a let expression / let expressions by taking the SCCs of a -- list of bindings and remaking Let (NonRec ...) ... and Let (Rec ...) -- ... listToLets :: [LetBinding] -> Term -> Term -- | The type forall a . a undefinedTy :: Type -- | The type forall a. forall b. a -> b unsafeCoerceTy :: Type -- | Create a vector of supplied elements mkVec :: DataCon -> DataCon -> Type -> Integer -> [Term] -> Term -- | Append elements to the supplied vector appendToVec :: DataCon -> Type -> Term -> Integer -> [Term] -> Term -- | Create let-bindings with case-statements that select elements out of a -- vector. Returns both the variables to which element-selections are -- bound and the let-bindings extractElems :: HasCallStack => Supply -> InScopeSet -> DataCon -> Type -> Char -> Integer -> Term -> (Supply, NonEmpty (Term, NonEmpty (Id, Term))) -- | Create let-bindings with case-statements that select elements out of a -- tree. Returns both the variables to which element-selections are bound -- and the let-bindings extractTElems :: Supply -> InScopeSet -> DataCon -> DataCon -> Type -> Char -> Integer -> Term -> (Supply, ([Term], [(Id, Term)])) -- | Create a vector of supplied elements mkRTree :: DataCon -> DataCon -> Type -> Integer -> [Term] -> Term -- | Determine whether a type is isomorphic to -- Clash.Signal.Internal.Signal -- -- It is i.e.: -- -- -- -- This also includes BiSignals, i.e.: -- -- isSignalType :: TyConMap -> Type -> Bool -- | Determines whether given type is an (alias of en) Enable line. isEnable :: TyConMap -> Type -> Bool -- | Determines whether given type is an (alias of en) Clock or Reset line isClockOrReset :: TyConMap -> Type -> Bool tyNatSize :: TyConMap -> Type -> Except String Integer mkUniqSystemTyVar :: (Supply, InScopeSet) -> (OccName, Kind) -> ((Supply, InScopeSet), TyVar) mkUniqSystemId :: (Supply, InScopeSet) -> (OccName, Type) -> ((Supply, InScopeSet), Id) mkUniqInternalId :: (Supply, InScopeSet) -> (OccName, Type) -> ((Supply, InScopeSet), Id) -- | Same as dataConInstArgTys, but it tries to compute -- existentials too, hence the extra argument TyConMap. WARNING: -- It will return the types of non-existentials only dataConInstArgTysE :: HasCallStack => InScopeSet -> TyConMap -> DataCon -> [Type] -> Maybe [Type] -- | Given a DataCon and a list of types, the type variables of the DataCon -- type are substituted for the list of types. The argument types are -- returned. -- -- The list of types should be equal to the number of type variables, -- otherwise Nothing is returned. dataConInstArgTys :: DataCon -> [Type] -> Maybe [Type] -- | Make a coercion primCo :: Type -> Term -- | Make an unsafe coercion primUCo :: Term undefinedPrims :: [Text] undefinedXPrims :: [Text] substArgTys :: DataCon -> [Type] -> [Type] -- | Try to reduce an arbitrary type to a literal type (Symbol or Nat), and -- subsequently extract its String representation tyLitShow :: TyConMap -> Type -> Except String String -- | Helper existential for shouldSplit, contains a function that: -- --
    --
  1. given a term of a type that should be split,
  2. --
  3. creates projections of that term for all the constructor -- arguments
  4. --
data Projections [Projections] :: (forall m. MonadUnique m => InScopeSet -> Term -> m [Term]) -> Projections -- | Determine whether we should split away types from a product type, i.e. -- clocks should always be separate arguments, and not part of a product. shouldSplit :: TyConMap -> Type -> Maybe ([Term] -> Term, Projections, [Type]) -- | Worker of shouldSplit, works on TypeView instead of -- Type shouldSplit0 :: TyConMap -> TypeView -> Maybe ([Term] -> Term, Projections, [Type]) -- | Potentially split apart a list of function argument types. e.g. given: -- --
--   [Int,(Clock,(Reset,Bool)),Char]
--   
-- -- we return -- --
--   [Int,Clock,Reset,Bool,Char]
--   
-- -- But we would leave -- --
--   [Int, (Bool,Int), Char]
--   
-- -- unchanged. splitShouldSplit :: TyConMap -> [Type] -> [Type] -- | Strip implicit parameter wrappers (IP) stripIP :: Type -> Type -- | Do an inverse topological sorting of the let-bindings in a -- let-expression inverseTopSortLetBindings :: HasCallStack => [(Id, Term)] -> [(Id, Term)] -- | Group let-bindings into cyclic groups and acyclic individual bindings sccLetBindings :: HasCallStack => [(Id, Term)] -> [SCC (Id, Term)] -- | Make a case-decomposition that extracts a field out of a -- (Sum-of-)Product type mkSelectorCase :: HasCallStack => MonadUnique m => String -> InScopeSet -> TyConMap -> Term -> Int -> Int -> m Term -- | Make a binder that should not be referenced mkWildValBinder :: MonadUnique m => InScopeSet -> Type -> m Id -- | Make a new, unique, identifier mkInternalVar :: MonadUnique m => InScopeSet -> OccName -> KindOrType -> m Id -- | Special primitives created during the normalization process. module Clash.Normalize.Primitives -- | The removedArg primitive represents an argument which is -- computationally irrelevant, and has been removed from the circuit (as -- removing it does not change the behaviour of the circuit). Examples of -- such arguments are unused arguments to blackboxes, as removing them -- does not affect the rendered HDL. removedArg :: PrimInfo -- | The undefined primitive represents an undefined value that was -- identified during normalization. This includes undefined results to -- compile-time evaluation, such as division by zero. undefined :: PrimInfo -- | The undefinedX primitive represents an X-exception throwing value that -- was identified during normalization. undefinedX :: PrimInfo -- | Check whether a term is work free or not. This is used by -- transformations / evaluation to check whether it is possible to -- perform changes without duplicating work in the result, e.g. inlining. module Clash.Rewrite.WorkFree -- | Determine whether a term does any work, i.e. adds to the size of the -- circuit. This function requires a cache (specified as a lens) to store -- the result for querying work info of global binders. isWorkFree :: forall s m. (HasCallStack, MonadState s m) => Lens' s (VarEnv Bool) -> BindingMap -> Term -> m Bool isWorkFreeClockOrResetOrEnable :: TyConMap -> Term -> Maybe Bool -- | A conservative version of isWorkFree. Is used to determine in -- bindConstantVar to determine whether an expression can be -- "bound" (locally inlined). While binding workfree expressions won't -- result in extra work for the circuit, it might very well cause extra -- work for Clash. In fact, using isWorkFree in -- bindConstantVar makes Clash two orders of magnitude slower -- for some of our test cases. -- -- In effect, this function is a version of isConstant that also -- considers references to clocks and resets constant. This allows us to -- bind HiddenClock(ResetEnable) constructs, allowing Clash to constant -- spec subconstants - most notably KnownDomain. Doing that enables Clash -- to eliminate any case-constructs on it. isWorkFreeIsh :: TyConMap -> Term -> Bool -- | Determine if a term represents a constant isConstant :: Term -> Bool isConstantNotClockReset :: TyConMap -> Term -> Bool -- | Normal forms for the partial evaluator. These provide a restricted -- model of how terms can be constructed (compared to the more liberal -- Term type) which give a stronger guarantee that evaluation does not -- produce invalid results. This module is only needed to define new -- evaluators, for calling an existing evaluator see -- Clash.Core.PartialEval. module Clash.Core.PartialEval.NormalForm -- | An argument applied to a function data constructor primitive. type Arg a = Either a Type type Args a = [Arg a] -- | Neutral terms cannot be reduced, as they represent things like -- variables which are unknown, partially applied functions, or case -- expressions where the subject cannot be inspected. Consider: -- -- v Stuck if "v" is a free variable p x1 ... xn Stuck if "p" is a -- primitive that cannot be reduced x $ y Stuck if "x" is not known to be -- a lambda x @ A Stuck if "x" is not known to be a type lambda case x of -- ... Stuck if "x" is neutral (cannot choose an alternative) -- -- Neutral terms can also be let expressions which preserve required -- bindings in the normal form representation. Examples of bindings that -- may be kept are bindings which perform work (and should not be copied) -- or bindings that are recursive and are still referred to by the body -- of the let expression. -- -- let ... in ... Preserved bindings are needed by the body data Neutral a NeVar :: !Id -> Neutral a NePrim :: !PrimInfo -> !Args a -> Neutral a NeApp :: !Neutral a -> !a -> Neutral a NeTyApp :: !Neutral a -> !Type -> Neutral a NeLet :: !Bind a -> !a -> Neutral a NeCase :: !a -> !Type -> ![(Pat, a)] -> Neutral a -- | A term which has been potentially evaluated to WHNF. If evaluation has -- occurred, then there will be no redexes at the head of the Value, but -- sub-terms may still have redexes. Data constructors are only -- considered to be values when fully applied, if partially applied they -- should be eta-expanded during evaluation. -- -- Thunks are included so that lazy evaluation can be modelled without -- needing to store Either Term Value in the environment. This makes the -- presentation simpler, with the caveat that values must be forced when -- they are required to not be thunks. data Value VNeutral :: !Neutral Value -> Value VLiteral :: !Literal -> Value VData :: !DataCon -> !Args Value -> !LocalEnv -> Value VLam :: !Id -> !Term -> !LocalEnv -> Value VTyLam :: !TyVar -> !Term -> !LocalEnv -> Value VCast :: !Value -> !Type -> !Type -> Value VTick :: !Value -> !TickInfo -> Value VThunk :: !Term -> !LocalEnv -> Value mkValueTicks :: Value -> [TickInfo] -> Value stripValue :: Value -> Value collectValueTicks :: Value -> (Value, [TickInfo]) isUndefined :: Value -> Bool isUndefinedX :: Value -> Bool -- | A term which is in beta-normal eta-long form (NF). This has no -- redexes, and all partially applied functions in sub-terms are -- eta-expanded. -- -- While not strictly necessary, NLam includes the environment at the -- point the original term was evaluated. This makes it easier for the -- AsTerm instance for Normal to reintroduce let expressions before -- lambdas without accidentally floating a let using a lambda bound -- variable outwards. data Normal NNeutral :: !Neutral Normal -> Normal NLiteral :: !Literal -> Normal NData :: !DataCon -> !Args Normal -> Normal NLam :: !Id -> !Normal -> !LocalEnv -> Normal NTyLam :: !TyVar -> !Normal -> !LocalEnv -> Normal NCast :: !Normal -> !Type -> !Type -> Normal NTick :: !Normal -> !TickInfo -> Normal data LocalEnv LocalEnv :: Id -> Map TyVar Type -> Map Id Value -> Word -> Bool -> LocalEnv -- | The id of the term currently under evaluation. [lenvContext] :: LocalEnv -> Id -- | Local type environment. These are types that are introduced while -- evaluating the current term (i.e. by type applications) [lenvTypes] :: LocalEnv -> Map TyVar Type -- | Local term environment. These are WHNF terms or unevaluated thunks -- introduced while evaluating the current term (i.e. by applications) [lenvValues] :: LocalEnv -> Map Id Value -- | The amount of fuel left in the local environment when the previous -- head was reached. This is needed so resuming evaluation does not lead -- to additional fuel being available. [lenvFuel] :: LocalEnv -> Word -- | When evaluating, keep data constructors for boxed data types (e.g. I#) -- instead of converting these back to their corresponding primitive. -- This is used when evaluating terms where the result is subject of a -- case expression (see note: lifted data types). [lenvKeepLifted] :: LocalEnv -> Bool data GlobalEnv GlobalEnv :: VarEnv (Binding Value) -> TyConMap -> InScopeSet -> Supply -> Word -> IntMap Value -> Int -> VarEnv Bool -> GlobalEnv -- | Global term environment. These are the potentially evaluated bodies of -- the top level definitions which are forced on lookup. [genvBindings] :: GlobalEnv -> VarEnv (Binding Value) -- | The type constructors known about by Clash. [genvTyConMap] :: GlobalEnv -> TyConMap -- | The set of in scope variables during partial evaluation. This includes -- new variables introduced by the evaluator (such as the ids of binders -- introduced during eta expansion.) [genvInScope] :: GlobalEnv -> InScopeSet -- | The supply of fresh names for generating identifiers. [genvSupply] :: GlobalEnv -> Supply -- | The remaining fuel which can be spent inlining global variables. This -- is saved in the local environment, so when evaluation resumes from -- WHNF the amount of fuel used is preserved. [genvFuel] :: GlobalEnv -> Word -- | The heap containing the results of any evaluated IO primitives. [genvHeap] :: GlobalEnv -> IntMap Value -- | The address of the next element to be inserted into the heap. [genvAddr] :: GlobalEnv -> Int -- | Cache for the results of isWorkFree. This is required to use -- Clash.Rewrite.WorkFree.isWorkFree. [genvWorkCache] :: GlobalEnv -> VarEnv Bool workFreeCache :: Lens' GlobalEnv (VarEnv Bool) instance GHC.Show.Show a => GHC.Show.Show (Clash.Core.PartialEval.NormalForm.Neutral a) instance GHC.Show.Show Clash.Core.PartialEval.NormalForm.Value instance GHC.Show.Show Clash.Core.PartialEval.NormalForm.LocalEnv instance GHC.Show.Show Clash.Core.PartialEval.NormalForm.Normal -- | The AsTerm class and relevant instances for the partial evaluator. -- This defines how to convert normal forms back into Terms which can be -- given as the result of evaluation. module Clash.Core.PartialEval.AsTerm -- | Convert a term in some normal form back into a Term. This is -- important, as it may perform substitutions which have not yet been -- performed (i.e. when converting from WHNF where heads contain the -- environment at that point). class AsTerm a asTerm :: AsTerm a => a -> Term instance Clash.Core.PartialEval.AsTerm.AsTerm a => Clash.Core.PartialEval.AsTerm.AsTerm (Clash.Core.PartialEval.NormalForm.Neutral a) instance Clash.Core.PartialEval.AsTerm.AsTerm Clash.Core.PartialEval.NormalForm.Value instance Clash.Core.PartialEval.AsTerm.AsTerm Clash.Core.PartialEval.NormalForm.Normal -- | The monad for partial evaluation, and its API. This should contain all -- auxiliary functions needed to define new evaluator implementations. -- This module is only needed to define new evaluators, for calling an -- existing evaluator see Clash.Core.PartialEval. module Clash.Core.PartialEval.Monad -- | The monad of partial evaluation. The inner monad is IO, as primitive -- evaluation can attempt to evaluate IO actions. data Eval a -- | Evaluate an action in the partial evaluator, returning the result, and -- the final state of the global environment. runEval :: GlobalEnv -> LocalEnv -> Eval a -> IO (a, GlobalEnv) getLocalEnv :: Eval LocalEnv setLocalEnv :: LocalEnv -> Eval a -> Eval a modifyLocalEnv :: (LocalEnv -> LocalEnv) -> Eval a -> Eval a getGlobalEnv :: Eval GlobalEnv modifyGlobalEnv :: (GlobalEnv -> GlobalEnv) -> Eval () getContext :: Eval Id withContext :: Id -> Eval a -> Eval a getTvSubst :: Eval Subst findTyVar :: TyVar -> Eval (Maybe Type) withTyVar :: TyVar -> Type -> Eval a -> Eval a withTyVars :: [(TyVar, Type)] -> Eval a -> Eval a findId :: Id -> Eval (Maybe Value) withId :: Id -> Value -> Eval a -> Eval a withIds :: [(Id, Value)] -> Eval a -> Eval a withoutId :: Id -> Eval a -> Eval a findBinding :: Id -> Eval (Maybe (Binding Value)) replaceBinding :: Binding Value -> Eval () getRef :: Int -> Eval Value setRef :: Int -> Value -> Eval () isKeepingLifted :: Eval Bool keepLifted :: Eval a -> Eval a getFuel :: Eval Word withFuel :: Eval a -> Eval a preserveFuel :: Eval a -> Eval a getTyConMap :: Eval TyConMap getInScope :: Eval InScopeSet getUniqueId :: OccName -> Type -> Eval Id getUniqueTyVar :: OccName -> Kind -> Eval TyVar workFreeValue :: Value -> Eval Bool instance Control.Monad.Catch.MonadMask Clash.Core.PartialEval.Monad.Eval instance Control.Monad.Catch.MonadCatch Clash.Core.PartialEval.Monad.Eval instance Control.Monad.Catch.MonadThrow Clash.Core.PartialEval.Monad.Eval instance Control.Monad.State.Class.MonadState Clash.Core.PartialEval.NormalForm.GlobalEnv Clash.Core.PartialEval.Monad.Eval instance Control.Monad.Reader.Class.MonadReader Clash.Core.PartialEval.NormalForm.LocalEnv Clash.Core.PartialEval.Monad.Eval instance Control.Monad.IO.Class.MonadIO Clash.Core.PartialEval.Monad.Eval instance Control.Monad.Fail.MonadFail Clash.Core.PartialEval.Monad.Eval instance GHC.Base.Monad Clash.Core.PartialEval.Monad.Eval instance GHC.Base.Alternative Clash.Core.PartialEval.Monad.Eval instance GHC.Base.Applicative Clash.Core.PartialEval.Monad.Eval instance GHC.Base.Functor Clash.Core.PartialEval.Monad.Eval -- | The main API of the partial evaluator. This exposes the main functions -- needed to call the evaluator, and the type of evaluators. A concrete -- implementation of an evaluator is required to use this module: this -- can be imported from the library for the compiler front-end, e.g. -- Clash.GHC.PartialEval in clash-ghc. module Clash.Core.PartialEval -- | An evaluator for Clash core. This consists of two functions: one to -- evaluate a term to weak-head normal form (WHNF) and another to -- recursively evaluate sub-terms to obtain beta-normal eta-long form -- (NF). data Evaluator Evaluator :: (Term -> Eval Value) -> (Value -> Eval Normal) -> Evaluator [evalWhnf] :: Evaluator -> Term -> Eval Value [quoteNf] :: Evaluator -> Value -> Eval Normal -- | Evaluate a term to WHNF, converting the result back to a Term. The -- global environment at the end of evaluation is also returned, callers -- should preserve any parts of the global environment needed for later -- calls. whnf :: Evaluator -> GlobalEnv -> Bool -> Id -> Term -> IO (Term, GlobalEnv) -- | Evaluate a term to NF, converting the result back to a Term. See -- whnf for more details. nf :: Evaluator -> GlobalEnv -> Bool -> Id -> Term -> IO (Term, GlobalEnv) mkGlobalEnv :: BindingMap -> TyConMap -> InScopeSet -> Supply -> Word -> IntMap Value -> Int -> GlobalEnv module Clash.Core.TermInfo termSize :: Term -> Word multPrimErr :: PrimInfo -> String splitMultiPrimArgs :: HasCallStack => MultiPrimInfo -> [Either Term Type] -> ([Either Term Type], [Id]) -- | Same as multiPrimInfo, but produced an error if it could not -- produce a MultiPrimInfo. multiPrimInfo' :: HasCallStack => TyConMap -> PrimInfo -> MultiPrimInfo -- | Produce MutliPrimInfo for given primitive multiPrimInfo :: TyConMap -> PrimInfo -> Maybe MultiPrimInfo -- | Does a term have a function type? isFun :: TyConMap -> Term -> Bool -- | Does a term have a function or polymorphic type? isPolyFun :: TyConMap -> Term -> Bool -- | Is a term a recursive let-binding? isLet :: Term -> Bool -- | Is a term a variable reference? isVar :: Term -> Bool isLocalVar :: Term -> Bool -- | Is a term a datatype constructor? isCon :: Term -> Bool -- | Is a term a primitive? isPrim :: Term -> Bool -- | Is a term a tick? isTick :: Term -> Bool -- | Is a term a cast? isCast :: Term -> Bool -- | Types for the Partial Evaluator module Clash.Core.Evaluator.Types whnf' :: Evaluator -> BindingMap -> VarEnv Term -> TyConMap -> PrimHeap -> Supply -> InScopeSet -> Bool -> Term -> (PrimHeap, PureHeap, Term) -- | Evaluate to WHNF given an existing Heap and Stack whnf :: Evaluator -> TyConMap -> Bool -> Machine -> Machine -- | An evaluator is a collection of basic building blocks which are used -- to define partial evaluation. In this implementation, it consists of -- two types of function: -- -- -- -- Variants of these functions also exist for evalauting primitive -- operations. This is because there may be multiple frontends to the -- compiler which can reuse a common step and unwind, but have different -- primitives. data Evaluator Evaluator :: Step -> Unwind -> PrimStep -> PrimUnwind -> Evaluator [step] :: Evaluator -> Step [unwind] :: Evaluator -> Unwind [primStep] :: Evaluator -> PrimStep [primUnwind] :: Evaluator -> PrimUnwind -- | Completely unwind the stack to get back the complete term unwindStack :: Machine -> Maybe Machine -- | A single step in the partial evaluator. The result is the new heap and -- stack, and the next expression to be reduced. type Step = Machine -> TyConMap -> Maybe Machine type Unwind = Value -> Step type PrimStep = TyConMap -> Bool -> PrimInfo -> [Type] -> [Value] -> Machine -> Maybe Machine type PrimUnwind = TyConMap -> PrimInfo -> [Type] -> [Value] -> Value -> [Term] -> Machine -> Maybe Machine -- | A machine represents the current state of the abstract machine used to -- evaluate terms. A machine has a term under evaluation, a stack, and -- three heaps: -- -- -- -- Machines also include a unique supply and InScopeSet. These are needed -- when new heap bindings are created, and are just an implementation -- detail. data Machine Machine :: PrimHeap -> PureHeap -> PureHeap -> Stack -> Supply -> InScopeSet -> Term -> Machine [mHeapPrim] :: Machine -> PrimHeap [mHeapGlobal] :: Machine -> PureHeap [mHeapLocal] :: Machine -> PureHeap [mStack] :: Machine -> Stack [mSupply] :: Machine -> Supply [mScopeNames] :: Machine -> InScopeSet [mTerm] :: Machine -> Term type PrimHeap = (IntMap Term, Int) type PureHeap = VarEnv Term type Stack = [StackFrame] data StackFrame Update :: IdScope -> Id -> StackFrame Apply :: Id -> StackFrame Instantiate :: Type -> StackFrame PrimApply :: PrimInfo -> [Type] -> [Value] -> [Term] -> StackFrame Scrutinise :: Type -> [Alt] -> StackFrame Tickish :: TickInfo -> StackFrame data Value -- | Functions Lambda :: Id -> Term -> Value -- | Type abstractions TyLambda :: TyVar -> Term -> Value -- | Data constructors DC :: DataCon -> [Either Term Type] -> Value -- | Literals Lit :: Literal -> Value -- | Clash's number types are represented by their "fromInteger#" primitive -- function. So some primitives are values. PrimVal :: PrimInfo -> [Type] -> [Value] -> Value -- | Used by lazy primitives Suspend :: Term -> Value -- | Preserve ticks from Terms in Values TickValue :: TickInfo -> Value -> Value -- | Preserve casts from Terms in Values CastValue :: Value -> Type -> Type -> Value valToTerm :: Value -> Term collectValueTicks :: Value -> (Value, [TickInfo]) -- | Are we in a context where special primitives must be forced. -- -- See [Note: forcing special primitives] forcePrims :: Machine -> Bool primCount :: Machine -> Int primLookup :: Int -> Machine -> Maybe Term primInsert :: Int -> Term -> Machine -> Machine primUpdate :: Int -> Term -> Machine -> Machine heapLookup :: IdScope -> Id -> Machine -> Maybe Term heapContains :: IdScope -> Id -> Machine -> Bool heapInsert :: IdScope -> Id -> Term -> Machine -> Machine heapDelete :: IdScope -> Id -> Machine -> Machine stackPush :: StackFrame -> Machine -> Machine stackPop :: Machine -> Maybe (Machine, StackFrame) stackClear :: Machine -> Machine stackNull :: Machine -> Bool getTerm :: Machine -> Term setTerm :: Term -> Machine -> Machine instance GHC.Show.Show Clash.Core.Evaluator.Types.Value instance GHC.Show.Show Clash.Core.Evaluator.Types.StackFrame instance GHC.Show.Show Clash.Core.Evaluator.Types.Machine instance Clash.Pretty.ClashPretty Clash.Core.Evaluator.Types.StackFrame instance Clash.Core.HasType.InferType Clash.Core.Evaluator.Types.Value -- | This module provides a way to access static files that are useful when -- working with Clash designs. module Clash.DataFiles -- | The Tcl Connector: a Tcl script that can parse Clash output and emit -- the correct commands for loading the design into Vivado (Quartus -- support will be added later). -- -- Apart from parsing the clash-manifest.json files produced by -- Clash, the Tcl Connector also supports the so-called -- Clash<->Tcl API. This functionality enables Clash -- primitives to pass complex instructions to the Tcl Connector. Current -- features are instantiating IP in Vivado and passing metadata along -- with Vivado XDC files. -- -- An example use of the Tcl Connector, demonstrating its basic features: -- --
--   source -notrace clashConnector.tcl
--   # Pass it the path to "clash-manifest.json" of your top entity
--   clash::readMetadata vhdl/Design.topEntity
--   # Instantiate IP (no-op if no IP defined)
--   file mkdir ip
--   clash::createAndReadIp -dir ip
--   # Read all VHDL/Verilog/SystemVerilog files generated by Clash
--   clash::readHdl
--   # Handle XDC files, in correct order
--   clash::readXdc early
--   # A file containing PACKAGE_PIN and IOSTANDARD definitions (but not
--   # create_clock, clocks are part of the Clash-generated files)
--   read_xdc Arty-A7-35-Master.xdc
--   set_property USED_IN implementation [get_files Arty-A7-35-Master.xdc]
--   clash::readXdc {normal late}
--   synth_design -top $clash::topEntity -part xc7a35ticsg324-1L
--   opt_design
--   place_design
--   route_design
--   write_bitstream ${clash::topEntity}.bit
--   
-- -- Clash.Xilinx.ClockGen and -- clash-cores:Clash.Cores.Xilinx modules make use of the IP -- instantiating functionality; XDC metadata functionality is not -- currently used as the IP is already packaged with correct constraints -- by Vivado. -- -- More documentation about the Tcl Connector and the Clash<->Tcl -- API will be made available later. -- -- In addition to this module, you can also write a copy of the Tcl -- script to a file by invoking -- --
--   cabal run clash-lib:static-files -- --tcl-connector clashConnector.tcl
--   
tclConnector :: IO FilePath module Clash.Backend primsRoot :: IO FilePath clashVer :: String type ModName = Text -- | Is a type used for internal or external use data Usage -- | Internal use Internal :: Usage -- | External use, field indicates the library name External :: Text -> Usage -- | Is '-fclash-aggresive-x-optimization-blackbox' set? newtype AggressiveXOptBB AggressiveXOptBB :: Bool -> AggressiveXOptBB -- | Is '-fclash-render-enums' set? newtype RenderEnums RenderEnums :: Bool -> RenderEnums -- | Kind of a HDL type. Used to determine whether types need conversions -- in order to cross top entity boundaries. data HWKind -- | A type defined in an HDL spec. Usually types such as: bool, bit, .. PrimitiveType :: HWKind -- | A user defined type that's simply a synonym for another type, very -- much like a type synonym in Haskell. As long as two synonym types -- refer to the same type, they can be used interchangeably. E.g., a -- subtype in VHDL. SynonymType :: HWKind -- | User defined type that's not interchangeable with any others, even if -- the underlying structures are the same. Similar to an ADT in Haskell. UserType :: HWKind type DomainMap = HashMap Text VDomainConfiguration emptyDomainMap :: DomainMap class HasUsageMap s usageMap :: HasUsageMap s => Lens' s UsageMap class (HasUsageMap state, HasIdentifierSet state) => Backend state -- | Initial state for state monad initBackend :: Backend state => ClashOpts -> state -- | What HDL is the backend generating hdlKind :: Backend state => state -> HDL -- | Location for the primitive definitions primDirs :: Backend state => state -> IO [FilePath] -- | Name of backend, used for directory to put output files in. Should be -- constant function / ignore argument. name :: Backend state => state -> String -- | File extension for target langauge extension :: Backend state => state -> String -- | Get the set of types out of state extractTypes :: Backend state => state -> HashSet HWType -- | Generate HDL for a Netlist component genHDL :: Backend state => ClashOpts -> ModName -> SrcSpan -> IdentifierSet -> UsageMap -> Component -> Ap (State state) ((String, Doc), [(String, Doc)]) -- | Generate a HDL package containing type definitions for the given -- HWTypes mkTyPackage :: Backend state => ModName -> [HWType] -> Ap (State state) [(String, Doc)] -- | Convert a Netlist HWType to a target HDL type hdlType :: Backend state => Usage -> HWType -> Ap (State state) Doc -- | Query what kind of type a given HDL type is hdlHWTypeKind :: Backend state => HWType -> State state HWKind -- | Convert a Netlist HWType to an HDL error value for that type hdlTypeErrValue :: Backend state => HWType -> Ap (State state) Doc -- | Convert a Netlist HWType to the root of a target HDL type hdlTypeMark :: Backend state => HWType -> Ap (State state) Doc -- | Create a record selector hdlRecSel :: Backend state => HWType -> Int -> Ap (State state) Doc -- | Create a signal declaration from an identifier (Text) and Netlist -- HWType hdlSig :: Backend state => Text -> HWType -> Ap (State state) Doc -- | Create a generative block statement marker genStmt :: Backend state => Bool -> State state Doc -- | Turn a Netlist Declaration to a HDL concurrent block inst :: Backend state => Declaration -> Ap (State state) (Maybe Doc) -- | Turn a Netlist expression into a HDL expression expr :: Backend state => Bool -> Expr -> Ap (State state) Doc -- | Bit-width of Int,Word,Integer iwWidth :: Backend state => State state Int -- | Convert to a bit-vector toBV :: Backend state => HWType -> Text -> Ap (State state) Doc -- | Convert from a bit-vector fromBV :: Backend state => HWType -> Text -> Ap (State state) Doc -- | Synthesis tool we're generating HDL for hdlSyn :: Backend state => State state HdlSyn -- | setModName setModName :: Backend state => ModName -> state -> state -- | Set the name of the current top entity setTopName :: Backend state => Identifier -> state -> state -- | Get the name of the current top entity getTopName :: Backend state => State state Identifier -- | setSrcSpan setSrcSpan :: Backend state => SrcSpan -> State state () -- | getSrcSpan getSrcSpan :: Backend state => State state SrcSpan -- | Block of declarations blockDecl :: Backend state => Identifier -> [Declaration] -> Ap (State state) Doc addIncludes :: Backend state => [(String, Doc)] -> State state () addLibraries :: Backend state => [Text] -> State state () addImports :: Backend state => [Text] -> State state () addAndSetData :: Backend state => FilePath -> State state String getDataFiles :: Backend state => State state [(String, FilePath)] addMemoryDataFile :: Backend state => (String, String) -> State state () getMemoryDataFiles :: Backend state => State state [(String, String)] ifThenElseExpr :: Backend state => state -> Bool -- | Whether -fclash-aggressive-x-optimization-blackboxes was set aggressiveXOptBB :: Backend state => State state AggressiveXOptBB -- | Whether -fclash-no-render-enums was set renderEnums :: Backend state => State state RenderEnums -- | All the domain configurations of design domainConfigurations :: Backend state => State state DomainMap -- | Set the domain configurations setDomainConfigurations :: Backend state => DomainMap -> state -> state -- | Type and instance definitions for Netlist modules module Clash.Netlist.Types -- | Internals of a Component data Declaration -- | Signal assignment Assignment :: !Identifier -> !Usage -> !Expr -> Declaration -- | Conditional signal assignment: CondAssignment :: !Identifier -> !HWType -> !Expr -> !HWType -> [(Maybe Literal, Expr)] -> Declaration -- | Instantiation of another component: InstDecl :: EntityOrComponent -> Maybe Text -> [Attr Text] -> !Identifier -> !Identifier -> [(Expr, HWType, Expr)] -> PortMap -> Declaration -- | Instantiation of blackbox declaration BlackBoxD :: !Text -> [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> !BlackBox -> BlackBoxContext -> Declaration -- | component declaration (VHDL). -- -- See this tutorial; refer to §4.5 of IEEE 1076-1993 CompDecl :: !Text -> [(Text, PortDirection, HWType)] -> Declaration -- | Signal declaration NetDecl' :: Maybe Comment -> !Identifier -> HWType -> Maybe Expr -> Declaration -- | HDL tick corresponding to a Core tick TickDecl :: CommentOrDirective -> Declaration -- | Sequential statement Seq :: [Seq] -> Declaration -- | Compilation conditional on some preprocessor symbol, note that -- declarations here are ignored for VHDL. See here for a discussion -- https://github.com/clash-lang/clash-compiler/pull/1798#discussion_r648571862 ConditionalDecl :: !Text -> [Declaration] -> Declaration pattern NetDecl :: Maybe Comment -> Identifier -> HWType -> Declaration type UsageMap = Map Text Usage -- | The usage of a signal refers to how the signal is written to in -- netlist. This is used to determine if the signal should be a -- wire or reg in (System)Verilog, or a signal -- or variable in VHDL. data Usage -- | Continuous assignment, which occurs in a concurrent context. Cont :: Usage -- | Procedural assignment, which occurs in a sequential context. Proc :: Blocking -> Usage -- | Procedural assignment in HDL can be blocking or non-blocking. This -- determines when the assignment takes place in simulation. The name -- refers to whether evaluation of the remaining statements in a process -- is blocked until the assignment is performed or not. -- -- See Also: -- -- IEEE 1364-2001, sections 9.2.1 and 9.2.2 IEEE 1076-1993, sections 8.4 -- and 8.5 data Blocking -- | A non-blocking assignment means the new value is not observed until -- the next time step in simulation. Using the signal later in the -- process will continue to return the old value. NonBlocking :: Blocking -- | A blocking assignment means the new value is observed immediately. -- Using the signal later in the process will return the new value. Blocking :: Blocking -- | Whether to preserve casing in ids or converted everything to -- lowercase. Influenced by '-fclash-lower-case-basic-identifiers' data PreserveCase PreserveCase :: PreserveCase ToLower :: PreserveCase -- | Monad that caches generated components (StateT) and remembers hidden -- inputs of components that are being generated (WriterT) newtype NetlistMonad a NetlistMonad :: StateT NetlistState (ReaderT NetlistEnv IO) a -> NetlistMonad a [runNetlist] :: NetlistMonad a -> StateT NetlistState (ReaderT NetlistEnv IO) a -- | Structures that hold an IdentifierSet class HasIdentifierSet s identifierSet :: HasIdentifierSet s => Lens' s IdentifierSet -- | An IdentifierSetMonad supports unique name generation for Clash -- Netlist class Monad m => IdentifierSetMonad m identifierSetM :: IdentifierSetMonad m => (IdentifierSet -> IdentifierSet) -> m IdentifierSet -- | Structure describing a top entity: it's id and its port annotations. data TopEntityT TopEntityT :: Id -> Maybe TopEntity -> Bool -> TopEntityT -- | Id of top entity [topId] :: TopEntityT -> Id -- | (Maybe) a topentity annotation [topAnnotation] :: TopEntityT -> Maybe TopEntity -- | Whether this entity is a test bench [topIsTestBench] :: TopEntityT -> Bool data BlackBox BBTemplate :: BlackBoxTemplate -> BlackBox BBFunction :: BBName -> BBHash -> TemplateFunction -> BlackBox -- | Expression used in RHS of a declaration data Expr -- | Literal expression Literal :: !Maybe (HWType, Size) -> !Literal -> Expr -- | DataCon application DataCon :: !HWType -> !Modifier -> [Expr] -> Expr -- | Signal reference Identifier :: !Identifier -> !Maybe Modifier -> Expr -- | Left e: tagToEnum#, Right e: dataToTag# DataTag :: !HWType -> !Either Identifier Identifier -> Expr -- | Instantiation of a BlackBox expression BlackBoxE :: !Text -> [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> !BlackBox -> !BlackBoxContext -> !Bool -> Expr -- | Convert some type to a BitVector. ToBv :: Maybe Identifier -> HWType -> Expr -> Expr -- | Convert BitVector to some type. FromBv :: Maybe Identifier -> HWType -> Expr -> Expr IfThenElse :: Expr -> Expr -> Expr -> Expr -- | Do nothing Noop :: Expr -- | Component: base unit of a Netlist data Component Component :: !Identifier -> [(Identifier, HWType)] -> [(Usage, (Identifier, HWType), Maybe Expr)] -> [Declaration] -> Component -- | Name of the component [componentName] :: Component -> !Identifier -- | Input ports [inputs] :: Component -> [(Identifier, HWType)] -- | Output ports [outputs] :: Component -> [(Usage, (Identifier, HWType), Maybe Expr)] -- | Internal declarations [declarations] :: Component -> [Declaration] -- | Internals of a Component data Declaration -- | Signal assignment Assignment :: !Identifier -> !Usage -> !Expr -> Declaration -- | Conditional signal assignment: CondAssignment :: !Identifier -> !HWType -> !Expr -> !HWType -> [(Maybe Literal, Expr)] -> Declaration -- | Instantiation of another component: InstDecl :: EntityOrComponent -> Maybe Text -> [Attr Text] -> !Identifier -> !Identifier -> [(Expr, HWType, Expr)] -> PortMap -> Declaration -- | Instantiation of blackbox declaration BlackBoxD :: !Text -> [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> !BlackBox -> BlackBoxContext -> Declaration -- | component declaration (VHDL). -- -- See this tutorial; refer to §4.5 of IEEE 1076-1993 CompDecl :: !Text -> [(Text, PortDirection, HWType)] -> Declaration -- | Signal declaration NetDecl' :: Maybe Comment -> !Identifier -> HWType -> Maybe Expr -> Declaration -- | HDL tick corresponding to a Core tick TickDecl :: CommentOrDirective -> Declaration -- | Sequential statement Seq :: [Seq] -> Declaration -- | Compilation conditional on some preprocessor symbol, note that -- declarations here are ignored for VHDL. See here for a discussion -- https://github.com/clash-lang/clash-compiler/pull/1798#discussion_r648571862 ConditionalDecl :: !Text -> [Declaration] -> Declaration -- | Representable hardware types data HWType -- | Empty type. Just Size for "empty" Vectors so we can still -- have primitives that can traverse e.g. Vectors of unit and know the -- length of that vector. Void :: Maybe HWType -> HWType -- | String type String :: HWType -- | Integer type (for parameters only) Integer :: HWType -- | Boolean type Bool :: HWType -- | Bit type Bit :: HWType -- | BitVector of a specified size BitVector :: !Size -> HWType -- | Unsigned integer with specified (exclusive) upper bounder Index :: !Integer -> HWType -- | Signed integer of a specified size Signed :: !Size -> HWType -- | Unsigned integer of a specified size Unsigned :: !Size -> HWType -- | Vector type Vector :: !Size -> !HWType -> HWType -- | MemBlob type MemBlob :: !Size -> !Size -> HWType -- | RTree type RTree :: !Size -> !HWType -> HWType -- | Sum type: Name and Constructor names Sum :: !Text -> [Text] -> HWType -- | Product type: Name, field names, and field types. Field names will be -- populated when using records. Product :: !Text -> Maybe [Text] -> [HWType] -> HWType -- | Sum-of-Product type: Name and Constructor names + field types SP :: !Text -> [(Text, [HWType])] -> HWType -- | Clock type corresponding to domain DomainName Clock :: !DomainName -> HWType -- | ClockN type corresponding to domain DomainName ClockN :: !DomainName -> HWType -- | Reset type corresponding to domain DomainName Reset :: !DomainName -> HWType -- | Enable type corresponding to domain DomainName Enable :: !DomainName -> HWType -- | Tagging type indicating a bidirectional (inout) port BiDirectional :: !PortDirection -> !HWType -> HWType -- | Same as Sum-Of-Product, but with a user specified bit representation. -- For more info, see: Clash.Annotations.BitRepresentations. CustomSP :: !Text -> !DataRepr' -> !Size -> [(ConstrRepr', Text, [HWType])] -> HWType -- | Same as Sum, but with a user specified bit representation. For more -- info, see: Clash.Annotations.BitRepresentations. CustomSum :: !Text -> !DataRepr' -> !Size -> [(ConstrRepr', Text)] -> HWType -- | Same as Product, but with a user specified bit representation. For -- more info, see: Clash.Annotations.BitRepresentations. CustomProduct :: !Text -> !DataRepr' -> !Size -> Maybe [Text] -> [(FieldAnn, HWType)] -> HWType -- | Annotated with HDL attributes Annotated :: [Attr Text] -> !HWType -> HWType -- | Domain name, period, active edge, reset kind, initial value behavior KnownDomain :: !DomainName -> !Integer -> !ActiveEdge -> !ResetKind -> !InitBehavior -> !ResetPolarity -> HWType -- | File type for simulation-level I/O FileType :: HWType -- | A collection of unique identifiers. Allows for fast fresh identifier -- generation. -- -- NB: use the functions in Clash.Netlist.Id. Don't use the -- constructor directly. data IdentifierSet IdentifierSet :: !Bool -> !PreserveCase -> !HDL -> !FreshCache -> !HashSet Identifier -> IdentifierSet -- | Allow escaped ids? If set to False, "make" will always behave like -- "makeBasic". [is_allowEscaped] :: IdentifierSet -> !Bool -- | Force all generated basic identifiers to lowercase. [is_lowerCaseBasicIds] :: IdentifierSet -> !PreserveCase -- | HDL to generate fresh identifiers for [is_hdl] :: IdentifierSet -> !HDL -- | Maps an i_baseNameCaseFold to a map mapping the number of -- extensions (in i_extensionsRev) to the maximum word at that -- basename/level. For example, if a set would contain the identifiers: -- -- -- -- the map would look like: -- -- -- -- This mapping makes sure we can quickly generate fresh identifiers. For -- example, generating a new id for "foo_1" would be a matter of looking -- up the base name in this map, concluding that the maximum identifier -- with this basename and this number of extensions is "foo_2", -- subsequently generating "foo_3". -- -- Note that an identifier with no extensions is also stored in this map -- for practical purposes, but the maximum ext is invalid. [is_freshCache] :: IdentifierSet -> !FreshCache -- | Identifier store [is_store] :: IdentifierSet -> !HashSet Identifier -- | HDL identifier. Consists of a base name and a number of extensions. An -- identifier with a base name of "foo" and a list of extensions [1, 2] -- will be rendered as "foo_1_2". -- -- Note: The Eq instance of Identifier is case insensitive! E.g., -- two identifiers with base names fooBar and FoObAR -- are considered the same. However, identifiers are stored case -- preserving. This means Clash won't generate two identifiers with -- differing case, but it will try to keep capitalization. -- -- The goal of this data structure is to greatly simplify how Clash deals -- with identifiers internally. Any Identifier should be trivially -- printable to any HDL. -- -- NB: use the functions in Clash.Netlist.Id. Don't use -- these constructors directly. data Identifier -- | Unparsed identifier. Used for things such as port names, which should -- appear in the HDL exactly as the user specified. RawIdentifier :: !Text -> Maybe Identifier -> !CallStack -> Identifier -- | Parsed and sanitized identifier. See various fields for more -- information on its invariants. UniqueIdentifier :: !Text -> !Text -> [Word] -> !IdentifierType -> !HDL -> !CallStack -> Identifier -- | Base name of identifier. make makes sure this field: -- -- [i_baseName] :: Identifier -> !Text -- | Same as i_baseName, but can be used for equality testing that -- doesn't depend on capitalization. [i_baseNameCaseFold] :: Identifier -> !Text -- | Extensions applied to base identifier. E.g., an identifier with a base -- name of foo and an extension of [6, 5] would render as -- foo_5_6. Note that extensions are stored in reverse order for -- easier manipulation. [i_extensionsRev] :: Identifier -> [Word] -- | See IdentifierType. [i_idType] :: Identifier -> !IdentifierType -- | HDL this identifier is generated for. [i_hdl] :: Identifier -> !HDL -- | Stores where this identifier was generated. Tracking is only enabled -- is debugIsOn, otherwise this field will be populated by an -- empty callstack. [i_provenance] :: Identifier -> !CallStack data IdentifierType -- | A basic identifier: does not have to be escaped in order to be a valid -- identifier in HDL. Basic :: IdentifierType -- | An extended identifier: has to be escaped, wrapped, or otherwise -- postprocessed before writhing it to HDL. Extended :: IdentifierType -- | Type of declaration, concurrent or sequential data DeclarationType Concurrent :: DeclarationType Sequential :: DeclarationType -- | Netlist-level identifier data NetlistId -- | Identifier generated in the NetlistMonad, always derived from another -- NetlistId NetlistId :: Identifier -> Type -> NetlistId -- | An original Core identifier CoreId :: Id -> NetlistId -- | A split identifier (into several sub-identifiers), needed to assign -- expressions of types that have to be split apart (e.g. tuples of -- Files) MultiId :: [Id] -> NetlistId data TemplateFunction [TemplateFunction] :: [Int] -> (BlackBoxContext -> Bool) -> (forall s. Backend s => BlackBoxContext -> State s Doc) -> TemplateFunction type BBHash = Int type BBName = String -- | Context used to fill in the holes of a BlackBox template data BlackBoxContext Context :: Text -> [(Expr, HWType)] -> [(Expr, HWType, Bool)] -> IntMap [(Either BlackBox (Identifier, [Declaration]), Usage, [BlackBoxTemplate], [BlackBoxTemplate], [((Text, Text), BlackBox)], BlackBoxContext)] -> [IdentifierText] -> Int -> Identifier -> Maybe IdentifierText -> BlackBoxContext -- | Blackbox function name (for error reporting) [bbName] :: BlackBoxContext -> Text -- | Result names and types. Will typically be a list with a single item. -- Multiple result targets will be used for "multi result primitives". -- See setupMultiResultPrim. [bbResults] :: BlackBoxContext -> [(Expr, HWType)] -- | Argument names, types, and whether it is a literal [bbInputs] :: BlackBoxContext -> [(Expr, HWType, Bool)] -- | Function arguments (subset of inputs): -- -- [bbFunctions] :: BlackBoxContext -> IntMap [(Either BlackBox (Identifier, [Declaration]), Usage, [BlackBoxTemplate], [BlackBoxTemplate], [((Text, Text), BlackBox)], BlackBoxContext)] [bbQsysIncName] :: BlackBoxContext -> [IdentifierText] -- | The scoping level this context is associated with, ensures that -- ~ARGN[k][n] holes are only filled with values from this -- context if k is equal to the scoping level of this context. [bbLevel] :: BlackBoxContext -> Int -- | The component the BlackBox is instantiated in [bbCompName] :: BlackBoxContext -> Identifier -- | The "context name", name set by setName, defaults to the name -- of the closest binder [bbCtxName] :: BlackBoxContext -> Maybe IdentifierText -- | Bit literal data Bit -- | High H :: Bit -- | Low L :: Bit -- | Undefined U :: Bit -- | High-impedance Z :: Bit -- | Literals used in an expression data Literal -- | Number literal NumLit :: !Integer -> Literal -- | Bit literal BitLit :: !Bit -> Literal -- | BitVector literal BitVecLit :: !Integer -> !Integer -> Literal -- | Boolean literal BoolLit :: !Bool -> Literal -- | Vector literal VecLit :: [Literal] -> Literal -- | String literal StringLit :: !String -> Literal -- | Expression Modifier data Modifier -- | Index the expression: (Type of expression, DataCon tag, Field Tag). -- Note that the type of the expression is the type we are slicing from, -- not the type returned by the index operation. Indexed :: (HWType, Int, Int) -> Modifier -- | See expression in a DataCon context: (Type of the expression, DataCon -- tag) DC :: (HWType, Int) -> Modifier -- | See the expression in the context of a Vector append operation VecAppend :: Modifier -- | See the expression in the context of a Tree append operation RTreeAppend :: Modifier -- | Slice the identifier of the given type from start to end Sliced :: (HWType, Int, Int) -> Modifier Nested :: Modifier -> Modifier -> Modifier data PortDirection In :: PortDirection Out :: PortDirection data EntityOrComponent Entity :: EntityOrComponent Comp :: EntityOrComponent Empty :: EntityOrComponent -- | Sequential statements data Seq -- | Clocked sequential statements AlwaysClocked :: ActiveEdge -> Expr -> [Seq] -> Seq -- | Statements to run at simulator start | Statements to run always Initial :: [Seq] -> Seq -- | Statements to run always | Declaration in sequential form AlwaysComb :: [Seq] -> Seq -- | The declaration | Branching statement SeqDecl :: Declaration -> Seq Branch :: !Expr -> !HWType -> [(Maybe Literal, [Seq])] -> Seq -- | Specifies how to wire up a component instance data PortMap -- | Port map based on port positions (port direction, type, assignment) -- -- HDL Example: -- -- bytemaster bytemaster_ds ( clk_1 , rst_1 , bitCtrl_0 ); IndexedPortMap :: [(PortDirection, HWType, Expr)] -> PortMap -- | Port map based on port names (port name, port direction, type, -- assignment) -- -- HDL Example: -- -- bytemaster bytemaster_ds ( .clk (clk_1) , .rst (rst_1) , .bitCtrl -- (bitCtrl_0) ); NamedPortMap :: [(Expr, PortDirection, HWType, Expr)] -> PortMap type DomainName = Text -- | Tree structure indicating which constructor fields were filtered from -- a type due to them being void. We need this information to generate -- stable and/or user-defined port mappings. data FilteredHWType FilteredHWType :: HWType -> [[(IsVoid, FilteredHWType)]] -> FilteredHWType type IsVoid = Bool -- | Size indication of a type (e.g. bit-size or number of elements) type Size = Int data CommentOrDirective Comment :: Comment -> CommentOrDirective Directive :: Directive -> CommentOrDirective type Directive = Text type Comment = Text -- | Existentially quantified backend data SomeBackend [SomeBackend] :: Backend backend => backend -> SomeBackend data ComponentPrefix ComponentPrefix :: Maybe Text -> Maybe Text -> ComponentPrefix -- | Prefix for top-level components [componentPrefixTop] :: ComponentPrefix -> Maybe Text -- | Prefix for all other components [componentPrefixOther] :: ComponentPrefix -> Maybe Text -- | State of the NetlistMonad data NetlistState NetlistState :: BindingMap -> ComponentMap -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> !(Identifier, SrcSpan) -> IdentifierSet -> IdentifierSet -> Set Text -> VarEnv Identifier -> VarEnv TopEntityT -> FilePath -> Int -> Bool -> Bool -> SomeBackend -> HWMap -> UsageMap -> NetlistState -- | Global binders [_bindings] :: NetlistState -> BindingMap -- | Cached components. Is an insertion ordered map to preserve a -- topologically sorted component list for the manifest file. [_components] :: NetlistState -> ComponentMap -- | Hardcoded Type -> HWType translator [_typeTranslator] :: NetlistState -> CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType)) [_curCompNm] :: NetlistState -> !(Identifier, SrcSpan) -- | All names currently in scope. [_seenIds] :: NetlistState -> IdentifierSet -- | Components (to be) generated during this netlist run. This is always a -- subset of seenIds. Reason d'etre: we currently generate -- components in a top down manner. E.g. given: -- -- -- -- we would generate component A first. Before trying to -- generate B and C. A might introduce a -- number of signal declarations. The names of these signals can't clash -- with the name of component B, hence we need to pick a name -- for B unique w.r.t. all these signal names. If we would postpone -- generating a unqiue name for B til _after_ generating all the -- signal names, the signal names would get all the "nice" names. E.g., a -- signal would be called "foo", thereby forcing the component B -- to be called "foo_1". Ideally, we'd use the "nice" names for -- components, and the "ugly" names for signals. To achieve this, we -- generate all the component names up front and subsequently store them -- in _seenComps. [_seenComps] :: NetlistState -> IdentifierSet -- | Keeps track of invocations of ´mkPrimitive´. It is currently used to -- filter duplicate warning invocations for dubious blackbox -- instantiations, see GitHub pull request #286. [_seenPrimitives] :: NetlistState -> Set Text -- | Names of components (to be) generated during this netlist run. -- Includes top entity names. [_componentNames] :: NetlistState -> VarEnv Identifier [_topEntityAnns] :: NetlistState -> VarEnv TopEntityT [_hdlDir] :: NetlistState -> FilePath -- | The current scoping level assigned to black box contexts [_curBBlvl] :: NetlistState -> Int -- | Whether we're compiling a testbench (suppresses some warnings) [_isTestBench] :: NetlistState -> Bool -- | Whether the backend supports ifThenElse expressions [_backEndITE] :: NetlistState -> Bool -- | The current HDL backend [_backend] :: NetlistState -> SomeBackend [_htyCache] :: NetlistState -> HWMap -- | The current way signals are assigned in netlist. This is used to -- determine how signals are rendered in HDL (i.e. wire/reg in Verilog, -- or signal/variable in VHDL). [_usages] :: NetlistState -> UsageMap type ComponentMap = OMap Unique (ComponentMeta, Component) data ComponentMeta ComponentMeta :: [Bool] -> SrcSpan -> IdentifierSet -> UsageMap -> ComponentMeta [cmWereVoids] :: ComponentMeta -> [Bool] [cmLoc] :: ComponentMeta -> SrcSpan [cmScope] :: ComponentMeta -> IdentifierSet [cmUsage] :: ComponentMeta -> UsageMap -- | Environment of the NetlistMonad data NetlistEnv NetlistEnv :: ClashEnv -> Text -> Text -> Maybe Text -> NetlistEnv [_clashEnv] :: NetlistEnv -> ClashEnv -- | Prefix for instance/register names [_prefixName] :: NetlistEnv -> Text -- | Postfix for instance/register names [_suffixName] :: NetlistEnv -> Text -- | (Maybe) user given instance/register name [_setName] :: NetlistEnv -> Maybe Text type IdentifierText = Text -- | See is_freshCache type FreshCache = HashMap Text (IntMap Word) type HWMap = Map Type (Either String FilteredHWType) -- | See ExpandedTopEntity data ExpandedPortName a -- | Same as PortName, but fully expanded ExpandedPortName :: HWType -> a -> ExpandedPortName a -- | Same as PortProduct, but fully expanded ExpandedPortProduct :: Text -> HWType -> [ExpandedPortName a] -> ExpandedPortName a -- | Same as TopEntity, but with all port names that end up in HDL -- specified data ExpandedTopEntity a ExpandedTopEntity :: [Maybe (ExpandedPortName a)] -> Maybe (ExpandedPortName a) -> ExpandedTopEntity a -- | Inputs with fully expanded port names. Nothing if port is void. [et_inputs] :: ExpandedTopEntity a -> [Maybe (ExpandedPortName a)] -- | Output with fully expanded port names. Nothing if port is void -- or BiDirectionalOut. [et_output] :: ExpandedTopEntity a -> Maybe (ExpandedPortName a) pattern NetDecl :: Maybe Comment -> Identifier -> HWType -> Declaration identifierKey# :: Identifier -> ((Text, Bool), [Word]) onSomeBackend :: (forall b. Backend b => b -> a) -> SomeBackend -> a fromSomeBackend :: (forall b. Backend b => b -> a) -> Getter SomeBackend a -- | Check if an input port is really an inout port. isBiDirectional :: (Identifier, HWType) -> Bool -- | Find the name and domain name of each clock argument of a component. -- -- This will not consider ClockN to be a clock argument, which -- means only the positive phase of a differential pair will be added to -- sdcClock. findClocks :: Component -> [(Text, Text)] -- | Smart constructor for Annotated. Wraps the given type in an -- Annotated if the attribute list is non-empty. If it is empty, -- it will return the given HWType unchanged. annotated :: [Attr Text] -> HWType -> HWType hwTypeDomain :: HWType -> Maybe DomainName -- | Extract hardware attributes from Annotated. Returns an empty list if -- non-Annotated given or if Annotated has an empty list of attributes. hwTypeAttrs :: HWType -> [Attr Text] lookupUsage :: Identifier -> UsageMap -> Maybe Usage isConstExpr :: Expr -> Bool toBit :: Integer -> Integer -> Bit -- | Eliminator for NetlistId, fails on MultiId netlistId1 :: HasCallStack => (Identifier -> r) -> (Id -> r) -> NetlistId -> r -- | Return the type(s) of a NetListId, returns multiple types -- when given a MultiId netlistTypes :: NetlistId -> [Type] -- | Return the type of a NetlistId, fails on MultiId netlistTypes1 :: HasCallStack => NetlistId -> Type emptyBBContext :: Text -> BlackBoxContext clashEnv :: Lens' NetlistEnv ClashEnv prefixName :: Lens' NetlistEnv Text setName :: Lens' NetlistEnv (Maybe Text) suffixName :: Lens' NetlistEnv Text backEndITE :: Lens' NetlistState Bool backend :: Lens' NetlistState SomeBackend bindings :: Lens' NetlistState BindingMap componentNames :: Lens' NetlistState (VarEnv Identifier) components :: Lens' NetlistState ComponentMap curBBlvl :: Lens' NetlistState Int curCompNm :: Lens' NetlistState (Identifier, SrcSpan) hdlDir :: Lens' NetlistState FilePath htyCache :: Lens' NetlistState HWMap isTestBench :: Lens' NetlistState Bool seenComps :: Lens' NetlistState IdentifierSet seenIds :: Lens' NetlistState IdentifierSet seenPrimitives :: Lens' NetlistState (Set Text) topEntityAnns :: Lens' NetlistState (VarEnv TopEntityT) typeTranslator :: Lens' NetlistState (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) usages :: Lens' NetlistState UsageMap intWidth :: Getter NetlistEnv Int customReprs :: Getter NetlistEnv CustomReprs tcCache :: Getter NetlistEnv TyConMap primitives :: Getter NetlistEnv CompiledPrimMap clashOpts :: Getter NetlistEnv ClashOpts instance Clash.Netlist.Types.IdentifierSetMonad Clash.Netlist.Types.NetlistMonad instance Clash.Netlist.Types.HasIdentifierSet s => Clash.Netlist.Types.IdentifierSetMonad (Control.Monad.Trans.State.Strict.State s) instance Clash.Netlist.Types.HasIdentifierSet s => Clash.Netlist.Types.IdentifierSetMonad (Control.Monad.Trans.State.Lazy.State s) instance Clash.Netlist.Types.IdentifierSetMonad m => Clash.Netlist.Types.IdentifierSetMonad (Data.Monoid.Ap m) instance Clash.Netlist.Types.HasIdentifierSet Clash.Netlist.Types.IdentifierSet instance Clash.Netlist.Types.HasIdentifierSet s => Clash.Netlist.Types.HasIdentifierSet (s, a) instance Clash.Backend.HasUsageMap Clash.Netlist.Types.NetlistState instance GHC.Classes.Eq Clash.Netlist.Types.TopEntityT instance GHC.Show.Show Clash.Netlist.Types.TopEntityT instance GHC.Generics.Generic Clash.Netlist.Types.TopEntityT instance Data.Hashable.Class.Hashable Clash.Netlist.Types.PreserveCase instance Data.Binary.Class.Binary Clash.Netlist.Types.PreserveCase instance GHC.Classes.Eq Clash.Netlist.Types.PreserveCase instance Control.DeepSeq.NFData Clash.Netlist.Types.PreserveCase instance GHC.Generics.Generic Clash.Netlist.Types.PreserveCase instance GHC.Show.Show Clash.Netlist.Types.PreserveCase instance GHC.Classes.Eq Clash.Netlist.Types.IdentifierType instance Control.DeepSeq.NFData Clash.Netlist.Types.IdentifierType instance GHC.Generics.Generic Clash.Netlist.Types.IdentifierType instance GHC.Show.Show Clash.Netlist.Types.IdentifierType instance Control.DeepSeq.NFData Clash.Netlist.Types.Identifier instance GHC.Generics.Generic Clash.Netlist.Types.Identifier instance GHC.Show.Show Clash.Netlist.Types.Identifier instance GHC.Show.Show Clash.Netlist.Types.IdentifierSet instance Control.DeepSeq.NFData Clash.Netlist.Types.IdentifierSet instance GHC.Generics.Generic Clash.Netlist.Types.IdentifierSet instance GHC.Show.Show Clash.Netlist.Types.ComponentPrefix instance GHC.Show.Show Clash.Netlist.Types.CommentOrDirective instance GHC.Show.Show Clash.Netlist.Types.Blocking instance Control.DeepSeq.NFData Clash.Netlist.Types.Blocking instance Data.Hashable.Class.Hashable Clash.Netlist.Types.Blocking instance GHC.Generics.Generic Clash.Netlist.Types.Blocking instance GHC.Classes.Eq Clash.Netlist.Types.Blocking instance Data.Binary.Class.Binary Clash.Netlist.Types.Blocking instance GHC.Show.Show Clash.Netlist.Types.Usage instance Control.DeepSeq.NFData Clash.Netlist.Types.Usage instance Data.Hashable.Class.Hashable Clash.Netlist.Types.Usage instance GHC.Generics.Generic Clash.Netlist.Types.Usage instance GHC.Classes.Eq Clash.Netlist.Types.Usage instance Data.Binary.Class.Binary Clash.Netlist.Types.Usage instance Control.DeepSeq.NFData Clash.Netlist.Types.ComponentMeta instance GHC.Show.Show Clash.Netlist.Types.ComponentMeta instance GHC.Generics.Generic Clash.Netlist.Types.ComponentMeta instance GHC.Show.Show Clash.Netlist.Types.EntityOrComponent instance Data.Hashable.Class.Hashable Clash.Netlist.Types.PortDirection instance Control.DeepSeq.NFData Clash.Netlist.Types.PortDirection instance GHC.Generics.Generic Clash.Netlist.Types.PortDirection instance GHC.Show.Show Clash.Netlist.Types.PortDirection instance GHC.Classes.Ord Clash.Netlist.Types.PortDirection instance GHC.Classes.Eq Clash.Netlist.Types.PortDirection instance Data.Hashable.Class.Hashable Clash.Netlist.Types.HWType instance Control.DeepSeq.NFData Clash.Netlist.Types.HWType instance GHC.Generics.Generic Clash.Netlist.Types.HWType instance GHC.Show.Show Clash.Netlist.Types.HWType instance GHC.Classes.Ord Clash.Netlist.Types.HWType instance GHC.Classes.Eq Clash.Netlist.Types.HWType instance GHC.Show.Show Clash.Netlist.Types.FilteredHWType instance GHC.Classes.Eq Clash.Netlist.Types.FilteredHWType instance Data.Traversable.Traversable Clash.Netlist.Types.ExpandedPortName instance Data.Foldable.Foldable Clash.Netlist.Types.ExpandedPortName instance GHC.Base.Functor Clash.Netlist.Types.ExpandedPortName instance GHC.Show.Show a => GHC.Show.Show (Clash.Netlist.Types.ExpandedPortName a) instance Data.Traversable.Traversable Clash.Netlist.Types.ExpandedTopEntity instance Data.Foldable.Foldable Clash.Netlist.Types.ExpandedTopEntity instance GHC.Base.Functor Clash.Netlist.Types.ExpandedTopEntity instance GHC.Show.Show a => GHC.Show.Show (Clash.Netlist.Types.ExpandedTopEntity a) instance GHC.Show.Show Clash.Netlist.Types.Modifier instance Language.Haskell.TH.Syntax.Lift Clash.Netlist.Types.Bit instance GHC.Show.Show Clash.Netlist.Types.Bit instance GHC.Classes.Eq Clash.Netlist.Types.Bit instance GHC.Show.Show Clash.Netlist.Types.Literal instance GHC.Classes.Eq Clash.Netlist.Types.Literal instance GHC.Show.Show Clash.Netlist.Types.PortMap instance GHC.Show.Show Clash.Netlist.Types.Seq instance GHC.Show.Show Clash.Netlist.Types.Declaration instance GHC.Show.Show Clash.Netlist.Types.Expr instance Data.Binary.Class.Binary Clash.Netlist.Types.BlackBox instance Control.DeepSeq.NFData Clash.Netlist.Types.BlackBox instance GHC.Generics.Generic Clash.Netlist.Types.BlackBox instance GHC.Show.Show Clash.Netlist.Types.BlackBoxContext instance Control.DeepSeq.NFData Clash.Netlist.Types.Component instance GHC.Generics.Generic Clash.Netlist.Types.Component instance GHC.Show.Show Clash.Netlist.Types.Component instance Control.Monad.Fail.MonadFail Clash.Netlist.Types.NetlistMonad instance Control.Monad.IO.Class.MonadIO Clash.Netlist.Types.NetlistMonad instance Control.Monad.State.Class.MonadState Clash.Netlist.Types.NetlistState Clash.Netlist.Types.NetlistMonad instance Control.Monad.Reader.Class.MonadReader Clash.Netlist.Types.NetlistEnv Clash.Netlist.Types.NetlistMonad instance GHC.Base.Applicative Clash.Netlist.Types.NetlistMonad instance GHC.Base.Monad Clash.Netlist.Types.NetlistMonad instance GHC.Base.Functor Clash.Netlist.Types.NetlistMonad instance GHC.Show.Show Clash.Netlist.Types.NetlistId instance GHC.Classes.Eq Clash.Netlist.Types.NetlistId instance Control.DeepSeq.NFData Clash.Netlist.Types.Declaration instance Control.DeepSeq.NFData Clash.Netlist.Types.Expr instance GHC.Show.Show Clash.Netlist.Types.BlackBox instance Control.DeepSeq.NFData Clash.Netlist.Types.TemplateFunction instance Data.Binary.Class.Binary Clash.Netlist.Types.TemplateFunction instance GHC.Base.Semigroup Clash.Netlist.Types.Usage instance Data.Aeson.Types.FromJSON.FromJSON Clash.Netlist.Types.Usage instance GHC.Base.Semigroup Clash.Netlist.Types.Blocking instance Data.Hashable.Class.Hashable Clash.Netlist.Types.Identifier instance GHC.Classes.Eq Clash.Netlist.Types.Identifier instance GHC.Classes.Ord Clash.Netlist.Types.Identifier -- | Verification module Clash.Verification.Pretty pprPslProperty :: HDL -> Text -> Text -> ActiveEdge -> Property' Text -> Declaration pprSvaProperty :: Text -> Text -> ActiveEdge -> Property' Text -> Declaration -- | Generate something like: always (posedge clk_i) isOn: cover -- (result);@ pprYosysSvaProperty :: Text -> Expr -> ActiveEdge -> Property' Text -> Declaration -- | Pretty print Property. Doesn't print valid HDL, but can be used for -- debugging purposes. pprProperty :: Property dom -> Declaration -- | Type and instance definitions for Rewrite modules module Clash.Rewrite.Types -- | State used by the inspection mechanism for recording rewrite steps. data RewriteStep RewriteStep :: Context -> String -> String -> Term -> Term -> RewriteStep -- | current context [t_ctx] :: RewriteStep -> Context -- | Name of the transformation [t_name] :: RewriteStep -> String -- | Name of the current binder [t_bndrS] :: RewriteStep -> String -- | Term before apply [t_before] :: RewriteStep -> Term -- | Term after apply [t_after] :: RewriteStep -> Term -- | State of a rewriting session data RewriteState extra RewriteState :: {-# UNPACK #-} !Word -> HashMap Text Word -> !BindingMap -> !Supply -> (Id, SrcSpan) -> {-# UNPACK #-} !Int -> PrimHeap -> VarEnv Bool -> !extra -> RewriteState extra -- | Total number of applied transformations [_transformCounter] :: RewriteState extra -> {-# UNPACK #-} !Word -- | Map that tracks how many times each transformation is applied [_transformCounters] :: RewriteState extra -> HashMap Text Word -- | Global binders [_bindings] :: RewriteState extra -> !BindingMap -- | Supply of unique numbers [_uniqSupply] :: RewriteState extra -> !Supply -- | Function which is currently normalized [_curFun] :: RewriteState extra -> (Id, SrcSpan) -- | Used for Fresh [_nameCounter] :: RewriteState extra -> {-# UNPACK #-} !Int -- | Used as a heap for compile-time evaluation of primitives that live in -- I/O [_globalHeap] :: RewriteState extra -> PrimHeap -- | Map telling whether a binder's definition is work-free [_workFreeBinders] :: RewriteState extra -> VarEnv Bool -- | Additional state [_extra] :: RewriteState extra -> !extra workFreeBinders :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) (VarEnv Bool) uniqSupply :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) Supply transformCounters :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) (HashMap Text Word) transformCounter :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) Word nameCounter :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) Int globalHeap :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) PrimHeap extra :: forall extra_a4mQI extra_a4mYu. Lens (RewriteState extra_a4mQI) (RewriteState extra_a4mYu) extra_a4mQI extra_a4mYu curFun :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) (Id, SrcSpan) bindings :: forall extra_a4mQI. Lens' (RewriteState extra_a4mQI) BindingMap -- | Read-only environment of a rewriting session data RewriteEnv RewriteEnv :: ClashEnv -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Evaluator -> Evaluator -> VarSet -> RewriteEnv -- | The global environment of the compiler [_clashEnv] :: RewriteEnv -> ClashEnv -- | Hardcode Type -> FilteredHWType translator [_typeTranslator] :: RewriteEnv -> CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType)) -- | Hardcoded evaluator for partial evaluation [_peEvaluator] :: RewriteEnv -> Evaluator -- | Hardcoded evaluator for WHNF (old evaluator) [_evaluator] :: RewriteEnv -> Evaluator -- | Functions that are considered TopEntities [_topEntities] :: RewriteEnv -> VarSet typeTranslator :: Lens' RewriteEnv (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) topEntities :: Lens' RewriteEnv VarSet peEvaluator :: Lens' RewriteEnv Evaluator evaluator :: Lens' RewriteEnv Evaluator clashEnv :: Lens' RewriteEnv ClashEnv debugOpts :: Getter RewriteEnv DebugOpts aggressiveXOpt :: Getter RewriteEnv Bool tcCache :: Getter RewriteEnv TyConMap tupleTcCache :: Getter RewriteEnv (IntMap TyConName) customReprs :: Getter RewriteEnv CustomReprs fuelLimit :: Getter RewriteEnv Word primitives :: Getter RewriteEnv CompiledPrimMap inlineLimit :: Getter RewriteEnv Int inlineFunctionLimit :: Getter RewriteEnv Word inlineConstantLimit :: Getter RewriteEnv Word inlineWFCacheLimit :: Getter RewriteEnv Word newInlineStrategy :: Getter RewriteEnv Bool specializationLimit :: Getter RewriteEnv Int normalizeUltra :: Getter RewriteEnv Bool -- | Monad that keeps track how many transformations have been applied and -- can generate fresh variables and unique identifiers. In addition, it -- keeps track if a transformation/rewrite has been successfully applied. newtype RewriteMonad extra a R :: RWST RewriteEnv Any (RewriteState extra) IO a -> RewriteMonad extra a [unR] :: RewriteMonad extra a -> RWST RewriteEnv Any (RewriteState extra) IO a -- | Run the computation in the RewriteMonad runR :: RewriteMonad extra a -> RewriteEnv -> RewriteState extra -> IO (a, RewriteState extra, Any) censor :: (Any -> Any) -> RewriteMonad extra a -> RewriteMonad extra a data TransformContext TransformContext :: !InScopeSet -> Context -> TransformContext [tfInScope] :: TransformContext -> !InScopeSet [tfContext] :: TransformContext -> Context -- | Monadic action that transforms a term given a certain context type Transform m = TransformContext -> Term -> m Term -- | A Transform action in the context of the RewriteMonad type Rewrite extra = Transform (RewriteMonad extra) instance Control.Monad.Fix.MonadFix (Clash.Rewrite.Types.RewriteMonad extra) instance GHC.Base.Monad (Clash.Rewrite.Types.RewriteMonad extra) instance GHC.Base.Functor (Clash.Rewrite.Types.RewriteMonad extra) instance GHC.Base.Applicative (Clash.Rewrite.Types.RewriteMonad extra) instance Control.Monad.State.Class.MonadState (Clash.Rewrite.Types.RewriteState extra) (Clash.Rewrite.Types.RewriteMonad extra) instance Control.Monad.Writer.Class.MonadWriter Data.Semigroup.Internal.Any (Clash.Rewrite.Types.RewriteMonad extra) instance Control.Monad.Reader.Class.MonadReader Clash.Rewrite.Types.RewriteEnv (Clash.Rewrite.Types.RewriteMonad extra) instance Clash.Util.MonadUnique (Clash.Rewrite.Types.RewriteMonad extra) instance Data.Binary.Class.Binary Clash.Rewrite.Types.RewriteStep instance Control.DeepSeq.NFData Clash.Rewrite.Types.RewriteStep instance GHC.Generics.Generic Clash.Rewrite.Types.RewriteStep instance GHC.Show.Show Clash.Rewrite.Types.RewriteStep -- | Rewriting combinators and traversals module Clash.Rewrite.Combinators -- | Apply a transformation on the subtrees of an term allR :: forall m. Monad m => Transform m -> Transform m -- | Only apply the second transformation if the first one succeeds. (!->) :: Rewrite m -> Rewrite m -> Rewrite m infixr 5 !-> -- | Only apply the second transformation if the first one fails. (>-!) :: Rewrite m -> Rewrite m -> Rewrite m infixr 5 >-! -- | Apply two transformations in succession, and perform a deepseq in -- between. (>-!->) :: Monad m => Transform m -> Transform m -> Transform m infixr 6 >-!-> -- | Apply two transformations in succession (>->) :: Monad m => Transform m -> Transform m -> Transform m infixr 6 >-> -- | Apply a transformation in a bottomup traversal bottomupR :: Monad m => Transform m -> Transform m -- | Keep applying a transformation until it fails. repeatR :: Rewrite m -> Rewrite m -- | Apply a transformation in a topdown traversal topdownR :: Rewrite m -> Rewrite m -- | Types used in Normalize modules module Clash.Normalize.Types -- | State of the NormalizeMonad data NormalizeState NormalizeState :: BindingMap -> Map (Id, Int, Either Term Type) Id -> VarEnv Int -> VarEnv (VarEnv Int) -> Map Text (Set Int) -> VarEnv Bool -> NormalizeState -- | Global binders [_normalized] :: NormalizeState -> BindingMap -- | Cache of previously specialized functions: -- -- [_specialisationCache] :: NormalizeState -> Map (Id, Int, Either Term Type) Id -- | Cache of how many times a function was specialized [_specialisationHistory] :: NormalizeState -> VarEnv Int -- | Cache of function where inlining took place: -- -- [_inlineHistory] :: NormalizeState -> VarEnv (VarEnv Int) -- | Cache for looking up constantness of blackbox arguments [_primitiveArgs] :: NormalizeState -> Map Text (Set Int) -- | Map telling whether a components is recursively defined. -- -- NB: there are only no mutually-recursive component, only -- self-recursive ones. [_recursiveComponents] :: NormalizeState -> VarEnv Bool specialisationHistory :: Lens' NormalizeState (VarEnv Int) specialisationCache :: Lens' NormalizeState (Map (Id, Int, Either Term Type) Id) recursiveComponents :: Lens' NormalizeState (VarEnv Bool) primitiveArgs :: Lens' NormalizeState (Map Text (Set Int)) normalized :: Lens' NormalizeState BindingMap inlineHistory :: Lens' NormalizeState (VarEnv (VarEnv Int)) -- | State monad that stores specialisation and inlining information type NormalizeMonad = State NormalizeState -- | RewriteSession with extra Normalisation information type NormalizeSession = RewriteMonad NormalizeState -- | A Transform action in the context of the RewriteMonad -- and NormalizeMonad type NormRewrite = Rewrite NormalizeState -- | Description of a Term in terms of the type "components" the -- Term has. -- -- Is used as a performance/size metric. data TermClassification TermClassification :: !Int -> !Int -> !Int -> TermClassification -- | Number of functions [_function] :: TermClassification -> !Int -- | Number of primitives [_primitive] :: TermClassification -> !Int -- | Number of selections/multiplexers [_selection] :: TermClassification -> !Int selection :: Lens' TermClassification Int primitive :: Lens' TermClassification Int function :: Lens' TermClassification Int instance GHC.Show.Show Clash.Normalize.Types.TermClassification -- | Blackbox implementations for "Clash.Sized.Internal.*.toInteger#". module Clash.Primitives.Sized.ToInteger bvToIntegerVerilog :: BlackBoxFunction bvToIntegerVHDL :: BlackBoxFunction indexToIntegerVerilog :: BlackBoxFunction indexToIntegerVHDL :: BlackBoxFunction signedToIntegerVerilog :: BlackBoxFunction signedToIntegerVHDL :: BlackBoxFunction unsignedToIntegerVerilog :: BlackBoxFunction unsignedToIntegerVHDL :: BlackBoxFunction -- | VHDL Blackbox implementations for -- "Clash.Sized.Internal.Signed.toInteger#". module Clash.Primitives.Sized.Signed fromIntegerTFvhdl :: TemplateFunction -- | Blackbox functions for primitives in the Clash.Magic module. module Clash.Primitives.Magic clashCompileErrorBBF :: HasCallStack => BlackBoxFunction -- | Blackbox generation for literal data constructors. (System)Verilog -- only! module Clash.Primitives.GHC.Literal assign :: Element -> [Element] -> [Element] signed :: Element -> [Element] signedLiteral :: Int -> Integer -> Element unsigned :: Element -> [Element] unsignedLiteral :: Int -> Integer -> Element -- | Constructs "clean" literals. literalTF :: Text -> (Bool -> [Either Term Type] -> Int -> (BlackBoxMeta, BlackBox)) -> BlackBoxFunction -- | Blackbox generation for GHC.Word.WordX# data constructors. -- (System)Verilog only! module Clash.Primitives.GHC.Word -- | Template function for Word8,Word16,.. Constructs "clean" literals. -- This function generates valid (System)Verilog only! wordTF :: BlackBoxFunction -- | Blackbox generation for GHC.Int.IntX# data constructors. -- (System)Verilog only! module Clash.Primitives.GHC.Int -- | Template function for Int8,Int16,.. Constructs "clean" literals. intTF :: BlackBoxFunction module Clash.Netlist.Id.Verilog keywords :: HashSet Text isKeyword :: Text -> Bool parseBasic :: Text -> Bool parseBasic' :: Text -> Bool parseExtended :: Text -> Bool toBasic' :: Text -> Text toBasic :: Text -> Text isBasicChar :: Char -> Bool unextend :: Text -> Text toText :: IdentifierType -> Text -> Text module Clash.Netlist.Id.VHDL -- | Identifiers which are imported from the following: -- -- use IEEE.STD_LOGIC_1164.ALL; use IEEE.NUMERIC_STD.ALL; use -- IEEE.MATH_REAL.ALL; use std.textio.all; -- -- Clash should not use these identifiers, as it can lead to errors when -- interfacing with an EDA tool. -- -- See https://github.com/clash-lang/clash-compiler/issues/1439. importedNames :: [Text] -- | Time units: are added to reservedWords as simulators trip -- over signals named after them. timeUnits :: [Text] keywords :: HashSet Text isKeyword :: Text -> Bool parseBasic :: Text -> Bool parseBasic' :: Text -> Bool parseExtended :: Text -> Bool toBasic :: Text -> Text isBasicChar :: Char -> Bool stripDollarPrefixes :: Text -> Text unextend :: Text -> Text toText :: IdentifierType -> Text -> Text module Clash.Netlist.Id.SystemVerilog keywords :: HashSet Text isKeyword :: Text -> Bool parseBasic :: Text -> Bool parseExtended :: Text -> Bool toBasic :: Text -> Text unextend :: Text -> Text toText :: IdentifierType -> Text -> Text module Clash.Netlist.Id.Internal -- | Return identifier with highest extension for given identifier. See -- is_freshCache for more information. -- -- For example, if the FreshCache contains "foo_12_25" and the given -- identifier is "foo_12_13" this function would return "Just 25". In -- this case, "foo_12_26" is guaranteed to be a fresh identifier. lookupFreshCache# :: FreshCache -> Identifier -> Maybe Word -- | Add new identifier to FreshCache, see is_freshCache for more -- information. updateFreshCache# :: HasCallStack => FreshCache -> Identifier -> FreshCache -- | Adds identifier at verbatim if its basename hasn't been used before. -- Otherwise it will return the first free identifier. mkUnique# :: HasCallStack => IdentifierSet -> Identifier -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of add add# :: HasCallStack => IdentifierSet -> Identifier -> IdentifierSet -- | Non-monadic, internal version of addMultiple addMultiple# :: (HasCallStack, Foldable t) => IdentifierSet -> t Identifier -> IdentifierSet -- | Non-monadic, internal version of addRaw addRaw# :: HasCallStack => IdentifierSet -> Text -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of make make# :: HasCallStack => IdentifierSet -> Text -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of makeBasic makeBasic# :: HasCallStack => IdentifierSet -> Text -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of makeBasicOr makeBasicOr# :: HasCallStack => IdentifierSet -> Text -> Text -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of next next# :: HasCallStack => IdentifierSet -> Identifier -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of nextN nextN# :: HasCallStack => Int -> IdentifierSet -> Identifier -> (IdentifierSet, [Identifier]) -- | Non-monadic, internal version of deepenN deepenN# :: HasCallStack => Int -> IdentifierSet -> Identifier -> (IdentifierSet, [Identifier]) -- | Non-monadic, internal version of deepen deepen# :: HasCallStack => IdentifierSet -> Identifier -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of suffix suffix# :: HasCallStack => IdentifierSet -> Identifier -> Text -> (IdentifierSet, Identifier) -- | Non-monadic, internal version of prefix prefix# :: HasCallStack => IdentifierSet -> Identifier -> Text -> (IdentifierSet, Identifier) toText# :: Identifier -> Text -- | Is given string a valid basic identifier in given HDL? isBasic# :: HDL -> Text -> Bool -- | Is given string a valid extended identifier in given HDL? isExtended# :: HDL -> Text -> Bool -- | Convert given string to ASCII. Retains all printable ASCII. All other -- characters are thrown out. toPrintableAscii# :: Text -> Text -- | Split identifiers such as "foo_1_2" into ("foo", [2, 1]). parseIdentifier# :: Text -> (Text, [Word]) make## :: HasCallStack => HDL -> Text -> Identifier toBasicId# :: HDL -> PreserveCase -> Text -> Text -- | Convert a Clash Core Id to an identifier. Makes sure returned -- identifier is unique. fromCoreId# :: IdentifierSet -> Id -> (IdentifierSet, Identifier) instance Prettyprinter.Internal.Pretty Clash.Netlist.Types.Identifier -- | Transform/format a Netlist Identifier so that it is acceptable as a -- HDL identifier module Clash.Netlist.Id -- | A collection of unique identifiers. Allows for fast fresh identifier -- generation. -- -- NB: use the functions in Clash.Netlist.Id. Don't use the -- constructor directly. data IdentifierSet -- | An IdentifierSetMonad supports unique name generation for Clash -- Netlist class Monad m => IdentifierSetMonad m identifierSetM :: IdentifierSetMonad m => (IdentifierSet -> IdentifierSet) -> m IdentifierSet -- | Structures that hold an IdentifierSet class HasIdentifierSet s identifierSet :: HasIdentifierSet s => Lens' s IdentifierSet -- | Identifier set without identifiers emptyIdentifierSet :: Bool -> PreserveCase -> HDL -> IdentifierSet -- | Make a identifier set filled with given identifiers makeSet :: Bool -> PreserveCase -> HDL -> HashSet Identifier -> IdentifierSet -- | Remove all identifiers from a set clearSet :: IdentifierSet -> IdentifierSet -- | HDL identifier. Consists of a base name and a number of extensions. An -- identifier with a base name of "foo" and a list of extensions [1, 2] -- will be rendered as "foo_1_2". -- -- Note: The Eq instance of Identifier is case insensitive! E.g., -- two identifiers with base names fooBar and FoObAR -- are considered the same. However, identifiers are stored case -- preserving. This means Clash won't generate two identifiers with -- differing case, but it will try to keep capitalization. -- -- The goal of this data structure is to greatly simplify how Clash deals -- with identifiers internally. Any Identifier should be trivially -- printable to any HDL. -- -- NB: use the functions in Clash.Netlist.Id. Don't use -- these constructors directly. data Identifier data IdentifierType -- | A basic identifier: does not have to be escaped in order to be a valid -- identifier in HDL. Basic :: IdentifierType -- | An extended identifier: has to be escaped, wrapped, or otherwise -- postprocessed before writhing it to HDL. Extended :: IdentifierType -- | Like addRaw, unsafeMake creates an identifier that will -- be spliced at verbatim in the HDL. As opposed to addRaw, the -- resulting Identifier might be generated at a later point as it is NOT -- added to an IdentifierSet. unsafeMake :: HasCallStack => Text -> Identifier -- | Like 'fromCoreId, unsafeFromCoreId creates an identifier that -- will be spliced at verbatim in the HDL. As opposed to -- fromCoreId, the resulting Identifier might be generated at a -- later point as it is NOT added to an IdentifierSet. unsafeFromCoreId :: HasCallStack => Id -> Identifier -- | Convert an identifier to string toText :: Identifier -> Text -- | Convert an identifier to string toLazyText :: Identifier -> Text toList :: IdentifierSet -> [Identifier] -- | Union of two identifier sets. Errors if given sets have been made with -- different options enabled. union :: HasCallStack => IdentifierSet -> IdentifierSet -> IdentifierSet -- | Make unique identifier based on given string make :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier -- | Make unique basic identifier based on given string makeBasic :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier -- | Make unique basic identifier based on given string. If given string -- can't be converted to a basic identifier (i.e., it would yield an -- empty string) the alternative name is used. makeBasicOr :: (HasCallStack, IdentifierSetMonad m) => Text -> Text -> m Identifier -- | Make unique identifier. Uses makeBasic if first argument is -- Basic makeAs :: (HasCallStack, IdentifierSetMonad m) => IdentifierType -> Text -> m Identifier -- | Add an identifier to an IdentifierSet add :: HasCallStack => IdentifierSetMonad m => Identifier -> m () -- | Add identifiers to an IdentifierSet addMultiple :: (HasCallStack, IdentifierSetMonad m, Foldable t) => t Identifier -> m () -- | Add a string as is to an IdentifierSet. Should only be used for -- identifiers that should be spliced at verbatim in HDL, such as port -- names. It's sanitized version will still be added to the identifier -- set, to prevent freshly generated variables clashing with the raw one. addRaw :: (HasCallStack, IdentifierSetMonad m) => Text -> m Identifier -- | Given identifier "foo_1_2" return "foo_1_2_0". If "foo_1_2_0" is -- already a member of the given set, return "foo_1_2_1" instead, etc. -- Identifier returned is guaranteed to be unique. deepen :: (HasCallStack, IdentifierSetMonad m) => Identifier -> m Identifier -- | Same as deepenM, but returns N fresh identifiers. For -- example, given "foo_23" is would return "foo_23_0", "foo_23_1", ... deepenN :: (HasCallStack, IdentifierSetMonad m) => Int -> Identifier -> m [Identifier] -- | Given identifier "foo_1_2" return "foo_1_3". If "foo_1_3" is already a -- member of the given set, return "foo_1_4" instead, etc. Identifier -- returned is guaranteed to be unique. next :: (HasCallStack, IdentifierSetMonad m) => Identifier -> m Identifier -- | Same as nextM, but returns N fresh identifiers nextN :: (HasCallStack, IdentifierSetMonad m) => Int -> Identifier -> m [Identifier] -- | Given identifier "foo_1_2" and a prefix "bar", return an identifier -- called "bar_foo". Identifier returned is guaranteed to be unique -- according to the rules of nextIdentifier. prefix :: (HasCallStack, IdentifierSetMonad m) => Identifier -> Text -> m Identifier -- | Given identifier "foo_1_2" and a suffix "bar", return an identifier -- called "foo_bar". Identifier returned is guaranteed to be unique -- according to the rules of nextIdentifier. suffix :: (HasCallStack, IdentifierSetMonad m) => Identifier -> Text -> m Identifier -- | Convert a Clash Core Id to an identifier. Makes sure returned -- identifier is unique. fromCoreId :: (HasCallStack, IdentifierSetMonad m) => Id -> m Identifier stripDollarPrefixes :: Text -> Text toBasicId# :: HDL -> PreserveCase -> Text -> Text -- | Is given string a valid basic identifier in given HDL? isBasic# :: HDL -> Text -> Bool -- | Is given string a valid extended identifier in given HDL? isExtended# :: HDL -> Text -> Bool -- | Houses internal BitRepresentation code which cannot be housed in -- clash-prelude due to its dependencies. module Clash.Annotations.BitRepresentation.ClashLib coreToType' :: Type -> Either String Type' -- | Converts a list of BitRepresentation.Bits to their Netlist -- counterpart. bitsToBits :: [Bit] -> [Bit] -- | Utilities for converting Core Type/Term to Netlist datatypes module Clash.Netlist.Util hmFindWithDefault :: (Eq k, Hashable k) => v -> k -> HashMap k v -> v -- | Generate a simple port_name expression. See: -- -- -- https://www.hdlworks.com/hdl_corner/vhdl_ref/VHDLContents/PortMap.htm -- -- This function will simply make the left part of a single port map, -- e.g. Rst in: -- -- Rst => Reset -- -- If you need more complex constructions, e.g. -- -- Q(3 downto 1) -- -- you can build an Expr manually. instPort :: Text -> Expr -- | Throw away information indicating which constructor fields were -- filtered due to being void. stripFiltered :: FilteredHWType -> HWType -- | Strip as many Void layers as possible. Might still return a -- Void if the void doesn't contain a hwtype. stripVoid :: HWType -> HWType flattenFiltered :: FilteredHWType -> [[Bool]] isVoidMaybe :: Bool -> Maybe HWType -> Bool -- | Determines if type is a zero-width construct ("void") isVoid :: HWType -> Bool -- | Same as isVoid, but on FilteredHWType instead of -- HWType isFilteredVoid :: FilteredHWType -> Bool squashLets :: Term -> Term -- | Split a normalized term into: a list of arguments, a list of -- let-bindings, and a variable reference that is the body of the -- let-binding. Returns a String containing the error if the term was not -- in a normalized form. splitNormalized :: TyConMap -> Term -> Either String ([Id], [LetBinding], Id) -- | Converts a Core type to a HWType given a function that translates -- certain builtin types. Errors if the Core type is not translatable. unsafeCoreTypeToHWType :: SrcSpan -> String -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> CustomReprs -> TyConMap -> Type -> State HWMap FilteredHWType -- | Same as unsafeCoreTypeToHWTypeM, but discards void filter -- information unsafeCoreTypeToHWTypeM' :: String -> Type -> NetlistMonad HWType -- | Converts a Core type to a HWType within the NetlistMonad; errors on -- failure unsafeCoreTypeToHWTypeM :: String -> Type -> NetlistMonad FilteredHWType -- | Same as coreTypeToHWTypeM, but discards void filter -- information coreTypeToHWTypeM' :: Type -> NetlistMonad (Maybe HWType) -- | Converts a Core type to a HWType within the NetlistMonad; -- Nothing on failure coreTypeToHWTypeM :: Type -> NetlistMonad (Maybe FilteredHWType) -- | Constructs error message for unexpected projections out of a type -- annotated with a custom bit representation. unexpectedProjectionErrorMsg :: DataRepr' -> Int -> Int -> String -- | Helper function of maybeConvertToCustomRepr convertToCustomRepr :: HasCallStack => CustomReprs -> DataRepr' -> HWType -> HWType -- | Given a map containing custom bit representation, a type, and the same -- type represented as HWType, convert the HWType to a CustomSP/CustomSum -- if it has a custom bit representation. maybeConvertToCustomRepr :: CustomReprs -> Type -> FilteredHWType -> FilteredHWType -- | Same as coreTypeToHWType, but discards void filter -- information coreTypeToHWType' :: (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> CustomReprs -> TyConMap -> Type -> State HWMap (Either String HWType) -- | Converts a Core type to a HWType given a function that translates -- certain builtin types. Returns a string containing the error message -- when the Core type is not translatable. coreTypeToHWType :: (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> CustomReprs -> TyConMap -> Type -> State HWMap (Either String FilteredHWType) -- | Generates original indices in list before filtering, given a list of -- removed indices. -- --
--   >>> originalIndices [False, False, True, False]
--   [0,1,3]
--   
originalIndices :: [Bool] -> [Int] -- | Converts an algebraic Core type (split into a TyCon and its argument) -- to a HWType. mkADT :: (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> CustomReprs -> TyConMap -> String -> TyConName -> [Type] -> ExceptT String (State HWMap) FilteredHWType -- | Determine whether a data constructor has unconstrained existential -- type variables, i.e. those that cannot be inferred by the (potential) -- constraints between the existential type variables and universal type -- variables. -- -- So here we have an example of a constrained existential: -- -- data Vec :: Nat -> Type -> Type where Nil :: Vec 0 a Cons :: -- forall m . (n ~ m + 1) => a -> Vec m a -> Vec n a -- -- where we can generate a type for m when we know n -- (by doing `n-1`). -- -- And here is an example of an unconstrained existential: -- -- data SomeSNat where where SomeSNat :: forall m . SNat m -> SomeSNat -- -- where there is no way to generate a type for m from any -- context. -- -- So why do we care? Because terms need to be completely monomorphic in -- order to be translated to circuits. And having a topEntity -- lambda-bound variable with an unconstrained existential type prevents -- us from achieving a fully monomorphic term. hasUnconstrainedExistential :: TyConMap -> DataCon -> Bool -- | Simple check if a TyCon is recursively defined. -- -- Note [Look through type families in recursivity check] -- -- Consider: -- --
--   data SList :: [Type] -> Type where
--     SNil  :: SList []
--     CSons :: a -> Sing (as :: [k]) -> SList (a:as)
--   
--   type family Sing [a] = SList [a]
--   
-- -- Without looking through type families, we would think that -- SList is not recursive. This lead to issue #1921 isRecursiveTy :: TyConMap -> TyConName -> Bool -- | Determines if a Core type is translatable to a HWType given a function -- that translates certain builtin types. representableType :: (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> CustomReprs -> Bool -> TyConMap -> Type -> Bool -- | Determines the bitsize of a type. For types that don't get turned into -- real values in hardware (string, integer) the size is 0. typeSize :: HWType -> Int -- | Determines the bitsize of the constructor of a type conSize :: HWType -> Int -- | Gives the HWType corresponding to a term. Returns an error if the term -- has a Core type that is not translatable to a HWType. termHWType :: String -> Term -> NetlistMonad HWType -- | Gives the HWType corresponding to a term. Returns Nothing if -- the term has a Core type that is not translatable to a HWType. termHWTypeM :: Term -> NetlistMonad (Maybe FilteredHWType) isBiSignalIn :: HWType -> Bool isBiSignalOut :: HWType -> Bool containsBiSignalIn :: HWType -> Bool -- | Uniquely rename all the variables and their references in a normalized -- term mkUniqueNormalized :: HasCallStack => InScopeSet -> Maybe (Maybe TopEntity) -> ([Id], [LetBinding], Id) -> NetlistMonad ([Bool], [(Identifier, HWType)], [Declaration], [(Identifier, HWType)], [Declaration], [LetBinding], Maybe Id) -- | Produce a Just when predicate is True, else Nothing orNothing :: Bool -> a -> Maybe a -- | Set the name of the binder if the given term is a blackbox requesting -- a specific name for the result binder. It might return multiple names -- in case of a multi result primitive. renameBinder :: (Id, Term) -> NetlistMonad [(Id, Id)] -- | Render a blackbox given its context. Renders _just_ the blackbox, not -- any corresponding includes, libraries, and so forth. evalBlackBox :: HasCallStack => SomeBackend -> BlackBoxContext -> BlackBox -> Text mkUniqueArguments :: Subst -> Maybe (ExpandedTopEntity Identifier) -> [Id] -> NetlistMonad ([Bool], [(Identifier, HWType)], [Declaration], Subst) mkUniqueResult :: Subst -> Maybe (ExpandedTopEntity Identifier) -> Id -> NetlistMonad (Maybe ([(Identifier, HWType)], [Declaration], Id, Subst)) -- | Same as idToPort, but * Throws an error if the port is a composite -- type with a BiSignalIn idToInPort :: Id -> NetlistMonad (Maybe (Identifier, HWType)) -- | Same as idToPort, but: * Throws an error if port is of type BiSignalIn idToOutPort :: Id -> NetlistMonad (Maybe (Identifier, HWType)) idToPort :: Id -> NetlistMonad (Maybe (Identifier, HWType)) setRepName :: Text -> Name a -> Name a -- | Make a set of IDs unique; also returns a substitution from old ID to -- new updated unique ID. mkUnique :: Subst -> [Id] -> NetlistMonad ([Id], Subst) -- | Preserve the complete state before running an action, and restore it -- afterwards. preserveState :: NetlistMonad a -> NetlistMonad a -- | Preserve the Netlist -- _curCompNm,_seenIds,_usageMap when executing a -- monadic action preserveVarEnv :: NetlistMonad a -> NetlistMonad a dcToLiteral :: HWType -> Int -> Literal extendPorts :: [PortName] -> [Maybe PortName] -- | Prefix given string before portnames except when this string is -- empty. prefixParent :: String -> PortName -> PortName -- | Make a new signal which is assigned with an initial value. This should -- be used in place of NetDecl directly, as it also updates the usage map -- to include the new identifier and usage. mkInit :: HasCallStack => DeclarationType -> Usage -> Identifier -> HWType -> Expr -> NetlistMonad [Declaration] -- | Determine if for the specified HDL, the type of assignment wanted can -- be performed on a signal which has been assigned another way. This -- identifies when a new intermediary signal needs to be created, e.g. -- -- canUse :: HDL -> Usage -> Usage -> Bool declareUse :: Usage -> Identifier -> NetlistMonad () -- | Like declareUse, but will throw an exception if we run into a -- name collision. declareUseOnce :: HasUsageMap s => Usage -> Identifier -> State s () -- | Declare uses which occur as a result of a component being -- instantiated, for example the following design (verilog) -- --
--   module f ( input p; output reg r ) ... endmodule
--   
--   module top ( ... )
--     ...
--     f f_inst ( .p(p), .r(foo));
--     ...
--   endmodule
--   
-- -- would declare a usage of foo, since it is assigned by f_inst. declareInstUses :: [(Expr, PortDirection, HWType, Expr)] -> NetlistMonad () assignmentWith :: HasCallStack => (Identifier -> Declaration) -> Usage -> Identifier -> NetlistMonad Declaration -- | Attempt to continuously assign an expression to the given identifier. -- If the assignment is not allowed for the backend being used, a new -- signal is created which allows the assignment. The identifier which -- holds the result of the assignment is returned alongside the new -- declarations. -- -- This function assumes the identifier being assigned is already -- declared. If the identifier is not in the usage map then an error is -- thrown. contAssign :: HasCallStack => Identifier -> Expr -> NetlistMonad Declaration procAssign :: HasCallStack => Blocking -> Identifier -> Expr -> NetlistMonad Declaration condAssign :: Identifier -> HWType -> Expr -> HWType -> [(Maybe Literal, Expr)] -> NetlistMonad Declaration -- | See toPrimitiveType / fromPrimitiveType convPrimitiveType :: HWType -> a -> NetlistMonad a -> NetlistMonad a -- | Top entities only expose primitive types or types that don't need -- explicit conversion to a primitive type (i.e., no types from the -- _types module). This function converts from a custom type to -- a primitive type if needed. -- -- See HWKind for more info on primitive type kinds. toPrimitiveType :: Identifier -> HWType -> NetlistMonad ([Declaration], Identifier, Expr, HWType) -- | Top entities only expose primitive types or types that don't need -- explicit conversion to a primitive type (i.e., no types from the -- _types module). This function converts from a primitive type -- to a custom type if needed. -- -- See HWKind for more info on primitive type kinds. fromPrimitiveType :: Identifier -> HWType -> NetlistMonad ([Declaration], Identifier, Expr, HWType) -- | Create port names for the declaration of a top entity. For -- instantiation see mkTopInstInput. mkTopInput :: ExpandedPortName Identifier -> NetlistMonad ([(Identifier, HWType)], [Declaration], Expr, Identifier) portProductError :: String -> HWType -> ExpandedPortName Identifier -> a -- | Create a Vector chain for a list of Identifiers mkVectorChain :: Int -> HWType -> [Expr] -> Expr -- | Create a RTree chain for a list of Identifiers mkRTreeChain :: Int -> HWType -> [Expr] -> Expr genComponentName :: Bool -> Maybe Text -> Id -> Text genTopName :: IdentifierSetMonad m => Maybe Text -> TopEntity -> m Identifier -- | Strips one or more layers of attributes from a HWType; stops at first -- non-Annotated. Accumulates all attributes of nested annotations. stripAttributes :: HWType -> ([Attr Text], HWType) -- | Create output port names for the declaration of a top entity. For -- instantiation see mkTopInstOutput. mkTopOutput :: ExpandedPortName Identifier -> NetlistMonad ([(Identifier, HWType)], [Declaration], Identifier) mkTopCompDecl :: Maybe Text -> [Attr Text] -> Identifier -> Identifier -> [(Expr, HWType, Expr)] -> [InstancePort] -> [InstancePort] -> Declaration -- | Instantiate a TopEntity, and add the proper type-conversions where -- needed mkTopUnWrapper :: Id -> ExpandedTopEntity Identifier -> (Identifier, HWType) -> [(Expr, HWType)] -> [Declaration] -> NetlistMonad [Declaration] data InstancePort InstancePort :: Identifier -> HWType -> InstancePort -- | Identifier to assign. Top entities are instantiated using positional -- arguments, so this doesn't hold a port name. [ip_id] :: InstancePort -> Identifier -- | Type assigned to port [ip_type] :: InstancePort -> HWType -- | Generate input port(s) associated with a single argument for an -- instantiation of a top entity. This function composes the input ports -- into a single signal and returns its name. mkTopInstInput :: ExpandedPortName Identifier -> NetlistMonad ([InstancePort], [Declaration], Identifier) -- | Consider the following type signature: -- --
--   f :: Signal dom (Vec 6 A) `Annotate` Attr "keep"
--     -> Signal dom (Vec 6 B)
--   
-- -- What does the annotation mean, considering that Clash will split these -- vectors into multiple in- and output ports? Should we apply the -- annotation to all individual ports? How would we handle pin mappings? -- For now, we simply throw an error. This is a helper function to do so. throwAnnotatedSplitError :: String -> String -> NetlistMonad a -- | Generate output port(s) for an instantiation of a top entity. This -- function combines all output ports into a signal identifier and -- returns its name. mkTopInstOutput :: HasCallStack => ExpandedPortName Identifier -> NetlistMonad ([InstancePort], [Declaration], Identifier) -- | Try to merge nested modifiers into a single modifier, needed by the -- VHDL and SystemVerilog backend. nestM :: Modifier -> Modifier -> Maybe Modifier -- | Determines if any type variables (exts) are bound in any of the given -- type or term variables (tms). It's currently only used to detect bound -- existentials, hence the name. bindsExistentials :: [TyVar] -> [Var a] -> Bool iteAlts :: HWType -> [Alt] -> Maybe (Term, Term) -- | Run a NetlistMonad computation in the context of the given source -- ticks and name modifier ticks withTicks :: [TickInfo] -> ([Declaration] -> NetlistMonad a) -> NetlistMonad a -- | Add the pre- and suffix names in the current environment to the given -- identifier affixName :: Text -> NetlistMonad Text -- | Errors expandTopEntity might yield data ExpandError -- | Synthesis attributes are not supported on PortProducts AttrError :: [Attr Text] -> ExpandError -- | Something was annotated as being a PortProduct, but wasn't one PortProductError :: PortName -> HWType -> ExpandError -- | Same as expandTopEntity, but also adds identifiers to the -- identifier set of the monad. expandTopEntityOrErrM :: HasCallStack => [(Maybe Id, FilteredHWType)] -> (Maybe Id, FilteredHWType) -> Maybe TopEntity -> NetlistMonad (ExpandedTopEntity Identifier) -- | Take a top entity and expand its port names. I.e., make sure -- that every port that should be generated in the HDL is part of the -- data structure. It works on FilteredHWType in order to generate -- stable port names. expandTopEntity :: HasCallStack => [(Maybe Id, FilteredHWType)] -> (Maybe Id, FilteredHWType) -> Maybe TopEntity -> Either ExpandError (ExpandedTopEntity (Either Text Text)) -- | Convert a Core Literal to a Netlist Literal mkLiteral :: Int -> Literal -> Expr instance GHC.Show.Show Clash.Netlist.Util.InstancePort -- | Utilities for rewriting: e.g. inlining, specialisation, etc. module Clash.Rewrite.Util -- | Lift an action working in the _extra state to the -- RewriteMonad zoomExtra :: State extra a -> RewriteMonad extra a -- | Some transformations might erroneously introduce shadowing. For -- example, a transformation might result in: -- -- let a = ... b = ... a = ... -- -- where the last a, shadows the first, while Clash assumes that -- this can't happen. This function finds those constructs and a list of -- found duplicates. findAccidentialShadows :: Term -> [[Id]] -- | Record if a transformation is successfully applied apply :: String -> Rewrite extra -> Rewrite extra applyDebug :: TransformContext -> String -> Term -> Bool -> Term -> RewriteMonad extra Term -- | Perform a transformation on a Term runRewrite :: String -> InScopeSet -> Rewrite extra -> Term -> RewriteMonad extra Term -- | Evaluate a RewriteSession to its inner monad. runRewriteSession :: RewriteEnv -> RewriteState extra -> RewriteMonad extra a -> IO a -- | Notify that a transformation has changed the expression setChanged :: RewriteMonad extra () -- | Identity function that additionally notifies that a transformation has -- changed the expression changed :: a -> RewriteMonad extra a closestLetBinder :: Context -> Maybe Id mkDerivedName :: TransformContext -> OccName -> TmName -- | Make a new binder and variable reference for a term mkTmBinderFor :: MonadUnique m => InScopeSet -> TyConMap -> Name a -> Term -> m Id -- | Make a new binder and variable reference for either a term or a type mkBinderFor :: MonadUnique m => InScopeSet -> TyConMap -> Name a -> Either Term Type -> m (Either Id TyVar) -- | Inline the binders in a let-binding that have a certain property inlineBinders :: (Term -> LetBinding -> RewriteMonad extra Bool) -> Rewrite extra -- | Determine whether a binder is a join-point created for a complex case -- expression. -- -- A join-point is when a local function only occurs in tail-call -- positions, and when it does, more than once. isJoinPointIn :: Id -> Term -> Bool -- | Count the number of (only) tail calls of a function in an expression. -- Nothing indicates that the function was used in a non-tail call -- position. tailCalls :: Id -> Term -> Maybe Int -- | Determines whether a function has the following shape: -- --
--   \(w :: Void) -> f a b c
--   
-- -- i.e. is a wrapper around a (partially) applied function f, -- where the introduced argument w is not used by f isVoidWrapper :: Term -> Bool -- | Inline the first set of binder into the second set of binders and into -- the body of the original let expression. substituteBinders :: InScopeSet -> [LetBinding] -> [LetBinding] -> Term -> ([LetBinding], ([LetBinding], Term)) -- | Lift the first set of binders to the level of global bindings, and -- substitute these lifted bindings into the second set of binders and -- the body of the original let expression. liftAndSubsituteBinders :: InScopeSet -> [LetBinding] -> [LetBinding] -> Term -> RewriteMonad extra ([LetBinding], Term) isFromInt :: Text -> Bool inlineOrLiftBinders :: (LetBinding -> RewriteMonad extra Bool) -> (Term -> LetBinding -> Bool) -> Rewrite extra -- | Create a global function for a Let-binding and return a Let-binding -- where the RHS is a reference to the new global function applied to the -- free variables of the original RHS liftBinding :: LetBinding -> RewriteMonad extra LetBinding -- | Make a global function for a name-term tuple mkFunction :: TmName -> SrcSpan -> InlineSpec -> Term -> RewriteMonad extra Id -- | Add a function to the set of global binders addGlobalBind :: TmName -> Type -> SrcSpan -> InlineSpec -> Term -> RewriteMonad extra () -- | Create a new name out of the given name, but with another unique. -- Resulting unique is guaranteed to not be in the given InScopeSet. cloneNameWithInScopeSet :: MonadUnique m => InScopeSet -> Name a -> m (Name a) -- | Create a new name out of the given name, but with another unique. -- Resulting unique is guaranteed to not be in the given BindingMap. cloneNameWithBindingMap :: MonadUnique m => BindingMap -> Name a -> m (Name a) -- | Determine if a term cannot be represented in hardware isUntranslatable :: Bool -> Term -> RewriteMonad extra Bool -- | Determine if a type cannot be represented in hardware isUntranslatableType :: Bool -> Type -> RewriteMonad extra Bool normalizeTermTypes :: TyConMap -> Term -> Term normalizeId :: TyConMap -> Id -> Id -- | Evaluate an expression to weak-head normal form (WHNF), and apply a -- transformation on the expression in WHNF. whnfRW :: Bool -> TransformContext -> Term -> Rewrite extra -> RewriteMonad extra Term -- | Binds variables on the PureHeap over the result of the rewrite -- -- To prevent unnecessary rewrites only do this when rewrite changed -- something. bindPureHeap :: TyConMap -> PureHeap -> Rewrite extra -> Rewrite extra -- | Remove unused binders in given let-binding. Returns Nothing if -- no unused binders were found. removeUnusedBinders :: Bind Term -> Term -> Maybe Term -- | The X-optimization transformation. module Clash.Normalize.Transformations.XOptimize -- | Remove all undefined alternatives from case expressions, replacing -- them with the value of another defined alternative. If there is one -- defined alternative, the entire expression is replaced with that -- alternative. If there are no defined alternatives, the entire -- expression is replaced with a call to errorX. -- -- e.g. It converts -- -- case x of D1 a -> f a D2 -> undefined D3 -> undefined -- -- to -- -- let subj = x a = case subj of D1 a -> field0 in f a -- -- where fieldN is an internal variable referring to the nth argument of -- a data constructor. xOptimize :: HasCallStack => NormRewrite -- | The separating arguments transformation module Clash.Normalize.Transformations.SeparateArgs -- | Split apart (global) function arguments that contain types that we -- want to separate off, e.g. Clocks. Works on both the definition side -- (i.e. the lambda), and the call site (i.e. the application of the -- global variable). e.g. turns -- --
--   f :: (Clock System, Reset System) -> Signal System Int
--   
-- -- into -- --
--   f :: Clock System -> Reset System -> Signal System Int
--   
separateArguments :: HasCallStack => NormRewrite -- | Transformations on primitives with multiple results. module Clash.Normalize.Transformations.MultiPrim setupMultiResultPrim :: HasCallStack => NormRewrite -- | The eta-expansion transformation. module Clash.Normalize.Transformations.EtaExpand -- | Eta-expand functions with a Synthesize annotation, needed to allow -- such functions to appear as arguments to higher-order primitives. etaExpandSyn :: HasCallStack => NormRewrite -- | Eta-expand top-level lambda's (DON'T use in a traversal!) etaExpansionTL :: HasCallStack => NormRewrite -- | Reductions of primitives -- -- Currently, it contains reductions for: -- -- -- -- Partially handles: -- -- module Clash.Normalize.PrimitiveReductions typeNatAdd :: TyConName typeNatMul :: TyConName typeNatSub :: TyConName vecHeadPrim :: TyConName -> Term vecLastPrim :: TyConName -> Term vecHeadTy :: TyConName -> Type vecTailPrim :: TyConName -> Term vecInitPrim :: TyConName -> Term vecTailTy :: TyConName -> Type -- | Makes two case statements: the first one extract the _head_ from the -- given vector, the latter the tail. extractHeadTail :: DataCon -> Type -> Integer -> Term -> (Term, Term) -- | Create a vector of supplied elements mkVecCons :: HasCallStack => DataCon -> Type -> Integer -> Term -> Term -> Term -- | Create an empty vector mkVecNil :: DataCon -> Type -> Term -- | Replace an application of the Clash.Sized.Vector.reverse -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.reverse reduceReverse :: Integer -> Type -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.zipWith -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.zipWith reduceZipWith :: PrimInfo -> Integer -> Type -> Type -> Type -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.map -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.map reduceMap :: PrimInfo -> Integer -> Type -> Type -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.imap -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.imap reduceImap :: Integer -> Type -> Type -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.iterateI -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of -- Clash.Sized.Vector.iterateI reduceIterateI :: Integer -> Type -> Type -> Term -> Term -> Term -> TransformContext -> RewriteMonad NormalizeState Term -- | Replace an application of the Clash.Sized.Vector.traverse# -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of -- Clash.Sized.Vector.traverse# reduceTraverse :: Integer -> Type -> Type -> Type -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Create the traversable vector -- -- e.g. for a length '2' input vector, we get -- --
--   (:>) <$> x0 <*> ((:>) <$> x1 <*> pure Nil)
--   
mkTravVec :: TyConName -> DataCon -> DataCon -> Term -> Term -> Term -> Type -> Integer -> [Term] -> Term -- | Replace an application of the Clash.Sized.Vector.foldr -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.foldr reduceFoldr :: PrimInfo -> Integer -> Type -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.fold -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.fold reduceFold :: Integer -> Type -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.dfold -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.dfold reduceDFold :: Integer -> Type -> Term -> Term -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.head -- primitive on vectors of a known length n, by a projection of -- the first element of a vector. reduceHead :: Integer -> Type -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.tail -- primitive on vectors of a known length n, by a projection of -- the tail of a vector. reduceTail :: Integer -> Type -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.last -- primitive on vectors of a known length n, by a projection of -- the last element of a vector. reduceLast :: Integer -> Type -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.init -- primitive on vectors of a known length n, by a projection of -- the init of a vector. reduceInit :: PrimInfo -> Integer -> Type -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.(++) -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.(++) reduceAppend :: Integer -> Integer -> Type -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.unconcat -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of -- Clash.Sized.Vector.unconcat reduceUnconcat :: PrimInfo -> Integer -> Integer -> Type -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.transpose -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of -- Clash.Sized.Vector.transpose reduceTranspose :: Integer -> Integer -> Type -> Term -> Term -> TransformContext -> NormalizeSession Term reduceReplicate :: Integer -> Type -> Type -> Term -> Term -> TransformContext -> NormalizeSession Term reduceReplace_int :: Integer -> Type -> Type -> Term -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term reduceIndex_int :: Integer -> Type -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.Vector.dtfold -- primitive on vectors of a known length n, by the fully -- unrolled recursive "definition" of Clash.Sized.Vector.dtfold reduceDTFold :: Integer -> Type -> Term -> Term -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term -- | Replace an application of the Clash.Sized.RTree.tdfold -- primitive on trees of a known depth n, by the fully unrolled -- recursive "definition" of Clash.Sized.RTree.tdfold reduceTFold :: Integer -> Type -> Term -> Term -> Term -> Term -> Term -> TransformContext -> NormalizeSession Term reduceTReplicate :: Integer -> Type -> Type -> Term -> Term -> TransformContext -> NormalizeSession Term buildSNat :: DataCon -> Integer -> Term -- | Transformations on case-expressions module Clash.Normalize.Transformations.Case -- | Move a Case-decomposition from the subject of a Case-decomposition to -- the alternatives caseCase :: HasCallStack => NormRewrite caseCon :: HasCallStack => NormRewrite -- | Remove non-reachable alternatives. For example, consider: -- --
--   data STy ty where
--     SInt :: Int -> STy Int
--     SBool :: Bool -> STy Bool
--   
--   f :: STy ty -> ty
--   f (SInt b) = b + 1
--   f (SBool True) = False
--   f (SBool False) = True
--   {-# NOINLINE f #-}
--   
--   g :: STy Int -> Int
--   g = f
--   
-- -- f is always specialized on STy Int. The SBool -- alternatives are therefore unreachable. Additional information can be -- found at: https://github.com/clash-lang/clash-compiler/pull/465 caseElemNonReachable :: HasCallStack => NormRewrite -- | Flatten ridiculous case-statements generated by GHC -- -- For case-statements in haskell of the form: -- --
--   f :: Unsigned 4 -> Unsigned 4
--   f x = case x of
--     0 -> 3
--     1 -> 2
--     2 -> 1
--     3 -> 0
--   
-- -- GHC generates Core that looks like: -- --
--   f = \(x :: Unsigned 4) -> case x == fromInteger 3 of
--                               False -> case x == fromInteger 2 of
--                                 False -> case x == fromInteger 1 of
--                                   False -> case x == fromInteger 0 of
--                                     False -> error "incomplete case"
--                                     True  -> fromInteger 3
--                                   True -> fromInteger 2
--                                 True -> fromInteger 1
--                               True -> fromInteger 0
--   
-- -- Which would result in a priority decoder circuit where a normal -- decoder circuit was desired. -- -- This transformation transforms the above Core to the saner: -- --
--   f = \(x :: Unsigned 4) -> case x of
--          _ -> error "incomplete case"
--          0 -> fromInteger 3
--          1 -> fromInteger 2
--          2 -> fromInteger 1
--          3 -> fromInteger 0
--   
caseFlat :: HasCallStack => NormRewrite -- | Lift the let-bindings out of the subject of a Case-decomposition caseLet :: HasCallStack => NormRewrite caseOneAlt :: Term -> NormalizeSession Term -- | Tries to eliminate existentials by using heuristics to determine what -- the existential should be. For example, consider Vec: -- -- data Vec :: Nat -> Type -> Type where Nil :: Vec 0 a Cons x xs -- :: a -> Vec n a -> Vec (n + 1) a -- -- Thus, null (annotated with existentials) could look like: -- -- null :: forall n . Vec n Bool -> Bool null v = case v of Nil {n ~ -- 0} -> True Cons {n1:Nat} {n~n1+1} (x :: a) (xs :: Vec n1 a) -> -- False -- -- When it's applied to a vector of length 5, this becomes: -- -- null :: Vec 5 Bool -> Bool null v = case v of Nil {5 ~ 0} -> -- True Cons {n1:Nat} {5~n1+1} (x :: a) (xs :: Vec n1 a) -> False -- -- This function solves n1 and replaces every occurrence with -- its solution. A very limited number of solutions are currently -- recognized: only adds (such as in the example) will be solved. elimExistentials :: HasCallStack => NormRewrite -- | Utilties to verify blackbox contexts against templates and rendering -- filled in templates module Clash.Netlist.BlackBox.Util inputHole :: Element -> Maybe Int -- | Determine if the number of normal/literal/function inputs of a -- blackbox context at least matches the number of argument that is -- expected by the template. verifyBlackBoxContext :: BlackBoxContext -> BlackBox -> Maybe String extractLiterals :: BlackBoxContext -> [Expr] -- | Update all the symbol references in a template, and increment the -- symbol counter for every newly encountered symbol. setSym :: forall m. IdentifierSetMonad m => BlackBoxContext -> BlackBoxTemplate -> m (BlackBoxTemplate, [Declaration]) selectNewName :: Foldable t => t String -> FilePath -> String renderFilePath :: [(String, FilePath)] -> String -> ([(String, FilePath)], String) -- | Render a blackbox given a certain context. Returns a filled out -- template and a list of hidden inputs that must be added to -- the encompassing component. renderTemplate :: Backend backend => BlackBoxContext -> BlackBoxTemplate -> State backend (Int -> Text) renderBlackBox :: Backend backend => [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> BlackBox -> BlackBoxContext -> State backend (Int -> Doc) -- | Render a single template element renderElem :: HasCallStack => Backend backend => BlackBoxContext -> Element -> State backend (Int -> Text) getDomainConf :: (Backend backend, HasCallStack) => HWType -> State backend VDomainConfiguration generalGetDomainConf :: forall m. (Monad m, HasCallStack) => m DomainMap -> HWType -> m VDomainConfiguration parseFail :: Text -> BlackBoxTemplate idToExpr :: (Text, HWType) -> (Expr, HWType, Bool) bbResult :: HasCallStack => String -> BlackBoxContext -> (Expr, HWType) -- | Fill out the template corresponding to an output/input assignment of a -- component instantiation, and turn it into a single identifier so it -- can be used for a new blackbox context. lineToIdentifier :: Backend backend => BlackBoxContext -> BlackBoxTemplate -> State backend Text lineToType :: BlackBoxContext -> BlackBoxTemplate -> HWType -- | Give a context and a tagged hole (of a template), returns part of the -- context that matches the tag of the hole. renderTag :: Backend backend => BlackBoxContext -> Element -> State backend Text -- | Compute string from a list of elements. Can interpret ~NAME string -- literals on template level (constants). elementsToText :: BlackBoxContext -> [Element] -> Either String Text elementToText :: BlackBoxContext -> Element -> Either String Text -- | Extracts string from SSymbol or string literals exprToString :: Expr -> Maybe String prettyBlackBox :: Monad m => BlackBoxTemplate -> Ap m Text prettyElem :: (HasCallStack, Monad m) => Element -> Ap m Text -- | Recursively walk Element, applying f to each element -- in the tree. walkElement :: (Element -> Maybe a) -> Element -> [a] -- | Determine variables used in an expression. Used for VHDL sensitivity -- list. Also see: -- https://github.com/clash-lang/clash-compiler/issues/365 usedVariables :: Expr -> [IdentifierText] -- | Collect arguments (e.g., ~ARG, ~LIT) used in this blackbox getUsedArguments :: BlackBox -> [Int] onBlackBox :: (BlackBoxTemplate -> r) -> (BBName -> BBHash -> TemplateFunction -> r) -> BlackBox -> r -- | Is the value of the Expr fully undefined? checkUndefined :: Expr -> Bool -- | Utility functions to generate Primitives module Clash.Primitives.Util -- | Generate a set of primitives that are found in the primitive -- definition files in the given directories. generatePrimMap :: HasCallStack => [UnresolvedPrimitive] -> [(Text, PrimitiveGuard ())] -> [FilePath] -> IO ResolvedPrimMap -- | Hash a compiled primitive map. It needs a separate function (as -- opposed to just hash) as it might contain (obviously -- unhashable) Haskell functions. This function takes the hash value -- stored with the function instead. hashCompiledPrimMap :: CompiledPrimMap -> Int -- | Determine what argument should be constant / literal constantArgs :: Text -> CompiledPrimitive -> Set Int -- | Parse a ByteString according to the given JSON template. Throws -- exception if it fails. decodeOrErrJson :: (HasCallStack, FromJSON a) => FilePath -> ByteString -> a -- | Parse a ByteString according to the given JSON template. Throws -- exception if it fails. decodeOrErrYaml :: (HasCallStack, FromJSON a) => FilePath -> ByteString -> a -- | Looks up the plurality of a function's function argument. See -- functionPlurality for more information. If not set, the -- returned plurality will default to 1. getFunctionPlurality :: HasCallStack => CompiledPrimitive -> [Either Term Type] -> [Type] -> Int -> NetlistMonad Int -- | Utility functions used by the normalisation transformations module Clash.Normalize.Util data ConstantSpecInfo ConstantSpecInfo :: [(Id, Term)] -> !Term -> !Bool -> ConstantSpecInfo -- | New let-bindings to be created for all the non-constants found [csrNewBindings] :: ConstantSpecInfo -> [(Id, Term)] -- | A term where all the non-constant constructs are replaced by variable -- references (found in csrNewBindings) [csrNewTerm] :: ConstantSpecInfo -> !Term -- | Whether the algorithm found a constant at all. (If it didn't, it's no -- use creating any new let-bindings!) [csrFoundConstant] :: ConstantSpecInfo -> !Bool -- | Determine if argument should reduce to a constant given a primitive -- and an argument number. Caches results. isConstantArg :: Text -> Int -> RewriteMonad NormalizeState Bool -- | Given a list of transformation contexts, determine if any of the -- contexts indicates that the current arg is to be reduced to a constant -- / literal. shouldReduce :: Context -> RewriteMonad NormalizeState Bool -- | Determine if a function is already inlined in the context of the -- NetlistMonad alreadyInlined :: Id -> Id -> NormalizeMonad (Maybe Int) -- | Record a new inlining in the inlineHistory addNewInline :: Id -> Id -> NormalizeMonad () -- | Assert whether a name is a reference to a recursive binder. isRecursiveBndr :: Id -> NormalizeSession Bool -- | Create a call graph for a set of global binders, given a root callGraph :: BindingMap -> Id -> CallGraph -- | Collect all binders mentioned in CallGraph into a HashSet collectCallGraphUniques :: CallGraph -> HashSet Unique -- | Give a "performance/size" classification of a function in normal form. classifyFunction :: Term -> TermClassification -- | Determine whether a function adds a lot of hardware or not. -- -- It is considered expensive when it has 2 or more of the following -- components: -- -- isCheapFunction :: Term -> Bool -- | Test whether a given term represents a non-recursive global variable isNonRecursiveGlobalVar :: Term -> NormalizeSession Bool -- | Calculate constant spec info. The goal of this function is to analyze -- a given term and yield a new term that: -- -- -- -- The result structure will additionally contain: -- -- -- -- This can be used in functions wanting to constant specialize over -- partially constant data structures. constantSpecInfo :: TransformContext -> Term -> RewriteMonad NormalizeState ConstantSpecInfo normalizeTopLvlBndr :: Bool -> Id -> Binding Term -> NormalizeSession (Binding Term) -- | Rewrite a term according to the provided transformation rewriteExpr :: (String, NormRewrite) -> (String, Term) -> (Id, SrcSpan) -> NormalizeSession Term -- | A tick to prefix an inlined expression with it's original name. For -- example, given -- -- foo = bar -- ... bar = baz -- ... baz = quuz -- ... -- -- if bar is inlined into foo, then the name of the component should -- contain the name of the inlined component. This tick ensures that the -- component in foo is called bar_baz instead of just baz. mkInlineTick :: Id -> TickInfo -- | Turn type equality constraints into substitutions and apply them. -- -- So given: -- --
--   /\dom . \(eq : dom ~ "System") . \(eta : Signal dom Bool) . eta
--   
-- -- we create the substitution [dom := System] and apply it to -- create: -- --
--   \(eq : "System" ~ "System") . \(eta : Signal "System" Bool) . eta
--   
-- -- NB: Users of this function should ensure it's only applied to -- TopEntities substWithTyEq :: Term -> Term -- | The type equivalent of substWithTyEq tvSubstWithTyEq :: Type -> Type instance GHC.Show.Show Clash.Normalize.Util.ConstantSpecInfo -- | Collection of utilities module Clash.Util.Graph -- | See: https://en.wikipedia.org/wiki/Topological_sorting. This -- function errors if edges mention nodes not mentioned in the node list -- or if the given graph contains cycles. topSort :: [(Int, a)] -> [(Int, Int)] -> Either String [a] -- | Same as `reverse (topSort nodes edges)` if alternative representations -- are considered the same. That is, topSort might produce multiple -- answers and still deliver on its promise of yielding a topologically -- sorted node list. Likewise, this function promises one of those -- lists in reverse, but not necessarily the reverse of topSort itself. reverseTopSort :: [(Int, a)] -> [(Int, Int)] -> Either String [a] -- | Get all the terms corresponding to a call graph callGraphBindings :: BindingMap -> Id -> [Term] -- | Transformations for specialization module Clash.Normalize.Transformations.Specialize -- | Propagate arguments of application inwards; except for Lam -- where the argument becomes let-bound. appProp tries to -- propagate as many arguments as possible, down as many levels as -- possible; and should be called in a top-down traversal. -- -- The idea is that this reduces the number of traversals, which -- hopefully leads to shorter compile times. -- -- Note [AppProp no shadowing] -- -- Case 1. -- -- Imagine: -- --
--   (case x of
--      D a b -> h a) (f x y)
--   
-- -- rewriting this to: -- --
--   let b = f x y
--   in  case x of
--         D a b -> h a b
--   
-- -- is very bad because b in h a b is now bound by the -- pattern instead of the newly introduced let-binding -- -- instead we must deshadow w.r.t. the new variable and rewrite to: -- --
--   let b = f x y
--   in  case x of
--         D a b1 -> h a b
--   
-- -- Case 2. -- -- Imagine -- --
--   (\x -> e) u
--   
-- -- where u has a free variable named x, rewriting this -- to: -- --
--   let x = u
--   in  e
--   
-- -- would be very bad, because the let-binding suddenly captures the free -- variable in u. To prevent this from happening we -- over-approximate and check whether x is in the current -- InScopeSet, and deshadow if that's the case, i.e. we then rewrite to: -- --
--   let x1 = u
--   in  e [x:=x1]
--   
-- -- Case 3. -- -- The same for: -- --
--   (let x = w in e) u
--   
-- -- where u again has a free variable x, rewriting this -- to: -- --
--   let x = w in (e u)
--   
-- -- would be bad because the let-binding now captures the free variable in -- u. -- -- To prevent this from happening, we unconditionally deshadow the -- function part of the application w.r.t. the free variables in the -- argument part of the application. It is okay to over-approximate in -- this case and deshadow w.r.t the current InScopeSet. appProp :: HasCallStack => NormRewrite -- | Specialize functions on arguments which are constant, except when they -- are clock, reset generators. constantSpec :: HasCallStack => NormRewrite -- | Specialize an application on its argument specialize :: NormRewrite -- | Specialize functions on their non-representable argument nonRepSpec :: HasCallStack => NormRewrite -- | Specialize functions on their type typeSpec :: HasCallStack => NormRewrite -- | Specialize functions on arguments which are zero-width. These -- arguments can have only one possible value, and specializing on this -- value may create additional opportunities for transformations to fire. -- -- As we can't remove zero-width arguements (as transformations cannot -- change the type of a term), we instead substitute all occurances of a -- lambda-bound variable with a zero-width type with the only value of -- that type. zeroWidthSpec :: HasCallStack => NormRewrite module Clash.Normalize.Transformations.Cast -- | Push cast over an argument to a function into that function -- -- This is done by specializing on the casted argument. Example: y = -- f (cast a) where f x = g x transforms to: y = f' a where f' -- x' = (\x -> g x) (cast x') -- -- The reason d'etre for this transformation is that we hope to end up -- with and expression where two casts are "back-to-back" after which we -- can eliminate them in eliminateCastCast. argCastSpec :: HasCallStack => NormRewrite -- | Push a cast over a case into it's alternatives. caseCast :: HasCallStack => NormRewrite -- | Eliminate two back to back casts where the type going in and coming -- out are the same -- --
--   (cast :: b -> a) $ (cast :: a -> b) x   ==> x
--   
elimCastCast :: HasCallStack => NormRewrite -- | Push a cast over a Let into it's body letCast :: HasCallStack => NormRewrite -- | Make a cast work-free by splitting the work of to a separate binding -- --
--   let x = cast (f a b)
--   ==>
--   let x  = cast x'
--       x' = f a b
--   
splitCastWork :: HasCallStack => NormRewrite -- | Transformations for converting to A-Normal Form. module Clash.Normalize.Transformations.ANF -- | Turn an expression into a modified ANF-form. As opposed to standard -- ANF, constants do not become let-bound. makeANF :: HasCallStack => NormRewrite -- | Bring an application of a DataCon or Primitive in ANF, when the -- argument is is considered non-representable nonRepANF :: HasCallStack => NormRewrite -- | Transformations for compile-time reduction of expressions / -- primitives. module Clash.Normalize.Transformations.Reduce -- | XXX: is given inverse topologically sorted binders, but returns -- topologically sorted binders -- -- TODO: check further speed improvements: -- --
    --
  1. Store the processed binders in a `Map Expr LetBinding`: * Trades -- O(1) cons and O(n)*aeqTerm find for: * O(log -- n)*aeqTerm insert and O(log n)*aeqTerm lookup
  2. --
  3. Store the processed binders in a `AEQTrie Expr LetBinding` * -- Trades O(1) cons and O(n)*aeqTerm find for: * O(e) -- insert and O(e) lookup
  4. --
reduceBinders :: Subst -> [LetBinding] -> [LetBinding] -> NormalizeSession (Subst, [LetBinding]) reduceConst :: HasCallStack => NormRewrite -- | Replace primitives by their "definition" if they would lead to -- let-bindings with a non-representable type when a function is in ANF. -- This happens for example when Clash.Size.Vector.map consumes or -- produces a vector of non-representable elements. -- -- Basically what this transformation does is replace a primitive the -- completely unrolled recursive definition that it represents. e.g. -- --
--   zipWith ($) (xs :: Vec 2 (Int -> Int)) (ys :: Vec 2 Int)
--   
-- -- is replaced by: -- --
--   let (x0  :: (Int -> Int))       = case xs  of (:>) _ x xr -> x
--       (xr0 :: Vec 1 (Int -> Int)) = case xs  of (:>) _ x xr -> xr
--       (x1  :: (Int -> Int)(       = case xr0 of (:>) _ x xr -> x
--       (y0  :: Int)                = case ys  of (:>) _ y yr -> y
--       (yr0 :: Vec 1 Int)          = case ys  of (:>) _ y yr -> xr
--       (y1  :: Int                 = case yr0 of (:>) _ y yr -> y
--   in  (($) x0 y0 :> ($) x1 y1 :> Nil)
--   
-- -- Currently, it only handles the following functions: -- -- -- -- Note [Unroll shouldSplit types] 1. Certain higher-order functions over -- Vec, such as map, have specialized code-paths to turn them into -- generate-for loops in HDL, instead of having to having to -- unroll/inline their recursive definitions, e.g. Clash.Sized.Vector.map -- --
    --
  1. Clash, in general, translates Haskell product types to VHDL -- records. This mostly works out fine, there is however one exception: -- certain synthesis tools, and some HDL simulation tools (like -- verilator), do not like it when the clock (and certain other global -- control signals) is contained in a record type; they want them to be -- separate inputs to the entity/module. And Clash actually does some -- transformations to try to ensure that values of type Clock do not end -- up in a VHDL record type.
  2. --
-- -- The problem is that the transformations in 2. never took into account -- the specialized code-paths in 1. Making the code-paths in 1. aware of -- the transformations in 2. is really not worth the effort for such a -- niche case. It's easier to just unroll the recursive definitions. -- -- See https://github.com/clash-lang/clash-compiler/issues/1606 reduceNonRepPrim :: HasCallStack => NormRewrite instance Clash.Normalize.Transformations.Reduce.AbstractOverMissingArgs (Clash.Rewrite.Types.TransformContext -> Clash.Normalize.Types.NormalizeSession Clash.Core.Term.Term) instance Clash.Normalize.Transformations.Reduce.AbstractOverMissingArgs a => Clash.Normalize.Transformations.Reduce.AbstractOverMissingArgs (Clash.Core.Term.Term -> a) -- | Transformations for inlining module Clash.Normalize.Transformations.Inline -- | Inline let-bindings when the RHS is either a local variable reference -- or is constant (except clock or reset generators) bindConstantVar :: HasCallStack => NormRewrite -- | Used by inlineCleanup to inline binders that we want to inline -- into the binders that we want to keep. inlineBndrsCleanup :: HasCallStack => InScopeSet -> VarEnv ((Id, Term), VarEnv Int) -> VarEnv ((Id, Term), VarEnv Int, Mark) -> [((Id, Term), VarEnv Int)] -> [(Id, Term)] -- | Only inline casts that just contain a Var, because these are -- guaranteed work-free. These are the result of the -- splitCastWork transformation. inlineCast :: HasCallStack => NormRewrite -- | Given a function in the desired normal form, inline all the following -- let-bindings: -- -- Let-bindings with an internal name that is only used once, where it -- binds: * a primitive that will be translated to an HDL expression (as -- opposed to a HDL declaration) * a projection case-expression (1 -- alternative) * a data constructor * I/O actions inlineCleanup :: HasCallStack => NormRewrite -- | Takes a binding and collapses its term if it is a noop collapseRHSNoops :: HasCallStack => NormRewrite -- | Inline function with a non-representable result if it's the subject of -- a Case-decomposition. It's a custom topdown traversal that -for -- efficiency reasons- does not explore alternative of cases whose -- subject triggered an inlineNonRepWorker. inlineNonRep :: HasCallStack => NormRewrite inlineOrLiftNonRep :: HasCallStack => NormRewrite -- | Inline anything of type SimIO: IO actions cannot be shared inlineSimIO :: HasCallStack => NormRewrite -- | Inline small functions inlineSmall :: HasCallStack => NormRewrite -- | Inline work-free functions, i.e. fully applied functions that evaluate -- to a constant inlineWorkFree :: HasCallStack => NormRewrite -- | Transformations on letrec expressions. module Clash.Normalize.Transformations.Letrec -- | Remove unused let-bindings deadCode :: HasCallStack => NormRewrite -- | Flatten's letrecs after inlineCleanup -- -- inlineCleanup sometimes exposes additional possibilities for -- caseCon, which then introduces let-bindings in what should be -- ANF. This transformation flattens those nested let-bindings again. -- -- NB: must only be called in the cleaning up phase. flattenLet :: HasCallStack => NormRewrite -- | Turn a normalized recursive function, where the recursive calls only -- pass along the unchanged original arguments, into let-recursive -- function. This means that all recursive calls are replaced by the same -- variable reference as found in the body of the top-level -- let-expression. recToLetRec :: HasCallStack => NormRewrite removeUnusedExpr :: HasCallStack => NormRewrite -- | Simplified CSE, only works on let-bindings, does an inverse -- topological sort of the let-bindings and then works from top to bottom -- -- XXX: Check whether inverse top-sort followed by single traversal -- removes as many binders as the previous "apply-until-fixpoint" -- approach in the presence of recursive groups in the let-bindings. If -- not but just for checking whether changes to transformation affect the -- eventual size of the circuit, it would be really helpful if we tracked -- circuit size in the regression/test suite. On the two examples that -- were tested, Reducer and PipelinesViaFolds, this new version of CSE -- removed the same amount of let-binders. simpleCSE :: HasCallStack => NormRewrite -- | Ensure that top-level lambda's eventually bind a let-expression of -- which the body is a variable-reference. topLet :: HasCallStack => NormRewrite -- | The disjointExpressionConsolidation transformation lifts -- applications of global binders out of alternatives of case-statements. -- -- e.g. It converts: -- --
--   case x of
--     A -> f 3 y
--     B -> f x x
--     C -> h x
--   
-- -- into: -- --
--   let f_arg0 = case x of {A -> 3; B -> x}
--       f_arg1 = case x of {A -> y; B -> x}
--       f_out  = f f_arg0 f_arg1
--   in  case x of
--         A -> f_out
--         B -> f_out
--         C -> h x
--   
module Clash.Normalize.Transformations.DEC -- | This transformation lifts applications of global binders out of -- alternatives of case-statements. -- -- e.g. It converts: -- --
--   case x of
--     A -> f 3 y
--     B -> f x x
--     C -> h x
--   
-- -- into: -- --
--   let f_arg0 = case x of {A -> 3; B -> x}
--       f_arg1 = case x of {A -> y; B -> x}
--       f_out  = f f_arg0 f_arg1
--   in  case x of
--         A -> f_out
--         B -> f_out
--         C -> h x
--   
-- -- Though that's a lie. It actually converts it into: -- --
--   let f_tupIn = case x of {A -> (3,y); B -> (x,x)}
--       f_arg0  = case f_tupIn of (l,_) -> l
--       f_arg1  = case f_tupIn of (_,r) -> r
--       f_out   = f f_arg0 f_arg1
--   in  case x of
--         A -> f_out
--         B -> f_out
--         C -> h x
--   
-- -- In order to share the expression that's in the subject of the case -- expression, and to share the decoder circuit that logic -- synthesis will create to map the bits of the subject expression to the -- bits needed to make the selection in the multiplexer. disjointExpressionConsolidation :: HasCallStack => NormRewrite instance Data.Foldable.Foldable Clash.Normalize.Transformations.DEC.CaseTree instance GHC.Base.Functor Clash.Normalize.Transformations.DEC.CaseTree instance GHC.Show.Show a => GHC.Show.Show (Clash.Normalize.Transformations.DEC.CaseTree a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Clash.Normalize.Transformations.DEC.CaseTree a) instance GHC.Base.Applicative Clash.Normalize.Transformations.DEC.CaseTree -- | Transformations of the Normalization process module Clash.Normalize.Transformations -- | Transformation process for normalization module Clash.Normalize.Strategy -- | Normalisation transformation normalization :: NormRewrite constantPropagation :: NormRewrite -- | Topdown traversal, stops upon first success topdownSucR :: Rewrite extra -> Rewrite extra innerMost :: Rewrite extra -> Rewrite extra applyMany :: [(String, Rewrite extra)] -> Rewrite extra -- | Turn CoreHW terms into normalized CoreHW Terms module Clash.Normalize -- | Run a NormalizeSession in a given environment runNormalization :: ClashEnv -> Supply -> BindingMap -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Evaluator -> Evaluator -> VarEnv Bool -> [Id] -> NormalizeSession a -> IO a normalize :: [Id] -> NormalizeSession BindingMap normalize' :: Id -> NormalizeSession ([Id], (Id, Binding Term)) -- | Check whether the normalized bindings are non-recursive. Errors when -- one of the components is recursive. checkNonRecursive :: BindingMap -> BindingMap -- | Perform general "clean up" of the normalized (non-recursive) function -- hierarchy. This includes: -- -- cleanupGraph :: Id -> BindingMap -> NormalizeSession BindingMap -- | A tree of identifiers and their bindings, with branches containing -- additional bindings which are used. See -- Clash.Driver.Types.Binding. data CallTree CLeaf :: (Id, Binding Term) -> CallTree CBranch :: (Id, Binding Term) -> [CallTree] -> CallTree mkCallTree :: [Id] -> BindingMap -> Id -> Maybe CallTree stripArgs :: [Id] -> [Id] -> [Either Term Type] -> Maybe [Either Term Type] flattenNode :: CallTree -> NormalizeSession (Either CallTree ((Id, Term), [CallTree])) flattenCallTree :: CallTree -> NormalizeSession CallTree callTreeToList :: [Id] -> CallTree -> ([Id], [(Id, Binding Term)]) -- | Functions to create BlackBox Contexts and fill in BlackBox templates module Clash.Netlist.BlackBox -- | Emits (colorized) warning to stderr warn :: ClashOpts -> String -> IO () -- | Generate the context for a BlackBox instantiation. mkBlackBoxContext :: HasCallStack => Text -> [Id] -> [Either Term Type] -> NetlistMonad (BlackBoxContext, [Declaration]) prepareBlackBox :: Text -> BlackBox -> BlackBoxContext -> NetlistMonad (BlackBox, [Declaration]) -- | Determine if a term represents a literal isLiteral :: Term -> Bool mkArgument :: Text -> Identifier -> Int -> Term -> NetlistMonad ((Expr, HWType, Bool), [Declaration]) -- | Extract a compiled primitive from a guarded primitive. Emit a warning -- if the guard wants to, or fail entirely. extractPrimWarnOrFail :: HasCallStack => Text -> NetlistMonad CompiledPrimitive mkPrimitive :: Bool -> Bool -> DeclarationType -> NetlistId -> PrimInfo -> [Either Term Type] -> [Declaration] -> NetlistMonad (Expr, [Declaration]) -- | Turn a mealyIO expression into a two sequential processes, -- one "initial" process for the starting state, and one clocked -- sequential process. collectMealy :: HasCallStack => Identifier -> NetlistId -> TyConMap -> [Term] -> NetlistMonad [Declaration] -- | Collect the sequential declarations for bindIO collectBindIO :: NetlistId -> [Term] -> NetlistMonad (Expr, [Declaration]) -- | Collect the sequential declarations for appIO collectAppIO :: NetlistId -> [Term] -> [Term] -> NetlistMonad (Expr, [Declaration]) -- | Unwrap the new-type wrapper for things of type SimIO, this is needed -- to allow applications of the `State# World` token to the underlying IO -- type. -- -- XXX: this is most likely needed because Ghc2Core that threw away the -- cast that this unwrapping; we should really start to support casts. unSimIO :: TyConMap -> Term -> Term -- | Create an template instantiation text and a partial blackbox content -- for an argument term, given that the term is a function. Errors if the -- term is not a function mkFunInput :: HasCallStack => Text -> Id -> Term -> NetlistMonad ((Either BlackBox (Identifier, [Declaration]), Usage, [BlackBoxTemplate], [BlackBoxTemplate], [((Text, Text), BlackBox)], BlackBoxContext), [Declaration]) -- | Create Netlists out of normalized CoreHW Terms module Clash.Netlist -- | Generate a hierarchical netlist out of a set of global binders with -- topEntity at the top. genNetlist :: ClashEnv -> Bool -> BindingMap -> VarEnv TopEntityT -> VarEnv Identifier -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Bool -> SomeBackend -> IdentifierSet -> FilePath -> Maybe Text -> Id -> IO (Component, ComponentMap, IdentifierSet) -- | Run a NetlistMonad action in a given environment runNetlistMonad :: ClashEnv -> Bool -> BindingMap -> VarEnv TopEntityT -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Bool -> SomeBackend -> IdentifierSet -> FilePath -> VarEnv Identifier -> NetlistMonad a -> IO (a, NetlistState) -- | Generate names for all binders in BindingMap, except for the -- ones already present in given identifier varenv. genNames :: Bool -> Maybe Text -> IdentifierSet -> VarEnv Identifier -> BindingMap -> (VarEnv Identifier, IdentifierSet) -- | Generate names for top entities. Should be executed at the very start -- of the synthesis process and shared between all passes. genTopNames :: ClashOpts -> HDL -> [TopEntityT] -> (VarEnv Identifier, IdentifierSet) -- | Generate a component for a given function (caching) genComponent :: HasCallStack => Id -> NetlistMonad (ComponentMeta, Component) -- | Generate a component for a given function genComponentT :: HasCallStack => Id -> Term -> NetlistMonad (ComponentMeta, Component) mkNetDecl :: (Id, Term) -> NetlistMonad [Declaration] -- | Generate a list of concurrent Declarations for a let-binder, return an -- empty list if the bound expression is represented by 0 bits mkDeclarations :: HasCallStack => Id -> Term -> NetlistMonad [Declaration] -- | Generate a list of Declarations for a let-binder, return an empty list -- if the bound expression is represented by 0 bits mkDeclarations' :: HasCallStack => DeclarationType -> Id -> Term -> NetlistMonad [Declaration] -- | Generate a declaration that selects an alternative based on the value -- of the scrutinee mkSelection :: DeclarationType -> NetlistId -> Term -> Type -> NonEmpty Alt -> [Declaration] -> NetlistMonad [Declaration] reorderDefault :: NonEmpty (Pat, Term) -> NonEmpty (Pat, Term) reorderCustom :: TyConMap -> CustomReprs -> Type -> NonEmpty (Pat, Term) -> NonEmpty (Pat, Term) patPos :: CustomReprs -> Pat -> Int -- | Generate a list of Declarations for a let-binder where the RHS is a -- function application mkFunApp :: HasCallStack => Identifier -> Id -> [Term] -> [Declaration] -> NetlistMonad [Declaration] toSimpleVar :: Identifier -> (Expr, Type) -> NetlistMonad (Expr, [Declaration]) -- | Generate an expression for a term occurring on the RHS of a let-binder mkExpr :: HasCallStack => Bool -> DeclarationType -> NetlistId -> Term -> NetlistMonad (Expr, [Declaration]) -- | Generate an expression that projects a field out of a -- data-constructor. -- -- Works for both product types, as sum-of-product types. mkProjection :: Bool -> NetlistId -> Term -> Type -> Alt -> NetlistMonad (Expr, [Declaration]) -- | Generate an expression for a DataCon application occurring on the RHS -- of a let-binder mkDcApplication :: HasCallStack => DeclarationType -> [HWType] -> NetlistId -> DataCon -> [Term] -> NetlistMonad (Expr, [Declaration]) module Clash.Primitives.Verification checkBBF :: BlackBoxFunction -- | Functions to read, write, and handle manifest files. module Clash.Driver.Manifest data PortDirection In :: PortDirection Out :: PortDirection InOut :: PortDirection data ManifestPort ManifestPort :: Text -> Text -> PortDirection -> Int -> Bool -> Maybe Text -> ManifestPort -- | Port name (as rendered in HDL) [mpName] :: ManifestPort -> Text -- | Type name (as rendered in HDL) [mpTypeName] :: ManifestPort -> Text -- | Port direction (in out inout) [mpDirection] :: ManifestPort -> PortDirection -- | Port width in bits [mpWidth] :: ManifestPort -> Int -- | Is this port a clock? [mpIsClock] :: ManifestPort -> Bool -- | Domain this port belongs to. This is currently only included for -- clock, reset, and enable ports. TODO: add to all ports originally -- defined as a Signal too. [mpDomain] :: ManifestPort -> Maybe Text -- | Just the fileNames part of Manifest newtype FilesManifest FilesManifest :: [(FilePath, ByteString)] -> FilesManifest -- | Information about the generated HDL between (sub)runs of the compiler data Manifest Manifest :: ByteString -> (Int, Int) -> [ManifestPort] -> [Text] -> Text -> [(FilePath, ByteString)] -> HashMap Text VDomainConfiguration -> [Text] -> Manifest -- | Hash digest of the TopEntity and all its dependencies. [manifestHash] :: Manifest -> ByteString -- | Compiler flags used to achieve successful compilation: -- -- [successFlags] :: Manifest -> (Int, Int) -- | Ports in the generated TopEntity. [ports] :: Manifest -> [ManifestPort] -- | Names of all the generated components for the TopEntity (does -- not include the names of the components of the TestBench -- accompanying the TopEntity). -- -- This list is reverse topologically sorted. I.e., a component might -- depend on any component listed before it, but not after it. [componentNames] :: Manifest -> [Text] -- | Design entry point. This is usually the component annotated with a -- TopEntity annotation. [topComponent] :: Manifest -> Text -- | Names and hashes of all the generated files for the -- TopEntity. Hashes are SHA256. -- -- This list is reverse topologically sorted. I.e., a component might -- depend on any component listed before it, but not after it. [fileNames] :: Manifest -> [(FilePath, ByteString)] -- | Domains encountered in design [domains] :: Manifest -> HashMap Text VDomainConfiguration -- | Dependencies of this design (fully qualified binder names). Is a -- transitive closure of all dependencies. -- -- This list is reverse topologically sorted. I.e., a component might -- depend on any component listed before it, but not after it. [transitiveDependencies] :: Manifest -> [Text] -- | Decode a hex digest to a ByteString. Returns a broken digest if the -- decode fails - hence it being marked as unsafe. unsafeFromHexDigest :: Text -> ByteString -- | Encode a ByteString to a hex digest. toHexDigest :: ByteString -> Text -- | Parse files part of a Manifest file parseFiles :: Object -> Parser [(FilePath, ByteString)] data UnexpectedModification -- | Clash generated file was modified Modified :: FilePath -> UnexpectedModification -- | Non-clash generated file was added Added :: FilePath -> UnexpectedModification -- | Clash generated file was removed Removed :: FilePath -> UnexpectedModification mkManifestPort :: Backend backend => backend -> Identifier -> HWType -> PortDirection -> ManifestPort -- | Filename manifest file should be written to and read from manifestFilename :: IsString a => a mkManifest :: Backend backend => backend -> HashMap Text VDomainConfiguration -> ClashOpts -> Component -> [Component] -> [Id] -> [(FilePath, ByteString)] -> ByteString -> Manifest -- | Pretty print an unexpected modification as a list item. pprintUnexpectedModification :: UnexpectedModification -> String -- | Pretty print a list of unexpected modifications. Print a maximum of -- n modifications. pprintUnexpectedModifications :: Int -> [UnexpectedModification] -> String -- | Reads a manifest file. Does not return manifest file if: -- -- -- -- Raises an exception if the manifest file or any of the files it is -- referring to was inaccessible. readFreshManifest :: [TopEntityT] -> (BindingMap, Id) -> CompiledPrimMap -> ClashOpts -> UTCTime -> FilePath -> IO (Maybe [UnexpectedModification], Maybe Manifest, ByteString) -- | Determines whether the HDL directory the given -- LocatedManifest was found in contains any user made -- modifications. This is used by Clash to protect the user against lost -- work. isUserModified :: FilePath -> FilesManifest -> IO [UnexpectedModification] -- | Read a manifest file from disk. Returns Nothing if file does -- not exist. Any other IO exception is re-raised. readManifest :: FromJSON a => FilePath -> IO (Maybe a) -- | Write manifest file to disk writeManifest :: FilePath -> Manifest -> IO () -- | Serialize a manifest. -- -- TODO: This should really yield a ByteString. serializeManifest :: Manifest -> Text instance GHC.Show.Show Clash.Driver.Manifest.PortDirection instance GHC.Read.Read Clash.Driver.Manifest.PortDirection instance GHC.Classes.Eq Clash.Driver.Manifest.PortDirection instance GHC.Generics.Generic Clash.Driver.Manifest.PortDirection instance GHC.Classes.Eq Clash.Driver.Manifest.ManifestPort instance GHC.Read.Read Clash.Driver.Manifest.ManifestPort instance GHC.Show.Show Clash.Driver.Manifest.ManifestPort instance GHC.Classes.Eq Clash.Driver.Manifest.Manifest instance GHC.Read.Read Clash.Driver.Manifest.Manifest instance GHC.Show.Show Clash.Driver.Manifest.Manifest instance GHC.Show.Show Clash.Driver.Manifest.UnexpectedModification instance Data.Aeson.Types.ToJSON.ToJSON Clash.Driver.Manifest.Manifest instance Data.Aeson.Types.FromJSON.FromJSON Clash.Driver.Manifest.Manifest instance Data.Aeson.Types.FromJSON.FromJSON Clash.Driver.Manifest.FilesManifest instance Data.Aeson.Types.ToJSON.ToJSON Clash.Driver.Manifest.ManifestPort instance Data.Aeson.Types.FromJSON.FromJSON Clash.Driver.Manifest.ManifestPort instance Data.Aeson.Types.ToJSON.ToJSON Clash.Driver.Manifest.PortDirection instance Data.Aeson.Types.FromJSON.FromJSON Clash.Driver.Manifest.PortDirection -- | Generate Verilog for assorted Netlist datatypes module Clash.Backend.Verilog -- | State for the VerilogM monad: data VerilogState include :: Monad m => [Text] -> Ap m Doc uselibs :: Monad m => [Text] -> Ap m Doc encodingNote :: Applicative m => HWType -> m Doc exprLit :: Lens' s (Maybe (Maybe Int)) -> Maybe (HWType, Size) -> Literal -> Ap (State s) Doc bits :: Lens' s (Maybe (Maybe Int)) -> [Bit] -> Ap (State s) Doc bit_char :: Lens' s (Maybe (Maybe Int)) -> Bit -> Ap (State s) Doc noEmptyInit :: (Monad m, Semigroup (m Doc)) => m Doc -> m Doc -- | Range slice, can be contiguous, or split into multiple sub-ranges data Range Contiguous :: Int -> Int -> Range Split :: [(Int, Int, Provenance)] -> Range -- | Select a sub-range from a range continueWithRange :: [(Int, Int)] -> HWType -> Range -> (Range, HWType) instance Clash.Netlist.Types.HasIdentifierSet Clash.Backend.Verilog.VerilogState instance Clash.Backend.HasUsageMap Clash.Backend.Verilog.VerilogState instance Clash.Backend.Backend Clash.Backend.Verilog.VerilogState -- | Generate VHDL for assorted Netlist datatypes module Clash.Backend.VHDL -- | State for the VHDLM monad: data VHDLState instance Clash.Netlist.Types.HasIdentifierSet Clash.Backend.VHDL.VHDLState instance Clash.Backend.HasUsageMap Clash.Backend.VHDL.VHDLState instance Clash.Backend.Backend Clash.Backend.VHDL.VHDLState -- | This module contains a mini dsl for creating haskell blackbox -- instantiations. module Clash.Primitives.DSL -- | Options for blackBoxHaskell function. Use def from -- package 'data-default' for a set of default options. data BlackBoxHaskellOpts BlackBoxHaskellOpts :: [Int] -> [HDL] -> Bool -> BlackBoxHaskellOpts -- | Arguments to ignore (i.e., remove during normalization) -- -- Default: [] [bo_ignoredArguments] :: BlackBoxHaskellOpts -> [Int] -- | HDLs to use the blackbox for -- -- Default: all [bo_supportedHdls] :: BlackBoxHaskellOpts -> [HDL] -- | Does this blackbox assign its results to multiple binders? -- -- Default: False. [bo_multiResult] :: BlackBoxHaskellOpts -> Bool -- | Create a blackBoxHaskell primitive. To be used as part of an -- annotation: -- --
--   {-# ANN myFunction (blackBoxHaskell 'myFunction 'myBBF def{bo_ignoredArguments=[1,2]}) #-}
--   
-- -- [1,2] would mean this blackbox ignores its second and -- third argument. blackBoxHaskell :: Name -> Name -> BlackBoxHaskellOpts -> Primitive -- | The state of a block. Contains a list of declarations and a the -- backend state. data BlockState backend BlockState :: [Declaration] -> IntMap Int -> backend -> BlockState backend -- | Declarations store [_bsDeclarations] :: BlockState backend -> [Declaration] -- | Tracks how many times a higher order function has been instantiated. -- Needed to fill in the second field of Decl [_bsHigherOrderCalls] :: BlockState backend -> IntMap Int -- | Backend state [_bsBackend] :: BlockState backend -> backend -- | A typed expression. data TExpr TExpr :: HWType -> Expr -> TExpr [ety] :: TExpr -> HWType [eex] :: TExpr -> Expr -- | Add a declaration to the state. addDeclaration :: Declaration -> State (BlockState backend) () -- | Assign an expression to an identifier, returns the new typed -- identifier expression. assign :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr -- | This creates a component declaration (for VHDL) given in and out port -- names, updating the 'BlockState backend' stored in the State -- monad. -- -- A typical result is that a -- --
--   component fifo port
--      ( rst : in std_logic
--      ...
--      ; full : out std_logic
--      ; empty : out std_logic );
--    end component;
--   
-- -- declaration would be added in the appropriate place. compInBlock :: forall backend. Backend backend => Text -> [(Text, HWType)] -> [(Text, HWType)] -> State (BlockState backend) () -- | Run a block declaration. declaration :: Backend backend => Text -> State (BlockState backend) () -> State backend Doc -- | Run a block declaration. Assign the result of the block builder to the -- result variable in the given blackbox context. declarationReturn :: Backend backend => BlackBoxContext -> Text -> State (BlockState backend) [TExpr] -> State backend Doc -- | Declare a new signal with the given name and type. declare :: Backend backend => Text -> HWType -> State (BlockState backend) TExpr -- | Declare n new signals with the given type and based on the -- given name declareN :: Backend backend => Text -> [HWType] -> State (BlockState backend) [TExpr] -- | Instantiate a component/entity in a block state instDecl :: forall backend. Backend backend => EntityOrComponent -> Identifier -> Identifier -> [(Text, TExpr)] -> [(Text, TExpr)] -> [(Text, TExpr)] -> State (BlockState backend) () -- | Instantiate/call a higher-order function. instHO :: Backend backend => BlackBoxContext -> Int -> (HWType, BlackBoxTemplate) -> [(TExpr, BlackBoxTemplate)] -> State (BlockState backend) TExpr -- | Wires the two given TExprs together using a newly declared -- signal with (exactly) the given name sigNm. The new signal -- has an annotated type, using the given attributes. viaAnnotatedSignal :: (HasCallStack, Backend backend) => Identifier -> TExpr -> TExpr -> [Attr Text] -> State (BlockState backend) () -- | Construct a fully defined BitVector literal bvLit :: Int -> Integer -> TExpr -- | A literal that can be used for hdl attributes. It has a Num and -- IsString instances for convenience. data LitHDL B :: Bool -> LitHDL S :: String -> LitHDL I :: Integer -> LitHDL -- | The high literal bit. pattern High :: TExpr -- | The low literal bit. pattern Low :: TExpr -- | Construct a product type given its type and fields constructProduct :: HWType -> [TExpr] -> TExpr -- | Create an n-tuple of TExpr tuple :: HasCallStack => [TExpr] -> TExpr -- | Create a vector of TExprs vec :: (HasCallStack, Backend backend) => [TExpr] -> State (BlockState backend) TExpr -- | The TExp inputs from a blackbox context. tInputs :: BlackBoxContext -> [(TExpr, HWType)] -- | The TExp result of a blackbox context. tResults :: BlackBoxContext -> [TExpr] -- | Try to get the literal string value of an expression. getStr :: TExpr -> Maybe String -- | Try to get the literal bool value of an expression. getBool :: TExpr -> Maybe Bool -- | Try to get a Vector of expressions. getVec :: TExpr -> Maybe [TExpr] exprToInteger :: Expr -> Maybe Integer -- | Try to get the literal nat value of an expression. tExprToInteger :: TExpr -> Maybe Integer -- | Extract the fields of a product type and return expressions to them. -- These new expressions are given unique names and get declared in the -- block scope. deconstructProduct :: (HasCallStack, Backend backend) => TExpr -> [Text] -> State (BlockState backend) [TExpr] -- | Extract the elements of a tuple expression and return expressions to -- them. These new expressions are given unique names and get declared in -- the block scope. untuple :: (HasCallStack, Backend backend) => TExpr -> [Text] -> State (BlockState backend) [TExpr] -- | Extract the elements of a vector expression and return expressions to -- them. If given expression is not an identifier, an intermediate -- variable will be used to assign the given expression to which is -- subsequently indexed. unvec :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) [TExpr] -- | Deconstruct a Maybe into its constructor Bit and -- contents of its Just field. Note that the contents might be -- undefined, if the constructor bit is set to Nothing. deconstructMaybe :: (HasCallStack, Backend backend) => TExpr -> (Text, Text) -> State (BlockState backend) (TExpr, TExpr) -- | Convert an expression from one type to another. Errors if result type -- and given expression are sized differently. bitCoerce :: (HasCallStack, Backend backend) => Text -> HWType -> TExpr -> State (BlockState backend) TExpr -- | Convert an expression to a BitVector toBV :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr -- | Convert an expression to a BitVector and add the given HDL attributes toBvWithAttrs :: Backend backend => [Attr Text] -> Text -> TExpr -> State (BlockState backend) TExpr -- | Convert an expression from a BitVector into some type. If the -- expression is Annotated, only convert the expression within. fromBV :: (HasCallStack, Backend backend) => Text -> HWType -> TExpr -> State (BlockState backend) TExpr -- | Convert an enable to a bit. enableToBit :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) TExpr -- | Convert a bool to a bit. boolToBit :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) TExpr -- | Use to create an output Bool from a Bit. The expression -- given must be the identifier of the bool you wish to get assigned. -- Returns a reference to a declared Bit that should get assigned -- by something (usually the output port of an entity). boolFromBit :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) TExpr -- | Used to create an output Bool from a BitVector of given -- size. Works in a similar way to boolFromBit above. -- -- TODO: Implement for (System)Verilog boolFromBitVector :: Size -> Text -> TExpr -> State (BlockState VHDLState) TExpr -- | Used to create an output Unsigned from a BitVector of -- given size. Works in a similar way to boolFromBit above. unsignedFromBitVector :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) TExpr -- | Used to create an output Bool from a number of Bits, -- using conjunction. Similarly to untuple, it returns a list of -- references to declared values (the inputs to the function) which -- should get assigned by something---usually output ports of an entity. -- -- TODO: Implement for (System)Verilog boolFromBits :: [Text] -> TExpr -> State (BlockState VHDLState) [TExpr] -- | Massage a reset to work as active-high reset. unsafeToActiveHigh :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr -- | Massage a reset to work as active-low reset. unsafeToActiveLow :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr -- | And together (&&) two expressions, assigning it to a -- new identifier. andExpr :: Backend backend => Text -> TExpr -> TExpr -> State (BlockState backend) TExpr -- | Negate (not) an expression, assigning it to a new identifier. notExpr :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr -- | Creates a BV that produces the following vhdl: -- --
--   (0 to n => ARG)
--   
-- -- TODO: Implement for (System)Verilog pureToBV :: Text -> Int -> TExpr -> State (BlockState VHDLState) TExpr -- | Creates a BV that produces the following vhdl: -- --
--   std_logic_vector(resize(ARG, n))
--   
-- -- TODO: Implement for (System)Verilog pureToBVResized :: Text -> Int -> TExpr -> State (BlockState VHDLState) TExpr -- | Allows assignment of a port to be "open" open :: Backend backend => HWType -> State (BlockState backend) TExpr clog2 :: Num i => Integer -> i -- | Convert a LitHDL to a TExpr -- -- N.B.: Clash 1.8 changed instDecl's type signature. Where -- it would previously accept LitHDL in its generics/parameters -- argument, it now accepts a TExpr. This function is mostly there -- to ease this transition. litTExpr :: LitHDL -> TExpr -- | Get an identifier to an expression, creating a new assignment if -- necessary. toIdentifier :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr tySize :: Num i => HWType -> i instance GHC.Show.Show Clash.Primitives.DSL.LitHDL instance GHC.Num.Num Clash.Primitives.DSL.LitHDL instance Data.String.IsString Clash.Primitives.DSL.LitHDL instance GHC.Show.Show Clash.Primitives.DSL.TExpr instance Clash.Backend.Backend backend => Clash.Netlist.Types.HasIdentifierSet (Clash.Primitives.DSL.BlockState backend) instance Clash.Backend.HasUsageMap backend => Clash.Backend.HasUsageMap (Clash.Primitives.DSL.BlockState backend) instance Data.Default.Class.Default Clash.Primitives.DSL.BlackBoxHaskellOpts -- | Blackbox template functions for -- Clash.Xilinx.ClockGen.{clockWizard,clockWizardDifferential} module Clash.Primitives.Xilinx.ClockGen clockWizardTF :: TemplateFunction clockWizardTclTF :: TemplateFunction clockWizardDifferentialTF :: TemplateFunction clockWizardDifferentialTclTF :: TemplateFunction -- | Blackbox implementations for functions in Clash.Sized.Vector. module Clash.Primitives.Sized.Vector -- | Blackbox function for iterateI iterateBBF :: HasCallStack => BlackBoxFunction -- | Type signature of function we're generating netlist for: -- -- iterateI :: KnownNat n => (a -> a) -> a -> Vec n a iterateTF :: TemplateFunction iterateTF' :: forall s. (HasCallStack, Backend s) => BlackBoxContext -> State s Doc data FCall FCall :: Identifier -> Identifier -> Identifier -> FCall -- | Calculates the number of function calls needed for an evaluation of -- fold, given the length of the vector given to fold. foldFunctionPlurality :: HasCallStack => Int -> Int -- | Blackbox function for fold foldBBF :: HasCallStack => BlackBoxFunction -- | Type signature of function we're generating netlist for: -- -- fold :: (a -> a -> a) -> Vec (n + 1) a -> a -- -- The implementation promises to create a (balanced) tree structure. foldTF :: TemplateFunction foldTF' :: forall s. (HasCallStack, Backend s) => BlackBoxContext -> State s Doc indexIntVerilog :: BlackBoxFunction indexIntVerilogTF :: TemplateFunction indexIntVerilogTemplate :: Backend s => BlackBoxContext -> State s Doc -- | Blackbox template functions for Clash.Intel.ClockGen module Clash.Primitives.Intel.ClockGen data Variant Altpll :: Variant AlteraPll :: Variant hdlUsed :: [Int] hdlValid :: BlackBoxContext -> Bool qsysUsed :: [Int] altpllTF :: TemplateFunction altpllQsysTF :: TemplateFunction alteraPllTF :: TemplateFunction alteraPllQsysTF :: TemplateFunction hdlTemplate :: forall s. Backend s => Variant -> BlackBoxContext -> State s Doc altpllQsysTemplate :: Backend s => BlackBoxContext -> State s Doc alteraPllQsysTemplate :: Backend s => BlackBoxContext -> State s Doc -- | Module that connects all the parts of the Clash compiler library module Clash.Driver -- | Worker function of splitTopEntityT splitTopAnn :: TyConMap -> SrcSpan -> Type -> TopEntity -> TopEntity splitTopEntityT :: HasCallStack => TyConMap -> BindingMap -> TopEntityT -> TopEntityT -- | Remove constraints such as 'a ~ 3'. removeForAll :: TopEntityT -> TopEntityT -- | Given a list of all found top entities and _maybe_ a top entity -- (+dependencies) passed in by '-main-is', return the list of top -- entities Clash needs to compile. selectTopEntities :: [TopEntityT] -> Maybe (TopEntityT, [TopEntityT]) -> [TopEntityT] -- | Get modification data of current clash binary. getClashModificationDate :: IO UTCTime hdlFromBackend :: forall backend. Backend backend => Proxy backend -> HDL replaceChar :: Char -> Char -> String -> String removeHistoryFile :: Maybe FilePath -> IO () prefixModuleName :: HDL -> Maybe Text -> Maybe TopEntity -> String -> (String, Maybe String) -- | Create a set of target HDL files for a set of functions generateHDL :: forall backend. Backend backend => ClashEnv -> ClashDesign -> Maybe backend -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Evaluator -> Evaluator -> Maybe (TopEntityT, [TopEntityT]) -> UTCTime -> IO () -- | Interpret a specific function from a specific module. This action -- tries two things: -- --
    --
  1. Interpret without explicitly loading the module. This will succeed -- if the module was already loaded through a package database (set using -- interpreterArgs).
  2. --
  3. If (1) fails, it does try to load it explicitly. If this also -- fails, an error is returned.
  4. --
loadImportAndInterpret :: (MonadIO m, MonadMask m) => [String] -> [String] -> String -> ModuleName -> String -> String -> m (Either (NonEmpty InterpreterError) a) -- | List of known BlackBoxFunctions used to prevent Hint from firing. This -- improves Clash startup times. knownBlackBoxFunctions :: HashMap String BlackBoxFunction -- | List of known TemplateFunctions used to prevent Hint from firing. This -- improves Clash startup times. knownTemplateFunctions :: HashMap String TemplateFunction -- | Compiles blackbox functions and parses blackbox templates. compilePrimitive :: [FilePath] -> [FilePath] -> FilePath -> ResolvedPrimitive -> IO CompiledPrimitive newtype HintError HintError :: String -> HintError processHintErrors :: (MonadThrow m, Monad m) => String -> Text -> Either (NonEmpty InterpreterError) t -> m t -- | Pretty print Components to HDL Documents createHDL :: Backend backend => backend -> ClashOpts -> IdentifierText -> IdentifierSet -> ComponentMap -> HashMap Text VDomainConfiguration -> Component -> IdentifierText -> ([(String, Doc)], [(String, FilePath)], [(String, String)]) writeEdam :: FilePath -> (Identifier, Unique) -> HashMap Unique [Unique] -> HashMap Unique [EdamFile] -> [(FilePath, ByteString)] -> IO (HashMap Unique [EdamFile], [(FilePath, ByteString)]) -- | Create an Edalize metadata file for using Edalize to build the -- project. -- -- TODO: Handle libraries. Also see: -- https://github.com/olofk/edalize/issues/220 createEDAM :: (Identifier, Unique) -> HashMap Unique [Unique] -> HashMap Unique [EdamFile] -> [FilePath] -> (HashMap Unique [EdamFile], Edam) asEdamFile :: Identifier -> FilePath -> EdamFile -- | Prepares directory for writing HDL files. prepareDir :: FilePath -> ClashOpts -> Maybe [UnexpectedModification] -> IO () -- | Write a file to disk in chunks. Returns SHA256 sum of file contents. writeAndHash :: FilePath -> ByteString -> IO ByteString -- | Writes a HDL file to the given directory. Returns SHA256 hash of -- written file. writeHDL :: FilePath -> (FilePath, Doc) -> IO ByteString -- | Copy given files writeMemoryDataFiles :: FilePath -> [(FilePath, String)] -> IO [ByteString] -- | Copy data files added with ~FILE copyDataFiles :: [FilePath] -> FilePath -> [(FilePath, FilePath)] -> IO [ByteString] -- | Normalize a complete hierarchy normalizeEntity :: ClashEnv -> BindingMap -> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))) -> Evaluator -> Evaluator -> [Id] -> Supply -> Id -> IO BindingMap -- | Reverse topologically sort given top entities. Also returns a mapping -- that maps a top entity to its reverse topologically sorted transitive -- dependencies. sortTop :: BindingMap -> [TopEntityT] -> ([TopEntityT], HashMap Unique [Unique]) instance GHC.Exception.Type.Exception Clash.Driver.HintError instance GHC.Show.Show Clash.Driver.HintError module Clash.Primitives.Annotations.SynthesisAttributes usedArguments :: [Int] annotateBBF :: HasCallStack => BlackBoxFunction annotateTF :: HasCallStack => KnownNat n => Vec n (Attr Text) -> TemplateFunction annotateBBTF :: (Backend s, KnownNat n, HasCallStack) => Vec n (Attr Text) -> BlackBoxContext -> State s Doc -- | Functions for expression manipulation module Clash.Netlist.Expr -- | Turns a constant expression of known bitsize into their corresponding -- bitstream representation, arranged as a tree that corresponds to the -- structure of the expression. -- -- NOTE: This conversion serves as a best effort approach and can be -- considered a hack. Fully featured constant expression evaluation is -- not available in clash yet and will replace this implementation once -- it is officially supported. bits :: HasCallStack => Size -> Expr -> Either Expr (Tree [Bool]) -- | Turns values into bitstreams of known length. If the bit stream -- requires more bits for representing the given value, then only the -- suffix of the corresponding bitstream gets returned. toBits :: Bits a => Int -> a -> [Bool] -- | Turns bitstreams into values. fromBits :: Bits a => [Bool] -> a -- | Generate SystemVerilog for assorted Netlist datatypes module Clash.Backend.SystemVerilog -- | State for the SystemVerilogM monad: data SystemVerilogState instance Clash.Netlist.Types.HasIdentifierSet Clash.Backend.SystemVerilog.SystemVerilogState instance Clash.Backend.HasUsageMap Clash.Backend.SystemVerilog.SystemVerilogState instance Clash.Backend.Backend Clash.Backend.SystemVerilog.SystemVerilogState