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

Copyright(C) 2012-2016, University of Twente
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

splitNormalized :: (Fresh m, Functor m) => HashMap TyConName 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 :: String -> (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)) -> HashMap TyConName TyCon -> 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 TyConName TyCon

TyCon cache

-> Type 
-> Maybe (Identifier, Integer) 

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

coreTypeToHWType :: (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)) -> HashMap TyConName TyCon -> 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 TyConName TyCon -> Type -> Maybe (Either String HWType))

Hardcoded Type -> HWType translator

-> HashMap TyConName TyCon

TyCon cache

-> String

String representation of the Core type for error messages

-> 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 TyConName TyCon -> TyConName -> Bool Source #

Simple check if a TyCon is recursively defined.

representableType :: (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)) -> HashMap TyConName TyCon -> Type -> Bool Source #

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 :: ([Id], [LetBinding], Id) -> NetlistMonad ([Id], [LetBinding], TmName) Source #

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

mkUnique Source #

Arguments

:: [(Id, Id)]

Existing substitution

-> [Id]

IDs to make unique

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

(Unique IDs, update substitution)

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

appendToName :: TmName -> String -> TmName Source #

Append a string to a name

preserveVarEnv :: NetlistMonad a -> NetlistMonad a Source #

Preserve the Netlist _varEnv and _varCount when executing a monadic action