yosys-rtl-0.1.0.1: Yosys RTL Intermediate Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Yosys.Rtl

Description

Yosys RTLIL

Synopsis

Lexical elements

newtype Ident Source #

Constructors

Ident Text 

Instances

Instances details
IsString Ident Source # 
Instance details

Defined in Yosys.Rtl

Methods

fromString :: String -> Ident #

Monoid Ident Source # 
Instance details

Defined in Yosys.Rtl

Methods

mempty :: Ident #

mappend :: Ident -> Ident -> Ident #

mconcat :: [Ident] -> Ident #

Semigroup Ident Source # 
Instance details

Defined in Yosys.Rtl

Methods

(<>) :: Ident -> Ident -> Ident #

sconcat :: NonEmpty Ident -> Ident #

stimes :: Integral b => b -> Ident -> Ident #

Read Ident Source # 
Instance details

Defined in Yosys.Rtl

Show Ident Source # 
Instance details

Defined in Yosys.Rtl

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Eq Ident Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Pretty Ident Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Ident -> Doc ann #

prettyList :: [Ident] -> Doc ann #

data Value Source #

Constructors

Value Integer [BinaryDigit] 

Instances

Instances details
IsString Value Source # 
Instance details

Defined in Yosys.Rtl

Methods

fromString :: String -> Value #

Read Value Source # 
Instance details

Defined in Yosys.Rtl

Show Value Source # 
Instance details

Defined in Yosys.Rtl

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Eq Value Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Pretty Value Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Value -> Doc ann #

prettyList :: [Value] -> Doc ann #

data BinaryDigit Source #

Constructors

B0 
B1 
X 
Z 
M 
D 

Instances

Instances details
IsString BinaryDigit Source # 
Instance details

Defined in Yosys.Rtl

Read BinaryDigit Source # 
Instance details

Defined in Yosys.Rtl

Show BinaryDigit Source # 
Instance details

Defined in Yosys.Rtl

Eq BinaryDigit Source # 
Instance details

Defined in Yosys.Rtl

Pretty BinaryDigit Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: BinaryDigit -> Doc ann #

prettyList :: [BinaryDigit] -> Doc ann #

File

data File Source #

Constructors

File (Maybe AutoIdxStmt) [Module] 

Instances

Instances details
Read File Source # 
Instance details

Defined in Yosys.Rtl

Show File Source # 
Instance details

Defined in Yosys.Rtl

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

Eq File Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: File -> File -> Bool #

(/=) :: File -> File -> Bool #

Pretty File Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: File -> Doc ann #

prettyList :: [File] -> Doc ann #

Autoindex statements

Modules

data Module Source #

Instances

Instances details
Read Module Source # 
Instance details

Defined in Yosys.Rtl

Show Module Source # 
Instance details

Defined in Yosys.Rtl

Eq Module Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Pretty Module Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Module -> Doc ann #

prettyList :: [Module] -> Doc ann #

newtype ModuleStmt Source #

Constructors

ModuleStmt Ident 

Instances

Instances details
IsString ModuleStmt Source # 
Instance details

Defined in Yosys.Rtl

Read ModuleStmt Source # 
Instance details

Defined in Yosys.Rtl

Show ModuleStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq ModuleStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty ModuleStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ModuleStmt -> Doc ann #

prettyList :: [ModuleStmt] -> Doc ann #

data ParamStmt Source #

Constructors

ParamStmt Ident (Maybe Constant) 

Instances

Instances details
Read ParamStmt Source # 
Instance details

Defined in Yosys.Rtl

Show ParamStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq ParamStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty ParamStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ParamStmt -> Doc ann #

prettyList :: [ParamStmt] -> Doc ann #

data Constant Source #

Instances

Instances details
IsString Constant Source # 
Instance details

Defined in Yosys.Rtl

Read Constant Source # 
Instance details

Defined in Yosys.Rtl

Show Constant Source # 
Instance details

Defined in Yosys.Rtl

Eq Constant Source # 
Instance details

