Copyright | (C) 2012-2016 University of Twente |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Type and instance definitions for Netlist modules
- newtype NetlistMonad a = NetlistMonad {
- runNetlist :: WriterT (Set (Identifier, HWType)) (StateT NetlistState (FreshMT IO)) a
- data NetlistState = NetlistState {
- _bindings :: HashMap TmName (Type, SrcSpan, Term)
- _varEnv :: Gamma
- _varCount :: !Int
- _components :: HashMap TmName (SrcSpan, Component)
- _primitives :: PrimMap BlackBoxTemplate
- _typeTranslator :: HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)
- _tcCache :: HashMap TyConName TyCon
- _curCompNm :: !(Identifier, SrcSpan)
- _dataFiles :: [(String, FilePath)]
- _intWidth :: Int
- _mkBasicIdFn :: Identifier -> Identifier
- _seenIds :: [Identifier]
- _seenComps :: [Identifier]
- _componentNames :: HashMap TmName Identifier
- type Identifier = Text
- data Component = Component {
- componentName :: !Identifier
- hiddenPorts :: [(Identifier, HWType)]
- inputs :: [(Identifier, HWType)]
- outputs :: [(Identifier, HWType)]
- declarations :: [Declaration]
- type Size = Int
- data HWType
- = Void
- | String
- | Bool
- | BitVector !Size
- | Index !Integer
- | Signed !Size
- | Unsigned !Size
- | Vector !Size !HWType
- | RTree !Size !HWType
- | Sum !Identifier [Identifier]
- | Product !Identifier [HWType]
- | SP !Identifier [(Identifier, [HWType])]
- | Clock !Identifier !Integer
- | Reset !Identifier !Integer
- data Declaration
- = Assignment !Identifier !Expr
- | CondAssignment !Identifier !HWType !Expr !HWType [(Maybe Literal, Expr)]
- | InstDecl !Identifier !Identifier [(Identifier, PortDirection, HWType, Expr)]
- | BlackBoxD !Text [Text] [Text] (Maybe (Text, BlackBoxTemplate)) !BlackBoxTemplate BlackBoxContext
- | NetDecl !Identifier !HWType
- data PortDirection
- data Modifier
- data Expr
- = Literal !(Maybe (HWType, Size)) !Literal
- | DataCon !HWType !Modifier [Expr]
- | Identifier !Identifier !(Maybe Modifier)
- | DataTag !HWType !(Either Identifier Identifier)
- | BlackBoxE !Text [Text] [Text] (Maybe (Text, BlackBoxTemplate)) !BlackBoxTemplate !BlackBoxContext !Bool
- data Literal
- data Bit
- data BlackBoxContext = Context {
- bbResult :: (SyncExpr, HWType)
- bbInputs :: [(SyncExpr, HWType, Bool)]
- bbFunctions :: IntMap (Either BlackBoxTemplate Declaration, BlackBoxContext)
- bbQsysIncName :: Maybe Identifier
- emptyBBContext :: BlackBoxContext
- type SyncIdentifier = Either Identifier (Identifier, (Identifier, Int))
- type SyncExpr = Either Expr (Expr, (Identifier, Integer))
- varEnv :: Lens' NetlistState Gamma
- varCount :: Lens' NetlistState Int
- typeTranslator :: Lens' NetlistState (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType))
- tcCache :: Lens' NetlistState (HashMap TyConName TyCon)
- seenIds :: Lens' NetlistState [Identifier]
- seenComps :: Lens' NetlistState [Identifier]
- primitives :: Lens' NetlistState (PrimMap BlackBoxTemplate)
- mkBasicIdFn :: Lens' NetlistState (Identifier -> Identifier)
- intWidth :: Lens' NetlistState Int
- dataFiles :: Lens' NetlistState [(String, FilePath)]
- curCompNm :: Lens' NetlistState (Identifier, SrcSpan)
- components :: Lens' NetlistState (HashMap TmName (SrcSpan, Component))
- componentNames :: Lens' NetlistState (HashMap TmName Identifier)
- bindings :: Lens' NetlistState (HashMap TmName (Type, SrcSpan, Term))
Documentation
newtype NetlistMonad a Source #
Monad that caches generated components (StateT) and remembers hidden inputs of components that are being generated (WriterT)
NetlistMonad | |
|
data NetlistState Source #
State of the NetlistMonad
NetlistState | |
|
type Identifier = Text Source #
Signal reference
Component: base unit of a Netlist
Component | |
|
Representable hardware types
Void | Empty type |
String | String type |
Bool | Boolean type |
BitVector !Size | BitVector of a specified size |
Index !Integer | Unsigned integer with specified (exclusive) upper bounder |
Signed !Size | Signed integer of a specified size |
Unsigned !Size | Unsigned integer of a specified size |
Vector !Size !HWType | Vector type |
RTree !Size !HWType | RTree type |
Sum !Identifier [Identifier] | Sum type: Name and Constructor names |
Product !Identifier [HWType] | Product type: Name and field types |
SP !Identifier [(Identifier, [HWType])] | Sum-of-Product type: Name and Constructor names + field types |
Clock !Identifier !Integer | Clock type with specified name and period |
Reset !Identifier !Integer | Reset type corresponding to clock with a specified name and period |
data Declaration Source #
Internals of a Component
Assignment !Identifier !Expr | Signal assignment:
|
CondAssignment !Identifier !HWType !Expr !HWType [(Maybe Literal, Expr)] | Conditional signal assignment:
|
InstDecl !Identifier !Identifier [(Identifier, PortDirection, HWType, Expr)] | Instantiation of another component |
BlackBoxD !Text [Text] [Text] (Maybe (Text, BlackBoxTemplate)) !BlackBoxTemplate BlackBoxContext | Instantiation of blackbox declaration |
NetDecl !Identifier !HWType | Signal declaration |
Expression Modifier
Indexed (HWType, Int, Int) | Index the expression: (Type of expression,DataCon tag,Field Tag) |
DC (HWType, Int) | See expression in a DataCon context: (Type of the expression, DataCon tag) |
VecAppend | See the expression in the context of a Vector append operation |
RTreeAppend | See the expression in the context of a Tree append operation |
Expression used in RHS of a declaration
Literal !(Maybe (HWType, Size)) !Literal | Literal expression |
DataCon !HWType !Modifier [Expr] | DataCon application |
Identifier !Identifier !(Maybe Modifier) | Signal reference |
DataTag !HWType !(Either Identifier Identifier) | |
BlackBoxE !Text [Text] [Text] (Maybe (Text, BlackBoxTemplate)) !BlackBoxTemplate !BlackBoxContext !Bool | Instantiation of a BlackBox expression |
Literals used in an expression
data BlackBoxContext Source #
Context used to fill in the holes of a BlackBox template
Context | |
|
type SyncIdentifier = Either Identifier (Identifier, (Identifier, Int)) Source #
Either the name of the identifier, or a tuple of the identifier and the corresponding clock
typeTranslator :: Lens' NetlistState (HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)) Source #
mkBasicIdFn :: Lens' NetlistState (Identifier -> Identifier) Source #
components :: Lens' NetlistState (HashMap TmName (SrcSpan, Component)) Source #