clash-lib-0.99.2: CAES Language for Synchronous Hardware - As a Library

Copyright(C) 2012-2016 University of Twente
2017 Google Inc. Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Netlist.Util

Contents

Description

Utilities for converting Core Type/Term to Netlist datatypes

Synopsis

Documentation

splitNormalized :: Fresh m => HashMap TyConOccName TyCon -> Term -> m (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 is the term was not in a normalized form.

unsafeCoreTypeToHWType :: SrcSpan -> String -> (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> HashMap TyConOccName TyCon -> Bool -> Type -> HWType Source #

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 #

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

coreTypeToHWTypeM :: Type -> NetlistMonad (Maybe HWType) Source #

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

synchronizedClk Source #

Arguments

:: HashMap TyConOccName TyCon

TyCon cache

-> Type 
-> Maybe (Identifier, Integer) 

Returns the name and period of the clock corresponding to a type

coreTypeToHWType :: (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> HashMap TyConOccName TyCon -> Bool -> Type -> Either String HWType Source #

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.

mkADT Source #

Arguments

:: (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType))

Hardcoded Type -> HWType translator

-> HashMap TyConOccName TyCon

TyCon cache

-> String

String representation of the Core type for error messages

-> Bool

Keep Void

-> TyConName

The TyCon

-> [Type]

Its applied arguments

-> Either String HWType 

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

isRecursiveTy :: HashMap TyConOccName TyCon -> TyConName -> Bool Source #

Simple check if a TyCon is recursively defined.

representableType Source #

Arguments

:: (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) 
-> Bool

Allow zero-bit things

-> Bool

String considered representable

-> HashMap TyConOccName TyCon 
-> 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

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 :: Term -> NetlistMonad (Maybe HWType) Source #

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

mkUniqueNormalized :: Maybe (Maybe TopEntity) -> ([Id], [LetBinding], Id) -> NetlistMonad ([(Identifier, HWType)], [Declaration], [(Identifier, HWType)], [Declaration], [LetBinding], TmName) Source #

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

mkUnique Source #

Arguments

:: [(TmOccName, Term)]

Existing substitution

-> [Id]

IDs to make unique

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

(Unique IDs, update substitution)

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

preserveVarEnv :: NetlistMonad a -> NetlistMonad a Source #

Preserve the Netlist _varEnv and _varCount when executing a monadic action

TopEntity Annotations

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

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

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

Generate output port mappings

mkTopUnWrapper Source #

Arguments

:: TmName

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

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

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