Defined in Yosys.Rtl

Pretty Constant Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Constant -> Doc ann #

prettyList :: [Constant] -> Doc ann #

data ModuleEndStmt Source #

Constructors

ModuleEndStmt 

Instances

Instances details
Read ModuleEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Show ModuleEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq ModuleEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty ModuleEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ModuleEndStmt -> Doc ann #

prettyList :: [ModuleEndStmt] -> Doc ann #

Attribute statements

data AttrStmt Source #

Constructors

AttrStmt Ident Constant 

Instances

Instances details
Read AttrStmt Source # 
Instance details

Defined in Yosys.Rtl

Show AttrStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq AttrStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty AttrStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: AttrStmt -> Doc ann #

prettyList :: [AttrStmt] -> Doc ann #

Signal specifications

data SigSpec Source #

Instances

Instances details
IsString SigSpec Source # 
Instance details

Defined in Yosys.Rtl

Methods

fromString :: String -> SigSpec #

Monoid SigSpec Source # 
Instance details

Defined in Yosys.Rtl

Semigroup SigSpec Source # 
Instance details

Defined in Yosys.Rtl

Read SigSpec Source # 
Instance details

Defined in Yosys.Rtl

Show SigSpec Source # 
Instance details

Defined in Yosys.Rtl

Eq SigSpec Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: SigSpec -> SigSpec -> Bool #

(/=) :: SigSpec -> SigSpec -> Bool #

Pretty SigSpec Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: SigSpec -> Doc ann #

prettyList :: [SigSpec] -> Doc ann #

Connections

data ConnStmt Source #

Constructors

ConnStmt SigSpec SigSpec 

Instances

Instances details
Read ConnStmt Source # 
Instance details

Defined in Yosys.Rtl

Show ConnStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq ConnStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty ConnStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ConnStmt -> Doc ann #

prettyList :: [ConnStmt] -> Doc ann #

Wires

data Wire Source #

Constructors

Wire [AttrStmt] WireStmt 

Instances

Instances details
Read Wire Source # 
Instance details

Defined in Yosys.Rtl

Show Wire Source # 
Instance details

Defined in Yosys.Rtl

Methods

showsPrec :: Int -> Wire -> ShowS #

show :: Wire -> String #

showList :: [Wire] -> ShowS #

Eq Wire Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Wire -> Wire -> Bool #

(/=) :: Wire -> Wire -> Bool #

Pretty Wire Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Wire -> Doc ann #

prettyList :: [Wire] -> Doc ann #

data WireStmt Source #

Constructors

WireStmt [WireOption] WireId 

Instances

Instances details
Read WireStmt Source # 
Instance details

Defined in Yosys.Rtl

Show WireStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq WireStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty WireStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: WireStmt -> Doc ann #

prettyList :: [WireStmt] -> Doc ann #

newtype WireId Source #

Constructors

WireId Ident 

Instances

Instances details
IsString WireId Source # 
Instance details

Defined in Yosys.Rtl

Methods

fromString :: String -> WireId #

Monoid WireId Source # 
Instance details

Defined in Yosys.Rtl

Semigroup WireId Source # 
Instance details

Defined in Yosys.Rtl

Read WireId Source # 
Instance details

Defined in Yosys.Rtl

Show WireId Source # 
Instance details

Defined in Yosys.Rtl

Eq WireId Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: WireId -> WireId -> Bool #

(/=) :: WireId -> WireId -> Bool #

Pretty WireId Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: WireId -> Doc ann #

prettyList :: [WireId] -> Doc ann #

Memories

data Memory Source #

Constructors

Memory [AttrStmt] MemoryStmt 

Instances

Instances details
Read Memory Source # 
Instance details

Defined in Yosys.Rtl

Show Memory Source # 
Instance details

Defined in Yosys.Rtl

Eq Memory Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Memory -> Memory -> Bool #

(/=) :: Memory -> Memory -> Bool #

Pretty Memory Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Memory -> Doc ann #

