Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Yosys.Rtl
Description
Yosys RTLIL
Synopsis
- newtype Ident = Ident Text
- data Value = Value Integer [BinaryDigit]
- data BinaryDigit
- data File = File (Maybe AutoIdxStmt) [Module]
- newtype AutoIdxStmt = AutoIdxStmt Integer
- data Module = Module [AttrStmt] ModuleStmt [ModuleBody] ModuleEndStmt
- newtype ModuleStmt = ModuleStmt Ident
- data ModuleBody
- data ParamStmt = ParamStmt Ident (Maybe Constant)
- data Constant
- data ModuleEndStmt = ModuleEndStmt
- data AttrStmt = AttrStmt Ident Constant
- data SigSpec
- data ConnStmt = ConnStmt SigSpec SigSpec
- data Wire = Wire [AttrStmt] WireStmt
- data WireStmt = WireStmt [WireOption] WireId
- newtype WireId = WireId Ident
- data WireOption
- data Memory = Memory [AttrStmt] MemoryStmt
- data MemoryStmt = MemoryStmt [MemoryOption] Ident
- data MemoryOption
- data Cell = Cell [AttrStmt] CellStmt [CellBodyStmt] CellEndStmt
- data CellStmt = CellStmt CellType CellId
- newtype CellId = CellId Ident
- newtype CellType = CellType Ident
- data ParamType
- data CellBodyStmt
- data CellEndStmt = CellEndStmt
- unaryCell :: CellStmt -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- notC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- posC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- negC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- reduceAndC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- reduceOrC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- reduceXorC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- reduceXnorC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- reduceBoolC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- logicNotC :: CellId -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> Cell
- binaryCell :: CellStmt -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- shiftCell :: CellStmt -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- andC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- orC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- xorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- xnorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- shlC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- shrC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- sshlC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- sshrC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- logicAndC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- logicOrC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- eqxC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- nexC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- powC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- ltC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- leC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- eqC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- neC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- geC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- gtC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- addC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- subC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- mulC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- divC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- modC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- divFloorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- modFloorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell
- muxC :: CellId -> Integer -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> Cell
- memRdV2C :: CellId -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> Cell
- memWrV2C :: CellId -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> Cell
- memInitV2C :: CellId -> Constant -> Constant -> Constant -> Constant -> Constant -> SigSpec -> SigSpec -> Cell
- memV2C :: CellId -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> Constant -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> SigSpec -> Cell
- data Process = Process [AttrStmt] ProcStmt ProcessBody ProcEndStmt
- newtype ProcStmt = ProcStmt Ident
- data ProcessBody = ProcessBody [AssignStmt] (Maybe Switch) [AssignStmt] [Sync]
- data AssignStmt = AssignStmt DestSigSpec SrcSigSpec
- newtype DestSigSpec = DestSigSpec SigSpec
- newtype SrcSigSpec = SrcSigSpec SigSpec
- data ProcEndStmt = ProcEndStmt
- data Switch = Switch SwitchStmt [Case] SwitchEndStmt
- data SwitchStmt = SwitchStmt [AttrStmt] SigSpec
- data Case = Case [AttrStmt] CaseStmt CaseBody
- newtype CaseStmt = CaseStmt (Maybe Compare)
- data Compare = Compare SigSpec [SigSpec]
- newtype CaseBody = CaseBody [Either Switch AssignStmt]
- data SwitchEndStmt = SwitchEndStmt
- data Sync = Sync SyncStmt [UpdateStmt]
- data SyncStmt
- data SyncType
- data UpdateStmt = UpdateStmt DestSigSpec SrcSigSpec
Lexical elements
Constructors
Value Integer [BinaryDigit] |
data BinaryDigit Source #
Instances
IsString BinaryDigit Source # | |
Defined in Yosys.Rtl Methods fromString :: String -> BinaryDigit # | |
Read BinaryDigit Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS BinaryDigit # readList :: ReadS [BinaryDigit] # readPrec :: ReadPrec BinaryDigit # readListPrec :: ReadPrec [BinaryDigit] # | |
Show BinaryDigit Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> BinaryDigit -> ShowS # show :: BinaryDigit -> String # showList :: [BinaryDigit] -> ShowS # | |
Eq BinaryDigit Source # | |
Defined in Yosys.Rtl | |
Pretty BinaryDigit Source # | |
Defined in Yosys.Rtl |
File
Constructors
File (Maybe AutoIdxStmt) [Module] |
Autoindex statements
newtype AutoIdxStmt Source #
Constructors
AutoIdxStmt Integer |
Instances
Num AutoIdxStmt Source # | |
Defined in Yosys.Rtl Methods (+) :: AutoIdxStmt -> AutoIdxStmt -> AutoIdxStmt # (-) :: AutoIdxStmt -> AutoIdxStmt -> AutoIdxStmt # (*) :: AutoIdxStmt -> AutoIdxStmt -> AutoIdxStmt # negate :: AutoIdxStmt -> AutoIdxStmt # abs :: AutoIdxStmt -> AutoIdxStmt # signum :: AutoIdxStmt -> AutoIdxStmt # fromInteger :: Integer -> AutoIdxStmt # | |
Read AutoIdxStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS AutoIdxStmt # readList :: ReadS [AutoIdxStmt] # readPrec :: ReadPrec AutoIdxStmt # readListPrec :: ReadPrec [AutoIdxStmt] # | |
Show AutoIdxStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> AutoIdxStmt -> ShowS # show :: AutoIdxStmt -> String # showList :: [AutoIdxStmt] -> ShowS # | |
Eq AutoIdxStmt Source # | |
Defined in Yosys.Rtl | |
Pretty AutoIdxStmt Source # | |
Defined in Yosys.Rtl |
Modules
Constructors
Module [AttrStmt] ModuleStmt [ModuleBody] ModuleEndStmt |
newtype ModuleStmt Source #
Constructors
ModuleStmt Ident |
Instances
IsString ModuleStmt Source # | |
Defined in Yosys.Rtl Methods fromString :: String -> ModuleStmt # | |
Read ModuleStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS ModuleStmt # readList :: ReadS [ModuleStmt] # readPrec :: ReadPrec ModuleStmt # readListPrec :: ReadPrec [ModuleStmt] # | |
Show ModuleStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> ModuleStmt -> ShowS # show :: ModuleStmt -> String # showList :: [ModuleStmt] -> ShowS # | |
Eq ModuleStmt Source # | |
Defined in Yosys.Rtl | |
Pretty ModuleStmt Source # | |
Defined in Yosys.Rtl |
data ModuleBody Source #
Constructors
ModuleBodyParamStmt ParamStmt | |
ModuleBodyWire Wire | |
ModuleBodyMemory Memory | |
ModuleBodyCell Cell | |
ModuleBodyProcess Process | |
ModuleBodyConnStmt ConnStmt |
Instances
Read ModuleBody Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS ModuleBody # readList :: ReadS [ModuleBody] # readPrec :: ReadPrec ModuleBody # readListPrec :: ReadPrec [ModuleBody] # | |
Show ModuleBody Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> ModuleBody -> ShowS # show :: ModuleBody -> String # showList :: [ModuleBody] -> ShowS # | |
Eq ModuleBody Source # | |
Defined in Yosys.Rtl | |
Pretty ModuleBody Source # | |
Defined in Yosys.Rtl |
Constructors
ConstantValue Value | |
ConstantInteger Integer | |
ConstantString Text |
data ModuleEndStmt Source #
Constructors
ModuleEndStmt |
Instances
Read ModuleEndStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS ModuleEndStmt # readList :: ReadS [ModuleEndStmt] # | |
Show ModuleEndStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> ModuleEndStmt -> ShowS # show :: ModuleEndStmt -> String # showList :: [ModuleEndStmt] -> ShowS # | |
Eq ModuleEndStmt Source # | |
Defined in Yosys.Rtl Methods (==) :: ModuleEndStmt -> ModuleEndStmt -> Bool # (/=) :: ModuleEndStmt -> ModuleEndStmt -> Bool # | |
Pretty ModuleEndStmt Source # | |
Defined in Yosys.Rtl |
Attribute statements
Signal specifications
Constructors
SigSpecConstant Constant | |
SigSpecWireId WireId | |
SigSpecSlice SigSpec Integer (Maybe Integer) | |
SigSpecCat [SigSpec] |
Connections
Wires
Constructors
WireStmt [WireOption] WireId |
data WireOption Source #
Constructors
WireOptionWidth Integer | |
WireOptionOffset Integer | |
WireOptionInput Integer | |
WireOptionOutput Integer | |
WireOptionInout Integer | |
WireOptionUpto | |
WireOptionSigned |
Instances
Read WireOption Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS WireOption # readList :: ReadS [WireOption] # readPrec :: ReadPrec WireOption # readListPrec :: ReadPrec [WireOption] # | |
Show WireOption Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> WireOption -> ShowS # show :: WireOption -> String # showList :: [WireOption] -> ShowS # | |
Eq WireOption Source # | |
Defined in Yosys.Rtl | |
Pretty WireOption Source # | |
Defined in Yosys.Rtl |
Memories
Constructors
Memory [AttrStmt] MemoryStmt |
data MemoryStmt Source #
Constructors
MemoryStmt [MemoryOption] Ident |
Instances
Read MemoryStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS MemoryStmt # readList :: ReadS [MemoryStmt] # readPrec :: ReadPrec MemoryStmt # readListPrec :: ReadPrec [MemoryStmt] # | |
Show MemoryStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> MemoryStmt -> ShowS # show :: MemoryStmt -> String # showList :: [MemoryStmt] -> ShowS # | |
Eq MemoryStmt Source # | |
Defined in Yosys.Rtl | |
Pretty MemoryStmt Source # | |
Defined in Yosys.Rtl |
data MemoryOption Source #
Instances
Read MemoryOption Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS MemoryOption # readList :: ReadS [MemoryOption] # | |
Show MemoryOption Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> MemoryOption -> ShowS # show :: MemoryOption -> String # showList :: [MemoryOption] -> ShowS # | |
Eq MemoryOption Source # | |
Defined in Yosys.Rtl | |
Pretty MemoryOption Source # | |
Defined in Yosys.Rtl |
Cells
Constructors
Cell [AttrStmt] CellStmt [CellBodyStmt] CellEndStmt |
data CellBodyStmt Source #
Constructors
CellParameter (Maybe ParamType) Ident Constant | |
CellConnect Ident SigSpec |
Instances
Read CellBodyStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS CellBodyStmt # readList :: ReadS [CellBodyStmt] # | |
Show CellBodyStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> CellBodyStmt -> ShowS # show :: CellBodyStmt -> String # showList :: [CellBodyStmt] -> ShowS # | |
Eq CellBodyStmt Source # | |
Defined in Yosys.Rtl | |
Pretty CellBodyStmt Source # | |
Defined in Yosys.Rtl |
data CellEndStmt Source #
Constructors
CellEndStmt |
Instances
Read CellEndStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS CellEndStmt # readList :: ReadS [CellEndStmt] # readPrec :: ReadPrec CellEndStmt # readListPrec :: ReadPrec [CellEndStmt] # | |
Show CellEndStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> CellEndStmt -> ShowS # show :: CellEndStmt -> String # showList :: [CellEndStmt] -> ShowS # | |
Eq CellEndStmt Source # | |
Defined in Yosys.Rtl | |
Pretty CellEndStmt Source # | |
Defined in Yosys.Rtl |
Unary cells
Binary cells
shiftCell :: CellStmt -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
andC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
orC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
xorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
xnorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
shlC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
shrC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
sshlC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
sshrC :: CellId -> Bool -> Integer -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
logicAndC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
logicOrC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
eqxC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
nexC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
powC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
ltC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
leC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
eqC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
neC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
geC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
gtC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
addC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
subC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
mulC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
divC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
modC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
divFloorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
modFloorC :: CellId -> Bool -> Integer -> Bool -> Integer -> Integer -> SigSpec -> SigSpec -> SigSpec -> Cell Source #
Multiplexers
Y = S ? B : A
Memories
Arguments
:: CellId | |
-> Constant | MEMID |
-> Constant | ABITS |
-> Constant | WIDTH |
-> Constant | CLK_ENABLE |
-> Constant | CLK_POLARITY |
-> Constant | TRANSPARENCY_MASK |
-> Constant | COLLISION_X_MASK |
-> Constant | ARST_VALUE |
-> Constant | SRST_VALUE |
-> Constant | INIT_VALUE |
-> Constant | CE_OVER_SRST |
-> SigSpec | CLK |
-> SigSpec | EN |
-> SigSpec | ADDR |
-> SigSpec | DATA |
-> SigSpec | ARST |
-> SigSpec | SRST |
-> Cell |
Arguments
:: CellId | |
-> Constant | MEMID |
-> Constant | SIZE |
-> Constant | ABITS |
-> Constant | WIDTH |
-> Constant | INIT |
-> Constant | RD_PORTS |
-> Constant | RD_WIDE_CONTINUATION |
-> Constant | RD_CLK_ENABLE |
-> Constant | RD_CLK_POLARITY |
-> Constant | RD_TRANSPARENCY_MASK |
-> Constant | RD_COLLISION_X_MASK |
-> Constant | RD_CE_OVER_SRST |
-> Constant | RD_INIT_VALUE |
-> Constant | RD_ARST_VALUE |
-> Constant | RD_SRST_VALUE |
-> Constant | WR_PORTS |
-> Constant | WR_WIDE_CONTINUATION |
-> Constant | WR_CLK_ENABLE |
-> Constant | WR_CLK_POLARITY |
-> Constant | WR_PRIORITY_MASK |
-> SigSpec | RD_CLK |
-> SigSpec | RD_EN |
-> SigSpec | RD_ADDR |
-> SigSpec | RD_DATA |
-> SigSpec | RD_ARST |
-> SigSpec | RD_SRST |
-> SigSpec | WR_CLK |
-> SigSpec | WR_EN |
-> SigSpec | WR_ADDR |
-> SigSpec | WR_DATA |
-> Cell |
Processes
Constructors
Process [AttrStmt] ProcStmt ProcessBody ProcEndStmt |
data ProcessBody Source #
Constructors
ProcessBody [AssignStmt] (Maybe Switch) [AssignStmt] [Sync] |
Instances
Read ProcessBody Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS ProcessBody # readList :: ReadS [ProcessBody] # readPrec :: ReadPrec ProcessBody # readListPrec :: ReadPrec [ProcessBody] # | |
Show ProcessBody Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> ProcessBody -> ShowS # show :: ProcessBody -> String # showList :: [ProcessBody] -> ShowS # | |
Eq ProcessBody Source # | |
Defined in Yosys.Rtl | |
Pretty ProcessBody Source # | |
Defined in Yosys.Rtl |
data AssignStmt Source #
Constructors
AssignStmt DestSigSpec SrcSigSpec |
Instances
Read AssignStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS AssignStmt # readList :: ReadS [AssignStmt] # readPrec :: ReadPrec AssignStmt # readListPrec :: ReadPrec [AssignStmt] # | |
Show AssignStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> AssignStmt -> ShowS # show :: AssignStmt -> String # showList :: [AssignStmt] -> ShowS # | |
Eq AssignStmt Source # | |
Defined in Yosys.Rtl | |
Pretty AssignStmt Source # | |
Defined in Yosys.Rtl |
newtype DestSigSpec Source #
Constructors
DestSigSpec SigSpec |
Instances
Read DestSigSpec Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS DestSigSpec # readList :: ReadS [DestSigSpec] # readPrec :: ReadPrec DestSigSpec # readListPrec :: ReadPrec [DestSigSpec] # | |
Show DestSigSpec Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> DestSigSpec -> ShowS # show :: DestSigSpec -> String # showList :: [DestSigSpec] -> ShowS # | |
Eq DestSigSpec Source # | |
Defined in Yosys.Rtl | |
Pretty DestSigSpec Source # | |
Defined in Yosys.Rtl |
newtype SrcSigSpec Source #
Constructors
SrcSigSpec SigSpec |
Instances
Read SrcSigSpec Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS SrcSigSpec # readList :: ReadS [SrcSigSpec] # readPrec :: ReadPrec SrcSigSpec # readListPrec :: ReadPrec [SrcSigSpec] # | |
Show SrcSigSpec Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> SrcSigSpec -> ShowS # show :: SrcSigSpec -> String # showList :: [SrcSigSpec] -> ShowS # | |
Eq SrcSigSpec Source # | |
Defined in Yosys.Rtl | |
Pretty SrcSigSpec Source # | |
Defined in Yosys.Rtl |
data ProcEndStmt Source #
Constructors
ProcEndStmt |
Instances
Read ProcEndStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS ProcEndStmt # readList :: ReadS [ProcEndStmt] # readPrec :: ReadPrec ProcEndStmt # readListPrec :: ReadPrec [ProcEndStmt] # | |
Show ProcEndStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> ProcEndStmt -> ShowS # show :: ProcEndStmt -> String # showList :: [ProcEndStmt] -> ShowS # | |
Eq ProcEndStmt Source # | |
Defined in Yosys.Rtl | |
Pretty ProcEndStmt Source # | |
Defined in Yosys.Rtl |
Switches
Constructors
Switch SwitchStmt [Case] SwitchEndStmt |
data SwitchStmt Source #
Constructors
SwitchStmt [AttrStmt] SigSpec |
Instances
Read SwitchStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS SwitchStmt # readList :: ReadS [SwitchStmt] # readPrec :: ReadPrec SwitchStmt # readListPrec :: ReadPrec [SwitchStmt] # | |
Show SwitchStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> SwitchStmt -> ShowS # show :: SwitchStmt -> String # showList :: [SwitchStmt] -> ShowS # | |
Eq SwitchStmt Source # | |
Defined in Yosys.Rtl | |
Pretty SwitchStmt Source # | |
Defined in Yosys.Rtl |
Constructors
CaseBody [Either Switch AssignStmt] |
data SwitchEndStmt Source #
Constructors
SwitchEndStmt |
Instances
Read SwitchEndStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS SwitchEndStmt # readList :: ReadS [SwitchEndStmt] # | |
Show SwitchEndStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> SwitchEndStmt -> ShowS # show :: SwitchEndStmt -> String # showList :: [SwitchEndStmt] -> ShowS # | |
Eq SwitchEndStmt Source # | |
Defined in Yosys.Rtl Methods (==) :: SwitchEndStmt -> SwitchEndStmt -> Bool # (/=) :: SwitchEndStmt -> SwitchEndStmt -> Bool # | |
Pretty SwitchEndStmt Source # | |
Defined in Yosys.Rtl |
Syncs
Constructors
Sync SyncStmt [UpdateStmt] |
Constructors
SyncStmt SyncType SigSpec | |
SyncStmtGlobal | |
SyncStmtInit | |
SyncStmtAlways |
data UpdateStmt Source #
Constructors
UpdateStmt DestSigSpec SrcSigSpec |
Instances
Read UpdateStmt Source # | |
Defined in Yosys.Rtl Methods readsPrec :: Int -> ReadS UpdateStmt # readList :: ReadS [UpdateStmt] # readPrec :: ReadPrec UpdateStmt # readListPrec :: ReadPrec [UpdateStmt] # | |
Show UpdateStmt Source # | |
Defined in Yosys.Rtl Methods showsPrec :: Int -> UpdateStmt -> ShowS # show :: UpdateStmt -> String # showList :: [UpdateStmt] -> ShowS # | |
Eq UpdateStmt Source # | |
Defined in Yosys.Rtl | |
Pretty UpdateStmt Source # | |
Defined in Yosys.Rtl |