Copyright | (C) 2012-2016 University of Twente 2016-2017 Myrtle Software Ltd 2017 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Create Netlists out of normalized CoreHW Terms
Synopsis
- genNetlist :: BindingMap -> [(TmName, Type, Maybe TopEntity, Maybe TmName)] -> PrimMap BlackBoxTemplate -> HashMap TyConOccName TyCon -> (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> [(String, FilePath)] -> Int -> (IdType -> Identifier -> Identifier) -> (IdType -> Identifier -> Identifier -> Identifier) -> [Identifier] -> FilePath -> TmOccName -> IO ([(SrcSpan, Component)], [(String, FilePath)], [Identifier])
- runNetlistMonad :: BindingMap -> HashMap TmOccName (Type, Maybe TopEntity) -> PrimMap BlackBoxTemplate -> HashMap TyConOccName TyCon -> (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) -> [(String, FilePath)] -> Int -> (IdType -> Identifier -> Identifier) -> (IdType -> Identifier -> Identifier -> Identifier) -> [Identifier] -> FilePath -> NetlistMonad a -> IO (a, NetlistState)
- genNames :: (IdType -> Identifier -> Identifier) -> [Identifier] -> HashMap TmOccName Identifier -> [TmName] -> ([Identifier], HashMap TmOccName Identifier)
- genComponent :: TmOccName -> NetlistMonad (SrcSpan, Component)
- genComponentT :: TmOccName -> Term -> NetlistMonad (SrcSpan, Component)
- mkNetDecl :: (Id, Embed Term) -> NetlistMonad (Maybe Declaration)
- mkDeclarations :: Id -> Term -> NetlistMonad [Declaration]
- mkDeclarations' :: Id -> Term -> NetlistMonad [Declaration]
- mkSelection :: Id -> Term -> Type -> [Alt] -> NetlistMonad [Declaration]
- mkFunApp :: Id -> TmName -> [Term] -> NetlistMonad [Declaration]
- toSimpleVar :: Id -> (Expr, Type) -> NetlistMonad (Expr, [Declaration])
- mkExpr :: Bool -> Either Identifier Id -> Type -> Term -> NetlistMonad (Expr, [Declaration])
- mkProjection :: Bool -> Either Identifier Id -> Term -> Type -> Alt -> NetlistMonad (Expr, [Declaration])
- mkDcApplication :: HWType -> Either Identifier Id -> DataCon -> [Term] -> NetlistMonad (Expr, [Declaration])
Documentation
:: BindingMap | Global binders |
-> [(TmName, Type, Maybe TopEntity, Maybe TmName)] | All the TopEntities |
-> PrimMap BlackBoxTemplate | Primitive definitions |
-> HashMap TyConOccName TyCon | TyCon cache |
-> (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) | Hardcoded Type -> HWType translator |
-> [(String, FilePath)] | Set of collected data-files |
-> Int | IntWordInteger bit-width |
-> (IdType -> Identifier -> Identifier) | valid identifiers |
-> (IdType -> Identifier -> Identifier -> Identifier) | extend valid identifiers |
-> [Identifier] | Seen components |
-> FilePath | HDL dir |
-> TmOccName | Name of the |
-> IO ([(SrcSpan, Component)], [(String, FilePath)], [Identifier]) |
Generate a hierarchical netlist out of a set of global binders with
topEntity
at the top.
:: BindingMap | Global binders |
-> HashMap TmOccName (Type, Maybe TopEntity) | TopEntity annotations |
-> PrimMap BlackBoxTemplate | Primitive Definitions |
-> HashMap TyConOccName TyCon | TyCon cache |
-> (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) | Hardcode Type -> HWType translator |
-> [(String, FilePath)] | Set of collected data-files |
-> Int | IntWordInteger bit-width |
-> (IdType -> Identifier -> Identifier) | valid identifiers |
-> (IdType -> Identifier -> Identifier -> Identifier) | extend valid identifiers |
-> [Identifier] | Seen components |
-> FilePath | HDL dir |
-> NetlistMonad a | Action to run |
-> IO (a, NetlistState) |
Run a NetlistMonad action in a given environment
genNames :: (IdType -> Identifier -> Identifier) -> [Identifier] -> HashMap TmOccName Identifier -> [TmName] -> ([Identifier], HashMap TmOccName Identifier) Source #
:: TmOccName | Name of the function |
-> NetlistMonad (SrcSpan, Component) |
Generate a component for a given function (caching)
:: TmOccName | Name of the function |
-> Term | Corresponding term |
-> NetlistMonad (SrcSpan, Component) |
Generate a component for a given function
mkNetDecl :: (Id, Embed Term) -> NetlistMonad (Maybe Declaration) Source #
:: 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
:: Id | LHS of the let-binder |
-> Term | RHS of the let-binder |
-> NetlistMonad [Declaration] |
Generate a list of Declarations for a let-binder
mkSelection :: Id -> Term -> Type -> [Alt] -> NetlistMonad [Declaration] Source #
Generate a declaration that selects an alternative based on the value of the scrutinee
:: Id | LHS of the let-binder |
-> TmName | Name of the applied function |
-> [Term] | Function arguments |
-> NetlistMonad [Declaration] |
Generate a list of Declarations for a let-binder where the RHS is a function application
toSimpleVar :: Id -> (Expr, Type) -> NetlistMonad (Expr, [Declaration]) Source #
:: Bool | Treat BlackBox expression as declaration |
-> Either Identifier Id | Id to assign the result to |
-> Type | Type of the LHS of the let-binder |
-> 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
:: Bool | Projection must bind to a simple variable |
-> Either Identifier Id | 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.
:: HWType | HWType of the LHS of the let-binder |
-> Either Identifier Id | Id to assign the result to |
-> 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