prettyList :: [Memory] -> Doc ann #

data MemoryStmt Source #

Constructors

MemoryStmt [MemoryOption] Ident 

Instances

Instances details
Read MemoryStmt Source # 
Instance details

Defined in Yosys.Rtl

Show MemoryStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq MemoryStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty MemoryStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: MemoryStmt -> Doc ann #

prettyList :: [MemoryStmt] -> Doc ann #

Cells

data Cell Source #

Instances

Instances details
Read Cell Source # 
Instance details

Defined in Yosys.Rtl

Show Cell Source # 
Instance details

Defined in Yosys.Rtl

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Eq Cell Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Cell -> Cell -> Bool #

(/=) :: Cell -> Cell -> Bool #

Pretty Cell Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Cell -> Doc ann #

prettyList :: [Cell] -> Doc ann #

data CellStmt Source #

Constructors

CellStmt CellType CellId 

Instances

Instances details
Read CellStmt Source # 
Instance details

Defined in Yosys.Rtl

Show CellStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq CellStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty CellStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: CellStmt -> Doc ann #

prettyList :: [CellStmt] -> Doc ann #

newtype CellId Source #

Constructors

CellId Ident 

Instances

Instances details
IsString CellId Source # 
Instance details

Defined in Yosys.Rtl

Methods

fromString :: String -> CellId #

Monoid CellId Source # 
Instance details

Defined in Yosys.Rtl

Semigroup CellId Source # 
Instance details

Defined in Yosys.Rtl

Read CellId Source # 
Instance details

Defined in Yosys.Rtl

Show CellId Source # 
Instance details

Defined in Yosys.Rtl

Eq CellId Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: CellId -> CellId -> Bool #

(/=) :: CellId -> CellId -> Bool #

Pretty CellId Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: CellId -> Doc ann #

prettyList :: [CellId] -> Doc ann #

newtype CellType Source #

Constructors

CellType Ident 

Instances

Instances details
IsString CellType Source # 
Instance details

Defined in Yosys.Rtl

Read CellType Source # 
Instance details

Defined in Yosys.Rtl

Show CellType Source # 
Instance details

Defined in Yosys.Rtl

Eq CellType Source # 
Instance details

Defined in Yosys.Rtl

Pretty CellType Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: CellType -> Doc ann #

prettyList :: [CellType] -> Doc ann #

data ParamType Source #

Constructors

Signed 
Real 

Instances

Instances details
Read ParamType Source # 
Instance details

Defined in Yosys.Rtl

Show ParamType Source # 
Instance details

Defined in Yosys.Rtl

Eq ParamType Source # 
Instance details

Defined in Yosys.Rtl

Pretty ParamType Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ParamType -> Doc ann #

prettyList :: [ParamType] -> Doc ann #

data CellEndStmt Source #

Constructors

CellEndStmt 

Instances

Instances details
Read CellEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Show CellEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq CellEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty CellEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: CellEndStmt -> Doc ann #

prettyList :: [CellEndStmt] -> Doc ann #

Unary cells

unaryCell Source #

Arguments

:: CellStmt 
-> Bool

\A_SIGNED

-> Integer

\A_WIDTH

-> Integer

\Y_WIDTH

-> SigSpec

A

-> SigSpec

Y

-> Cell 

Binary cells

binaryCell Source #

Arguments

:: CellStmt 
-> Bool

\A_SIGNED

-> Integer

\A_WIDTH

-> Bool

\B_SIGNED

-> Integer

\B_WIDTH

-> Integer

\Y_WIDTH

-> SigSpec

A

-> SigSpec

B

-> SigSpec

Y

-> Cell 

Multiplexers

muxC Source #

Arguments

:: CellId 
-> Integer

WIDTH

-> SigSpec

A

-> SigSpec

B

-> SigSpec

S

-> SigSpec

Y

-> Cell 

Y = S ? B : A

Memories

memRdV2C Source #

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 

memWrV2C Source #

Arguments

:: CellId 
-> Constant

MEMID

-> Constant

