verismith-1.1.0: Random verilog generation and simulator testing.
Copyright(c) 2019 Yann Herklotz Grave
LicenseGPL-3
Maintaineryann [at] yannherklotz [dot] com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Verismith.Verilog

Description

Verilog implementation with random generation and mutations.

Synopsis

Documentation

data SourceInfo a Source #

Top level type which contains all the source code and associated information.

Constructors

SourceInfo 

Fields

Instances

Instances details
Functor SourceInfo Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

fmap :: (a -> b) -> SourceInfo a -> SourceInfo b #

(<$) :: a -> SourceInfo b -> SourceInfo a #

Annotations SourceInfo Source # 
Instance details

Defined in Verismith.Verilog.AST

Data a => Data (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceInfo a -> c (SourceInfo a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SourceInfo a) #

toConstr :: SourceInfo a -> Constr #

dataTypeOf :: SourceInfo a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SourceInfo a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SourceInfo a)) #

gmapT :: (forall b. Data b => b -> b) -> SourceInfo a -> SourceInfo a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceInfo a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceInfo a -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourceInfo a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceInfo a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceInfo a -> m (SourceInfo a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceInfo a -> m (SourceInfo a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceInfo a -> m (SourceInfo a) #

Monoid (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Semigroup (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Generic (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep (SourceInfo a) 
Instance details

Defined in Verismith.Verilog.AST

type Rep (SourceInfo a) = D1 ('MetaData "SourceInfo" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SourceInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_infoTop") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "_infoSrc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Verilog a))))

Methods

from :: SourceInfo a -> Rep (SourceInfo a) x #

to :: Rep (SourceInfo a) x -> SourceInfo a #

Show a => Show (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData a => NFData (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: SourceInfo a -> () #

Eq a => Eq (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(==) :: SourceInfo a -> SourceInfo a -> Bool #

(/=) :: SourceInfo a -> SourceInfo a -> Bool #

Ord a => Ord (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Show ann => Source (SourceInfo ann) Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: SourceInfo ann -> Text Source #

Distance (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate (SourceInfo ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> SourceInfo ann -> SourceInfo ann Source #

type Rep (SourceInfo a) Source # 
Instance details

Defined in Verismith.Verilog.AST

type Rep (SourceInfo a) = D1 ('MetaData "SourceInfo" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SourceInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_infoTop") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "_infoSrc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Verilog a))))

newtype Verilog a Source #

The complete sourcetext for the Verilog module.

Constructors

Verilog 

Fields

Instances

Instances details
Functor Verilog Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

fmap :: (a -> b) -> Verilog a -> Verilog b #

(<$) :: a -> Verilog b -> Verilog a #

Annotations Verilog Source # 
Instance details

Defined in Verismith.Verilog.AST

Data a => Data (Verilog a) Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Methods

mempty :: Verilog a #

mappend :: Verilog a -> Verilog a -> Verilog a #

mconcat :: [Verilog a] -> Verilog a #

Semigroup (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(<>) :: Verilog a -> Verilog a -> Verilog a #

sconcat :: NonEmpty (Verilog a) -> Verilog a #

stimes :: Integral b => b -> Verilog a -> Verilog a #

Generic (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep (Verilog a) 
Instance details

Defined in Verismith.Verilog.AST

type Rep (Verilog a) = D1 ('MetaData "Verilog" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Verilog" 'PrefixI 'True) (S1 ('MetaSel ('Just "getVerilog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModDecl a])))

Methods

from :: Verilog a -> Rep (Verilog a) x #

to :: Rep (Verilog a) x -> Verilog a #

Show a => Show (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> Verilog a -> ShowS #

show :: Verilog a -> String #

showList :: [Verilog a] -> ShowS #

NFData a => NFData (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Verilog a -> () #

Eq a => Eq (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(==) :: Verilog a -> Verilog a -> Bool #

(/=) :: Verilog a -> Verilog a -> Bool #

Ord a => Ord (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: Verilog a -> Verilog a -> Ordering #

(<) :: Verilog a -> Verilog a -> Bool #

(<=) :: Verilog a -> Verilog a -> Bool #

(>) :: Verilog a -> Verilog a -> Bool #

(>=) :: Verilog a -> Verilog a -> Bool #

max :: Verilog a -> Verilog a -> Verilog a #

min :: Verilog a -> Verilog a -> Verilog a #

Wrapped (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Unwrapped (Verilog a) 
Instance details

Defined in Verismith.Verilog.AST

type Unwrapped (Verilog a) = [ModDecl a]

Methods

_Wrapped' :: Iso' (Verilog a) (Unwrapped (Verilog a)) #

Show ann => Source (Verilog ann) Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: Verilog ann -> Text Source #

Distance (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate (Verilog ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Verilog ann -> Verilog ann Source #

Verilog a1 ~ t => Rewrapped (Verilog a2) t Source # 
Instance details

Defined in Verismith.Verilog.AST

type Rep (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

type Rep (Verilog a) = D1 ('MetaData "Verilog" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Verilog" 'PrefixI 'True) (S1 ('MetaSel ('Just "getVerilog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModDecl a])))
type Unwrapped (Verilog a) Source # 
Instance details

Defined in Verismith.Verilog.AST

type Unwrapped (Verilog a) = [ModDecl a]

parseVerilog Source #

Arguments

:: Text

Name of parsed object.

-> Text

Content to be parsed.

-> Either Text (Verilog ann)

Returns String with error message if parse fails.

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

Instances details
Data a => Data (GenVerilog a) Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.CodeGen

Eq a => Eq (GenVerilog a) Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

(==) :: GenVerilog a -> GenVerilog a -> Bool #

(/=) :: GenVerilog a -> GenVerilog a -> Bool #

Ord a => Ord (GenVerilog a) Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Mutate a => Mutate (GenVerilog a) Source # 
Instance details

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

Instances details
Data Identifier Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Monoid Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

Semigroup Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

Generic Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep Identifier 
Instance details

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)))
Show Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Identifier -> () #

Eq Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

Ord Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

Wrapped Identifier Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Unwrapped Identifier 
Instance details

Defined in Verismith.Verilog.AST

Source Identifier Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Distance Identifier Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate Identifier Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Identifier ~ t => Rewrapped Identifier t Source # 
Instance details

Defined in Verismith.Verilog.AST

type Rep Identifier Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Control

newtype Delay Source #

Verilog syntax for adding a delay, which is represented as #num.

Constructors

Delay 

Fields

Instances

Instances details
Data Delay Source # 
Instance details

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 #

toConstr :: Delay -> Constr #

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep Delay 
Instance details

Defined in Verismith.Verilog.AST

type Rep Delay = D1 ('MetaData "Delay" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Delay" 'PrefixI 'True) (S1 ('MetaSel ('Just "_getDelay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Methods

from :: Delay -> Rep Delay x #

to :: Rep Delay x -> Delay #

Num Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

Show Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> Delay -> ShowS #

show :: Delay -> String #

showList :: [Delay] -> ShowS #

NFData Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Delay -> () #

Eq Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: Delay -> Delay -> Ordering #

(<) :: Delay -> Delay -> Bool #

(<=) :: Delay -> Delay -> Bool #

(>) :: Delay -> Delay -> Bool #

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

max :: Delay -> Delay -> Delay #

min :: Delay -> Delay -> Delay #

Wrapped Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Unwrapped Delay 
Instance details

Defined in Verismith.Verilog.AST

Source Delay Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: Delay -> Text Source #

Mutate Delay Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Delay -> Delay Source #

Delay ~ t => Rewrapped Delay t Source # 
Instance details

Defined in Verismith.Verilog.AST

type Rep Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

type Rep Delay = D1 ('MetaData "Delay" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Delay" 'PrefixI 'True) (S1 ('MetaSel ('Just "_getDelay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type Unwrapped Delay Source # 
Instance details

Defined in Verismith.Verilog.AST

data Event Source #

Verilog syntax for an event, such as @x, which is used for always blocks

Instances

Instances details
Data Event Source # 
Instance details

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 #

toConstr :: Event -> Constr #

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 # 
Instance details

Defined in Verismith.Verilog.AST

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Show Event Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

NFData Event Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Event -> () #

Eq Event Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord Event Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: Event -> Event -> Ordering #

(<) :: Event -> Event -> Bool #

(<=) :: Event -> Event -> Bool #

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Plated Event Source # 
Instance details

Defined in Verismith.Verilog.AST

Corecursive Event Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: Event -> Text Source #

Mutate Event Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Event -> Event Source #

type Rep Event Source # 
Instance details

Defined in Verismith.Verilog.AST

type Base Event Source # 
Instance details

Defined in Verismith.Verilog.AST

type Base Event

Operators

data BinaryOperator Source #

Binary operators that are currently supported in the verilog generation.

Instances

Instances details
Data BinaryOperator Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep BinaryOperator 
Instance details

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))))))
Show BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: BinaryOperator -> () #

Eq BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

Ord BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

Mutate BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog.Mutate

type Rep BinaryOperator Source # 
Instance details

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

Instances details
Data UnaryOperator Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep UnaryOperator 
Instance details

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)))))
Show UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: UnaryOperator -> () #

Eq UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

Ord UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog.AST

Source UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Mutate UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog.Mutate

type Rep UnaryOperator Source # 
Instance details

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

data Task Source #

Task call, which is similar to function calls.

Constructors

Task 

Instances

Instances details
Data Task Source # 
Instance details

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 #

toConstr :: Task -> Constr #

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep Task 
Instance details

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])))

Methods

from :: Task -> Rep Task x #

to :: Rep Task x -> Task #

Show Task Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> Task -> ShowS #

show :: Task -> String #

showList :: [Task] -> ShowS #

NFData Task Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Task -> () #

Eq Task Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord Task Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: Task -> Task -> Ordering #

(<) :: Task -> Task -> Bool #

(<=) :: Task -> Task -> Bool #

(>) :: Task -> Task -> Bool #

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

max :: Task -> Task -> Task #

min :: Task -> Task -> Task #

Source Task Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: Task -> Text Source #

Mutate Task Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Task -> Task Source #

type Rep Task Source # 
Instance details

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

data LVal Source #

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 
RegSize 
RegConcat 

Fields

Instances

Instances details
Data LVal Source # 
Instance details

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 #

toConstr :: LVal -> Constr #

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 # 
Instance details

Defined in Verismith.Verilog.AST

Methods

fromString :: String -> LVal #

Generic LVal Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep LVal 
Instance details

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]))))

Methods

from :: LVal -> Rep LVal x #

to :: Rep LVal x -> LVal #

Show LVal Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> LVal -> ShowS #

show :: LVal -> String #

showList :: [LVal] -> ShowS #

NFData LVal Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: LVal -> () #

Eq LVal Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord LVal Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: LVal -> LVal -> Ordering #

(<) :: LVal -> LVal -> Bool #

(<=) :: LVal -> LVal -> Bool #

(>) :: LVal -> LVal -> Bool #

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

max :: LVal -> LVal -> LVal #

min :: LVal -> LVal -> LVal #

Source LVal Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: LVal -> Text Source #

Mutate LVal Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> LVal -> LVal Source #

type Rep LVal Source # 
Instance details

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

data PortDir Source #

Different port direction that are supported in Verilog.

Constructors

PortIn 
PortOut 
PortInOut 

Instances

Instances details
Data PortDir Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep PortDir 
Instance details

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)))

Methods

from :: PortDir -> Rep PortDir x #

to :: Rep PortDir x -> PortDir #

Show PortDir Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData PortDir Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: PortDir -> () #

Eq PortDir Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord PortDir Source # 
Instance details

Defined in Verismith.Verilog.AST

Source PortDir Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Distance PortDir Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate PortDir Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> PortDir -> PortDir Source #

type Rep PortDir Source # 
Instance details

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)))

data PortType Source #

Currently, only wire and reg are supported, as the other net types are not that common and not a priority.

Constructors

Wire 
Reg 

Instances

Instances details
Data PortType Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep PortType 
Instance details

Defined in Verismith.Verilog.AST

type Rep PortType = D1 ('MetaData "PortType" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Wire" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reg" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: PortType -> Rep PortType x #

to :: Rep PortType x -> PortType #

Show PortType Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData PortType Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: PortType -> () #

Eq PortType Source # 
Instance details

Defined in Verismith.Verilog.AST

Ord PortType Source # 
Instance details

Defined in Verismith.Verilog.AST

Source PortType Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Distance PortType Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate PortType Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> PortType -> PortType Source #

type Rep PortType Source # 
Instance details

Defined in Verismith.Verilog.AST

type Rep PortType = D1 ('MetaData "PortType" "Verismith.Verilog.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Wire" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reg" 'PrefixI 'False) (U1 :: Type -> Type))

data Port 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 

Instances

Instances details
Data Port Source # 
Instance details

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 #

toConstr :: Port -> Constr #

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep Port 
Instance details

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))))

