Safe Haskell | None |
---|
Type and instance definitions for Netlist modules
- newtype NetlistMonad a = NetlistMonad {
- runNetlist :: WriterT [(Identifier, HWType)] (StateT NetlistState (FreshMT IO)) a
- type VHDLState = (HashSet HWType, Int, HashMap HWType Doc)
- data NetlistState = NetlistState {}
- type Identifier = Text
- data Component = Component {
- componentName :: Identifier
- hiddenPorts :: [(Identifier, HWType)]
- inputs :: [(Identifier, HWType)]
- output :: (Identifier, HWType)
- declarations :: [Declaration]
- type Size = Int
- data HWType
- = Void
- | Bit
- | Bool
- | Integer
- | Signed Size
- | Unsigned Size
- | Vector Size HWType
- | Sum Identifier [Identifier]
- | Product Identifier [HWType]
- | SP Identifier [(Identifier, [HWType])]
- | Clock Int
- | Reset Int
- data Declaration
- = Assignment Identifier Expr
- | CondAssignment Identifier Expr [(Maybe Expr, Expr)]
- | InstDecl Identifier Identifier [(Identifier, Expr)]
- | BlackBoxD Text
- | NetDecl Identifier HWType (Maybe Expr)
- data Modifier
- data Expr
- data Literal
- data Bit
- vhdlMState :: Lens' NetlistState VHDLState
- varEnv :: Lens' NetlistState Gamma
- varCount :: Lens' NetlistState Int
- typeTranslator :: Lens' NetlistState (Type -> Maybe (Either String HWType))
- primitives :: Lens' NetlistState PrimMap
- components :: Lens' NetlistState (HashMap TmName Component)
- cmpCount :: Lens' NetlistState Int
- bindings :: Lens' NetlistState (HashMap TmName (Type, Term))
Documentation
newtype NetlistMonad a Source
Monad that caches generated components (StateT) and remembers hidden inputs of components that are being generated (WriterT)
NetlistMonad | |
|
Monad NetlistMonad | |
Functor NetlistMonad | |
Applicative NetlistMonad | |
MonadIO NetlistMonad | |
Fresh NetlistMonad | |
MonadState NetlistState NetlistMonad | |
MonadWriter [(Identifier, HWType)] NetlistMonad |
type VHDLState = (HashSet HWType, Int, HashMap HWType Doc)Source
State for the VHDLM
monad:
- Previously encountered HWTypes
- Product type counter
- Cache for previously generated product type names
data NetlistState Source
State of the NetlistMonad
NetlistState | |
|
MonadState NetlistState NetlistMonad |
type Identifier = TextSource
Signal reference
Component: base unit of a Netlist
Component | |
|
Representable hardware types
Void | Empty type |
Bit | Bit type |
Bool | Boolean type |
Integer | Integer type |
Signed Size | Signed integer of a specified size |
Unsigned Size | Unsigned integer of a specified size |
Vector Size HWType | Vector 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 Int | Clock type with specified period |
Reset Int | Reset type corresponding to clock with a specified period |
Eq HWType | |
Show HWType | |
Generic HWType | |
Hashable HWType | |
MonadState VHDLState BlackBoxMonad | |
MonadWriter [(Identifier, HWType)] NetlistMonad | |
MonadWriter [(Identifier, HWType)] BlackBoxMonad |
data Declaration Source
Internals of a Component
Assignment Identifier Expr | Signal assignment:
|
CondAssignment Identifier Expr [(Maybe Expr, Expr)] | Conditional signal assignment:
|
InstDecl Identifier Identifier [(Identifier, Expr)] | Instantiation of another component |
BlackBoxD Text | Instantiation of blackbox declaration |
NetDecl Identifier HWType (Maybe Expr) | Signal declaration |
Expression Modifier
Expression used in RHS of a declaration
Literals used in an expression
typeTranslator :: Lens' NetlistState (Type -> Maybe (Either String HWType))Source