| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
CLaSH.Netlist.Types
Description
Type and instance definitions for Netlist modules
- newtype NetlistMonad a = NetlistMonad {
- runNetlist :: WriterT [(Identifier, HWType)] (StateT NetlistState (FreshMT IO)) a
- 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
- data Declaration
- data Modifier
- data Expr
- data Literal
- data Bit
- data BlackBoxContext = Context {
- bbResult :: (SyncExpr, HWType)
- bbInputs :: [(SyncExpr, HWType, Bool)]
- bbFunctions :: IntMap (Either BlackBoxTemplate Declaration, BlackBoxContext)
- emptyBBContext :: BlackBoxContext
- type SyncIdentifier = Either Identifier (Identifier, (Identifier, Int))
- type SyncExpr = Either Expr (Expr, (Identifier, Int))
- 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)
- 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)
Constructors
| NetlistMonad | |
Fields
| |
data NetlistState Source
State of the NetlistMonad
Constructors
| NetlistState | |
Fields
| |
Instances
type Identifier = Text Source
Signal reference
Component: base unit of a Netlist
Constructors
| Component | |
Fields
| |
Representable hardware types
Constructors
| Void | Empty type |
| Bool | Boolean type |
| Integer | Integer type |
| BitVector Size | BitVector of a specified size |
| Index Size | 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 |
| 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 |
data Declaration Source
Internals of a Component
Constructors
| 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 BlackBoxTemplate BlackBoxContext | Instantiation of blackbox declaration |
| NetDecl Identifier HWType | Signal declaration |
Instances
Expression Modifier
Expression used in RHS of a declaration
Constructors
| 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 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
Constructors
| Context | |
Fields
| |
Instances
type SyncIdentifier = Either Identifier (Identifier, (Identifier, Int)) Source
Either the name of the identifier, or a tuple of the identifier and the corresponding clock