Methods

from :: Port -> Rep Port x #

to :: Rep Port x -> Port #

Show Port Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> Port -> ShowS #

show :: Port -> String #

showList :: [Port] -> ShowS #

NFData Port Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Port -> () #

Eq Port Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord Port Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: Port -> Port -> Ordering #

(<) :: Port -> Port -> Bool #

(<=) :: Port -> Port -> Bool #

(>) :: Port -> Port -> Bool #

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

max :: Port -> Port -> Port #

min :: Port -> Port -> Port #

Source Port Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: Port -> Text Source #

Distance Port Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate Port Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Port -> Port Source #

type Rep Port Source # 
Instance details

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

data Expr Source #

Verilog expression, which can either be a primary expression, unary expression, binary operator expression or a conditional expression.

Instances

Instances details
Data Expr Source # 
Instance details

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 #

toConstr :: Expr -> Constr #

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 # 
Instance details

Defined in Verismith.Verilog.AST

Methods

fromString :: String -> Expr #

Monoid Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

mempty :: Expr #

mappend :: Expr -> Expr -> Expr #

mconcat :: [Expr] -> Expr #

Semigroup Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(<>) :: Expr -> Expr -> Expr #

sconcat :: NonEmpty Expr -> Expr #

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

Generic Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep Expr 
Instance details

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))))))