ABITS

-> Constant

WIDTH

-> Constant

CLK_ENABLE

-> Constant

CLK_POLARITY

-> Constant

PORTID

-> Constant

PRIORITY_MASK

-> SigSpec

CLK

-> SigSpec

EN

-> SigSpec

ADDR

-> SigSpec

DATA

-> Cell 

memInitV2C Source #

Arguments

:: CellId 
-> Constant

MEMID

-> Constant

ABITS

-> Constant

WIDTH

-> Constant

WORDS

-> Constant

PRIORITY

-> SigSpec

ADDR

-> SigSpec

DATA

-> Cell 

memV2C Source #

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

data Process Source #

Instances

Instances details
Read Process Source # 
Instance details

Defined in Yosys.Rtl

Show Process Source # 
Instance details

Defined in Yosys.Rtl

Eq Process Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Process -> Process -> Bool #

(/=) :: Process -> Process -> Bool #

Pretty Process Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Process -> Doc ann #

prettyList :: [Process] -> Doc ann #

newtype ProcStmt Source #

Constructors

ProcStmt Ident 

Instances

Instances details
IsString ProcStmt Source # 
Instance details

Defined in Yosys.Rtl

Monoid ProcStmt Source # 
Instance details

Defined in Yosys.Rtl

Semigroup ProcStmt Source # 
Instance details

Defined in Yosys.Rtl

Read ProcStmt Source # 
Instance details

Defined in Yosys.Rtl

Show ProcStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq ProcStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty ProcStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ProcStmt -> Doc ann #

prettyList :: [ProcStmt] -> Doc ann #

data ProcessBody Source #

Instances

Instances details
Read ProcessBody Source # 
Instance details

Defined in Yosys.Rtl

Show ProcessBody Source # 
Instance details

Defined in Yosys.Rtl

Eq ProcessBody Source # 
Instance details

Defined in Yosys.Rtl

Pretty ProcessBody Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ProcessBody -> Doc ann #

prettyList :: [ProcessBody] -> Doc ann #

data AssignStmt Source #

Instances

Instances details
Read AssignStmt Source # 
Instance details

Defined in Yosys.Rtl

Show AssignStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq AssignStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty AssignStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: AssignStmt -> Doc ann #

prettyList :: [AssignStmt] -> Doc ann #

newtype DestSigSpec Source #

Constructors

DestSigSpec SigSpec 

Instances

Instances details
Read DestSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Show DestSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Eq DestSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Pretty DestSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: DestSigSpec -> Doc ann #

prettyList :: [DestSigSpec] -> Doc ann #

newtype SrcSigSpec Source #

Constructors

SrcSigSpec SigSpec 

Instances

Instances details
Read SrcSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Show SrcSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Eq SrcSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Pretty SrcSigSpec Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: SrcSigSpec -> Doc ann #

prettyList :: [SrcSigSpec] -> Doc ann #

data ProcEndStmt Source #

Constructors

ProcEndStmt 

Instances

Instances details
Read ProcEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Show ProcEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq ProcEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty ProcEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: ProcEndStmt -> Doc ann #

prettyList :: [ProcEndStmt] -> Doc ann #

Switches

data Switch Source #

Instances

Instances details
Read Switch Source # 
Instance details

Defined in Yosys.Rtl

Show Switch Source # 
Instance details

Defined in Yosys.Rtl

Eq Switch Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Switch -> Switch -> Bool #

(/=) :: Switch -> Switch -> Bool #

Pretty Switch Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Switch -> Doc ann #

prettyList :: [Switch] -> Doc ann #

data SwitchStmt Source #

Constructors

SwitchStmt [AttrStmt] SigSpec 

Instances

Instances details
Read SwitchStmt Source # 
Instance details

Defined in Yosys.Rtl

Show SwitchStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq SwitchStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty SwitchStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: SwitchStmt -> Doc ann #

prettyList :: [SwitchStmt] -> Doc ann #

data Case Source #

Constructors

