clash-lib-1.2.5: CAES Language for Synchronous Hardware - As a Library
Copyright(C) 2012-2016 University of Twente
2017 Myrtle Software Ltd
2017-2018 Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Netlist.Util

Description

Utilities for converting Core Type/Term to Netlist datatypes

Synopsis

Documentation

stripFiltered :: FilteredHWType -> HWType Source #

Throw away information indicating which constructor fields were filtered due to being void.

stripVoid :: HWType -> HWType Source #

Strip as many Void layers as possible. Might still return a Void if the void doesn't contain a hwtype.

isVoid :: HWType -> Bool Source #

Determines if type is a zero-width construct ("void")

isFilteredVoid :: FilteredHWType -> Bool Source #

Same as isVoid, but on FilteredHWType instead of HWType

splitNormalized :: TyConMap -> Term -> Either String ([Id], [LetBinding], Id) Source #

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.

unsafeCoreTypeToHWType' Source #

Arguments

:: SrcSpan

Approximate location in original source file

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

Same as unsafeCoreTypeToHWType, but discards void filter information

unsafeCoreTypeToHWType Source #

Arguments

:: SrcSpan

Approximate location in original source file

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

Converts a Core type to a HWType given a function that translates certain builtin types. Errors if the Core type is not translatable.

unsafeCoreTypeToHWTypeM' :: String -> Type -> NetlistMonad HWType Source #

Same as unsafeCoreTypeToHWTypeM, but discards void filter information

unsafeCoreTypeToHWTypeM :: String -> Type -> NetlistMonad FilteredHWType Source #

Converts a Core type to a HWType within the NetlistMonad; errors on failure

coreTypeToHWTypeM' Source #

Arguments

:: Type

Type to convert to HWType

-> NetlistMonad (Maybe HWType) 

Same as coreTypeToHWTypeM, but discards void filter information

coreTypeToHWTypeM Source #

Arguments

:: Type

Type to convert to HWType

-> NetlistMonad (Maybe FilteredHWType) 

Converts a Core type to a HWType within the NetlistMonad; Nothing on failure

unexpectedProjectionErrorMsg Source #

Arguments

:: DataRepr' 
-> Int

Constructor index

-> Int

Field index

-> String 

Constructs error message for unexpected projections out of a type annotated with a custom bit representation.

convertToCustomRepr :: HasCallStack => CustomReprs -> DataRepr' -> HWType -> HWType Source #

Helper function of maybeConvertToCustomRepr

maybeConvertToCustomRepr Source #

Arguments

:: CustomReprs

Map containing all custom representations index on its type

-> Type

Custom reprs are index on type, so we need the clash core type to look it up.

-> HWType

Type of previous argument represented as a 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.

coreTypeToHWType' Source #

Arguments

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

Type to convert to HWType

-> State HWMap (Either String HWType) 

Same as coreTypeToHWType, but discards void filter information

coreTypeToHWType Source #

Arguments

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

Type to convert to HWType

-> State HWMap (Either String FilteredHWType) 

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.

originalIndices Source #

Arguments

:: [Bool]

Were voids. Length must be less than or equal to n.

-> [Int]

Original indices

Generates original indices in list before filtering, given a list of removed indices.

>>> originalIndices [False, False, True, False]
[0,1,3]

mkADT Source #

Arguments

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

Hardcoded Type -> HWType translator

-> CustomReprs 
-> TyConMap

TyCon cache

-> String

String representation of the Core type for error messages

-> TyConName

The TyCon

-> [Type]

Its applied arguments

-> ExceptT String (State HWMap) FilteredHWType

An error string or a tuple with the type and possibly a list of removed arguments.

Converts an algebraic Core type (split into a TyCon and its argument) to a HWType.

hasUnconstrainedExistential :: TyConMap -> DataCon -> Bool Source #

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.

isRecursiveTy :: TyConMap -> TyConName -> Bool Source #

Simple check if a TyCon is recursively defined.

representableType Source #

Arguments

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

String considered representable

-> TyConMap 
-> Type 
-> Bool 

Determines if a Core type is translatable to a HWType given a function that translates certain builtin types.

typeSize :: HWType -> Int Source #

Determines the bitsize of a type. For types that don't get turned into real values in hardware (string, integer) the size is 0.

conSize :: HWType -> Int Source #

Determines the bitsize of the constructor of a type

typeLength :: HWType -> Int Source #

Gives the length of length-indexed types

termHWType :: String -> Term -> NetlistMonad HWType Source #

Gives the HWType corresponding to a term. Returns an error if the term has a Core type that is not translatable to a HWType.