Methods

from :: Expr -> Rep Expr x #

to :: Rep Expr x -> Expr #

Num Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(+) :: Expr -> Expr -> Expr #

(-) :: Expr -> Expr -> Expr #

(*) :: Expr -> Expr -> Expr #

negate :: Expr -> Expr #

abs :: Expr -> Expr #

signum :: Expr -> Expr #

fromInteger :: Integer -> Expr #

Show Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

NFData Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Expr -> () #

Eq Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: Expr -> Expr -> Ordering #

(<) :: Expr -> Expr -> Bool #

(<=) :: Expr -> Expr -> Bool #

(>) :: Expr -> Expr -> Bool #

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

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

Plated Expr Source # 
Instance details

Defined in Verismith.Verilog.AST

Corecursive Expr Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: Expr -> Text Source #

Mutate Expr Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Expr -> Expr Source #

type Rep Expr Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

type Base Expr

data ConstExpr Source #

Constant expression, which are known before simulation at compile time.

Instances

Instances details
Data ConstExpr Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Monoid ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Semigroup ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Generic ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep ConstExpr 
Instance details

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)))))
Num ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Show ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: ConstExpr -> () #

Eq ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Ord ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Plated ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.AST

Corecursive ConstExpr Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.CodeGen

Distance ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ConstExpr -> ConstExpr Source #

