Copyright | (c) 2019 Yann Herklotz Grave |
---|---|
License | GPL-3 |
Maintainer | yann [at] yannherklotz [dot] com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Verismith.Verilog
Description
Verilog implementation with random generation and mutations.
Synopsis
- data SourceInfo a = SourceInfo {}
- newtype Verilog a = Verilog {
- getVerilog :: [ModDecl a]
- parseVerilog :: Text -> Text -> Either Text (Verilog ann)
- newtype GenVerilog a = GenVerilog {
- unGenVerilog :: a
- genSource :: Source a => a -> Text
- newtype Identifier = Identifier {}
- newtype Delay = Delay {}
- data Event
- = EId !Identifier
- | EExpr !Expr
- | EAll
- | EPosEdge !Identifier
- | ENegEdge !Identifier
- | EOr !Event !Event
- | EComb !Event !Event
- data BinaryOperator
- data UnaryOperator
- data Task = Task {
- _taskName :: !Identifier
- _taskExpr :: [Expr]
- taskName :: Lens' Task Identifier
- taskExpr :: Lens' Task [Expr]
- data LVal
- = RegId {
- _regId :: !Identifier
- | RegExpr {
- _regExprId :: !Identifier
- _regExpr :: !Expr
- | RegSize {
- _regSizeId :: !Identifier
- _regSizeRange :: !Range
- | RegConcat { }
- = RegId {
- regId :: Traversal' LVal Identifier
- regExprId :: Traversal' LVal Identifier
- regExpr :: Traversal' LVal Expr
- regSizeId :: Traversal' LVal Identifier
- regSizeRange :: Traversal' LVal Range
- regConc :: Traversal' LVal [Expr]
- data PortDir
- data PortType
- data Port = Port {
- _portType :: !PortType
- _portSigned :: !Bool
- _portSize :: !Range
- _portName :: !Identifier
- portType :: Lens' Port PortType
- portSigned :: Lens' Port Bool
- portSize :: Lens' Port Range
- portName :: Lens' Port Identifier
- data Expr
- = Number !BitVec
- | Id !Identifier
- | VecSelect !Identifier !Expr
- | RangeSelect !Identifier !Range
- | Concat !(NonEmpty Expr)
- | UnOp !UnaryOperator !Expr
- | BinOp !Expr !BinaryOperator !Expr
- | Cond !Expr !Expr !Expr
- | Appl !Identifier !Expr
- | Str !Text
- data ConstExpr
- = ConstNum { }
- | ParamId { }
- | ConstConcat {
- _constConcat :: !(NonEmpty ConstExpr)
- | ConstUnOp { }
- | ConstBinOp { }
- | ConstCond {
- _constCond :: !ConstExpr
- _constTrue :: !ConstExpr
- _constFalse :: !ConstExpr
- | ConstStr { }
- constToExpr :: ConstExpr -> Expr
- exprToConst :: Expr -> ConstExpr
- constNum :: Traversal' ConstExpr BitVec
- data Assign = Assign {
- _assignReg :: !LVal
- _assignDelay :: !(Maybe Delay)
- _assignExpr :: !Expr
- assignReg :: Lens' Assign LVal
- assignDelay :: Lens' Assign (Maybe Delay)
- assignExpr :: Lens' Assign Expr
- data ContAssign = ContAssign {}
- contAssignNetLVal :: Lens' ContAssign Identifier
- contAssignExpr :: Lens' ContAssign Expr
- data Statement a
- = TimeCtrl {
- _statDelay :: !Delay
- _statDStat :: Maybe (Statement a)
- | EventCtrl {
- _statEvent :: !Event
- _statEStat :: Maybe (Statement a)
- | SeqBlock {
- _statements :: [Statement a]
- | BlockAssign { }
- | NonBlockAssign { }
- | TaskEnable {
- _stmntTask :: !Task
- | SysTaskEnable {
- _stmntSysTask :: !Task
- | CondStmnt {
- _stmntCondExpr :: Expr
- _stmntCondTrue :: Maybe (Statement a)
- _stmntCondFalse :: Maybe (Statement a)
- | StmntCase {
- _stmntCaseType :: !CaseType
- _stmntCaseExpr :: !Expr
- _stmntCasePair :: ![CasePair a]
- _stmntCaseDefault :: !(Maybe (Statement a))
- | ForLoop { }
- | StmntAnn a (Statement a)
- = TimeCtrl {
- statDelay :: forall a f. Applicative f => (Delay -> f Delay) -> Statement a -> f (Statement a)
- statDStat :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a)
- statEvent :: forall a f. Applicative f => (Event -> f Event) -> Statement a -> f (Statement a)
- statEStat :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a)
- statements :: forall a f. Applicative f => ([Statement a] -> f [Statement a]) -> Statement a -> f (Statement a)
- stmntBA :: forall a f. Applicative f => (Assign -> f Assign) -> Statement a -> f (Statement a)
- stmntNBA :: forall a f. Applicative f => (Assign -> f Assign) -> Statement a -> f (Statement a)
- stmntTask :: forall a f. Applicative f => (Task -> f Task) -> Statement a -> f (Statement a)
- stmntSysTask :: forall a f. Applicative f => (Task -> f Task) -> Statement a -> f (Statement a)
- stmntCondExpr :: forall a f. Applicative f => (Expr -> f Expr) -> Statement a -> f (Statement a)
- stmntCondTrue :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a)
- stmntCondFalse :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a)
- data ModDecl a
- = ModDecl {
- _modId :: !Identifier
- _modOutPorts :: ![Port]
- _modInPorts :: ![Port]
- _modItems :: ![ModItem a]
- _modParams :: ![Parameter]
- | ModDeclAnn a (ModDecl a)
- = ModDecl {
- modId :: forall a f. Applicative f => (Identifier -> f Identifier) -> ModDecl a -> f (ModDecl a)
- modOutPorts :: forall a f. Applicative f => ([Port] -> f [Port]) -> ModDecl a -> f (ModDecl a)
- modInPorts :: forall a f. Applicative f => ([Port] -> f [Port]) -> ModDecl a -> f (ModDecl a)
- modItems :: forall a f. Applicative f => ([ModItem a] -> f [ModItem a]) -> ModDecl a -> f (ModDecl a)
- data ModItem a
- = ModCA { }
- | ModInst {
- _modInstId :: !Identifier
- _modInstDecl :: [ModConn]
- _modInstName :: !Identifier
- _modInstConns :: [ModConn]
- | Initial !(Statement a)
- | Always !(Statement a)
- | Property { }
- | Decl { }
- | ParamDecl { }
- | LocalParamDecl { }
- | ModItemAnn a (ModItem a)
- modContAssign :: forall a f. Applicative f => (ContAssign -> f ContAssign) -> ModItem a -> f (ModItem a)
- modInstId :: forall a f. Applicative f => (Identifier -> f Identifier) -> ModItem a -> f (ModItem a)
- modInstName :: forall a f. Applicative f => (Identifier -> f Identifier) -> ModItem a -> f (ModItem a)
- modInstConns :: forall a f. Applicative f => ([ModConn] -> f [ModConn]) -> ModItem a -> f (ModItem a)
- traverseModItem :: Applicative f => (Expr -> f Expr) -> ModItem ann -> f (ModItem ann)
- declDir :: forall a f. Applicative f => (Maybe PortDir -> f (Maybe PortDir)) -> ModItem a -> f (ModItem a)
- declPort :: forall a f. Applicative f => (Port -> f Port) -> ModItem a -> f (ModItem a)
- data ModConn
- = ModConn { }
- | ModConnNamed {
- _modConnName :: !Identifier
- _modExpr :: !Expr
- modConnName :: Traversal' ModConn Identifier
- modExpr :: Lens' ModConn Expr
- getModule :: forall a f. Applicative f => (ModDecl a -> f (ModDecl a)) -> Verilog a -> f (Verilog a)
- getSourceId :: forall a f. Applicative f => (Text -> f Text) -> Verilog a -> f (Verilog a)
- verilog :: QuasiQuoter
Documentation
data SourceInfo a Source #
Top level type which contains all the source code and associated information.
Constructors
SourceInfo | |
Instances
The complete sourcetext for the Verilog module.
Constructors
Verilog | |
Fields
|
Instances
Functor Verilog Source # | |||||
Annotations Verilog Source # | |||||
Data a => Data (Verilog a) Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Verilog a -> c (Verilog a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Verilog a) # toConstr :: Verilog a -> Constr # dataTypeOf :: Verilog a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Verilog a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Verilog a)) # gmapT :: (forall b. Data b => b -> b) -> Verilog a -> Verilog a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Verilog a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Verilog a -> r # gmapQ :: (forall d. Data d => d -> u) -> Verilog a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Verilog a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Verilog a -> m (Verilog a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Verilog a -> m (Verilog a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Verilog a -> m (Verilog a) # | |||||
Monoid (Verilog a) Source # | |||||
Semigroup (Verilog a) Source # | |||||
Generic (Verilog a) Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show a => Show (Verilog a) Source # | |||||
NFData a => NFData (Verilog a) Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq a => Eq (Verilog a) Source # | |||||
Ord a => Ord (Verilog a) Source # | |||||
Wrapped (Verilog a) Source # | |||||
Show ann => Source (Verilog ann) Source # | |||||
Distance (Verilog a) Source # | |||||
Mutate (Verilog ann) Source # | |||||
Verilog a1 ~ t => Rewrapped (Verilog a2) t Source # | |||||
Defined in Verismith.Verilog.AST | |||||
type Rep (Verilog a) Source # | |||||
Defined in Verismith.Verilog.AST | |||||
type Unwrapped (Verilog a) Source # | |||||
Defined in Verismith.Verilog.AST |
Arguments
:: Text | Name of parsed object. |
-> Text | Content to be parsed. |
-> Either Text (Verilog ann) | Returns |
Parse a String
containing verilog code. The parser currently only supports
the subset of Verilog that is being generated randomly.
newtype GenVerilog a Source #
Constructors
GenVerilog | |
Fields
|
Instances
Data a => Data (GenVerilog a) Source # | |
Defined in Verismith.Verilog.CodeGen Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenVerilog a -> c (GenVerilog a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenVerilog a) # toConstr :: GenVerilog a -> Constr # dataTypeOf :: GenVerilog a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GenVerilog a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GenVerilog a)) # gmapT :: (forall b. Data b => b -> b) -> GenVerilog a -> GenVerilog a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenVerilog a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenVerilog a -> r # gmapQ :: (forall d. Data d => d -> u) -> GenVerilog a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenVerilog a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenVerilog a -> m (GenVerilog a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenVerilog a -> m (GenVerilog a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenVerilog a -> m (GenVerilog a) # | |
Source a => Show (GenVerilog a) Source # | |
Defined in Verismith.Verilog.CodeGen Methods showsPrec :: Int -> GenVerilog a -> ShowS # show :: GenVerilog a -> String # showList :: [GenVerilog a] -> ShowS # | |
Eq a => Eq (GenVerilog a) Source # | |
Defined in Verismith.Verilog.CodeGen | |
Ord a => Ord (GenVerilog a) Source # | |
Defined in Verismith.Verilog.CodeGen Methods compare :: GenVerilog a -> GenVerilog a -> Ordering # (<) :: GenVerilog a -> GenVerilog a -> Bool # (<=) :: GenVerilog a -> GenVerilog a -> Bool # (>) :: GenVerilog a -> GenVerilog a -> Bool # (>=) :: GenVerilog a -> GenVerilog a -> Bool # max :: GenVerilog a -> GenVerilog a -> GenVerilog a # min :: GenVerilog a -> GenVerilog a -> GenVerilog a # | |
Mutate a => Mutate (GenVerilog a) Source # | |
Defined in Verismith.Verilog.Mutate Methods mutExpr :: (Expr -> Expr) -> GenVerilog a -> GenVerilog a Source # |
Primitives
Identifier
newtype Identifier Source #
Identifier in Verilog. This is just a string of characters that can either be lowercase and uppercase for now. This might change in the future though, as Verilog supports many more characters in Identifiers.
Constructors
Identifier | |
Fields |
Instances
Data Identifier Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identifier -> c Identifier # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Identifier # toConstr :: Identifier -> Constr # dataTypeOf :: Identifier -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Identifier) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identifier) # gmapT :: (forall b. Data b => b -> b) -> Identifier -> Identifier # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r # gmapQ :: (forall d. Data d => d -> u) -> Identifier -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Identifier -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier # | |||||
IsString Identifier Source # | |||||
Defined in Verismith.Verilog.AST Methods fromString :: String -> Identifier # | |||||
Monoid Identifier Source # | |||||
Defined in Verismith.Verilog.AST Methods mempty :: Identifier # mappend :: Identifier -> Identifier -> Identifier # mconcat :: [Identifier] -> Identifier # | |||||
Semigroup Identifier Source # | |||||
Defined in Verismith.Verilog.AST Methods (<>) :: Identifier -> Identifier -> Identifier # sconcat :: NonEmpty Identifier -> Identifier # stimes :: Integral b => b -> Identifier -> Identifier # | |||||
Generic Identifier Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show Identifier Source # | |||||
Defined in Verismith.Verilog.AST Methods showsPrec :: Int -> Identifier -> ShowS # show :: Identifier -> String # showList :: [Identifier] -> ShowS # | |||||
NFData Identifier Source # | |||||
Defined in Verismith.Verilog.AST Methods rnf :: Identifier -> () # | |||||
Eq Identifier Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Ord Identifier Source # | |||||
Defined in Verismith.Verilog.AST Methods compare :: Identifier -> Identifier -> Ordering # (<) :: Identifier -> Identifier -> Bool # (<=) :: Identifier -> Identifier -> Bool # (>) :: Identifier -> Identifier -> Bool # (>=) :: Identifier -> Identifier -> Bool # max :: Identifier -> Identifier -> Identifier # min :: Identifier -> Identifier -> Identifier # | |||||
Wrapped Identifier Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
Methods | |||||
Source Identifier Source # | |||||
Defined in Verismith.Verilog.CodeGen Methods genSource :: Identifier -> Text Source # | |||||
Distance Identifier Source # | |||||
Defined in Verismith.Verilog.Distance Methods distance :: Identifier -> Identifier -> Int Source # udistance :: Identifier -> Identifier -> Int Source # dempty :: Identifier -> Int Source # | |||||
Mutate Identifier Source # | |||||
Defined in Verismith.Verilog.Mutate Methods mutExpr :: (Expr -> Expr) -> Identifier -> Identifier Source # | |||||
Identifier ~ t => Rewrapped Identifier t Source # | |||||
Defined in Verismith.Verilog.AST | |||||
type Rep Identifier Source # | |||||
Defined in Verismith.Verilog.AST type Rep Identifier = D1 ('MetaData "Identifier" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Identifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "getIdentifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |||||
type Unwrapped Identifier Source # | |||||
Defined in Verismith.Verilog.AST |
Control
Verilog syntax for adding a delay, which is represented as #num
.
Instances
Data Delay Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delay -> c Delay # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delay # dataTypeOf :: Delay -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Delay) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delay) # gmapT :: (forall b. Data b => b -> b) -> Delay -> Delay # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delay -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delay -> r # gmapQ :: (forall d. Data d => d -> u) -> Delay -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Delay -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delay -> m Delay # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delay -> m Delay # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delay -> m Delay # | |||||
Generic Delay Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Num Delay Source # | |||||
Show Delay Source # | |||||
NFData Delay Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq Delay Source # | |||||
Ord Delay Source # | |||||
Wrapped Delay Source # | |||||
Source Delay Source # | |||||
Mutate Delay Source # | |||||
Delay ~ t => Rewrapped Delay t Source # | |||||
Defined in Verismith.Verilog.AST | |||||
type Rep Delay Source # | |||||
Defined in Verismith.Verilog.AST | |||||
type Unwrapped Delay Source # | |||||
Defined in Verismith.Verilog.AST |
Verilog syntax for an event, such as @x
, which is used for always blocks
Constructors
EId !Identifier | |
EExpr !Expr | |
EAll | |
EPosEdge !Identifier | |
ENegEdge !Identifier | |
EOr !Event !Event | |
EComb !Event !Event |
Instances
Data Event Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Event -> c Event # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Event # dataTypeOf :: Event -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Event) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event) # gmapT :: (forall b. Data b => b -> b) -> Event -> Event # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r # gmapQ :: (forall d. Data d => d -> u) -> Event -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Event -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Event -> m Event # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event # | |||||
Generic Event Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show Event Source # | |||||
NFData Event Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq Event Source # | |||||
Ord Event Source # | |||||
Plated Event Source # | |||||
Defined in Verismith.Verilog.AST Methods plate :: Traversal' Event Event # | |||||
Corecursive Event Source # | |||||
Defined in Verismith.Verilog.AST Methods embed :: Base Event Event -> Event # ana :: (a -> Base Event a) -> a -> Event # apo :: (a -> Base Event (Either Event a)) -> a -> Event # postpro :: Recursive Event => (forall b. Base Event b -> Base Event b) -> (a -> Base Event a) -> a -> Event # gpostpro :: (Recursive Event, Monad m) => (forall b. m (Base Event b) -> Base Event (m b)) -> (forall c. Base Event c -> Base Event c) -> (a -> Base Event (m a)) -> a -> Event # | |||||
Recursive Event Source # | |||||
Defined in Verismith.Verilog.AST Methods project :: Event -> Base Event Event # cata :: (Base Event a -> a) -> Event -> a # para :: (Base Event (Event, a) -> a) -> Event -> a # gpara :: (Corecursive Event, Comonad w) => (forall b. Base Event (w b) -> w (Base Event b)) -> (Base Event (EnvT Event w a) -> a) -> Event -> a # prepro :: Corecursive Event => (forall b. Base Event b -> Base Event b) -> (Base Event a -> a) -> Event -> a # gprepro :: (Corecursive Event, Comonad w) => (forall b. Base Event (w b) -> w (Base Event b)) -> (forall c. Base Event c -> Base Event c) -> (Base Event (w a) -> a) -> Event -> a # | |||||
Source Event Source # | |||||
Mutate Event Source # | |||||
type Rep Event Source # | |||||
Defined in Verismith.Verilog.AST type Rep Event = D1 ('MetaData "Event" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "EId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :+: (C1 ('MetaCons "EExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: C1 ('MetaCons "EAll" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EPosEdge" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :+: C1 ('MetaCons "ENegEdge" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier))) :+: (C1 ('MetaCons "EOr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Event) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Event)) :+: C1 ('MetaCons "EComb" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Event) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Event))))) | |||||
type Base Event Source # | |||||
Defined in Verismith.Verilog.AST |
Operators
data BinaryOperator Source #
Binary operators that are currently supported in the verilog generation.
Constructors
BinPlus | |
BinMinus | |
BinTimes | |
BinDiv | |
BinMod | |
BinEq | |
BinNEq | |
BinCEq | |
BinCNEq | |
BinLAnd | |
BinLOr | |
BinLT | |
BinLEq | |
BinGT | |
BinGEq | |
BinAnd | |
BinOr | |
BinXor | |
BinXNor | |
BinXNorInv | |
BinPower | |
BinLSL | |
BinLSR | |
BinASL | |
BinASR |
Instances
Data BinaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinaryOperator -> c BinaryOperator # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinaryOperator # toConstr :: BinaryOperator -> Constr # dataTypeOf :: BinaryOperator -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinaryOperator) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinaryOperator) # gmapT :: (forall b. Data b => b -> b) -> BinaryOperator -> BinaryOperator # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOperator -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOperator -> r # gmapQ :: (forall d. Data d => d -> u) -> BinaryOperator -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinaryOperator -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinaryOperator -> m BinaryOperator # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOperator -> m BinaryOperator # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOperator -> m BinaryOperator # | |||||
Generic BinaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
Methods from :: BinaryOperator -> Rep BinaryOperator x # to :: Rep BinaryOperator x -> BinaryOperator # | |||||
Show BinaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods showsPrec :: Int -> BinaryOperator -> ShowS # show :: BinaryOperator -> String # showList :: [BinaryOperator] -> ShowS # | |||||
NFData BinaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods rnf :: BinaryOperator -> () # | |||||
Eq BinaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods (==) :: BinaryOperator -> BinaryOperator -> Bool # (/=) :: BinaryOperator -> BinaryOperator -> Bool # | |||||
Ord BinaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods compare :: BinaryOperator -> BinaryOperator -> Ordering # (<) :: BinaryOperator -> BinaryOperator -> Bool # (<=) :: BinaryOperator -> BinaryOperator -> Bool # (>) :: BinaryOperator -> BinaryOperator -> Bool # (>=) :: BinaryOperator -> BinaryOperator -> Bool # max :: BinaryOperator -> BinaryOperator -> BinaryOperator # min :: BinaryOperator -> BinaryOperator -> BinaryOperator # | |||||
Mutate BinaryOperator Source # | |||||
Defined in Verismith.Verilog.Mutate Methods mutExpr :: (Expr -> Expr) -> BinaryOperator -> BinaryOperator Source # | |||||
type Rep BinaryOperator Source # | |||||
Defined in Verismith.Verilog.AST type Rep BinaryOperator = D1 ('MetaData "BinaryOperator" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((((C1 ('MetaCons "BinPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BinMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinTimes" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "BinDiv" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BinMod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinEq" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BinNEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BinCEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinCNEq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "BinLAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BinLOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinLT" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "BinLEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BinGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinGEq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "BinAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BinOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinXor" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BinXNor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BinXNorInv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinPower" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BinLSL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinLSR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BinASL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinASR" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
data UnaryOperator Source #
Unary operators that are currently supported by the generator.
Instances
Data UnaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnaryOperator -> c UnaryOperator # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnaryOperator # toConstr :: UnaryOperator -> Constr # dataTypeOf :: UnaryOperator -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnaryOperator) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnaryOperator) # gmapT :: (forall b. Data b => b -> b) -> UnaryOperator -> UnaryOperator # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOperator -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOperator -> r # gmapQ :: (forall d. Data d => d -> u) -> UnaryOperator -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnaryOperator -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnaryOperator -> m UnaryOperator # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOperator -> m UnaryOperator # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOperator -> m UnaryOperator # | |||||
Generic UnaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show UnaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods showsPrec :: Int -> UnaryOperator -> ShowS # show :: UnaryOperator -> String # showList :: [UnaryOperator] -> ShowS # | |||||
NFData UnaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods rnf :: UnaryOperator -> () # | |||||
Eq UnaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods (==) :: UnaryOperator -> UnaryOperator -> Bool # (/=) :: UnaryOperator -> UnaryOperator -> Bool # | |||||
Ord UnaryOperator Source # | |||||
Defined in Verismith.Verilog.AST Methods compare :: UnaryOperator -> UnaryOperator -> Ordering # (<) :: UnaryOperator -> UnaryOperator -> Bool # (<=) :: UnaryOperator -> UnaryOperator -> Bool # (>) :: UnaryOperator -> UnaryOperator -> Bool # (>=) :: UnaryOperator -> UnaryOperator -> Bool # max :: UnaryOperator -> UnaryOperator -> UnaryOperator # min :: UnaryOperator -> UnaryOperator -> UnaryOperator # | |||||
Source UnaryOperator Source # | |||||
Defined in Verismith.Verilog.CodeGen Methods genSource :: UnaryOperator -> Text Source # | |||||
Mutate UnaryOperator Source # | |||||
Defined in Verismith.Verilog.Mutate Methods mutExpr :: (Expr -> Expr) -> UnaryOperator -> UnaryOperator Source # | |||||
type Rep UnaryOperator Source # | |||||
Defined in Verismith.Verilog.AST type Rep UnaryOperator = D1 ('MetaData "UnaryOperator" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "UnPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnMinus" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnLNot" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnNot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnAnd" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "UnNand" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnNor" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "UnXor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnNxor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnNxorInv" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Task
Task call, which is similar to function calls.
Constructors
Task | |
Fields
|
Instances
Data Task Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Task -> c Task # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Task # dataTypeOf :: Task -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Task) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Task) # gmapT :: (forall b. Data b => b -> b) -> Task -> Task # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Task -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Task -> r # gmapQ :: (forall d. Data d => d -> u) -> Task -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Task -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Task -> m Task # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Task -> m Task # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Task -> m Task # | |||||
Generic Task Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show Task Source # | |||||
NFData Task Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq Task Source # | |||||
Ord Task Source # | |||||
Source Task Source # | |||||
Mutate Task Source # | |||||
type Rep Task Source # | |||||
Defined in Verismith.Verilog.AST type Rep Task = D1 ('MetaData "Task" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Task" 'PrefixI 'True) (S1 ('MetaSel ('Just "_taskName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_taskExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expr]))) |
Left hand side value
Type that represents the left hand side of an assignment, which can be a concatenation such as in:
{a, b, c} = 32'h94238;
Constructors
RegId | |
Fields
| |
RegExpr | |
Fields
| |
RegSize | |
Fields
| |
RegConcat | |
Instances
Data LVal Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LVal -> c LVal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LVal # dataTypeOf :: LVal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LVal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LVal) # gmapT :: (forall b. Data b => b -> b) -> LVal -> LVal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LVal -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LVal -> r # gmapQ :: (forall d. Data d => d -> u) -> LVal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LVal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LVal -> m LVal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LVal -> m LVal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LVal -> m LVal # | |||||
IsString LVal Source # | |||||
Defined in Verismith.Verilog.AST Methods fromString :: String -> LVal # | |||||
Generic LVal Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show LVal Source # | |||||
NFData LVal Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq LVal Source # | |||||
Ord LVal Source # | |||||
Source LVal Source # | |||||
Mutate LVal Source # | |||||
type Rep LVal Source # | |||||
Defined in Verismith.Verilog.AST type Rep LVal = D1 ('MetaData "LVal" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "RegId" 'PrefixI 'True) (S1 ('MetaSel ('Just "_regId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :+: C1 ('MetaCons "RegExpr" 'PrefixI 'True) (S1 ('MetaSel ('Just "_regExprId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_regExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))) :+: (C1 ('MetaCons "RegSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "_regSizeId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_regSizeRange") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Range)) :+: C1 ('MetaCons "RegConcat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_regConc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expr])))) |
Ports
Different port direction that are supported in Verilog.
Instances
Data PortDir Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PortDir -> c PortDir # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PortDir # toConstr :: PortDir -> Constr # dataTypeOf :: PortDir -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PortDir) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortDir) # gmapT :: (forall b. Data b => b -> b) -> PortDir -> PortDir # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PortDir -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PortDir -> r # gmapQ :: (forall d. Data d => d -> u) -> PortDir -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PortDir -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PortDir -> m PortDir # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PortDir -> m PortDir # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PortDir -> m PortDir # | |||||
Generic PortDir Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show PortDir Source # | |||||
NFData PortDir Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq PortDir Source # | |||||
Ord PortDir Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Source PortDir Source # | |||||
Distance PortDir Source # | |||||
Mutate PortDir Source # | |||||
type Rep PortDir Source # | |||||
Defined in Verismith.Verilog.AST type Rep PortDir = D1 ('MetaData "PortDir" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "PortIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PortOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PortInOut" 'PrefixI 'False) (U1 :: Type -> Type))) |
Currently, only wire
and reg
are supported, as the other net types are
not that common and not a priority.
Instances
Data PortType Source # | |
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PortType -> c PortType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PortType # toConstr :: PortType -> Constr # dataTypeOf :: PortType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PortType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PortType) # gmapT :: (forall b. Data b => b -> b) -> PortType -> PortType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PortType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PortType -> r # gmapQ :: (forall d. Data d => d -> u) -> PortType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PortType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PortType -> m PortType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PortType -> m PortType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PortType -> m PortType # | |
Generic PortType Source # | |
Defined in Verismith.Verilog.AST | |
Show PortType Source # | |
NFData PortType Source # | |
Defined in Verismith.Verilog.AST | |
Eq PortType Source # | |
Ord PortType Source # | |
Defined in Verismith.Verilog.AST | |
Source PortType Source # | |
Distance PortType Source # | |
Mutate PortType Source # | |
type Rep PortType Source # | |
Port declaration. It contains information about the type of the port, the size, and the port name. It used to also contain information about if it was an input or output port. However, this is not always necessary and was more cumbersome than useful, as a lot of ports can be declared without input and output port.
This is now implemented inside '(ModDecl ann)' itself, which uses a list of output and input ports.
Constructors
Port | |
Fields
|
Instances
Data Port Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Port -> c Port # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Port # dataTypeOf :: Port -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Port) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Port) # gmapT :: (forall b. Data b => b -> b) -> Port -> Port # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Port -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Port -> r # gmapQ :: (forall d. Data d => d -> u) -> Port -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Port -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Port -> m Port # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Port -> m Port # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Port -> m Port # | |||||
Generic Port Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show Port Source # | |||||
NFData Port Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq Port Source # | |||||
Ord Port Source # | |||||
Source Port Source # | |||||
Distance Port Source # | |||||
Mutate Port Source # | |||||
type Rep Port Source # | |||||
Defined in Verismith.Verilog.AST type Rep Port = D1 ('MetaData "Port" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Port" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_portType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PortType) :*: S1 ('MetaSel ('Just "_portSigned") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_portSize") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Range) :*: S1 ('MetaSel ('Just "_portName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier)))) |
Expression
Verilog expression, which can either be a primary expression, unary expression, binary operator expression or a conditional expression.
Constructors
Number !BitVec | |
Id !Identifier | |
VecSelect !Identifier !Expr | |
RangeSelect !Identifier !Range | |
Concat !(NonEmpty Expr) | |
UnOp !UnaryOperator !Expr | |
BinOp !Expr !BinaryOperator !Expr | |
Cond !Expr !Expr !Expr | |
Appl !Identifier !Expr | |
Str !Text |
Instances
Data Expr Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr -> c Expr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Expr # dataTypeOf :: Expr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Expr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Expr) # gmapT :: (forall b. Data b => b -> b) -> Expr -> Expr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r # gmapQ :: (forall d. Data d => d -> u) -> Expr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr -> m Expr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr # | |||||
IsString Expr Source # | |||||
Defined in Verismith.Verilog.AST Methods fromString :: String -> Expr # | |||||
Monoid Expr Source # | |||||
Semigroup Expr Source # | |||||
Generic Expr Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Num Expr Source # | |||||
Show Expr Source # | |||||
NFData Expr Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq Expr Source # | |||||
Ord Expr Source # | |||||
Plated Expr Source # | |||||
Defined in Verismith.Verilog.AST Methods plate :: Traversal' Expr Expr # | |||||
Corecursive Expr Source # | |||||
Defined in Verismith.Verilog.AST Methods embed :: Base Expr Expr -> Expr # ana :: (a -> Base Expr a) -> a -> Expr # apo :: (a -> Base Expr (Either Expr a)) -> a -> Expr # postpro :: Recursive Expr => (forall b. Base Expr b -> Base Expr b) -> (a -> Base Expr a) -> a -> Expr # gpostpro :: (Recursive Expr, Monad m) => (forall b. m (Base Expr b) -> Base Expr (m b)) -> (forall c. Base Expr c -> Base Expr c) -> (a -> Base Expr (m a)) -> a -> Expr # | |||||
Recursive Expr Source # | |||||
Defined in Verismith.Verilog.AST Methods project :: Expr -> Base Expr Expr # cata :: (Base Expr a -> a) -> Expr -> a # para :: (Base Expr (Expr, a) -> a) -> Expr -> a # gpara :: (Corecursive Expr, Comonad w) => (forall b. Base Expr (w b) -> w (Base Expr b)) -> (Base Expr (EnvT Expr w a) -> a) -> Expr -> a # prepro :: Corecursive Expr => (forall b. Base Expr b -> Base Expr b) -> (Base Expr a -> a) -> Expr -> a # gprepro :: (Corecursive Expr, Comonad w) => (forall b. Base Expr (w b) -> w (Base Expr b)) -> (forall c. Base Expr c -> Base Expr c) -> (Base Expr (w a) -> a) -> Expr -> a # | |||||
Source Expr Source # | |||||
Mutate Expr Source # | |||||
type Rep Expr Source # | |||||
Defined in Verismith.Verilog.AST type Rep Expr = D1 ('MetaData "Expr" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 BitVec)) :+: C1 ('MetaCons "Id" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier))) :+: (C1 ('MetaCons "VecSelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: (C1 ('MetaCons "RangeSelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Range)) :+: C1 ('MetaCons "Concat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)))))) :+: ((C1 ('MetaCons "UnOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnaryOperator) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: C1 ('MetaCons "BinOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinaryOperator) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))) :+: (C1 ('MetaCons "Cond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))) :+: (C1 ('MetaCons "Appl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: C1 ('MetaCons "Str" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text)))))) | |||||
type Base Expr Source # | |||||
Defined in Verismith.Verilog.AST |
Constant expression, which are known before simulation at compile time.
Constructors
ConstNum | |
ParamId | |
Fields | |
ConstConcat | |
Fields
| |
ConstUnOp | |
Fields
| |
ConstBinOp | |
Fields
| |
ConstCond | |
Fields
| |
ConstStr | |
Instances
Data ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstExpr -> c ConstExpr # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConstExpr # toConstr :: ConstExpr -> Constr # dataTypeOf :: ConstExpr -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConstExpr) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstExpr) # gmapT :: (forall b. Data b => b -> b) -> ConstExpr -> ConstExpr # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstExpr -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstExpr -> r # gmapQ :: (forall d. Data d => d -> u) -> ConstExpr -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstExpr -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstExpr -> m ConstExpr # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstExpr -> m ConstExpr # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstExpr -> m ConstExpr # | |||||
IsString ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST Methods fromString :: String -> ConstExpr # | |||||
Monoid ConstExpr Source # | |||||
Semigroup ConstExpr Source # | |||||
Generic ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Num ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Show ConstExpr Source # | |||||
NFData ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq ConstExpr Source # | |||||
Ord ConstExpr Source # | |||||
Plated ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST Methods | |||||
Corecursive ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST Methods embed :: Base ConstExpr ConstExpr -> ConstExpr # ana :: (a -> Base ConstExpr a) -> a -> ConstExpr # apo :: (a -> Base ConstExpr (Either ConstExpr a)) -> a -> ConstExpr # postpro :: Recursive ConstExpr => (forall b. Base ConstExpr b -> Base ConstExpr b) -> (a -> Base ConstExpr a) -> a -> ConstExpr # gpostpro :: (Recursive ConstExpr, Monad m) => (forall b. m (Base ConstExpr b) -> Base ConstExpr (m b)) -> (forall c. Base ConstExpr c -> Base ConstExpr c) -> (a -> Base ConstExpr (m a)) -> a -> ConstExpr # | |||||
Recursive ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST Methods project :: ConstExpr -> Base ConstExpr ConstExpr # cata :: (Base ConstExpr a -> a) -> ConstExpr -> a # para :: (Base ConstExpr (ConstExpr, a) -> a) -> ConstExpr -> a # gpara :: (Corecursive ConstExpr, Comonad w) => (forall b. Base ConstExpr (w b) -> w (Base ConstExpr b)) -> (Base ConstExpr (EnvT ConstExpr w a) -> a) -> ConstExpr -> a # prepro :: Corecursive ConstExpr => (forall b. Base ConstExpr b -> Base ConstExpr b) -> (Base ConstExpr a -> a) -> ConstExpr -> a # gprepro :: (Corecursive ConstExpr, Comonad w) => (forall b. Base ConstExpr (w b) -> w (Base ConstExpr b)) -> (forall c. Base ConstExpr c -> Base ConstExpr c) -> (Base ConstExpr (w a) -> a) -> ConstExpr -> a # | |||||
Source ConstExpr Source # | |||||
Distance ConstExpr Source # | |||||
Mutate ConstExpr Source # | |||||
type Rep ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST type Rep ConstExpr = D1 ('MetaData "ConstExpr" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "ConstNum" 'PrefixI 'True) (S1 ('MetaSel ('Just "_constNum") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 BitVec)) :+: (C1 ('MetaCons "ParamId" 'PrefixI 'True) (S1 ('MetaSel ('Just "_constParamId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :+: C1 ('MetaCons "ConstConcat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_constConcat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty ConstExpr))))) :+: ((C1 ('MetaCons "ConstUnOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "_constUnOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnaryOperator) :*: S1 ('MetaSel ('Just "_constPrim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConstExpr)) :+: C1 ('MetaCons "ConstBinOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "_constLhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConstExpr) :*: (S1 ('MetaSel ('Just "_constBinOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinaryOperator) :*: S1 ('MetaSel ('Just "_constRhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConstExpr)))) :+: (C1 ('MetaCons "ConstCond" 'PrefixI 'True) (S1 ('MetaSel ('Just "_constCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConstExpr) :*: (S1 ('MetaSel ('Just "_constTrue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConstExpr) :*: S1 ('MetaSel ('Just "_constFalse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConstExpr))) :+: C1 ('MetaCons "ConstStr" 'PrefixI 'True) (S1 ('MetaSel ('Just "_constStr") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text))))) | |||||
type Base ConstExpr Source # | |||||
Defined in Verismith.Verilog.AST |
constToExpr :: ConstExpr -> Expr Source #
exprToConst :: Expr -> ConstExpr Source #
Assignment
Constructors
Assign | |
Fields
|
Instances
Data Assign Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Assign -> c Assign # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Assign # toConstr :: Assign -> Constr # dataTypeOf :: Assign -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Assign) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Assign) # gmapT :: (forall b. Data b => b -> b) -> Assign -> Assign # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Assign -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Assign -> r # gmapQ :: (forall d. Data d => d -> u) -> Assign -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Assign -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Assign -> m Assign # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Assign -> m Assign # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Assign -> m Assign # | |||||
Generic Assign Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show Assign Source # | |||||
NFData Assign Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq Assign Source # | |||||
Ord Assign Source # | |||||
Mutate Assign Source # | |||||
type Rep Assign Source # | |||||
Defined in Verismith.Verilog.AST type Rep Assign = D1 ('MetaData "Assign" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Assign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_assignReg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LVal) :*: (S1 ('MetaSel ('Just "_assignDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay)) :*: S1 ('MetaSel ('Just "_assignExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))) |
data ContAssign Source #
Type for continuous assignment.
assign x = 2'b1;
Constructors
ContAssign | |
Fields |
Instances
Data ContAssign Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContAssign -> c ContAssign # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContAssign # toConstr :: ContAssign -> Constr # dataTypeOf :: ContAssign -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ContAssign) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContAssign) # gmapT :: (forall b. Data b => b -> b) -> ContAssign -> ContAssign # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContAssign -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContAssign -> r # gmapQ :: (forall d. Data d => d -> u) -> ContAssign -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ContAssign -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContAssign -> m ContAssign # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContAssign -> m ContAssign # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContAssign -> m ContAssign # | |||||
Generic ContAssign Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show ContAssign Source # | |||||
Defined in Verismith.Verilog.AST Methods showsPrec :: Int -> ContAssign -> ShowS # show :: ContAssign -> String # showList :: [ContAssign] -> ShowS # | |||||
NFData ContAssign Source # | |||||
Defined in Verismith.Verilog.AST Methods rnf :: ContAssign -> () # | |||||
Eq ContAssign Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Ord ContAssign Source # | |||||
Defined in Verismith.Verilog.AST Methods compare :: ContAssign -> ContAssign -> Ordering # (<) :: ContAssign -> ContAssign -> Bool # (<=) :: ContAssign -> ContAssign -> Bool # (>) :: ContAssign -> ContAssign -> Bool # (>=) :: ContAssign -> ContAssign -> Bool # max :: ContAssign -> ContAssign -> ContAssign # min :: ContAssign -> ContAssign -> ContAssign # | |||||
Source ContAssign Source # | |||||
Defined in Verismith.Verilog.CodeGen Methods genSource :: ContAssign -> Text Source # | |||||
Mutate ContAssign Source # | |||||
Defined in Verismith.Verilog.Mutate Methods mutExpr :: (Expr -> Expr) -> ContAssign -> ContAssign Source # | |||||
type Rep ContAssign Source # | |||||
Defined in Verismith.Verilog.AST type Rep ContAssign = D1 ('MetaData "ContAssign" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ContAssign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_contAssignNetLVal") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_contAssignExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))) |
Statment
Statements in Verilog.
Constructors
TimeCtrl | Time control ( |
Fields
| |
EventCtrl | |
Fields
| |
SeqBlock | Sequential block ( |
Fields
| |
BlockAssign | blocking assignment ( |
NonBlockAssign | Non blocking assignment ( |
TaskEnable | |
Fields
| |
SysTaskEnable | |
Fields
| |
CondStmnt | |
Fields
| |
StmntCase | |
Fields
| |
ForLoop | Loop bounds shall be statically computable for a for loop. |
StmntAnn a (Statement a) |
Instances
Functor Statement Source # | |||||
Annotations Statement Source # | |||||
Data a => Data (Statement a) Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Statement a -> c (Statement a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Statement a) # toConstr :: Statement a -> Constr # dataTypeOf :: Statement a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Statement a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Statement a)) # gmapT :: (forall b. Data b => b -> b) -> Statement a -> Statement a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Statement a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Statement a -> r # gmapQ :: (forall d. Data d => d -> u) -> Statement a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Statement a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Statement a -> m (Statement a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement a -> m (Statement a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement a -> m (Statement a) # | |||||
Monoid (Statement a) Source # | |||||
Semigroup (Statement a) Source # | |||||
Generic (Statement a) Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show a => Show (Statement a) Source # | |||||
NFData a => NFData (Statement a) Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq a => Eq (Statement a) Source # | |||||
Ord a => Ord (Statement a) Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Plated (Statement a) Source # | |||||
Defined in Verismith.Verilog.AST Methods plate :: Traversal' (Statement a) (Statement a) # | |||||
Show ann => Source (Statement ann) Source # | |||||
Distance (Statement a) Source # | |||||
Mutate (Statement ann) Source # | |||||
type Rep (Statement a) Source # | |||||
Defined in Verismith.Verilog.AST type Rep (Statement a) = D1 ('MetaData "Statement" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "TimeCtrl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_statDelay") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Delay) :*: S1 ('MetaSel ('Just "_statDStat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Statement a)))) :+: C1 ('MetaCons "EventCtrl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_statEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Event) :*: S1 ('MetaSel ('Just "_statEStat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Statement a))))) :+: (C1 ('MetaCons "SeqBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "_statements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Statement a])) :+: (C1 ('MetaCons "BlockAssign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stmntBA") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Assign)) :+: C1 ('MetaCons "NonBlockAssign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stmntNBA") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Assign))))) :+: ((C1 ('MetaCons "TaskEnable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stmntTask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Task)) :+: (C1 ('MetaCons "SysTaskEnable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stmntSysTask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Task)) :+: C1 ('MetaCons "CondStmnt" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stmntCondExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "_stmntCondTrue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Statement a))) :*: S1 ('MetaSel ('Just "_stmntCondFalse") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Statement a))))))) :+: (C1 ('MetaCons "StmntCase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_stmntCaseType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CaseType) :*: S1 ('MetaSel ('Just "_stmntCaseExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_stmntCasePair") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [CasePair a]) :*: S1 ('MetaSel ('Just "_stmntCaseDefault") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Statement a))))) :+: (C1 ('MetaCons "ForLoop" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_forAssign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Assign) :*: S1 ('MetaSel ('Just "_forExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_forIncr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Assign) :*: S1 ('MetaSel ('Just "_forStmnt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Statement a)))) :+: C1 ('MetaCons "StmntAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Statement a))))))) |
statDelay :: forall a f. Applicative f => (Delay -> f Delay) -> Statement a -> f (Statement a) Source #
statDStat :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a) Source #
statEvent :: forall a f. Applicative f => (Event -> f Event) -> Statement a -> f (Statement a) Source #
statEStat :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a) Source #
statements :: forall a f. Applicative f => ([Statement a] -> f [Statement a]) -> Statement a -> f (Statement a) Source #
stmntBA :: forall a f. Applicative f => (Assign -> f Assign) -> Statement a -> f (Statement a) Source #
stmntNBA :: forall a f. Applicative f => (Assign -> f Assign) -> Statement a -> f (Statement a) Source #
stmntTask :: forall a f. Applicative f => (Task -> f Task) -> Statement a -> f (Statement a) Source #
stmntSysTask :: forall a f. Applicative f => (Task -> f Task) -> Statement a -> f (Statement a) Source #
stmntCondExpr :: forall a f. Applicative f => (Expr -> f Expr) -> Statement a -> f (Statement a) Source #
stmntCondTrue :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a) Source #
stmntCondFalse :: forall a f. Applicative f => (Maybe (Statement a) -> f (Maybe (Statement a))) -> Statement a -> f (Statement a) Source #
Module
'module' module_identifier [list_of_ports] ';' { module_item } end_module
Constructors
ModDecl | |
Fields
| |
ModDeclAnn a (ModDecl a) |
Instances
Functor ModDecl Source # | |||||
Annotations ModDecl Source # | |||||
Data a => Data (ModDecl a) Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModDecl a -> c (ModDecl a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ModDecl a) # toConstr :: ModDecl a -> Constr # dataTypeOf :: ModDecl a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ModDecl a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ModDecl a)) # gmapT :: (forall b. Data b => b -> b) -> ModDecl a -> ModDecl a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModDecl a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModDecl a -> r # gmapQ :: (forall d. Data d => d -> u) -> ModDecl a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModDecl a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModDecl a -> m (ModDecl a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModDecl a -> m (ModDecl a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModDecl a -> m (ModDecl a) # | |||||
Generic (ModDecl a) Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show a => Show (ModDecl a) Source # | |||||
NFData a => NFData (ModDecl a) Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq a => Eq (ModDecl a) Source # | |||||
Ord a => Ord (ModDecl a) Source # | |||||
Plated (ModDecl a) Source # | |||||
Defined in Verismith.Verilog.AST Methods plate :: Traversal' (ModDecl a) (ModDecl a) # | |||||
Show ann => Source (ModDecl ann) Source # | |||||
Distance (ModDecl a) Source # | |||||
Mutate (ModDecl ann) Source # | |||||
type Rep (ModDecl a) Source # | |||||
Defined in Verismith.Verilog.AST type Rep (ModDecl a) = D1 ('MetaData "ModDecl" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ModDecl" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_modId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_modOutPorts") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Port])) :*: (S1 ('MetaSel ('Just "_modInPorts") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Port]) :*: (S1 ('MetaSel ('Just "_modItems") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ModItem a]) :*: S1 ('MetaSel ('Just "_modParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Parameter])))) :+: C1 ('MetaCons "ModDeclAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ModDecl a)))) |
modId :: forall a f. Applicative f => (Identifier -> f Identifier) -> ModDecl a -> f (ModDecl a) Source #
modOutPorts :: forall a f. Applicative f => ([Port] -> f [Port]) -> ModDecl a -> f (ModDecl a) Source #
modInPorts :: forall a f. Applicative f => ([Port] -> f [Port]) -> ModDecl a -> f (ModDecl a) Source #
modItems :: forall a f. Applicative f => ([ModItem a] -> f [ModItem a]) -> ModDecl a -> f (ModDecl a) Source #
Module item which is the body of the module expression.
Constructors
ModCA | |
Fields | |
ModInst | |
Fields
| |
Initial !(Statement a) | |
Always !(Statement a) | |
Property | |
Fields | |
Decl | |
ParamDecl | |
Fields | |
LocalParamDecl | |
Fields | |
ModItemAnn a (ModItem a) |
Instances
Functor ModItem Source # | |||||
Annotations ModItem Source # | |||||
Data a => Data (ModItem a) Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModItem a -> c (ModItem a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ModItem a) # toConstr :: ModItem a -> Constr # dataTypeOf :: ModItem a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ModItem a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ModItem a)) # gmapT :: (forall b. Data b => b -> b) -> ModItem a -> ModItem a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModItem a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModItem a -> r # gmapQ :: (forall d. Data d => d -> u) -> ModItem a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModItem a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModItem a -> m (ModItem a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModItem a -> m (ModItem a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModItem a -> m (ModItem a) # | |||||
Generic (ModItem a) Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show a => Show (ModItem a) Source # | |||||
NFData a => NFData (ModItem a) Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq a => Eq (ModItem a) Source # | |||||
Ord a => Ord (ModItem a) Source # | |||||
Show ann => Source (ModItem ann) Source # | |||||
Distance (ModItem a) Source # | |||||
Mutate (ModItem ann) Source # | |||||
type Rep (ModItem a) Source # | |||||
Defined in Verismith.Verilog.AST type Rep (ModItem a) = D1 ('MetaData "ModItem" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "ModCA" 'PrefixI 'True) (S1 ('MetaSel ('Just "_modContAssign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContAssign)) :+: C1 ('MetaCons "ModInst" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_modInstId") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_modInstDecl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModConn])) :*: (S1 ('MetaSel ('Just "_modInstName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_modInstConns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModConn])))) :+: (C1 ('MetaCons "Initial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Statement a))) :+: C1 ('MetaCons "Always" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Statement a))))) :+: ((C1 ('MetaCons "Property" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_moditemPropLabel") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_moditemPropEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Event)) :*: (S1 ('MetaSel ('Just "_moditemPropBodyL") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr)) :*: S1 ('MetaSel ('Just "_moditemPropBodyR") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr))) :+: C1 ('MetaCons "Decl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_declDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe PortDir)) :*: (S1 ('MetaSel ('Just "_declPort") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Port) :*: S1 ('MetaSel ('Just "_declVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ConstExpr))))) :+: (C1 ('MetaCons "ParamDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_paramDecl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Parameter))) :+: (C1 ('MetaCons "LocalParamDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_localParamDecl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty LocalParam))) :+: C1 ('MetaCons "ModItemAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ModItem a))))))) |
modContAssign :: forall a f. Applicative f => (ContAssign -> f ContAssign) -> ModItem a -> f (ModItem a) Source #
modInstId :: forall a f. Applicative f => (Identifier -> f Identifier) -> ModItem a -> f (ModItem a) Source #
modInstName :: forall a f. Applicative f => (Identifier -> f Identifier) -> ModItem a -> f (ModItem a) Source #
modInstConns :: forall a f. Applicative f => ([ModConn] -> f [ModConn]) -> ModItem a -> f (ModItem a) Source #
traverseModItem :: Applicative f => (Expr -> f Expr) -> ModItem ann -> f (ModItem ann) Source #
declDir :: forall a f. Applicative f => (Maybe PortDir -> f (Maybe PortDir)) -> ModItem a -> f (ModItem a) Source #
This is currently a type because direct module declaration should also be added:
mod a(.y(y1), .x1(x11), .x2(x22));
Constructors
ModConn | |
ModConnNamed | |
Fields
|
Instances
Data ModConn Source # | |||||
Defined in Verismith.Verilog.AST Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModConn -> c ModConn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModConn # toConstr :: ModConn -> Constr # dataTypeOf :: ModConn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModConn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModConn) # gmapT :: (forall b. Data b => b -> b) -> ModConn -> ModConn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModConn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModConn -> r # gmapQ :: (forall d. Data d => d -> u) -> ModConn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ModConn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModConn -> m ModConn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModConn -> m ModConn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModConn -> m ModConn # | |||||
Generic ModConn Source # | |||||
Defined in Verismith.Verilog.AST Associated Types
| |||||
Show ModConn Source # | |||||
NFData ModConn Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Eq ModConn Source # | |||||
Ord ModConn Source # | |||||
Defined in Verismith.Verilog.AST | |||||
Mutate ModConn Source # | |||||
type Rep ModConn Source # | |||||
Defined in Verismith.Verilog.AST type Rep ModConn = D1 ('MetaData "ModConn" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ModConn" 'PrefixI 'True) (S1 ('MetaSel ('Just "_modExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: C1 ('MetaCons "ModConnNamed" 'PrefixI 'True) (S1 ('MetaSel ('Just "_modConnName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_modExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))) |
Useful Lenses and Traversals
getModule :: forall a f. Applicative f => (ModDecl a -> f (ModDecl a)) -> Verilog a -> f (Verilog a) Source #
getSourceId :: forall a f. Applicative f => (Text -> f Text) -> Verilog a -> f (Verilog a) Source #
Quote
verilog :: QuasiQuoter Source #
Quasiquoter for verilog, so that verilog can be written inline and be parsed to an AST at compile time.