Copyright | (C) 2012-2016 University of Twente 2017 Google Inc. Myrtle Software Ltd |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Utilities for converting Core Type/Term to Netlist datatypes
Synopsis
- isVoid :: HWType -> Bool
- mkIdentifier :: IdType -> Identifier -> NetlistMonad Identifier
- extendIdentifier :: IdType -> Identifier -> Identifier -> NetlistMonad Identifier
- splitNormalized :: Fresh m => HashMap TyConOccName TyCon -> Term -> m (Either String ([Id], [LetBinding], Id))
- unsafeCoreTypeToHWType :: SrcSpan -> String -> (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> HashMap TyConOccName TyCon -> Bool -> Type -> HWType
- unsafeCoreTypeToHWTypeM :: String -> Type -> NetlistMonad HWType
- coreTypeToHWTypeM :: Type -> NetlistMonad (Maybe HWType)
- synchronizedClk :: HashMap TyConOccName TyCon -> Type -> Maybe (Identifier, Integer)
- coreTypeToHWType :: (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> HashMap TyConOccName TyCon -> Bool -> Type -> Either String HWType
- mkADT :: (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> HashMap TyConOccName TyCon -> String -> Bool -> TyConName -> [Type] -> Either String HWType
- isRecursiveTy :: HashMap TyConOccName TyCon -> TyConName -> Bool
- representableType :: (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> Bool -> Bool -> HashMap TyConOccName TyCon -> Type -> Bool
- typeSize :: HWType -> Int
- conSize :: HWType -> Int
- typeLength :: HWType -> Int
- termHWType :: String -> Term -> NetlistMonad HWType
- termHWTypeM :: Term -> NetlistMonad (Maybe HWType)
- mkUniqueNormalized :: Maybe (Maybe TopEntity) -> ([Id], [LetBinding], Id) -> NetlistMonad ([(Identifier, HWType)], [Declaration], [(Identifier, HWType)], [Declaration], [LetBinding], TmName)
- mkUniqueArguments :: Maybe (Maybe TopEntity) -> [Id] -> NetlistMonad ([(Identifier, HWType)], [Declaration], [(TmOccName, Term)])
- mkUniqueResult :: Maybe (Maybe TopEntity) -> Id -> NetlistMonad ([(Identifier, HWType)], [Declaration], Id, (TmOccName, Term))
- idToPort :: Id -> NetlistMonad (Identifier, HWType)
- repName :: String -> Name a -> Name a
- mkUnique :: [(TmOccName, Term)] -> [Id] -> NetlistMonad ([Id], [(TmOccName, Term)])
- mkUniqueIdentifier :: IdType -> Identifier -> NetlistMonad Identifier
- preserveVarEnv :: NetlistMonad a -> NetlistMonad a
- dcToLiteral :: HWType -> Int -> Literal
- extendPorts :: [PortName] -> [Maybe PortName]
- appendNumber :: (Identifier, HWType) -> Int -> (Identifier, HWType)
- portName :: String -> Identifier -> Identifier
- appendIdentifier :: (Identifier, HWType) -> Int -> NetlistMonad (Identifier, HWType)
- uniquePortName :: String -> Identifier -> NetlistMonad Identifier
- mkInput :: Maybe PortName -> (Identifier, HWType) -> NetlistMonad ([(Identifier, HWType)], [Declaration], Expr, Identifier)
- filterVoid :: HWType -> HWType
- mkVectorChain :: Int -> HWType -> [Expr] -> Expr
- mkRTreeChain :: Int -> HWType -> [Expr] -> Expr
- genComponentName :: [Identifier] -> (IdType -> Identifier -> Identifier) -> TmName -> Identifier
- mkOutput :: Maybe PortName -> (Identifier, HWType) -> NetlistMonad ([(Identifier, HWType)], [Declaration], Identifier)
- mkTopUnWrapper :: TmName -> Maybe TopEntity -> Manifest -> (Identifier, HWType) -> [(Expr, HWType)] -> NetlistMonad [Declaration]
- argBV :: Maybe Identifier -> Either Identifier (Identifier, HWType) -> Expr -> Declaration
- resBV :: Maybe Identifier -> Either Identifier (Identifier, HWType) -> Expr
- doConv :: HWType -> Maybe (Maybe Identifier) -> Bool -> Expr -> Expr
- mkTopInput :: Maybe Identifier -> [(Identifier, Identifier)] -> Maybe PortName -> (Identifier, HWType) -> NetlistMonad ([(Identifier, Identifier)], ([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType)))
- mkTopOutput :: Maybe Identifier -> [(Identifier, Identifier)] -> Maybe PortName -> (Identifier, HWType) -> NetlistMonad ([(Identifier, Identifier)], ([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType)))
- concatPortDecls3 :: [([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType))] -> ([(Identifier, Identifier, HWType)], [Declaration], [Either Identifier (Identifier, HWType)])
Documentation
mkIdentifier :: IdType -> Identifier -> NetlistMonad Identifier Source #
extendIdentifier :: IdType -> Identifier -> Identifier -> NetlistMonad Identifier Source #
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
:: 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.
:: (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.
:: (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.
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
mkUniqueArguments :: Maybe (Maybe TopEntity) -> [Id] -> NetlistMonad ([(Identifier, HWType)], [Declaration], [(TmOccName, Term)]) Source #
mkUniqueResult :: Maybe (Maybe TopEntity) -> Id -> NetlistMonad ([(Identifier, HWType)], [Declaration], Id, (TmOccName, Term)) Source #
idToPort :: Id -> NetlistMonad (Identifier, HWType) Source #
:: [(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 #
appendNumber :: (Identifier, HWType) -> Int -> (Identifier, HWType) Source #
portName :: String -> Identifier -> Identifier Source #
appendIdentifier :: (Identifier, HWType) -> Int -> NetlistMonad (Identifier, HWType) Source #
uniquePortName :: String -> Identifier -> NetlistMonad Identifier Source #
mkInput :: Maybe PortName -> (Identifier, HWType) -> NetlistMonad ([(Identifier, HWType)], [Declaration], Expr, Identifier) Source #
filterVoid :: HWType -> HWType Source #
mkVectorChain :: Int -> HWType -> [Expr] -> Expr Source #
Create a Vector chain for a list of Identifier
s
mkRTreeChain :: Int -> HWType -> [Expr] -> Expr Source #
Create a RTree chain for a list of Identifier
s
genComponentName :: [Identifier] -> (IdType -> Identifier -> Identifier) -> TmName -> Identifier Source #
mkOutput :: Maybe PortName -> (Identifier, HWType) -> NetlistMonad ([(Identifier, HWType)], [Declaration], Identifier) Source #
Generate output port mappings
:: TmName | Name of the TopEntity component |
-> Maybe TopEntity | (maybe) a corresponding |
-> Manifest | a corresponding |
-> (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
:: Maybe Identifier | (maybe) Name of the _TopEntity_ |
-> Either Identifier (Identifier, HWType) | Either:
* A normal argument
* An argument with a |
-> Expr | |
-> Declaration |
Convert between BitVector for an argument
:: Maybe Identifier | (mabye) Name of the _TopEntity_ |
-> Either Identifier (Identifier, HWType) | Either:
* A normal result
* A result with a |
-> Expr |
Convert between BitVector for the result
:: HWType | We only need it for certain types |
-> Maybe (Maybe Identifier) |
|
-> Bool |
|
-> Expr | The expression on top of which we have to add conversion logic |
-> Expr |
Add to/from-BitVector conversion logic
:: Maybe Identifier | (maybe) Name of the _TopEntity_ |
-> [(Identifier, Identifier)] | Rendered input port names and types |
-> Maybe PortName | (maybe) The |
-> (Identifier, HWType) | |
-> NetlistMonad ([(Identifier, Identifier)], ([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType))) |
Generate input port mappings for the TopEntity
:: Maybe Identifier | (maybe) Name of the _TopEntity_ |
-> [(Identifier, Identifier)] | Rendered output port names and types |
-> Maybe PortName | (maybe) The |
-> (Identifier, HWType) | |
-> NetlistMonad ([(Identifier, Identifier)], ([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType))) |
Generate output port mappings for the TopEntity
concatPortDecls3 :: [([(Identifier, Identifier, HWType)], [Declaration], Either Identifier (Identifier, HWType))] -> ([(Identifier, Identifier, HWType)], [Declaration], [Either Identifier (Identifier, HWType)]) Source #