type Rep ConstExpr Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Assignment

data Assign Source #

Constructors

Assign 

Instances

Instances details
Data Assign Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep Assign 
Instance details

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))))

Methods

from :: Assign -> Rep Assign x #

to :: Rep Assign x -> Assign #

Show Assign Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData Assign Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Assign -> () #

Eq Assign Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord Assign Source # 
Instance details

Defined in Verismith.Verilog.AST

Mutate Assign Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Assign -> Assign Source #

type Rep Assign Source # 
Instance details

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;

Instances

Instances details
Data ContAssign Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep ContAssign 
Instance details

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)))
Show ContAssign Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData ContAssign Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: ContAssign -> () #

Eq ContAssign Source # 
Instance details

Defined in Verismith.Verilog.AST

Ord ContAssign Source # 
Instance details

Defined in Verismith.Verilog.AST

Source ContAssign Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Mutate ContAssign Source # 
Instance details

Defined in Verismith.Verilog.Mutate

type Rep ContAssign Source # 
Instance details

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

data Statement a Source #

Statements in Verilog.

Constructors

TimeCtrl

Time control (#NUM)

EventCtrl 
SeqBlock

Sequential block (begin ... end)

Fields

BlockAssign

blocking assignment (=)

Fields

NonBlockAssign

Non blocking assignment (<=)

Fields

TaskEnable 

Fields

SysTaskEnable 

Fields

CondStmnt 
StmntCase 
ForLoop

Loop bounds shall be statically computable for a for loop.

StmntAnn a (Statement a) 

Instances

Instances details
Functor Statement Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

fmap :: (a -> b) -> Statement a -> Statement b #

(<$) :: a -> Statement b -> Statement a #

Annotations Statement Source # 
Instance details

Defined in Verismith.Verilog.AST

Data a => Data (Statement a) Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Semigroup (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(<>) :: Statement a -> Statement a -> Statement a #

sconcat :: NonEmpty (Statement a) -> Statement a #

stimes :: Integral b => b -> Statement a -> Statement a #

Generic (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep (Statement a) 
Instance details

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)))))))