termHWTypeM Source #

Arguments

:: Term

Term to convert to HWType

-> NetlistMonad (Maybe FilteredHWType) 

Gives the HWType corresponding to a term. Returns Nothing if the term has a Core type that is not translatable to a HWType.

collectPortNames' :: [String] -> PortName -> [Identifier] Source #

Helper function of collectPortNames, which operates on a PortName instead of a TopEntity.

collectPortNames :: TopEntity -> [Identifier] Source #

Recursively get all port names from top entity annotations. The result is a list of user defined port names, which should not be used by routines generating unique function names. Only completely qualified names are returned, as it does not (and cannot) account for any implicitly named ports under a PortProduct.

filterVoidPorts :: FilteredHWType -> PortName -> PortName Source #

Remove ports having a void-type from user supplied PortName annotation

mkUniqueNormalized Source #

Arguments

:: HasCallStack 
=> InScopeSet 
-> Maybe (Maybe TopEntity)

Top entity annotation where:

  • Nothing: term is not a top entity
  • Just Nothing: term is a top entity, but has no explicit annotation
  • Just (Just ..): term is a top entity, and has an explicit annotation
-> ([Id], [LetBinding], Id) 
-> NetlistMonad ([Bool], [(Identifier, HWType)], [Declaration], [(Identifier, HWType)], [Declaration], [LetBinding], Maybe Id) 

Uniquely rename all the variables and their references in a normalized term

setBinderName Source #

Arguments

:: Subst

Current substitution

-> Id

The binder for the result

-> Bool

Whether the result binder is referenced by another binder

-> (Id, Subst, [(Id, Term)])
  • The (renamed) binder for the result
  • The updated substitution in case the result binder is renamed
  • A new binding, to assign the result in case the original binder for the result got renamed.
-> (Id, Term)

The binding

-> NetlistMonad ((Id, Subst, [(Id, Term)]), Id) 

Set the name of the binder

Normally, it just keeps the existing name, but there are two exceptions:

  1. It's the binding for the result which is also referenced by another binding; in this case it's suffixed with _rec
  2. The binding binds a primitive that has a name control field
  3. takes priority over 1. Additionally, we create an additional binder when the return value gets a new name.

mkUniqueArguments Source #

Arguments

:: Subst 
-> Maybe (Maybe TopEntity)

Top entity annotation where:

  • Nothing: term is not a top entity
  • Just Nothing: term is a top entity, but has no explicit annotation
  • Just (Just ..): term is a top entity, and has an explicit annotation
-> [Id] 
-> NetlistMonad ([Bool], [(Identifier, HWType)], [Declaration], Subst) 

mkUniqueResult Source #

Arguments

:: Subst 
-> Maybe (Maybe TopEntity)

Top entity annotation where:

  • Nothing: term is not a top entity
  • Just Nothing: term is a top entity, but has no explicit annotation
  • Just (Just ..): term is a top entity, and has an explicit annotation
-> Id 
-> NetlistMonad (Maybe ([(Identifier, HWType)], [Declaration], Id, Subst)) 

idToInPort :: Id -> NetlistMonad (Maybe (Identifier, HWType)) Source #

Same as idToPort, but * Throws an error if the port is a composite type with a BiSignalIn

idToOutPort :: Id -> NetlistMonad (Maybe (Identifier, HWType)) Source #

Same as idToPort, but: * Throws an error if port is of type BiSignalIn

repName :: Text -> Name a -> Name a Source #

mkUnique Source #

Arguments

:: Subst

Existing substitution

-> [Id]

IDs to make unique

-> NetlistMonad ([Id], Subst)

(Unique IDs, update substitution)

Make a set of IDs unique; also returns a substitution from old ID to new updated unique ID.

preserveState :: NetlistMonad a -> NetlistMonad a Source #

Preserve the complete state before running an action, and restore it afterwards.

preserveVarEnv :: NetlistMonad a -> NetlistMonad a Source #

Preserve the Netlist _varCount,_curCompNm,_seenIds when executing a monadic action

TopEntity Annotations

extendPorts :: [PortName] -> [Maybe PortName] Source #

prefixParent :: String -> PortName -> PortName Source #

Prefix given string before portnames except when this string is empty.

uniquePortName :: String -> Identifier -> NetlistMonad Identifier Source #

