Copyright | (C) 2012-2016 University of Twente 2017 Myrtle Software Ltd Google Inc. |
---|---|
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
Synopsis
- data Declaration where
- Assignment !Identifier !Expr
- CondAssignment !Identifier !HWType !Expr !HWType [(Maybe Literal, Expr)]
- InstDecl (Maybe Identifier) !Identifier !Identifier [(Expr, PortDirection, HWType, Expr)]
- BlackBoxD !Text [BlackBoxTemplate] [BlackBoxTemplate] (Maybe ((Text, Text), BlackBoxTemplate)) !BlackBoxTemplate BlackBoxContext
- NetDecl' (Maybe Identifier) WireOrReg !Identifier (Either Identifier HWType)
- pattern NetDecl :: Maybe Identifier -> Identifier -> HWType -> Declaration
- data BlackBoxContext = Context {
- bbResult :: (Expr, HWType)
- bbInputs :: [(Expr, HWType, Bool)]
- bbFunctions :: IntMap (Either BlackBoxTemplate (Identifier, [Declaration]), WireOrReg, [BlackBoxTemplate], [BlackBoxTemplate], Maybe ((Text, Text), BlackBoxTemplate), BlackBoxContext)
- bbQsysIncName :: Maybe Identifier
- bbLevel :: Int
- data Bit
- data Literal
- data Expr
- = Literal !(Maybe (HWType, Size)) !Literal
- | DataCon !HWType !Modifier [Expr]
- | Identifier !Identifier !(Maybe Modifier)
- | DataTag !HWType !(Either Identifier Identifier)
- | BlackBoxE !Text [BlackBoxTemplate] [BlackBoxTemplate] (Maybe ((Text, Text), BlackBoxTemplate)) !BlackBoxTemplate !BlackBoxContext !Bool
- | ConvBV (Maybe Identifier) HWType Bool Expr
- data Modifier
- data PortDirection
- data WireOrReg
- data Declaration
- = Assignment !Identifier !Expr
- | CondAssignment !Identifier !HWType !Expr !HWType [(Maybe Literal, Expr)]
- | InstDecl (Maybe Identifier) !Identifier !Identifier [(Expr, PortDirection, HWType, Expr)]
- | BlackBoxD !Text [BlackBoxTemplate] [BlackBoxTemplate] (Maybe ((Text, Text), BlackBoxTemplate)) !BlackBoxTemplate BlackBoxContext
- | NetDecl' (Maybe Identifier) WireOrReg !Identifier (Either Identifier HWType)
- data HWType
- = Void (Maybe HWType)
- | String
- | Bool
- | Bit
- | 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 !ClockKind
- | Reset !Identifier !Integer !ResetKind
- type Size = Int
- data Component = Component {
- componentName :: !Identifier
- inputs :: [(Identifier, HWType)]
- outputs :: [(WireOrReg, (Identifier, HWType))]
- declarations :: [Declaration]
- type Identifier = Text
- data NetlistState = NetlistState {
- _bindings :: BindingMap
- _varCount :: !Int
- _components :: HashMap TmOccName (SrcSpan, Component)
- _primitives :: PrimMap BlackBoxTemplate
- _typeTranslator :: HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)
- _tcCache :: HashMap TyConOccName TyCon
- _curCompNm :: !(Identifier, SrcSpan)
- _dataFiles :: [(String, FilePath)]
- _intWidth :: Int
- _mkIdentifierFn :: IdType -> Identifier -> Identifier
- _extendIdentifierFn :: IdType -> Identifier -> Identifier -> Identifier
- _seenIds :: [Identifier]
- _seenComps :: [Identifier]
- _componentNames :: HashMap TmOccName Identifier
- _topEntityAnns :: HashMap TmOccName (Type, Maybe TopEntity)
- _hdlDir :: FilePath
- _curBBlvl :: Int
- newtype NetlistMonad a = NetlistMonad {
- runNetlist :: StateT NetlistState (FreshMT IO) a
- pattern NetDecl :: Maybe Identifier -> Identifier -> HWType -> Declaration
- emptyBBContext :: BlackBoxContext
- bindings :: Lens' NetlistState BindingMap
- componentNames :: Lens' NetlistState (HashMap TmOccName Identifier)
- components :: Lens' NetlistState (HashMap TmOccName (SrcSpan, Component))
- curBBlvl :: Lens' NetlistState Int
- curCompNm :: Lens' NetlistState (Identifier, SrcSpan)
- dataFiles :: Lens' NetlistState [(String, FilePath)]
- extendIdentifierFn :: Lens' NetlistState (IdType -> Identifier -> Identifier -> Identifier)
- hdlDir :: Lens' NetlistState FilePath
- intWidth :: Lens' NetlistState Int
- mkIdentifierFn :: Lens' NetlistState (IdType -> Identifier -> Identifier)
- primitives :: Lens' NetlistState (PrimMap BlackBoxTemplate)
- seenComps :: Lens' NetlistState [Identifier]
- seenIds :: Lens' NetlistState [Identifier]
- tcCache :: Lens' NetlistState (HashMap TyConOccName TyCon)
- topEntityAnns :: Lens' NetlistState (HashMap TmOccName (Type, Maybe TopEntity))
- typeTranslator :: Lens' NetlistState (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType))
- varCount :: Lens' NetlistState Int
Documentation
data Declaration Source #
Internals of a Component
Assignment !Identifier !Expr | Signal assignment:
|
CondAssignment !Identifier !HWType !Expr !HWType [(Maybe Literal, Expr)] | Conditional signal assignment:
|
InstDecl (Maybe Identifier) !Identifier !Identifier [(Expr, PortDirection, HWType, Expr)] | Instantiation of another component |
BlackBoxD !Text [BlackBoxTemplate] [BlackBoxTemplate] (Maybe ((Text, Text), BlackBoxTemplate)) !BlackBoxTemplate BlackBoxContext | Instantiation of blackbox declaration |
NetDecl' (Maybe Identifier) WireOrReg !Identifier (Either Identifier HWType) | Signal declaration |
pattern NetDecl :: Maybe Identifier -> Identifier -> HWType -> Declaration |
Instances
Show Declaration Source # | |
showsPrec :: Int -> Declaration -> ShowS # show :: Declaration -> String # showList :: [Declaration] -> ShowS # | |
NFData Declaration Source # | |
rnf :: Declaration -> () # |
data BlackBoxContext Source #
Context used to fill in the holes of a BlackBox template
Context | |
|
Instances
Show BlackBoxContext Source # | |
showsPrec :: Int -> BlackBoxContext -> ShowS # show :: BlackBoxContext -> String # showList :: [BlackBoxContext] -> ShowS # |
Bit literal
Literals used in an expression
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 [BlackBoxTemplate] [BlackBoxTemplate] (Maybe ((Text, Text), BlackBoxTemplate)) !BlackBoxTemplate !BlackBoxContext !Bool | Instantiation of a BlackBox expression |
ConvBV (Maybe Identifier) HWType Bool Expr |
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 |
Nested Modifier Modifier |
data PortDirection Source #
Instances
Show PortDirection Source # | |
showsPrec :: Int -> PortDirection -> ShowS # show :: PortDirection -> String # showList :: [PortDirection] -> ShowS # |
data Declaration Source #
Internals of a Component
Assignment !Identifier !Expr | Signal assignment:
|
CondAssignment !Identifier !HWType !Expr !HWType [(Maybe Literal, Expr)] | Conditional signal assignment:
|
InstDecl (Maybe Identifier) !Identifier !Identifier [(Expr, PortDirection, HWType, Expr)] | Instantiation of another component |
BlackBoxD !Text [BlackBoxTemplate] [BlackBoxTemplate] (Maybe ((Text, Text), BlackBoxTemplate)) !BlackBoxTemplate BlackBoxContext | Instantiation of blackbox declaration |
NetDecl' (Maybe Identifier) WireOrReg !Identifier (Either Identifier HWType) | Signal declaration |
Instances
Show Declaration Source # | |
showsPrec :: Int -> Declaration -> ShowS # show :: Declaration -> String # showList :: [Declaration] -> ShowS # | |
NFData Declaration Source # | |
rnf :: Declaration -> () # |
Representable hardware types
Void (Maybe HWType) | Empty type. |
String | String type |
Bool | Boolean type |
Bit | Bit 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 !ClockKind | Clock type with specified name and period |
Reset !Identifier !Integer !ResetKind | Reset type corresponding to clock with a specified name and period |
Instances
Component: base unit of a Netlist
Component | |
|
type Identifier = Text Source #
Signal reference
data NetlistState Source #
State of the NetlistMonad
NetlistState | |
|
Instances
MonadState NetlistState NetlistMonad Source # | |
get :: NetlistMonad NetlistState # put :: NetlistState -> NetlistMonad () # state :: (NetlistState -> (a, NetlistState)) -> NetlistMonad a # |
newtype NetlistMonad a Source #
Monad that caches generated components (StateT) and remembers hidden inputs of components that are being generated (WriterT)
Instances
pattern NetDecl :: Maybe Identifier -> Identifier -> HWType -> Declaration Source #
extendIdentifierFn :: Lens' NetlistState (IdType -> Identifier -> Identifier -> Identifier) Source #
mkIdentifierFn :: Lens' NetlistState (IdType -> Identifier -> Identifier) Source #
typeTranslator :: Lens' NetlistState (HashMap TyConOccName TyCon -> Bool -> Type -> Maybe (Either String HWType)) Source #