clash-lib-1.5.0: Clash: a functional hardware description language - As a library
Copyright(C) 2012-2016 University of Twente
2016-2017 Myrtle Software Ltd
2017-2018 Google Inc.
2021-2022 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Netlist

Description

Create Netlists out of normalized CoreHW Terms

Synopsis

Documentation

genNetlist Source #

Arguments

:: ClashEnv 
-> Bool

Whether this we're compiling a testbench (suppresses certain warnings)

-> BindingMap

Global binders

-> VarEnv TopEntityT

TopEntity annotations

-> VarEnv Identifier

Top entity names

-> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType)))

Hardcoded Type -> HWType translator

-> Bool

Whether the backend supports ifThenElse expressions

-> SomeBackend

The current HDL backend

-> IdentifierSet

Seen components

-> FilePath

HDL dir

-> Maybe Text

Component name prefix

-> Id

Name of the topEntity

-> IO (Component, ComponentMap, IdentifierSet) 

Generate a hierarchical netlist out of a set of global binders with topEntity at the top.

runNetlistMonad Source #

Arguments

:: Bool

Whether this we're compiling a testbench (suppresses certain warnings)

-> ClashOpts

Options Clash was called with

-> CustomReprs

Custom bit representations for certain types

-> BindingMap

Global binders

-> VarEnv TopEntityT

TopEntity annotations

-> CompiledPrimMap

Primitive Definitions

-> TyConMap

TyCon cache

-> (CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType)))

Hardcode Type -> HWType translator

-> Int

IntWordInteger bit-width

-> Bool

Whether the backend supports ifThenElse expressions

-> SomeBackend

The current HDL backend

-> IdentifierSet

Seen components

-> FilePath

HDL dir

-> VarEnv Identifier

Seen components

-> NetlistMonad a

Action to run

-> IO (a, NetlistState) 

Run a NetlistMonad action in a given environment

genNames Source #

Arguments

:: Bool

New inline strategy enabled?

-> Maybe Text

Prefix

-> IdentifierSet

Identifier set to extend

-> VarEnv Identifier

Pre-generated names

-> BindingMap 
-> (VarEnv Identifier, IdentifierSet) 

Generate names for all binders in BindingMap, except for the ones already present in given identifier varenv.

genTopNames Source #

Arguments

:: ClashOpts 
-> HDL

HDL to generate identifiers for

-> [TopEntityT] 
-> (VarEnv Identifier, IdentifierSet) 

Generate names for top entities. Should be executed at the very start of the synthesis process and shared between all passes.

genComponent Source #

Arguments

:: HasCallStack 
=> Id

Name of the function

-> NetlistMonad (ComponentMeta, Component) 

Generate a component for a given function (caching)

genComponentT Source #

Arguments

:: HasCallStack 
=> Id

Name of the function

-> Term

Corresponding term

-> NetlistMonad (ComponentMeta, Component) 

Generate a component for a given function

mkDeclarations Source #

Arguments

:: HasCallStack 
=> Id

LHS of the let-binder

-> Term

RHS of the let-binder

-> 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' Source #

Arguments

:: HasCallStack 
=> DeclarationType

Concurrent of sequential declaration

-> Id

LHS of the let-binder

-> Term

RHS of the let-binder

-> NetlistMonad [Declaration] 

Generate a list of Declarations for a let-binder, return an empty list if the bound expression is represented by 0 bits

mkSelection :: DeclarationType -> NetlistId -> Term -> Type -> [Alt] -> [Declaration] -> NetlistMonad [Declaration] Source #

Generate a declaration that selects an alternative based on the value of the scrutinee

reorderCustom :: TyConMap -> CustomReprs -> Type -> [(Pat, Term)] -> [(Pat, Term)] Source #

patPos :: CustomReprs -> Pat -> Int Source #

mkFunApp Source #

Arguments

:: HasCallStack 
=> Identifier

LHS of the let-binder

-> Id

Name of the applied function

-> [Term]

Function arguments

-> [Declaration]

Tick declarations

-> NetlistMonad [Declaration] 

Generate a list of Declarations for a let-binder where the RHS is a function application

mkExpr Source #

Arguments

:: HasCallStack 
=> Bool

Treat BlackBox expression as declaration

-> DeclarationType

Should the returned declarations be concurrent or sequential?

-> NetlistId

Name hint for the id to (potentially) assign the result to

-> Term

Term to convert to an expression

-> NetlistMonad (Expr, [Declaration])

Returned expression and a list of generate BlackBox declarations

Generate an expression for a term occurring on the RHS of a let-binder

mkProjection Source #

Arguments

:: Bool

Projection must bind to a simple variable

-> NetlistId

Name hint for the signal to which the projection is (potentially) assigned

-> Term

The subject/scrutinee of the projection

-> Type

The type of the result

-> Alt

The field to be projected

-> 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.

mkDcApplication Source #

Arguments

:: HasCallStack 
=> [HWType]

HWType of the LHS of the let-binder, can multiple types when we're creating a "split" product type (e.g. a tuple of a Clock and Reset)

-> NetlistId

Name hint for result id

-> DataCon

Applied DataCon

-> [Term]

DataCon Arguments

-> NetlistMonad (Expr, [Declaration])

Returned expression and a list of generate BlackBox declarations

Generate an expression for a DataCon application occurring on the RHS of a let-binder