In addition to the original port name (where the user should assert that it's a valid identifier), we also add the version of the port name that has gone through the 'mkIdentifier Basic' process. Why? so that the provided port name is copied verbatim into the generated HDL, but that in e.g. case-insensitive HDLs, a case-variant of the port name is not used as one of the signal names.

mkVectorChain :: Int -> HWType -> [Expr] -> Expr Source #

Create a Vector chain for a list of Identifiers

mkRTreeChain :: Int -> HWType -> [Expr] -> Expr Source #

Create a RTree chain for a list of Identifiers

stripAttributes :: HWType -> ([Attr'], HWType) Source #

Strips one or more layers of attributes from a HWType; stops at first non-Annotated. Accumilates all attributes of nested annotations.

mkOutput :: Maybe PortName -> (Identifier, HWType) -> NetlistMonad (Maybe ([(Identifier, HWType)], [Declaration], Identifier)) Source #

Generate output port mappings

mkOutput' :: Maybe PortName -> (Identifier, HWType) -> NetlistMonad ([(Identifier, HWType)], [Declaration], Identifier) Source #

Generate output port mappings. Will yield Nothing if the only output is Void.

mkTopUnWrapper Source #

Arguments

:: Id

Name of the TopEntity component

-> Maybe TopEntity

(maybe) a corresponding TopEntity annotation

-> Manifest

a corresponding Manifest

-> (Identifier, HWType)

The name and type of the signal to which to assign the result

-> [(Expr, HWType)]

The arguments

-> [Declaration]

Tick declarations

-> NetlistMonad [Declaration] 

Instantiate a TopEntity, and add the proper type-conversions where needed

argBV Source #

Arguments

:: Maybe Identifier

(maybe) Name of the _TopEntity_

-> Either Identifier (Identifier, HWType)

Either: * A normal argument * An argument with a PortName

-> Expr 
-> Declaration 

Convert between BitVector for an argument

resBV Source #

Arguments

:: Maybe Identifier

(mabye) Name of the _TopEntity_

-> Either Identifier (Identifier, HWType)

Either: * A normal result * A result with a PortName

-> Expr 

Convert between BitVector for the result

doConv Source #

Arguments

:: HWType

We only need it for certain types

-> Maybe (Maybe Identifier)
  • Nothing: No _given_ TopEntity, no need for conversion, this happens when we have a _TestBench_, but no _TopEntity_ annotation.
  • Just Nothing: Converting to/from a BitVector for one of the internally defined types.
  • Just (Just top): Converting to/from a BitVector for one of the types defined by top.
-> Bool
  • True: convert to a BitVector
  • False: convert from a BitVector
-> Expr

The expression on top of which we have to add conversion logic

-> Expr 

Add to/from-BitVector conversion logic

mkTopInput Source #

Arguments

:: Maybe Identifier

(maybe) Name of the _TopEntity_

-> [(Identifier, Identifier)]

Rendered input port names and types

-> Maybe PortName

(maybe) The PortName of a _TopEntity_ annotation for this input

-> (Identifier, HWType) 
-> NetlistMonad ([(Identifier, Identifier)], ([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType))) 

Generate input port mappings for the TopEntity

throwAnnotatedSplitError :: String -> String -> NetlistMonad a Source #

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.

mkTopOutput Source #

Arguments

:: Maybe Identifier

(maybe) Name of the _TopEntity_

-> [(Identifier, Identifier)]

Rendered output port names and types

-> Maybe PortName

(maybe) The PortName of a _TopEntity_ annotation for this output

-> (Identifier, HWType) 
-> NetlistMonad (Maybe ([(Identifier, Identifier)], ([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType)))) 

Generate output port mappings for the TopEntity. Yields Nothing if the output is Void

mkTopOutput' Source #

Arguments

:: Maybe Identifier

(maybe) Name of the _TopEntity_

-> [(Identifier, Identifier)]

Rendered output port names and types

-> Maybe PortName

(maybe) The PortName of a _TopEntity_ annotation for this output

-> (Identifier, HWType) 
-> NetlistMonad ([(Identifier, Identifier)], ([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType))) 

Generate output port mappings for the TopEntity

nestM :: Modifier -> Modifier -> Maybe Modifier Source #

Try to merge nested modifiers into a single modifier, needed by the VHDL and SystemVerilog backend.

bindsExistentials :: [TyVar] -> [Var a] -> Bool Source #

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.

withTicks Source #

Arguments

:: [TickInfo] 
-> ([Declaration] -> NetlistMonad a)

The source ticks are turned into TickDecls and are passed as an argument to the NetlistMonad computation. Name modifier ticks will change the local environment for the NetlistMonad computation.

-> NetlistMonad a 

Run a NetlistMonad computation in the context of the given source ticks and name modifier ticks

affixName :: Identifier -> NetlistMonad Identifier Source #

Add the pre- and suffix names in the current environment to the given identifier