Methods

from :: Statement a -> Rep (Statement a) x #

to :: Rep (Statement a) x -> Statement a #

Show a => Show (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData a => NFData (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: Statement a -> () #

Eq a => Eq (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(==) :: Statement a -> Statement a -> Bool #

(/=) :: Statement a -> Statement a -> Bool #

Ord a => Ord (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Plated (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Show ann => Source (Statement ann) Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: Statement ann -> Text Source #

Distance (Statement a) Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate (Statement ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Statement ann -> Statement ann Source #

type Rep (Statement a) Source # 
Instance details

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

data ModDecl a Source #

'module' module_identifier [list_of_ports] ';' { module_item } end_module

Constructors

ModDecl 
ModDeclAnn a (ModDecl a) 

Instances

Instances details
Functor ModDecl Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

fmap :: (a -> b) -> ModDecl a -> ModDecl b #

(<$) :: a -> ModDecl b -> ModDecl a #

Annotations ModDecl Source # 
Instance details

Defined in Verismith.Verilog.AST

Data a => Data (ModDecl a) Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep (ModDecl a) 
Instance details

Defined in Verismith.Verilog.AST

Methods

from :: ModDecl a -> Rep (ModDecl a) x #

to :: Rep (ModDecl a) x -> ModDecl a #

Show a => Show (ModDecl a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> ModDecl a -> ShowS #

show :: ModDecl a -> String #

showList :: [ModDecl a] -> ShowS #

NFData a => NFData (ModDecl a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: ModDecl a -> () #

Eq a => Eq (ModDecl a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(==) :: ModDecl a -> ModDecl a -> Bool #

(/=) :: ModDecl a -> ModDecl a -> Bool #

Ord a => Ord (ModDecl a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: ModDecl a -> ModDecl a -> Ordering #

(<) :: ModDecl a -> ModDecl a -> Bool #

(<=) :: ModDecl a -> ModDecl a -> Bool #

(>) :: ModDecl a -> ModDecl a -> Bool #

(>=) :: ModDecl a -> ModDecl a -> Bool #

max :: ModDecl a -> ModDecl a -> ModDecl a #

min :: ModDecl a -> ModDecl a -> ModDecl a #

Plated (ModDecl a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

plate :: Traversal' (ModDecl a) (ModDecl a) #

Show ann => Source (ModDecl ann) Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: ModDecl ann -> Text Source #

Distance (ModDecl a) Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate (ModDecl ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ModDecl ann -> ModDecl ann Source #

type Rep (ModDecl a) Source # 
Instance details

Defined in Verismith.Verilog.AST

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 #

data ModItem a Source #

Module item which is the body of the module expression.

Instances

Instances details
Functor ModItem Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

fmap :: (a -> b) -> ModItem a -> ModItem b #

(<$) :: a -> ModItem b -> ModItem a #

Annotations ModItem Source # 
Instance details

Defined in Verismith.Verilog.AST

Data a => Data (ModItem a) Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep (ModItem a) 
Instance details

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)))))))

Methods

from :: ModItem a -> Rep (ModItem a) x #

to :: Rep (ModItem a) x -> ModItem a #

Show a => Show (ModItem a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

showsPrec :: Int -> ModItem a -> ShowS #

show :: ModItem a -> String #

showList :: [ModItem a] -> ShowS #

NFData a => NFData (ModItem a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: ModItem a -> () #

Eq a => Eq (ModItem a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

(==) :: ModItem a -> ModItem a -> Bool #

(/=) :: ModItem a -> ModItem a -> Bool #

Ord a => Ord (ModItem a) Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

compare :: ModItem a -> ModItem a -> Ordering #

(<) :: ModItem a -> ModItem a -> Bool #

(<=) :: ModItem a -> ModItem a -> Bool #

(>) :: ModItem a -> ModItem a -> Bool #

(>=) :: ModItem a -> ModItem a -> Bool #

max :: ModItem a -> ModItem a -> ModItem a #

min :: ModItem a -> ModItem a -> ModItem a #

Show ann => Source (ModItem ann) Source # 
Instance details

Defined in Verismith.Verilog.CodeGen

Methods

genSource :: ModItem ann -> Text Source #

Distance (ModItem a) Source # 
Instance details

Defined in Verismith.Verilog.Distance

Mutate (ModItem ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ModItem ann -> ModItem ann Source #

type Rep (ModItem a) Source # 
Instance details

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 #

declPort :: forall a f. Applicative f => (Port -> f Port) -> ModItem a -> f (ModItem a) Source #

data ModConn Source #

This is currently a type because direct module declaration should also be added:

mod a(.y(y1), .x1(x11), .x2(x22));

Constructors

ModConn 

Fields

ModConnNamed 

Instances

Instances details
Data ModConn Source # 
Instance details

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 # 
Instance details

Defined in Verismith.Verilog.AST

Associated Types

type Rep ModConn 
Instance details

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)))

Methods

from :: ModConn -> Rep ModConn x #

to :: Rep ModConn x -> ModConn #

Show ModConn Source # 
Instance details

Defined in Verismith.Verilog.AST

NFData ModConn Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

rnf :: ModConn -> () #

Eq ModConn Source # 
Instance details

Defined in Verismith.Verilog.AST

Methods

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

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

Ord ModConn Source # 
Instance details

Defined in Verismith.Verilog.AST

Mutate ModConn Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ModConn -> ModConn Source #

type Rep ModConn Source # 
Instance details

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.