Case [AttrStmt] CaseStmt CaseBody 

Instances

Instances details
Read Case Source # 
Instance details

Defined in Yosys.Rtl

Show Case Source # 
Instance details

Defined in Yosys.Rtl

Methods

showsPrec :: Int -> Case -> ShowS #

show :: Case -> String #

showList :: [Case] -> ShowS #

Eq Case Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Case -> Case -> Bool #

(/=) :: Case -> Case -> Bool #

Pretty Case Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Case -> Doc ann #

prettyList :: [Case] -> Doc ann #

newtype CaseStmt Source #

Constructors

CaseStmt (Maybe Compare) 

Instances

Instances details
Read CaseStmt Source # 
Instance details

Defined in Yosys.Rtl

Show CaseStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq CaseStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty CaseStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: CaseStmt -> Doc ann #

prettyList :: [CaseStmt] -> Doc ann #

data Compare Source #

Constructors

Compare SigSpec [SigSpec] 

Instances

Instances details
Read Compare Source # 
Instance details

Defined in Yosys.Rtl

Show Compare Source # 
Instance details

Defined in Yosys.Rtl

Eq Compare Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Compare -> Compare -> Bool #

(/=) :: Compare -> Compare -> Bool #

Pretty Compare Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Compare -> Doc ann #

prettyList :: [Compare] -> Doc ann #

newtype CaseBody Source #

Instances

Instances details
Read CaseBody Source # 
Instance details

Defined in Yosys.Rtl

Show CaseBody Source # 
Instance details

Defined in Yosys.Rtl

Eq CaseBody Source # 
Instance details

Defined in Yosys.Rtl

Pretty CaseBody Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: CaseBody -> Doc ann #

prettyList :: [CaseBody] -> Doc ann #

data SwitchEndStmt Source #

Constructors

SwitchEndStmt 

Instances

Instances details
Read SwitchEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Show SwitchEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq SwitchEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty SwitchEndStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: SwitchEndStmt -> Doc ann #

prettyList :: [SwitchEndStmt] -> Doc ann #

Syncs

data Sync Source #

Constructors

Sync SyncStmt [UpdateStmt] 

Instances

Instances details
Read Sync Source # 
Instance details

Defined in Yosys.Rtl

Show Sync Source # 
Instance details

Defined in Yosys.Rtl

Methods

showsPrec :: Int -> Sync -> ShowS #

show :: Sync -> String #

showList :: [Sync] -> ShowS #

Eq Sync Source # 
Instance details

Defined in Yosys.Rtl

Methods

(==) :: Sync -> Sync -> Bool #

(/=) :: Sync -> Sync -> Bool #

Pretty Sync Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: Sync -> Doc ann #

prettyList :: [Sync] -> Doc ann #

data SyncStmt Source #

Instances

Instances details
Read SyncStmt Source # 
Instance details

Defined in Yosys.Rtl

Show SyncStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq SyncStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty SyncStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: SyncStmt -> Doc ann #

prettyList :: [SyncStmt] -> Doc ann #

data SyncType Source #

Constructors

Low 
High 
Posedge 
Negedge 
Edge 

Instances

Instances details
Read SyncType Source # 
Instance details

Defined in Yosys.Rtl

Show SyncType Source # 
Instance details

Defined in Yosys.Rtl

Eq SyncType Source # 
Instance details

Defined in Yosys.Rtl

Pretty SyncType Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: SyncType -> Doc ann #

prettyList :: [SyncType] -> Doc ann #

data UpdateStmt Source #

Instances

Instances details
Read UpdateStmt Source # 
Instance details

Defined in Yosys.Rtl

Show UpdateStmt Source # 
Instance details

Defined in Yosys.Rtl

Eq UpdateStmt Source # 
Instance details

Defined in Yosys.Rtl

Pretty UpdateStmt Source # 
Instance details

Defined in Yosys.Rtl

Methods

pretty :: UpdateStmt -> Doc ann #

prettyList :: [UpdateStmt] -> Doc ann #