verismith-1.1.0: Random verilog generation and simulator testing.
Safe HaskellNone
LanguageHaskell2010

Verismith.Verilog2005.AST

Synopsis

Documentation

data GenMinTypMax et Source #

Minimum, Typical, Maximum

Constructors

MTMSingle !et 
MTMFull 

Fields

Instances

Instances details
Data et => Data (GenMinTypMax et) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenMinTypMax et -> c (GenMinTypMax et) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenMinTypMax et) #

toConstr :: GenMinTypMax et -> Constr #

dataTypeOf :: GenMinTypMax et -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenMinTypMax et -> GenMinTypMax et #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenMinTypMax et -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenMinTypMax et -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenMinTypMax et -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenMinTypMax et -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenMinTypMax et -> m (GenMinTypMax et) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenMinTypMax et -> m (GenMinTypMax et) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenMinTypMax et -> m (GenMinTypMax et) #

Generic (GenMinTypMax et) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (GenMinTypMax et) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenMinTypMax et) = D1 ('MetaData "GenMinTypMax" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "MTMSingle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et)) :+: C1 ('MetaCons "MTMFull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mtmMin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et) :*: (S1 ('MetaSel ('Just "_mtmTyp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et) :*: S1 ('MetaSel ('Just "_mtmMax") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et))))

Methods

from :: GenMinTypMax et -> Rep (GenMinTypMax et) x #

to :: Rep (GenMinTypMax et) x -> GenMinTypMax et #

Show et => Show (GenMinTypMax et) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq et => Eq (GenMinTypMax et) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: GenMinTypMax et -> GenMinTypMax et -> Bool #

(/=) :: GenMinTypMax et -> GenMinTypMax et -> Bool #

type Rep (GenMinTypMax et) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenMinTypMax et) = D1 ('MetaData "GenMinTypMax" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "MTMSingle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et)) :+: C1 ('MetaCons "MTMFull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mtmMin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et) :*: (S1 ('MetaSel ('Just "_mtmTyp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et) :*: S1 ('MetaSel ('Just "_mtmMax") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 et))))

newtype Identifier Source #

Identifier, do not use for other things (like a string literal), used for biplate

Constructors

Identifier ByteString 

Instances

Instances details
Data Identifier Source # 
Instance details

Defined in Verismith.Verilog2005.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.Verilog2005.AST

Generic Identifier Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Identifier 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Identifier = D1 ('MetaData "Identifier" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Identifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
Show Identifier Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Identifier Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Identifier Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Identifier = D1 ('MetaData "Identifier" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Identifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data Identified t Source #

Quickly add an identifier to all members of a sum type, other uses are discouraged

Constructors

Identified 

Fields

Instances

Instances details
Eq1 Identified Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

liftEq :: (a -> b -> Bool) -> Identified a -> Identified b -> Bool #

Show1 Identified Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identified a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identified a] -> ShowS #

Functor Identified Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

Data t => Data (Identified t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identified t -> c (Identified t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Identified t) #

toConstr :: Identified t -> Constr #

dataTypeOf :: Identified t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Identified t -> Identified t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identified t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identified t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identified t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identified t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identified t -> m (Identified t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identified t -> m (Identified t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identified t -> m (Identified t) #

Generic (Identified t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (Identified t) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (Identified t) = D1 ('MetaData "Identified" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Identified" 'PrefixI 'True) (S1 ('MetaSel ('Just "_identIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_identData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t)))

Methods

from :: Identified t -> Rep (Identified t) x #

to :: Rep (Identified t) x -> Identified t #

Show t => Show (Identified t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq t => Eq (Identified t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: Identified t -> Identified t -> Bool #

(/=) :: Identified t -> Identified t -> Bool #

type Rep (Identified t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (Identified t) = D1 ('MetaData "Identified" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Identified" 'PrefixI 'True) (S1 ('MetaSel ('Just "_identIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_identData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t)))

data UnaryOperator Source #

Unary operators

Instances

Instances details
Data UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.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 #

Bounded UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep UnaryOperator 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep UnaryOperator = D1 ('MetaData "UnaryOperator" "Verismith.Verilog2005.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 "UnXNor" 'PrefixI 'False) (U1 :: Type -> Type)))))
Show UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep UnaryOperator = D1 ('MetaData "UnaryOperator" "Verismith.Verilog2005.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 "UnXNor" 'PrefixI 'False) (U1 :: Type -> Type)))))

data BinaryOperator Source #

Binary operators

Instances

Instances details
Data BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.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 #

Bounded BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep BinaryOperator 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep BinaryOperator = D1 ('MetaData "BinaryOperator" "Verismith.Verilog2005.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 "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.Verilog2005.AST

Eq BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep BinaryOperator = D1 ('MetaData "BinaryOperator" "Verismith.Verilog2005.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 "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 Number Source #

Instances

Instances details
Data Number Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Number -> Constr #

dataTypeOf :: Number -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Number Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

from :: Number -> Rep Number x #

to :: Rep Number x -> Number #

Show Number Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Number Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep Number Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data GenPrim i r a Source #

Parametric primary expression

Instances

Instances details
(Data r, Data i, Data a) => Data (GenPrim i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (GenPrim i r a) #

toConstr :: GenPrim i r a -> Constr #

dataTypeOf :: GenPrim i r a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenPrim i r a -> GenPrim i r a #

gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> GenPrim i r a -> r0 #

gmapQr :: forall r0 r'. (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> GenPrim i r a -> r0 #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenPrim i r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenPrim i r a -> m (GenPrim i r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenPrim i r a -> m (GenPrim i r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenPrim i r a -> m (GenPrim i r a) #

Generic (GenPrim i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (GenPrim i r a) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenPrim i r a) = D1 ('MetaData "GenPrim" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "PrimNumber" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pnSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Natural)) :*: (S1 ('MetaSel ('Just "_pnSigned") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_pnValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Number))) :+: C1 ('MetaCons "PrimReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))) :+: (C1 ('MetaCons "PrimIdent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_piIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 i) :*: S1 ('MetaSel ('Just "_piSub") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r)) :+: C1 ('MetaCons "PrimConcat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (GenExpr i r a)))))) :+: ((C1 ('MetaCons "PrimMultConcat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pmcMul") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr Identifier (Maybe CRangeExpr) a)) :*: S1 ('MetaSel ('Just "_pmcExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (GenExpr i r a)))) :+: C1 ('MetaCons "PrimFun" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pfIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 i) :*: (S1 ('MetaSel ('Just "_pfAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_pfArg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [GenExpr i r a])))) :+: (C1 ('MetaCons "PrimSysFun" 'PrefixI 'True) (S1 ('MetaSel ('Just "_psfIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_psfArg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [GenExpr i r a])) :+: (C1 ('MetaCons "PrimMinTypMax" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenMinTypMax (GenExpr i r a)))) :+: C1 ('MetaCons "PrimString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))))))

Methods

from :: GenPrim i r a -> Rep (GenPrim i r a) x #

to :: Rep (GenPrim i r a) x -> GenPrim i r a #

(Show r, Show i, Show a) => Show (GenPrim i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> GenPrim i r a -> ShowS #

show :: GenPrim i r a -> String #

showList :: [GenPrim i r a] -> ShowS #

(Eq r, Eq i, Eq a) => Eq (GenPrim i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: GenPrim i r a -> GenPrim i r a -> Bool #

(/=) :: GenPrim i r a -> GenPrim i r a -> Bool #

type Rep (GenPrim i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenPrim i r a) = D1 ('MetaData "GenPrim" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "PrimNumber" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pnSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Natural)) :*: (S1 ('MetaSel ('Just "_pnSigned") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_pnValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Number))) :+: C1 ('MetaCons "PrimReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))) :+: (C1 ('MetaCons "PrimIdent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_piIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 i) :*: S1 ('MetaSel ('Just "_piSub") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r)) :+: C1 ('MetaCons "PrimConcat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (GenExpr i r a)))))) :+: ((C1 ('MetaCons "PrimMultConcat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pmcMul") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr Identifier (Maybe CRangeExpr) a)) :*: S1 ('MetaSel ('Just "_pmcExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (GenExpr i r a)))) :+: C1 ('MetaCons "PrimFun" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pfIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 i) :*: (S1 ('MetaSel ('Just "_pfAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_pfArg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [GenExpr i r a])))) :+: (C1 ('MetaCons "PrimSysFun" 'PrefixI 'True) (S1 ('MetaSel ('Just "_psfIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_psfArg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [GenExpr i r a])) :+: (C1 ('MetaCons "PrimMinTypMax" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenMinTypMax (GenExpr i r a)))) :+: C1 ('MetaCons "PrimString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))))))

data HierIdent Source #

Hierarchical identifier

Constructors

HierIdent 

Instances

Instances details
Data HierIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: HierIdent -> Constr #

dataTypeOf :: HierIdent -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic HierIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep HierIdent 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep HierIdent = D1 ('MetaData "HierIdent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "HierIdent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_hiPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Identifier, Maybe CExpr)]) :*: S1 ('MetaSel ('Just "_hiIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)))
Show HierIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq HierIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep HierIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep HierIdent = D1 ('MetaData "HierIdent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "HierIdent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_hiPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [(Identifier, Maybe CExpr)]) :*: S1 ('MetaSel ('Just "_hiIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)))

data GenDimRange e Source #

Indexing for dimension and range

Constructors

GenDimRange 

Fields

Instances

Instances details
Data e => Data (GenDimRange e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenDimRange e -> c (GenDimRange e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenDimRange e) #

toConstr :: GenDimRange e -> Constr #

dataTypeOf :: GenDimRange e -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenDimRange e -> GenDimRange e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenDimRange e -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenDimRange e -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenDimRange e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenDimRange e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenDimRange e -> m (GenDimRange e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenDimRange e -> m (GenDimRange e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenDimRange e -> m (GenDimRange e) #

Generic (GenDimRange e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (GenDimRange e) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenDimRange e) = D1 ('MetaData "GenDimRange" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GenDimRange" 'PrefixI 'True) (S1 ('MetaSel ('Just "_gdrDim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [e]) :*: S1 ('MetaSel ('Just "_gdrRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenRangeExpr e))))

Methods

from :: GenDimRange e -> Rep (GenDimRange e) x #

to :: Rep (GenDimRange e) x -> GenDimRange e #

Show e => Show (GenDimRange e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq e => Eq (GenDimRange e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenDimRange e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenDimRange e) = D1 ('MetaData "GenDimRange" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GenDimRange" 'PrefixI 'True) (S1 ('MetaSel ('Just "_gdrDim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [e]) :*: S1 ('MetaSel ('Just "_gdrRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenRangeExpr e))))

data GenExpr i r a Source #

Parametric expression

Constructors

ExprPrim !(GenPrim i r a) 
ExprUnOp 

Fields

ExprBinOp 

Fields

ExprCond 

Fields

Instances

Instances details
(Data i, Data r, Data a) => Data (GenExpr i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

gunfold :: (forall b r0. Data b => c (b -> r0) -> c r0) -> (forall r1. r1 -> c r1) -> Constr -> c (GenExpr i r a) #

toConstr :: GenExpr i r a -> Constr #

dataTypeOf :: GenExpr i r a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenExpr i r a -> GenExpr i r a #

gmapQl :: (r0 -> r' -> r0) -> r0 -> (forall d. Data d => d -> r') -> GenExpr i r a -> r0 #

gmapQr :: forall r0 r'. (r' -> r0 -> r0) -> r0 -> (forall d. Data d => d -> r') -> GenExpr i r a -> r0 #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenExpr i r a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenExpr i r a -> m (GenExpr i r a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenExpr i r a -> m (GenExpr i r a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenExpr i r a -> m (GenExpr i r a) #

Generic (GenExpr i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (GenExpr i r a) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenExpr i r a) = D1 ('MetaData "GenExpr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "ExprPrim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenPrim i r a))) :+: C1 ('MetaCons "ExprUnOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "_euOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnaryOperator) :*: (S1 ('MetaSel ('Just "_euAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_euPrim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenPrim i r a))))) :+: (C1 ('MetaCons "ExprBinOp" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_ebLhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)) :*: S1 ('MetaSel ('Just "_ebOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinaryOperator)) :*: (S1 ('MetaSel ('Just "_ebAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_ebRhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)))) :+: C1 ('MetaCons "ExprCond" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_ecCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)) :*: S1 ('MetaSel ('Just "_ecAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Just "_ecTrue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)) :*: S1 ('MetaSel ('Just "_ecFalse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a))))))

Methods

from :: GenExpr i r a -> Rep (GenExpr i r a) x #

to :: Rep (GenExpr i r a) x -> GenExpr i r a #

(Show r, Show i, Show a) => Show (GenExpr i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> GenExpr i r a -> ShowS #

show :: GenExpr i r a -> String #

showList :: [GenExpr i r a] -> ShowS #

(Eq r, Eq i, Eq a) => Eq (GenExpr i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: GenExpr i r a -> GenExpr i r a -> Bool #

(/=) :: GenExpr i r a -> GenExpr i r a -> Bool #

(Data i, Data r, Data a) => Plated (GenExpr i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

plate :: Traversal' (GenExpr i r a) (GenExpr i r a) #

type Rep (GenExpr i r a) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenExpr i r a) = D1 ('MetaData "GenExpr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "ExprPrim" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenPrim i r a))) :+: C1 ('MetaCons "ExprUnOp" 'PrefixI 'True) (S1 ('MetaSel ('Just "_euOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnaryOperator) :*: (S1 ('MetaSel ('Just "_euAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_euPrim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenPrim i r a))))) :+: (C1 ('MetaCons "ExprBinOp" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_ebLhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)) :*: S1 ('MetaSel ('Just "_ebOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinaryOperator)) :*: (S1 ('MetaSel ('Just "_ebAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "_ebRhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)))) :+: C1 ('MetaCons "ExprCond" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_ecCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)) :*: S1 ('MetaSel ('Just "_ecAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Just "_ecTrue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a)) :*: S1 ('MetaSel ('Just "_ecFalse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr i r a))))))

newtype CExpr Source #

Instances

Instances details
Data CExpr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: CExpr -> Constr #

dataTypeOf :: CExpr -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic CExpr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep CExpr 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep CExpr = D1 ('MetaData "CExpr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "CExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenExpr Identifier (Maybe CRangeExpr) Attributes))))

Methods

from :: CExpr -> Rep CExpr x #

to :: Rep CExpr x -> CExpr #

Show CExpr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> CExpr -> ShowS #

show :: CExpr -> String #

showList :: [CExpr] -> ShowS #

Eq CExpr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep CExpr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep CExpr = D1 ('MetaData "CExpr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "CExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenExpr Identifier (Maybe CRangeExpr) Attributes))))

newtype Expr Source #

Instances

Instances details
Data Expr Source # 
Instance details

Defined in Verismith.Verilog2005.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 #

Generic Expr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Expr 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Expr = D1 ('MetaData "Expr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Expr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenExpr HierIdent (Maybe DimRange) Attributes))))

Methods

from :: Expr -> Rep Expr x #

to :: Rep Expr x -> Expr #

Show Expr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Eq Expr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep Expr Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Expr = D1 ('MetaData "Expr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'True) (C1 ('MetaCons "Expr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenExpr HierIdent (Maybe DimRange) Attributes))))

data Attribute Source #

Attributes which can be set to various nodes in the AST.

Instances

Instances details
Data Attribute Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Attribute -> Constr #

dataTypeOf :: Attribute -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Attribute Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Attribute 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Attribute = D1 ('MetaData "Attribute" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Attribute" 'PrefixI 'True) (S1 ('MetaSel ('Just "_attrIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_attrValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (GenExpr Identifier (Maybe CRangeExpr) ())))))
Show Attribute Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Attribute Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Attribute Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Attribute = D1 ('MetaData "Attribute" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Attribute" 'PrefixI 'True) (S1 ('MetaSel ('Just "_attrIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_attrValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (GenExpr Identifier (Maybe CRangeExpr) ())))))

data Attributed t Source #

Constructors

Attributed 

Fields

Instances

Instances details
Foldable Attributed Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

fold :: Monoid m => Attributed m -> m #

foldMap :: Monoid m => (a -> m) -> Attributed a -> m #

foldMap' :: Monoid m => (a -> m) -> Attributed a -> m #

foldr :: (a -> b -> b) -> b -> Attributed a -> b #

foldr' :: (a -> b -> b) -> b -> Attributed a -> b #

foldl :: (b -> a -> b) -> b -> Attributed a -> b #

foldl' :: (b -> a -> b) -> b -> Attributed a -> b #

foldr1 :: (a -> a -> a) -> Attributed a -> a #

foldl1 :: (a -> a -> a) -> Attributed a -> a #

toList :: Attributed a -> [a] #

null :: Attributed a -> Bool #

length :: Attributed a -> Int #

elem :: Eq a => a -> Attributed a -> Bool #

maximum :: Ord a => Attributed a -> a #

minimum :: Ord a => Attributed a -> a #

sum :: Num a => Attributed a -> a #

product :: Num a => Attributed a -> a #

Traversable Attributed Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

traverse :: Applicative f => (a -> f b) -> Attributed a -> f (Attributed b) #

sequenceA :: Applicative f => Attributed (f a) -> f (Attributed a) #

mapM :: Monad m => (a -> m b) -> Attributed a -> m (Attributed b) #

sequence :: Monad m => Attributed (m a) -> m (Attributed a) #

Applicative Attributed Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

pure :: a -> Attributed a #

(<*>) :: Attributed (a -> b) -> Attributed a -> Attributed b #

liftA2 :: (a -> b -> c) -> Attributed a -> Attributed b -> Attributed c #

(*>) :: Attributed a -> Attributed b -> Attributed b #

(<*) :: Attributed a -> Attributed b -> Attributed a #

Functor Attributed Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

Data t => Data (Attributed t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attributed t -> c (Attributed t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Attributed t) #

toConstr :: Attributed t -> Constr #

dataTypeOf :: Attributed t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Attributed t -> Attributed t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attributed t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attributed t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Attributed t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Attributed t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attributed t -> m (Attributed t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attributed t -> m (Attributed t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attributed t -> m (Attributed t) #

Generic (Attributed t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (Attributed t) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (Attributed t) = D1 ('MetaData "Attributed" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Attributed" 'PrefixI 'True) (S1 ('MetaSel ('Just "_attrAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Attributes) :*: S1 ('MetaSel ('Just "_attrData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t)))

Methods

from :: Attributed t -> Rep (Attributed t) x #

to :: Rep (Attributed t) x -> Attributed t #

Show t => Show (Attributed t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq t => Eq (Attributed t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: Attributed t -> Attributed t -> Bool #

(/=) :: Attributed t -> Attributed t -> Bool #

type Rep (Attributed t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (Attributed t) = D1 ('MetaData "Attributed" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Attributed" 'PrefixI 'True) (S1 ('MetaSel ('Just "_attrAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Attributes) :*: S1 ('MetaSel ('Just "_attrData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t)))

data AttrIded t Source #

Constructors

AttrIded 

Fields

Instances

Instances details
Functor AttrIded Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

Data t => Data (AttrIded t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttrIded t -> c (AttrIded t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AttrIded t) #

toConstr :: AttrIded t -> Constr #

dataTypeOf :: AttrIded t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> AttrIded t -> AttrIded t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttrIded t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttrIded t -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttrIded t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttrIded t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttrIded t -> m (AttrIded t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttrIded t -> m (AttrIded t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttrIded t -> m (AttrIded t) #

Generic (AttrIded t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (AttrIded t) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (AttrIded t) = D1 ('MetaData "AttrIded" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "AttrIded" 'PrefixI 'True) (S1 ('MetaSel ('Just "_aiAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Attributes) :*: (S1 ('MetaSel ('Just "_aiIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_aiData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t))))

Methods

from :: AttrIded t -> Rep (AttrIded t) x #

to :: Rep (AttrIded t) x -> AttrIded t #

Show t => Show (AttrIded t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> AttrIded t -> ShowS #

show :: AttrIded t -> String #

showList :: [AttrIded t] -> ShowS #

Eq t => Eq (AttrIded t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: AttrIded t -> AttrIded t -> Bool #

(/=) :: AttrIded t -> AttrIded t -> Bool #

type Rep (AttrIded t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (AttrIded t) = D1 ('MetaData "AttrIded" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "AttrIded" 'PrefixI 'True) (S1 ('MetaSel ('Just "_aiAttr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Attributes) :*: (S1 ('MetaSel ('Just "_aiIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_aiData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t))))

data Range2 Source #

Range2

Constructors

Range2 

Fields

Instances

Instances details
Data Range2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Range2 -> Constr #

dataTypeOf :: Range2 -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Range2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Range2 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Range2 = D1 ('MetaData "Range2" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Range2" 'PrefixI 'True) (S1 ('MetaSel ('Just "_r2MSB") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr) :*: S1 ('MetaSel ('Just "_r2LSB") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr)))

Methods

from :: Range2 -> Rep Range2 x #

to :: Rep Range2 x -> Range2 #

Show Range2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Range2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep Range2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Range2 = D1 ('MetaData "Range2" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Range2" 'PrefixI 'True) (S1 ('MetaSel ('Just "_r2MSB") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr) :*: S1 ('MetaSel ('Just "_r2LSB") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr)))

data GenRangeExpr e Source #

Range expressions

Constructors

GRESingle !e 
GREPair !Range2 
GREBaseOff 

Fields

Instances

Instances details
Data e => Data (GenRangeExpr e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenRangeExpr e -> c (GenRangeExpr e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenRangeExpr e) #

toConstr :: GenRangeExpr e -> Constr #

dataTypeOf :: GenRangeExpr e -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenRangeExpr e -> GenRangeExpr e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenRangeExpr e -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenRangeExpr e -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenRangeExpr e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenRangeExpr e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenRangeExpr e -> m (GenRangeExpr e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenRangeExpr e -> m (GenRangeExpr e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenRangeExpr e -> m (GenRangeExpr e) #

Generic (GenRangeExpr e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (GenRangeExpr e) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenRangeExpr e) = D1 ('MetaData "GenRangeExpr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GRESingle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 e)) :+: (C1 ('MetaCons "GREPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Range2)) :+: C1 ('MetaCons "GREBaseOff" 'PrefixI 'True) (S1 ('MetaSel ('Just "_greBase") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 e) :*: (S1 ('MetaSel ('Just "_greMin_plus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_greOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr)))))

Methods

from :: GenRangeExpr e -> Rep (GenRangeExpr e) x #

to :: Rep (GenRangeExpr e) x -> GenRangeExpr e #

Show e => Show (GenRangeExpr e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq e => Eq (GenRangeExpr e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenRangeExpr e) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (GenRangeExpr e) = D1 ('MetaData "GenRangeExpr" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GRESingle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 e)) :+: (C1 ('MetaCons "GREPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Range2)) :+: C1 ('MetaCons "GREBaseOff" 'PrefixI 'True) (S1 ('MetaSel ('Just "_greBase") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 e) :*: (S1 ('MetaSel ('Just "_greMin_plus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_greOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr)))))

data NumIdent Source #

Number or Identifier

Instances

Instances details
Data NumIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: NumIdent -> Constr #

dataTypeOf :: NumIdent -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NumIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep NumIdent 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NumIdent = D1 ('MetaData "NumIdent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NIIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :+: (C1 ('MetaCons "NIReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "NINumber" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural))))

Methods

from :: NumIdent -> Rep NumIdent x #

to :: Rep NumIdent x -> NumIdent #

Show NumIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq NumIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NumIdent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NumIdent = D1 ('MetaData "NumIdent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NIIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :+: (C1 ('MetaCons "NIReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "NINumber" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural))))

data Delay3 Source #

Delay3

Instances

Instances details
Data Delay3 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Delay3 -> Constr #

dataTypeOf :: Delay3 -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Delay3 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

from :: Delay3 -> Rep Delay3 x #

to :: Rep Delay3 x -> Delay3 #

Show Delay3 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Delay3 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep Delay3 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data Delay2 Source #

Delay2

Constructors

D2Base !NumIdent 
D21 !MinTypMax 
D22 

Instances

Instances details
Data Delay2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Delay2 -> Constr #

dataTypeOf :: Delay2 -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Delay2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Delay2 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

from :: Delay2 -> Rep Delay2 x #

to :: Rep Delay2 x -> Delay2 #

Show Delay2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Delay2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep Delay2 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data Delay1 Source #

Delay1

Constructors

D1Base !NumIdent 
D11 !MinTypMax 

Instances

Instances details
Data Delay1 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Delay1 -> Constr #

dataTypeOf :: Delay1 -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Delay1 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Delay1 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Delay1 = D1 ('MetaData "Delay1" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "D1Base" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumIdent)) :+: C1 ('MetaCons "D11" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MinTypMax)))

Methods

from :: Delay1 -> Rep Delay1 x #

to :: Rep Delay1 x -> Delay1 #

Show Delay1 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Delay1 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep Delay1 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Delay1 = D1 ('MetaData "Delay1" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "D1Base" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumIdent)) :+: C1 ('MetaCons "D11" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MinTypMax)))

data SignRange Source #

Signedness and range are often together

Constructors

SignRange 

Fields

Instances

Instances details
Data SignRange Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: SignRange -> Constr #

dataTypeOf :: SignRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SignRange Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep SignRange 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SignRange = D1 ('MetaData "SignRange" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SignRange" 'PrefixI 'True) (S1 ('MetaSel ('Just "_srSign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_srRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Range2))))
Show SignRange Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq SignRange Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SignRange Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SignRange = D1 ('MetaData "SignRange" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SignRange" 'PrefixI 'True) (S1 ('MetaSel ('Just "_srSign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_srRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Range2))))

data SpecTerm Source #

Specify terminal

Constructors

SpecTerm 

Instances

Instances details
Data SpecTerm Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: SpecTerm -> Constr #

dataTypeOf :: SpecTerm -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SpecTerm Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep SpecTerm 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecTerm = D1 ('MetaData "SpecTerm" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SpecTerm" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_stRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CRangeExpr))))

Methods

from :: SpecTerm -> Rep SpecTerm x #

to :: Rep SpecTerm x -> SpecTerm #

Show SpecTerm Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq SpecTerm Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecTerm Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecTerm = D1 ('MetaData "SpecTerm" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SpecTerm" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_stRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CRangeExpr))))

data EventPrefix Source #

Event expression prefix

Constructors

EPAny 
EPPos 
EPNeg 

Instances

Instances details
Data EventPrefix Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: EventPrefix -> Constr #

dataTypeOf :: EventPrefix -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded EventPrefix Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum EventPrefix Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic EventPrefix Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep EventPrefix 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventPrefix = D1 ('MetaData "EventPrefix" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "EPAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EPPos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EPNeg" 'PrefixI 'False) (U1 :: Type -> Type)))
Show EventPrefix Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq EventPrefix Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventPrefix Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventPrefix = D1 ('MetaData "EventPrefix" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "EPAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EPPos" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EPNeg" 'PrefixI 'False) (U1 :: Type -> Type)))

data Dir Source #

Port datatransfer directions

Constructors

DirIn 
DirOut 
DirInOut 

Instances

Instances details
Data Dir Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Dir -> Constr #

dataTypeOf :: Dir -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Dir Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

minBound :: Dir #

maxBound :: Dir #

Enum Dir Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

succ :: Dir -> Dir #

pred :: Dir -> Dir #

toEnum :: Int -> Dir #

fromEnum :: Dir -> Int #

enumFrom :: Dir -> [Dir] #

enumFromThen :: Dir -> Dir -> [Dir] #

enumFromTo :: Dir -> Dir -> [Dir] #

enumFromThenTo :: Dir -> Dir -> Dir -> [Dir] #

Generic Dir Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Dir 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Dir = D1 ('MetaData "Dir" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "DirIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DirOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirInOut" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Dir -> Rep Dir x #

to :: Rep Dir x -> Dir #

Show Dir Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> Dir -> ShowS #

show :: Dir -> String #

showList :: [Dir] -> ShowS #

Eq Dir Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep Dir Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Dir = D1 ('MetaData "Dir" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "DirIn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DirOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DirInOut" 'PrefixI 'False) (U1 :: Type -> Type)))

data AbsType Source #

Abstract types for variables, parameters, functions and tasks

Instances

Instances details
Data AbsType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: AbsType -> Constr #

dataTypeOf :: AbsType -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded AbsType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum AbsType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic AbsType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep AbsType 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep AbsType = D1 ('MetaData "AbsType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "ATInteger" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ATReal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ATRealtime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ATTime" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: AbsType -> Rep AbsType x #

to :: Rep AbsType x -> AbsType #

Show AbsType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq AbsType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep AbsType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep AbsType = D1 ('MetaData "AbsType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "ATInteger" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ATReal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ATRealtime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ATTime" 'PrefixI 'False) (U1 :: Type -> Type)))

data ComType t Source #

Function, parameter and task type

Constructors

CTAbstract !AbsType 
CTConcrete 

Fields

Instances

Instances details
Data t => Data (ComType t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComType t -> c (ComType t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ComType t) #

toConstr :: ComType t -> Constr #

dataTypeOf :: ComType t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ComType t -> ComType t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComType t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComType t -> r #

gmapQ :: (forall d. Data d => d -> u) -> ComType t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComType t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComType t -> m (ComType t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComType t -> m (ComType t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComType t -> m (ComType t) #

Generic (ComType t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (ComType t) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (ComType t) = D1 ('MetaData "ComType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CTAbstract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AbsType)) :+: C1 ('MetaCons "CTConcrete" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ctcExtra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t) :*: S1 ('MetaSel ('Just "_ctcSignRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SignRange)))

Methods

from :: ComType t -> Rep (ComType t) x #

to :: Rep (ComType t) x -> ComType t #

Show t => Show (ComType t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> ComType t -> ShowS #

show :: ComType t -> String #

showList :: [ComType t] -> ShowS #

Eq t => Eq (ComType t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: ComType t -> ComType t -> Bool #

(/=) :: ComType t -> ComType t -> Bool #

type Rep (ComType t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (ComType t) = D1 ('MetaData "ComType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CTAbstract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AbsType)) :+: C1 ('MetaCons "CTConcrete" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ctcExtra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t) :*: S1 ('MetaSel ('Just "_ctcSignRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SignRange)))

data NetType Source #

Net type

Instances

Instances details
Data NetType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: NetType -> Constr #

dataTypeOf :: NetType -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded NetType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum NetType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic NetType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep NetType 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetType = D1 ('MetaData "NetType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "NTSupply1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTSupply0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NTTri" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NTTriAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTTriOr" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "NTTri1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NTTri0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTUwire" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NTWire" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NTWAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTWOr" 'PrefixI 'False) (U1 :: Type -> Type)))))

Methods

from :: NetType -> Rep NetType x #

to :: Rep NetType x -> NetType #

Show NetType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq NetType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep NetType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetType = D1 ('MetaData "NetType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "NTSupply1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTSupply0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NTTri" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NTTriAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTTriOr" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "NTTri1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NTTri0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTUwire" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NTWire" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NTWAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NTWOr" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Strength Source #

Net drive strengths

Instances

Instances details
Data Strength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Strength -> Constr #

dataTypeOf :: Strength -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Strength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum Strength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic Strength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Strength 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Strength = D1 ('MetaData "Strength" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "StrSupply" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrStrong" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StrPull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrWeak" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Strength -> Rep Strength x #

to :: Rep Strength x -> Strength #

Show Strength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Strength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Strength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Strength = D1 ('MetaData "Strength" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "StrSupply" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrStrong" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StrPull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrWeak" 'PrefixI 'False) (U1 :: Type -> Type)))

data DriveStrength Source #

Constructors

DSNormal 

Fields

DSHighZ 

Fields

Instances

Instances details
Data DriveStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: DriveStrength -> Constr #

dataTypeOf :: DriveStrength -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DriveStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep DriveStrength 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep DriveStrength = D1 ('MetaData "DriveStrength" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "DSNormal" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ds0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Strength) :*: S1 ('MetaSel ('Just "_ds1") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Strength)) :+: C1 ('MetaCons "DSHighZ" 'PrefixI 'True) (S1 ('MetaSel ('Just "_dsHZ") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_dsStr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Strength)))
Show DriveStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq DriveStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep DriveStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep DriveStrength = D1 ('MetaData "DriveStrength" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "DSNormal" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ds0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Strength) :*: S1 ('MetaSel ('Just "_ds1") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Strength)) :+: C1 ('MetaCons "DSHighZ" 'PrefixI 'True) (S1 ('MetaSel ('Just "_dsHZ") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_dsStr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Strength)))

data ChargeStrength Source #

Capacitor charge

Constructors

CSSmall 
CSMedium 
CSLarge 

Instances

Instances details
Data ChargeStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ChargeStrength -> Constr #

dataTypeOf :: ChargeStrength -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded ChargeStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum ChargeStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic ChargeStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ChargeStrength 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ChargeStrength = D1 ('MetaData "ChargeStrength" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CSSmall" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CSMedium" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CSLarge" 'PrefixI 'False) (U1 :: Type -> Type)))
Show ChargeStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ChargeStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ChargeStrength Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ChargeStrength = D1 ('MetaData "ChargeStrength" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CSSmall" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CSMedium" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CSLarge" 'PrefixI 'False) (U1 :: Type -> Type)))

data LValue dr Source #

Left side of assignments

Constructors

LVSingle 

Fields

LVConcat !(NonEmpty (LValue dr)) 

Instances

Instances details
Data dr => Data (LValue dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LValue dr -> c (LValue dr) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LValue dr) #

toConstr :: LValue dr -> Constr #

dataTypeOf :: LValue dr -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> LValue dr -> LValue dr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LValue dr -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LValue dr -> r #

gmapQ :: (forall d. Data d => d -> u) -> LValue dr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LValue dr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LValue dr -> m (LValue dr) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LValue dr -> m (LValue dr) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LValue dr -> m (LValue dr) #

Generic (LValue dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (LValue dr) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (LValue dr) = D1 ('MetaData "LValue" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "LVSingle" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lvIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_lvDimRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe dr))) :+: C1 ('MetaCons "LVConcat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (LValue dr)))))

Methods

from :: LValue dr -> Rep (LValue dr) x #

to :: Rep (LValue dr) x -> LValue dr #

Show dr => Show (LValue dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> LValue dr -> ShowS #

show :: LValue dr -> String #

showList :: [LValue dr] -> ShowS #

Eq dr => Eq (LValue dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: LValue dr -> LValue dr -> Bool #

(/=) :: LValue dr -> LValue dr -> Bool #

type Rep (LValue dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (LValue dr) = D1 ('MetaData "LValue" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "LVSingle" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lvIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_lvDimRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe dr))) :+: C1 ('MetaCons "LVConcat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (LValue dr)))))

data Assign dr Source #

Assignment

Constructors

Assign 

Fields

Instances

Instances details
Data dr => Data (Assign dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Assign dr -> c (Assign dr) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Assign dr) #

toConstr :: Assign dr -> Constr #

dataTypeOf :: Assign dr -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Assign dr -> Assign dr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Assign dr -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Assign dr -> r #

gmapQ :: (forall d. Data d => d -> u) -> Assign dr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Assign dr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Assign dr -> m (Assign dr) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Assign dr -> m (Assign dr) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Assign dr -> m (Assign dr) #

Generic (Assign dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (Assign dr) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (Assign dr) = D1 ('MetaData "Assign" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Assign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_aLValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LValue dr)) :*: S1 ('MetaSel ('Just "_aValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))

Methods

from :: Assign dr -> Rep (Assign dr) x #

to :: Rep (Assign dr) x -> Assign dr #

Show dr => Show (Assign dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> Assign dr -> ShowS #

show :: Assign dr -> String #

showList :: [Assign dr] -> ShowS #

Eq dr => Eq (Assign dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep (Assign dr) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (Assign dr) = D1 ('MetaData "Assign" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Assign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_aLValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LValue dr)) :*: S1 ('MetaSel ('Just "_aValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))

data Parameter Source #

Parameter

Constructors

Parameter 

Instances

Instances details
Data Parameter Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Parameter -> Constr #

dataTypeOf :: Parameter -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Parameter Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Parameter 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Parameter = D1 ('MetaData "Parameter" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Parameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "_paramType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ComType ())) :*: S1 ('MetaSel ('Just "_paramValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))
Show Parameter Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Parameter Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Parameter Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Parameter = D1 ('MetaData "Parameter" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Parameter" 'PrefixI 'True) (S1 ('MetaSel ('Just "_paramType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ComType ())) :*: S1 ('MetaSel ('Just "_paramValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))

data ParamOver Source #

DefParam assignment

Constructors

ParamOver 

Instances

Instances details
Data ParamOver Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ParamOver -> Constr #

dataTypeOf :: ParamOver -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ParamOver Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ParamOver 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ParamOver = D1 ('MetaData "ParamOver" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ParamOver" 'PrefixI 'True) (S1 ('MetaSel ('Just "_poIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_poValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))
Show ParamOver Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ParamOver Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ParamOver Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ParamOver = D1 ('MetaData "ParamOver" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ParamOver" 'PrefixI 'True) (S1 ('MetaSel ('Just "_poIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_poValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))

data ParamAssign Source #

Parameter assignment list

Instances

Instances details
Data ParamAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ParamAssign -> Constr #

dataTypeOf :: ParamAssign -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ParamAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ParamAssign 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ParamAssign = D1 ('MetaData "ParamAssign" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ParamPositional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Expr])) :+: C1 ('MetaCons "ParamNamed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Identified (Maybe MinTypMax)])))
Show ParamAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ParamAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ParamAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ParamAssign = D1 ('MetaData "ParamAssign" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ParamPositional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Expr])) :+: C1 ('MetaCons "ParamNamed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Identified (Maybe MinTypMax)])))

data PortAssign Source #

Port assignment list

Instances

Instances details
Data PortAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: PortAssign -> Constr #

dataTypeOf :: PortAssign -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PortAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep PortAssign 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PortAssign = D1 ('MetaData "PortAssign" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "PortNamed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrIded (Maybe Expr)])) :+: C1 ('MetaCons "PortPositional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Attributed (Maybe Expr)])))
Show PortAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq PortAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PortAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PortAssign = D1 ('MetaData "PortAssign" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "PortNamed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrIded (Maybe Expr)])) :+: C1 ('MetaCons "PortPositional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Attributed (Maybe Expr)])))

data EventPrim Source #

Event primitive

Constructors

EventPrim 

Fields

Instances

Instances details
Data EventPrim Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: EventPrim -> Constr #

dataTypeOf :: EventPrim -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic EventPrim Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep EventPrim 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventPrim = D1 ('MetaData "EventPrim" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "EventPrim" 'PrefixI 'True) (S1 ('MetaSel ('Just "_epOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EventPrefix) :*: S1 ('MetaSel ('Just "_epExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))
Show EventPrim Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq EventPrim Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventPrim Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventPrim = D1 ('MetaData "EventPrim" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "EventPrim" 'PrefixI 'True) (S1 ('MetaSel ('Just "_epOp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EventPrefix) :*: S1 ('MetaSel ('Just "_epExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))

data EventControl Source #

Event control

Instances

Instances details
Data EventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: EventControl -> Constr #

dataTypeOf :: EventControl -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic EventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep EventControl 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventControl = D1 ('MetaData "EventControl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ECIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent)) :+: (C1 ('MetaCons "ECExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty EventPrim))) :+: C1 ('MetaCons "ECDeps" 'PrefixI 'False) (U1 :: Type -> Type)))
Show EventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq EventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep EventControl = D1 ('MetaData "EventControl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ECIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent)) :+: (C1 ('MetaCons "ECExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty EventPrim))) :+: C1 ('MetaCons "ECDeps" 'PrefixI 'False) (U1 :: Type -> Type)))

data DelayEventControl Source #

Delay or Event control

Instances

Instances details
Data DelayEventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: DelayEventControl -> Constr #

dataTypeOf :: DelayEventControl -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DelayEventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep DelayEventControl 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep DelayEventControl = D1 ('MetaData "DelayEventControl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "DECDelay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Delay1)) :+: (C1 ('MetaCons "DECEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EventControl)) :+: C1 ('MetaCons "DECRepeat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_decrExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_decrEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EventControl))))
Show DelayEventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq DelayEventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep DelayEventControl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep DelayEventControl = D1 ('MetaData "DelayEventControl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "DECDelay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Delay1)) :+: (C1 ('MetaCons "DECEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EventControl)) :+: C1 ('MetaCons "DECRepeat" 'PrefixI 'True) (S1 ('MetaSel ('Just "_decrExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_decrEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EventControl))))

data ProcContAssign Source #

Procedural continuous assignment

Instances

Instances details
Data ProcContAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ProcContAssign -> Constr #

dataTypeOf :: ProcContAssign -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ProcContAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ProcContAssign 
Instance details

Defined in Verismith.Verilog2005.AST

Show ProcContAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ProcContAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ProcContAssign Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data LoopStatement Source #

Loop statement

Instances

Instances details
Data LoopStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: LoopStatement -> Constr #

dataTypeOf :: LoopStatement -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic LoopStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep LoopStatement 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep LoopStatement = D1 ('MetaData "LoopStatement" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "LSForever" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSRepeat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))) :+: (C1 ('MetaCons "LSWhile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: C1 ('MetaCons "LSFor" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lsfInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign) :*: (S1 ('MetaSel ('Just "_lsfCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_lsfUpd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign)))))
Show LoopStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq LoopStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep LoopStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep LoopStatement = D1 ('MetaData "LoopStatement" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "LSForever" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LSRepeat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))) :+: (C1 ('MetaCons "LSWhile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: C1 ('MetaCons "LSFor" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lsfInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign) :*: (S1 ('MetaSel ('Just "_lsfCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_lsfUpd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign)))))

data FCaseItem Source #

Case item

Constructors

FCaseItem 

Fields

Instances

Instances details
Data FCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: FCaseItem -> Constr #

dataTypeOf :: FCaseItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic FCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep FCaseItem 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep FCaseItem = D1 ('MetaData "FCaseItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "FCaseItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fciPat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)) :*: S1 ('MetaSel ('Just "_fciVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt)))
Show FCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq FCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep FCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep FCaseItem = D1 ('MetaData "FCaseItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "FCaseItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fciPat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)) :*: S1 ('MetaSel ('Just "_fciVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt)))

data CaseItem Source #

Constructors

CaseItem 

Fields

Instances

Instances details
Data CaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: CaseItem -> Constr #

dataTypeOf :: CaseItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic CaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep CaseItem 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep CaseItem = D1 ('MetaData "CaseItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CaseItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ciPat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)) :*: S1 ('MetaSel ('Just "_ciVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt)))

Methods

from :: CaseItem -> Rep CaseItem x #

to :: Rep CaseItem x -> CaseItem #

Show CaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq CaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep CaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep CaseItem = D1 ('MetaData "CaseItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CaseItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ciPat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)) :*: S1 ('MetaSel ('Just "_ciVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt)))

data FunctionStatement Source #

Function statement, more limited than general statement because they are purely combinational

Instances

Instances details
Data FunctionStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: FunctionStatement -> Constr #

dataTypeOf :: FunctionStatement -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic FunctionStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep FunctionStatement 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep FunctionStatement = D1 ('MetaData "FunctionStatement" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "FSBlockAssign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign)) :+: (C1 ('MetaCons "FSCase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_fscType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZOX) :*: S1 ('MetaSel ('Just "_fscExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_fscBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [FCaseItem]) :*: S1 ('MetaSel ('Just "_fscDef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt))) :+: C1 ('MetaCons "FSIf" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fsiExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "_fsiTrue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt) :*: S1 ('MetaSel ('Just "_fsiFalse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt))))) :+: (C1 ('MetaCons "FSDisable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent)) :+: (C1 ('MetaCons "FSLoop" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fslHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LoopStatement) :*: S1 ('MetaSel ('Just "_fslBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrFStmt)) :+: C1 ('MetaCons "FSBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fsbHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identifier, [AttrIded StdBlockDecl]))) :*: (S1 ('MetaSel ('Just "_fsbPar_seq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_fsbStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrFStmt]))))))
Show FunctionStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq FunctionStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Plated FunctionStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep FunctionStatement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep FunctionStatement = D1 ('MetaData "FunctionStatement" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "FSBlockAssign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign)) :+: (C1 ('MetaCons "FSCase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_fscType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZOX) :*: S1 ('MetaSel ('Just "_fscExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_fscBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [FCaseItem]) :*: S1 ('MetaSel ('Just "_fscDef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt))) :+: C1 ('MetaCons "FSIf" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fsiExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "_fsiTrue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt) :*: S1 ('MetaSel ('Just "_fsiFalse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybFStmt))))) :+: (C1 ('MetaCons "FSDisable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent)) :+: (C1 ('MetaCons "FSLoop" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fslHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LoopStatement) :*: S1 ('MetaSel ('Just "_fslBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrFStmt)) :+: C1 ('MetaCons "FSBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fsbHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identifier, [AttrIded StdBlockDecl]))) :*: (S1 ('MetaSel ('Just "_fsbPar_seq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_fsbStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrFStmt]))))))

data Statement Source #

Statement

Instances

Instances details
Data Statement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: Statement -> Constr #

dataTypeOf :: Statement -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Statement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Statement 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Statement = D1 ('MetaData "Statement" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "SBlockAssign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sbaBlock") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_sbaAssign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign) :*: S1 ('MetaSel ('Just "_sbaDelev") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DelayEventControl)))) :+: (C1 ('MetaCons "SCase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_scType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZOX) :*: S1 ('MetaSel ('Just "_scExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_scBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [CaseItem]) :*: S1 ('MetaSel ('Just "_scDef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))) :+: C1 ('MetaCons "SIf" 'PrefixI 'True) (S1 ('MetaSel ('Just "_siExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "_siTrue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt) :*: S1 ('MetaSel ('Just "_siFalse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))))) :+: (C1 ('MetaCons "SDisable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent)) :+: (C1 ('MetaCons "SEventTrigger" 'PrefixI 'True) (S1 ('MetaSel ('Just "_setIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_setIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Expr])) :+: C1 ('MetaCons "SLoop" 'PrefixI 'True) (S1 ('MetaSel ('Just "_slHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LoopStatement) :*: S1 ('MetaSel ('Just "_slBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrStmt))))) :+: ((C1 ('MetaCons "SProcContAssign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProcContAssign)) :+: (C1 ('MetaCons "SProcTimingControl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sptcControl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Either Delay1 EventControl)) :*: S1 ('MetaSel ('Just "_sptcStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt)) :+: C1 ('MetaCons "SBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sbHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identifier, [AttrIded StdBlockDecl]))) :*: (S1 ('MetaSel ('Just "_sbPar_seq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_sbStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrStmt]))))) :+: (C1 ('MetaCons "SSysTaskEnable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ssteIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_ssteArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Maybe Expr])) :+: (C1 ('MetaCons "STaskEnable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_steIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_steArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Expr])) :+: C1 ('MetaCons "SWait" 'PrefixI 'True) (S1 ('MetaSel ('Just "_swExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_swStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))))))
Show Statement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Statement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Plated Statement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Statement Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Statement = D1 ('MetaData "Statement" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "SBlockAssign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sbaBlock") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_sbaAssign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarAssign) :*: S1 ('MetaSel ('Just "_sbaDelev") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DelayEventControl)))) :+: (C1 ('MetaCons "SCase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_scType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZOX) :*: S1 ('MetaSel ('Just "_scExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_scBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [CaseItem]) :*: S1 ('MetaSel ('Just "_scDef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))) :+: C1 ('MetaCons "SIf" 'PrefixI 'True) (S1 ('MetaSel ('Just "_siExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "_siTrue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt) :*: S1 ('MetaSel ('Just "_siFalse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))))) :+: (C1 ('MetaCons "SDisable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent)) :+: (C1 ('MetaCons "SEventTrigger" 'PrefixI 'True) (S1 ('MetaSel ('Just "_setIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_setIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Expr])) :+: C1 ('MetaCons "SLoop" 'PrefixI 'True) (S1 ('MetaSel ('Just "_slHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LoopStatement) :*: S1 ('MetaSel ('Just "_slBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrStmt))))) :+: ((C1 ('MetaCons "SProcContAssign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProcContAssign)) :+: (C1 ('MetaCons "SProcTimingControl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sptcControl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Either Delay1 EventControl)) :*: S1 ('MetaSel ('Just "_sptcStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt)) :+: C1 ('MetaCons "SBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sbHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identifier, [AttrIded StdBlockDecl]))) :*: (S1 ('MetaSel ('Just "_sbPar_seq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_sbStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrStmt]))))) :+: (C1 ('MetaCons "SSysTaskEnable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ssteIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_ssteArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Maybe Expr])) :+: (C1 ('MetaCons "STaskEnable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_steIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HierIdent) :*: S1 ('MetaSel ('Just "_steArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Expr])) :+: C1 ('MetaCons "SWait" 'PrefixI 'True) (S1 ('MetaSel ('Just "_swExpr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_swStmt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))))))

data NInputType Source #

N-input logic gate types

Constructors

NITAnd 
NITOr 
NITXor 

Instances

Instances details
Data NInputType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: NInputType -> Constr #

dataTypeOf :: NInputType -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded NInputType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum NInputType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic NInputType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep NInputType 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NInputType = D1 ('MetaData "NInputType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NITAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NITOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NITXor" 'PrefixI 'False) (U1 :: Type -> Type)))
Show NInputType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq NInputType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NInputType Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NInputType = D1 ('MetaData "NInputType" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NITAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NITOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NITXor" 'PrefixI 'False) (U1 :: Type -> Type)))

type EdgeDesc = Vector Bool Source #

Edge descriptor, a 6 Bool array (01, 0x, 10, 1x, x0, x1)

data InstanceName Source #

Instance name

Constructors

InstanceName 

Instances

Instances details
Data InstanceName Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: InstanceName -> Constr #

dataTypeOf :: InstanceName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic InstanceName Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep InstanceName 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep InstanceName = D1 ('MetaData "InstanceName" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "InstanceName" 'PrefixI 'True) (S1 ('MetaSel ('Just "_INIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_INRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Range2))))
Show InstanceName Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq InstanceName Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep InstanceName Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep InstanceName = D1 ('MetaData "InstanceName" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "InstanceName" 'PrefixI 'True) (S1 ('MetaSel ('Just "_INIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_INRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Range2))))

data GICMos Source #

Gate instances

Instances

Instances details
Data GICMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GICMos -> Constr #

dataTypeOf :: GICMos -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GICMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GICMos 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GICMos = D1 ('MetaData "GICMos" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GICMos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gicmName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gicmOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gicmInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "_gicmNControl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_gicmPControl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))))

Methods

from :: GICMos -> Rep GICMos x #

to :: Rep GICMos x -> GICMos #

Show GICMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GICMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep GICMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GICMos = D1 ('MetaData "GICMos" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GICMos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gicmName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gicmOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gicmInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "_gicmNControl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_gicmPControl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))))

data GIEnable Source #

Instances

Instances details
Data GIEnable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GIEnable -> Constr #

dataTypeOf :: GIEnable -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GIEnable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GIEnable 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIEnable = D1 ('MetaData "GIEnable" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIEnable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gieName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gieOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gieInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_gieEnable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

Methods

from :: GIEnable -> Rep GIEnable x #

to :: Rep GIEnable x -> GIEnable #

Show GIEnable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GIEnable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIEnable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIEnable = D1 ('MetaData "GIEnable" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIEnable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gieName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gieOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gieInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_gieEnable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

data GIMos Source #

Constructors

GIMos 

Instances

Instances details
Data GIMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GIMos -> Constr #

dataTypeOf :: GIMos -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GIMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GIMos 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIMos = D1 ('MetaData "GIMos" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIMos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gimName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gimOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gimInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_gimEnable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

Methods

from :: GIMos -> Rep GIMos x #

to :: Rep GIMos x -> GIMos #

Show GIMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> GIMos -> ShowS #

show :: GIMos -> String #

showList :: [GIMos] -> ShowS #

Eq GIMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep GIMos Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIMos = D1 ('MetaData "GIMos" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIMos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gimName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gimOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gimInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_gimEnable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

data GINIn Source #

Instances

Instances details
Data GINIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GINIn -> Constr #

dataTypeOf :: GINIn -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GINIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GINIn 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GINIn = D1 ('MetaData "GINIn" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GINIn" 'PrefixI 'True) (S1 ('MetaSel ('Just "_giniName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_giniOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_giniInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)))))

Methods

from :: GINIn -> Rep GINIn x #

to :: Rep GINIn x -> GINIn #

Show GINIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> GINIn -> ShowS #

show :: GINIn -> String #

showList :: [GINIn] -> ShowS #

Eq GINIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep GINIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GINIn = D1 ('MetaData "GINIn" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GINIn" 'PrefixI 'True) (S1 ('MetaSel ('Just "_giniName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_giniOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_giniInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)))))

data GINOut Source #

Instances

Instances details
Data GINOut Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GINOut -> Constr #

dataTypeOf :: GINOut -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GINOut Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GINOut 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GINOut = D1 ('MetaData "GINOut" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GINOut" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ginoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_ginoOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty NetLValue)) :*: S1 ('MetaSel ('Just "_ginoInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

Methods

from :: GINOut -> Rep GINOut x #

to :: Rep GINOut x -> GINOut #

Show GINOut Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GINOut Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep GINOut Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GINOut = D1 ('MetaData "GINOut" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GINOut" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ginoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_ginoOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty NetLValue)) :*: S1 ('MetaSel ('Just "_ginoInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

data GIPassEn Source #

Instances

Instances details
Data GIPassEn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GIPassEn -> Constr #

dataTypeOf :: GIPassEn -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GIPassEn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GIPassEn 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIPassEn = D1 ('MetaData "GIPassEn" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIPassEn" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gipeName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gipeLhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gipeRhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_gipeEnable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

Methods

from :: GIPassEn -> Rep GIPassEn x #

to :: Rep GIPassEn x -> GIPassEn #

Show GIPassEn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GIPassEn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIPassEn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIPassEn = D1 ('MetaData "GIPassEn" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIPassEn" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_gipeName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_gipeLhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)) :*: (S1 ('MetaSel ('Just "_gipeRhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_gipeEnable") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))))

data GIPass Source #

Constructors

GIPass 

Instances

Instances details
Data GIPass Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GIPass -> Constr #

dataTypeOf :: GIPass -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GIPass Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GIPass 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIPass = D1 ('MetaData "GIPass" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIPass" 'PrefixI 'True) (S1 ('MetaSel ('Just "_gipsName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_gipsLhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_gipsRhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue))))

Methods

from :: GIPass -> Rep GIPass x #

to :: Rep GIPass x -> GIPass #

Show GIPass Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GIPass Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep GIPass Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIPass = D1 ('MetaData "GIPass" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIPass" 'PrefixI 'True) (S1 ('MetaSel ('Just "_gipsName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_gipsLhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_gipsRhs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue))))

data GIPull Source #

Constructors

GIPull 

Instances

Instances details
Data GIPull Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GIPull -> Constr #

dataTypeOf :: GIPull -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GIPull Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GIPull 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIPull = D1 ('MetaData "GIPull" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIPull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_giplName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_giplOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)))

Methods

from :: GIPull -> Rep GIPull x #

to :: Rep GIPull x -> GIPull #

Show GIPull Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GIPull Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep GIPull Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GIPull = D1 ('MetaData "GIPull" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GIPull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_giplName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: S1 ('MetaSel ('Just "_giplOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue)))

data TimingCheckEvent Source #

Timing check (controlled) event

Instances

Instances details
Data TimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: TimingCheckEvent -> Constr #

dataTypeOf :: TimingCheckEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep TimingCheckEvent 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep TimingCheckEvent = D1 ('MetaData "TimingCheckEvent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "TimingCheckEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tceEvCtl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe EdgeDesc)) :*: (S1 ('MetaSel ('Just "_tceSpecTerm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm) :*: S1 ('MetaSel ('Just "_tceTimChkCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Bool, Expr))))))
Show TimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq TimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep TimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep TimingCheckEvent = D1 ('MetaData "TimingCheckEvent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "TimingCheckEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tceEvCtl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe EdgeDesc)) :*: (S1 ('MetaSel ('Just "_tceSpecTerm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm) :*: S1 ('MetaSel ('Just "_tceTimChkCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Bool, Expr))))))

data ControlledTimingCheckEvent Source #

Instances

Instances details
Data ControlledTimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ControlledTimingCheckEvent -> Constr #

dataTypeOf :: ControlledTimingCheckEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ControlledTimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ControlledTimingCheckEvent 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ControlledTimingCheckEvent = D1 ('MetaData "ControlledTimingCheckEvent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ControlledTimingCheckEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ctceEvCtl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EdgeDesc) :*: (S1 ('MetaSel ('Just "_ctceSpecTerm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm) :*: S1 ('MetaSel ('Just "_ctceTimChkCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Bool, Expr))))))
Show ControlledTimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ControlledTimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ControlledTimingCheckEvent Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ControlledTimingCheckEvent = D1 ('MetaData "ControlledTimingCheckEvent" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ControlledTimingCheckEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ctceEvCtl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EdgeDesc) :*: (S1 ('MetaSel ('Just "_ctceSpecTerm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm) :*: S1 ('MetaSel ('Just "_ctceTimChkCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Bool, Expr))))))

data STCArgs Source #

System timing check common arguments

Instances

Instances details
Data STCArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: STCArgs -> Constr #

dataTypeOf :: STCArgs -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic STCArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep STCArgs 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep STCArgs = D1 ('MetaData "STCArgs" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "STCArgs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_stcaDataEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent) :*: S1 ('MetaSel ('Just "_stcaRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent)) :*: (S1 ('MetaSel ('Just "_stcaTimChkLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_stcaNotifier") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier)))))

Methods

from :: STCArgs -> Rep STCArgs x #

to :: Rep STCArgs x -> STCArgs #

Show STCArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq STCArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep STCArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep STCArgs = D1 ('MetaData "STCArgs" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "STCArgs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_stcaDataEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent) :*: S1 ('MetaSel ('Just "_stcaRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent)) :*: (S1 ('MetaSel ('Just "_stcaTimChkLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_stcaNotifier") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier)))))

data STCAddArgs Source #

Setuphold and Recrem additionnal arguments

Instances

Instances details
Data STCAddArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: STCAddArgs -> Constr #

dataTypeOf :: STCAddArgs -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic STCAddArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep STCAddArgs 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep STCAddArgs = D1 ('MetaData "STCAddArgs" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "STCAddArgs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_stcaaTimChkLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_stcaaStampCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe MinTypMax))) :*: (S1 ('MetaSel ('Just "_stcaaChkTimCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe MinTypMax)) :*: (S1 ('MetaSel ('Just "_stcaaDelayedRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identified (Maybe CMinTypMax)))) :*: S1 ('MetaSel ('Just "_stcaaDelayedData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identified (Maybe CMinTypMax))))))))
Show STCAddArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq STCAddArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep STCAddArgs Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep STCAddArgs = D1 ('MetaData "STCAddArgs" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "STCAddArgs" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_stcaaTimChkLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_stcaaStampCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe MinTypMax))) :*: (S1 ('MetaSel ('Just "_stcaaChkTimCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe MinTypMax)) :*: (S1 ('MetaSel ('Just "_stcaaDelayedRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identified (Maybe CMinTypMax)))) :*: S1 ('MetaSel ('Just "_stcaaDelayedData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Identified (Maybe CMinTypMax))))))))

data ModulePathCondition Source #

Module path condition

Instances

Instances details
Data ModulePathCondition Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ModulePathCondition -> Constr #

dataTypeOf :: ModulePathCondition -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ModulePathCondition Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ModulePathCondition 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModulePathCondition = D1 ('MetaData "ModulePathCondition" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "MPCCond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr Identifier () Attributes))) :+: (C1 ('MetaCons "MPCNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MPCAlways" 'PrefixI 'False) (U1 :: Type -> Type)))
Show ModulePathCondition Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ModulePathCondition Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModulePathCondition Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModulePathCondition = D1 ('MetaData "ModulePathCondition" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "MPCCond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenExpr Identifier () Attributes))) :+: (C1 ('MetaCons "MPCNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MPCAlways" 'PrefixI 'False) (U1 :: Type -> Type)))

data SpecPath Source #

Specify path declaration

Instances

Instances details
Data SpecPath Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: SpecPath -> Constr #

dataTypeOf :: SpecPath -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SpecPath Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep SpecPath 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecPath = D1 ('MetaData "SpecPath" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SPParallel" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sppInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm) :*: S1 ('MetaSel ('Just "_sppOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm)) :+: C1 ('MetaCons "SPFull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_spfInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SpecTerm)) :*: S1 ('MetaSel ('Just "_spfOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SpecTerm))))

Methods

from :: SpecPath -> Rep SpecPath x #

to :: Rep SpecPath x -> SpecPath #

Show SpecPath Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq SpecPath Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecPath Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecPath = D1 ('MetaData "SpecPath" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SPParallel" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sppInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm) :*: S1 ('MetaSel ('Just "_sppOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecTerm)) :+: C1 ('MetaCons "SPFull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_spfInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SpecTerm)) :*: S1 ('MetaSel ('Just "_spfOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SpecTerm))))

data PathDelayValue Source #

Specify Item path delcaration delay value list

Instances

Instances details
Data PathDelayValue Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: PathDelayValue -> Constr #

dataTypeOf :: PathDelayValue -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PathDelayValue Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep PathDelayValue 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PathDelayValue = D1 ('MetaData "PathDelayValue" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "PDV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)) :+: C1 ('MetaCons "PDV2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :+: (C1 ('MetaCons "PDV3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :+: (C1 ('MetaCons "PDV6" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))) :+: C1 ('MetaCons "PDV12" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))))))))
Show PathDelayValue Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq PathDelayValue Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PathDelayValue Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PathDelayValue = D1 ('MetaData "PathDelayValue" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "PDV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)) :+: C1 ('MetaCons "PDV2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :+: (C1 ('MetaCons "PDV3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :+: (C1 ('MetaCons "PDV6" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))) :+: C1 ('MetaCons "PDV12" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))))))))

data SpecifyItem (f :: Type -> Type) Source #

Specify block item | f is either Identity or NonEmpty | it is used to abstract between several specify items in a block and a single comma separated one

Instances

Instances details
(Typeable f, forall a. Data a => Data (f a)) => Data (SpecifyItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpecifyItem f -> c (SpecifyItem f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpecifyItem f) #

toConstr :: SpecifyItem f -> Constr #

dataTypeOf :: SpecifyItem f -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> SpecifyItem f -> SpecifyItem f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpecifyItem f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpecifyItem f -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpecifyItem f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpecifyItem f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpecifyItem f -> m (SpecifyItem f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecifyItem f -> m (SpecifyItem f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpecifyItem f -> m (SpecifyItem f) #

(forall a. Generic a => Generic (f a)) => Generic (SpecifyItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (SpecifyItem f) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (SpecifyItem f) = D1 ('MetaData "SpecifyItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((((C1 ('MetaCons "SISpecParam" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sipcRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Range2)) :*: S1 ('MetaSel ('Just "_sipcDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecParamDecl))) :+: C1 ('MetaCons "SIPulsestyleOnevent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm)))) :+: (C1 ('MetaCons "SIPulsestyleOndetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm))) :+: C1 ('MetaCons "SIShowcancelled" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm))))) :+: ((C1 ('MetaCons "SINoshowcancelled" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm))) :+: C1 ('MetaCons "SIPathDeclaration" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sipdCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModulePathCondition) :*: S1 ('MetaSel ('Just "_sipdConn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecPath)) :*: (S1 ('MetaSel ('Just "_sipdPolarity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "_sipdEDS") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Expr, Maybe Bool))) :*: S1 ('MetaSel ('Just "_sipdValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PathDelayValue))))) :+: (C1 ('MetaCons "SISetup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)) :+: (C1 ('MetaCons "SIHold" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)) :+: C1 ('MetaCons "SISetupHold" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sishArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: S1 ('MetaSel ('Just "_sishAddArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCAddArgs)))))) :+: (((C1 ('MetaCons "SIRecovery" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)) :+: C1 ('MetaCons "SIRemoval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs))) :+: (C1 ('MetaCons "SIRecrem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sirArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: S1 ('MetaSel ('Just "_sirAddArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCAddArgs)) :+: C1 ('MetaCons "SISkew" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)))) :+: ((C1 ('MetaCons "SITimeSkew" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sitsArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: (S1 ('MetaSel ('Just "_sitsEvBased") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)) :*: S1 ('MetaSel ('Just "_sitsRemActive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)))) :+: C1 ('MetaCons "SIFullSkew" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sifsArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: S1 ('MetaSel ('Just "_sifsTimChkLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_sifsEvBased") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)) :*: S1 ('MetaSel ('Just "_sifsRemActive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr))))) :+: (C1 ('MetaCons "SIPeriod" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sipCRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControlledTimingCheckEvent) :*: (S1 ('MetaSel ('Just "_sipTimCtlLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_sipNotif") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier)))) :+: (C1 ('MetaCons "SIWidth" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_siwRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControlledTimingCheckEvent) :*: S1 ('MetaSel ('Just "_siwTimCtlLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_siwThresh") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)) :*: S1 ('MetaSel ('Just "_siwNotif") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier)))) :+: C1 ('MetaCons "SINoChange" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sincRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent) :*: S1 ('MetaSel ('Just "_sincDataEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent)) :*: (S1 ('MetaSel ('Just "_sincStartEdgeOff") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MinTypMax) :*: (S1 ('MetaSel ('Just "_sincEndEdgeOff") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MinTypMax) :*: S1 ('MetaSel ('Just "_sincNotif") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier))))))))))

Methods

from :: SpecifyItem f -> Rep (SpecifyItem f) x #

to :: Rep (SpecifyItem f) x -> SpecifyItem f #

(Show1 f, forall a. Show a => Show (f a)) => Show (SpecifyItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

(Eq1 f, forall a. Eq a => Eq (f a)) => Eq (SpecifyItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (SpecifyItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (SpecifyItem f) = D1 ('MetaData "SpecifyItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((((C1 ('MetaCons "SISpecParam" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sipcRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Range2)) :*: S1 ('MetaSel ('Just "_sipcDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecParamDecl))) :+: C1 ('MetaCons "SIPulsestyleOnevent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm)))) :+: (C1 ('MetaCons "SIPulsestyleOndetect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm))) :+: C1 ('MetaCons "SIShowcancelled" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm))))) :+: ((C1 ('MetaCons "SINoshowcancelled" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f SpecTerm))) :+: C1 ('MetaCons "SIPathDeclaration" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sipdCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModulePathCondition) :*: S1 ('MetaSel ('Just "_sipdConn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SpecPath)) :*: (S1 ('MetaSel ('Just "_sipdPolarity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "_sipdEDS") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Expr, Maybe Bool))) :*: S1 ('MetaSel ('Just "_sipdValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PathDelayValue))))) :+: (C1 ('MetaCons "SISetup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)) :+: (C1 ('MetaCons "SIHold" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)) :+: C1 ('MetaCons "SISetupHold" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sishArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: S1 ('MetaSel ('Just "_sishAddArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCAddArgs)))))) :+: (((C1 ('MetaCons "SIRecovery" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)) :+: C1 ('MetaCons "SIRemoval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs))) :+: (C1 ('MetaCons "SIRecrem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sirArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: S1 ('MetaSel ('Just "_sirAddArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCAddArgs)) :+: C1 ('MetaCons "SISkew" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs)))) :+: ((C1 ('MetaCons "SITimeSkew" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sitsArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: (S1 ('MetaSel ('Just "_sitsEvBased") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)) :*: S1 ('MetaSel ('Just "_sitsRemActive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)))) :+: C1 ('MetaCons "SIFullSkew" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sifsArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 STCArgs) :*: S1 ('MetaSel ('Just "_sifsTimChkLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_sifsEvBased") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)) :*: S1 ('MetaSel ('Just "_sifsRemActive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr))))) :+: (C1 ('MetaCons "SIPeriod" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sipCRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControlledTimingCheckEvent) :*: (S1 ('MetaSel ('Just "_sipTimCtlLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Just "_sipNotif") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier)))) :+: (C1 ('MetaCons "SIWidth" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_siwRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControlledTimingCheckEvent) :*: S1 ('MetaSel ('Just "_siwTimCtlLim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "_siwThresh") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)) :*: S1 ('MetaSel ('Just "_siwNotif") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier)))) :+: C1 ('MetaCons "SINoChange" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_sincRefEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent) :*: S1 ('MetaSel ('Just "_sincDataEvent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TimingCheckEvent)) :*: (S1 ('MetaSel ('Just "_sincStartEdgeOff") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MinTypMax) :*: (S1 ('MetaSel ('Just "_sincEndEdgeOff") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MinTypMax) :*: S1 ('MetaSel ('Just "_sincNotif") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Identifier))))))))))

data SpecParamDecl Source #

Specparam declaration

Instances

Instances details
Data SpecParamDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: SpecParamDecl -> Constr #

dataTypeOf :: SpecParamDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SpecParamDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep SpecParamDecl 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecParamDecl = D1 ('MetaData "SpecParamDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SPDAssign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_spdaIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_spdaValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)) :+: C1 ('MetaCons "SPDPathPulse" 'PrefixI 'True) (S1 ('MetaSel ('Just "_spdpInOut") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (SpecTerm, SpecTerm))) :*: (S1 ('MetaSel ('Just "_spdpReject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Just "_spdpError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))))
Show SpecParamDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq SpecParamDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecParamDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SpecParamDecl = D1 ('MetaData "SpecParamDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SPDAssign" 'PrefixI 'True) (S1 ('MetaSel ('Just "_spdaIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_spdaValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax)) :+: C1 ('MetaCons "SPDPathPulse" 'PrefixI 'True) (S1 ('MetaSel ('Just "_spdpInOut") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (SpecTerm, SpecTerm))) :*: (S1 ('MetaSel ('Just "_spdpReject") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax) :*: S1 ('MetaSel ('Just "_spdpError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CMinTypMax))))

data NetProp Source #

Net common properties

Constructors

NetProp 

Instances

Instances details
Data NetProp Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: NetProp -> Constr #

dataTypeOf :: NetProp -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NetProp Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep NetProp 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetProp = D1 ('MetaData "NetProp" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NetProp" 'PrefixI 'True) (S1 ('MetaSel ('Just "_npSigned") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_npVector") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Maybe Bool, Range2))) :*: S1 ('MetaSel ('Just "_npDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)))))

Methods

from :: NetProp -> Rep NetProp x #

to :: Rep NetProp x -> NetProp #

Show NetProp Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq NetProp Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep NetProp Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetProp = D1 ('MetaData "NetProp" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NetProp" 'PrefixI 'True) (S1 ('MetaSel ('Just "_npSigned") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_npVector") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Maybe Bool, Range2))) :*: S1 ('MetaSel ('Just "_npDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)))))

data NetDecl Source #

Net declaration

Constructors

NetDecl 

Fields

Instances

Instances details
Data NetDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: NetDecl -> Constr #

dataTypeOf :: NetDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NetDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep NetDecl 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetDecl = D1 ('MetaData "NetDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NetDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ndIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_ndDim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Range2])))

Methods

from :: NetDecl -> Rep NetDecl x #

to :: Rep NetDecl x -> NetDecl #

Show NetDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq NetDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep NetDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetDecl = D1 ('MetaData "NetDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NetDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ndIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_ndDim") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Range2])))

data NetInit Source #

Net initialisation

Constructors

NetInit 

Fields

Instances

Instances details
Data NetInit Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: NetInit -> Constr #

dataTypeOf :: NetInit -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NetInit Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep NetInit 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetInit = D1 ('MetaData "NetInit" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NetInit" 'PrefixI 'True) (S1 ('MetaSel ('Just "_niIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_niValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))

Methods

from :: NetInit -> Rep NetInit x #

to :: Rep NetInit x -> NetInit #

Show NetInit Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq NetInit Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep NetInit Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep NetInit = D1 ('MetaData "NetInit" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "NetInit" 'PrefixI 'True) (S1 ('MetaSel ('Just "_niIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_niValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))

data BlockDecl (f :: Type -> Type) t Source #

Block declaration | t is used to abstract between block_decl and modgen_decl | f is used to abstract between the separated and grouped modgen_item

Constructors

BDReg 

Fields

BDInt !(f t) 
BDReal !(f t) 
BDTime !(f t) 
BDRealTime !(f t) 
BDEvent !(f [Range2]) 
BDLocalParam 

Fields

Instances

Instances details
(Typeable t, Data t, Typeable f, forall a. Data a => Data (f a)) => Data (BlockDecl f t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockDecl f t -> c (BlockDecl f t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BlockDecl f t) #

toConstr :: BlockDecl f t -> Constr #

dataTypeOf :: BlockDecl f t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (BlockDecl f t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (BlockDecl f t)) #

gmapT :: (forall b. Data b => b -> b) -> BlockDecl f t -> BlockDecl f t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockDecl f t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockDecl f t -> r #

gmapQ :: (forall d. Data d => d -> u) -> BlockDecl f t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockDecl f t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockDecl f t -> m (BlockDecl f t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockDecl f t -> m (BlockDecl f t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockDecl f t -> m (BlockDecl f t) #

(Generic t, forall a. Generic a => Generic (f a)) => Generic (BlockDecl f t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (BlockDecl f t) 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

from :: BlockDecl f t -> Rep (BlockDecl f t) x #

to :: Rep (BlockDecl f t) x -> BlockDecl f t #

(Show t, forall a. Show a => Show (f a)) => Show (BlockDecl f t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> BlockDecl f t -> ShowS #

show :: BlockDecl f t -> String #

showList :: [BlockDecl f t] -> ShowS #

(Eq t, forall a. Eq a => Eq (f a)) => Eq (BlockDecl f t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: BlockDecl f t -> BlockDecl f t -> Bool #

(/=) :: BlockDecl f t -> BlockDecl f t -> Bool #

type Rep (BlockDecl f t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data StdBlockDecl Source #

Block item declaration (for statement blocks [begin/fork], tasks, and functions)

Instances

Instances details
Data StdBlockDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: StdBlockDecl -> Constr #

dataTypeOf :: StdBlockDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic StdBlockDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep StdBlockDecl 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep StdBlockDecl = D1 ('MetaData "StdBlockDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SBDBlockDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BlockDecl Identity [Range2]))) :+: C1 ('MetaCons "SBDParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Parameter)))
Show StdBlockDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq StdBlockDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep StdBlockDecl Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep StdBlockDecl = D1 ('MetaData "StdBlockDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SBDBlockDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BlockDecl Identity [Range2]))) :+: C1 ('MetaCons "SBDParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Parameter)))

data TFBlockDecl t Source #

Task and Function block declaration

Constructors

TFBDStd !StdBlockDecl 
TFBDPort 

Fields

Instances

Instances details
Data t => Data (TFBlockDecl t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TFBlockDecl t -> c (TFBlockDecl t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TFBlockDecl t) #

toConstr :: TFBlockDecl t -> Constr #

dataTypeOf :: TFBlockDecl t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> TFBlockDecl t -> TFBlockDecl t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TFBlockDecl t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TFBlockDecl t -> r #

gmapQ :: (forall d. Data d => d -> u) -> TFBlockDecl t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TFBlockDecl t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TFBlockDecl t -> m (TFBlockDecl t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TFBlockDecl t -> m (TFBlockDecl t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TFBlockDecl t -> m (TFBlockDecl t) #

Generic (TFBlockDecl t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (TFBlockDecl t) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (TFBlockDecl t) = D1 ('MetaData "TFBlockDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "TFBDStd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StdBlockDecl)) :+: C1 ('MetaCons "TFBDPort" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tfbdpDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t) :*: S1 ('MetaSel ('Just "_tfbdpType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ComType Bool))))

Methods

from :: TFBlockDecl t -> Rep (TFBlockDecl t) x #

to :: Rep (TFBlockDecl t) x -> TFBlockDecl t #

Show t => Show (TFBlockDecl t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq t => Eq (TFBlockDecl t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (TFBlockDecl t) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (TFBlockDecl t) = D1 ('MetaData "TFBlockDecl" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "TFBDStd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StdBlockDecl)) :+: C1 ('MetaCons "TFBDPort" 'PrefixI 'True) (S1 ('MetaSel ('Just "_tfbdpDir") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t) :*: S1 ('MetaSel ('Just "_tfbdpType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ComType Bool))))

data GenCaseItem Source #

Case generate branch

Constructors

GenCaseItem 

Instances

Instances details
Data GenCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GenCaseItem -> Constr #

dataTypeOf :: GenCaseItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GenCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GenCaseItem 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GenCaseItem = D1 ('MetaData "GenCaseItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GenCaseItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_gciPat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty CExpr)) :*: S1 ('MetaSel ('Just "_gciVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GenerateCondBlock)))
Show GenCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GenCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GenCaseItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GenCaseItem = D1 ('MetaData "GenCaseItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GenCaseItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_gciPat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty CExpr)) :*: S1 ('MetaSel ('Just "_gciVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GenerateCondBlock)))

data UDPInst Source #

UDP named instantiation

Instances

Instances details
Data UDPInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: UDPInst -> Constr #

dataTypeOf :: UDPInst -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic UDPInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep UDPInst 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep UDPInst = D1 ('MetaData "UDPInst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "UDPInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_udpiName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_udpiLValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_udpiArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)))))

Methods

from :: UDPInst -> Rep UDPInst x #

to :: Rep UDPInst x -> UDPInst #

Show UDPInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq UDPInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep UDPInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep UDPInst = D1 ('MetaData "UDPInst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "UDPInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_udpiName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe InstanceName)) :*: (S1 ('MetaSel ('Just "_udpiLValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_udpiArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)))))

data ModInst Source #

Module named instantiation

Constructors

ModInst 

Instances

Instances details
Data ModInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ModInst -> Constr #

dataTypeOf :: ModInst -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ModInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ModInst 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModInst = D1 ('MetaData "ModInst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ModInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_miName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InstanceName) :*: S1 ('MetaSel ('Just "_miPort") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PortAssign)))

Methods

from :: ModInst -> Rep ModInst x #

to :: Rep ModInst x -> ModInst #

Show ModInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ModInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep ModInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModInst = D1 ('MetaData "ModInst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ModInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_miName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InstanceName) :*: S1 ('MetaSel ('Just "_miPort") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PortAssign)))

data UknInst Source #

Unknown named instantiation

Constructors

UknInst 

Instances

Instances details
Data UknInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: UknInst -> Constr #

dataTypeOf :: UknInst -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic UknInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep UknInst 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep UknInst = D1 ('MetaData "UknInst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "UknInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_uiName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InstanceName) :*: (S1 ('MetaSel ('Just "_uiArg0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_uiArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)))))

Methods

from :: UknInst -> Rep UknInst x #

to :: Rep UknInst x -> UknInst #

Show UknInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq UknInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

type Rep UknInst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep UknInst = D1 ('MetaData "UknInst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "UknInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_uiName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InstanceName) :*: (S1 ('MetaSel ('Just "_uiArg0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetLValue) :*: S1 ('MetaSel ('Just "_uiArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Expr)))))

data ModGenCondItem Source #

Module or Generate conditional item because scoping rules are special

Instances

Instances details
Data ModGenCondItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ModGenCondItem -> Constr #

dataTypeOf :: ModGenCondItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ModGenCondItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ModGenCondItem 
Instance details

Defined in Verismith.Verilog2005.AST

Show ModGenCondItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ModGenCondItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModGenCondItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data GenerateCondBlock Source #

Generate Block or Conditional Item or nothing because scoping rules are special

Instances

Instances details
Data GenerateCondBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: GenerateCondBlock -> Constr #

dataTypeOf :: GenerateCondBlock -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic GenerateCondBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep GenerateCondBlock 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GenerateCondBlock = D1 ('MetaData "GenerateCondBlock" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GCBEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GCBBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GenerateBlock)) :+: C1 ('MetaCons "GCBConditional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributed ModGenCondItem)))))
Show GenerateCondBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq GenerateCondBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GenerateCondBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep GenerateCondBlock = D1 ('MetaData "GenerateCondBlock" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "GCBEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GCBBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GenerateBlock)) :+: C1 ('MetaCons "GCBConditional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Attributed ModGenCondItem)))))

data ModGenItem (f :: Type -> Type) Source #

Module or Generate item | f is either Identity or NonEmpty | it is used to abstract between several modgen items in a block and a single comma separated one

Constructors

MGINetInit 
MGINetDecl 
MGITriD 
MGITriC 
MGIBlockDecl !(BlockDecl (Compose f Identified) (Either [Range2] CExpr)) 
MGIGenVar !(f Identifier) 
MGITask 
MGIFunc 
MGIDefParam !(f ParamOver) 
MGIContAss 
MGICMos 

Fields

MGIEnable 
MGIMos 

Fields

MGINIn 
MGINOut 
MGIPassEn 
MGIPass 

Fields

MGIPull 
MGIUDPInst 
MGIModInst 
MGIUnknownInst 
MGIInitial !AttrStmt 
MGIAlways !AttrStmt 
MGILoopGen 
MGICondItem !ModGenCondItem 

Instances

Instances details
Plated ModGenBlockedItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

(Typeable f, forall a. Data a => Data (f a)) => Data (ModGenItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModGenItem f -> c (ModGenItem f) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ModGenItem f) #

toConstr :: ModGenItem f -> Constr #

dataTypeOf :: ModGenItem f -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ModGenItem f -> ModGenItem f #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModGenItem f -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModGenItem f -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModGenItem f -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModGenItem f -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModGenItem f -> m (ModGenItem f) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModGenItem f -> m (ModGenItem f) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModGenItem f -> m (ModGenItem f) #

(forall a. Generic a => Generic (f a)) => Generic (ModGenItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep (ModGenItem f) 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (ModGenItem f) = D1 ('MetaData "ModGenItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((((C1 ('MetaCons "MGINetInit" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mginiType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetType) :*: S1 ('MetaSel ('Just "_mginiDrive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength)) :*: (S1 ('MetaSel ('Just "_mginiProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mginiInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetInit)))) :+: (C1 ('MetaCons "MGINetDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgindType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetType) :*: (S1 ('MetaSel ('Just "_mgindProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mgindDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetDecl)))) :+: C1 ('MetaCons "MGITriD" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgitdDrive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgitdProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mgitdInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetInit)))))) :+: (C1 ('MetaCons "MGITriC" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgitcCharge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChargeStrength) :*: (S1 ('MetaSel ('Just "_mgitcProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mgitcDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetDecl)))) :+: (C1 ('MetaCons "MGIBlockDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BlockDecl (Compose f Identified) (Either [Range2] CExpr)))) :+: C1 ('MetaCons "MGIGenVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Identifier)))))) :+: ((C1 ('MetaCons "MGITask" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgitAuto") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgitIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :*: (S1 ('MetaSel ('Just "_mgitDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrIded (TFBlockDecl Dir)]) :*: S1 ('MetaSel ('Just "_mgitBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))) :+: (C1 ('MetaCons "MGIFunc" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgifAuto") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgifType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (ComType ())))) :*: (S1 ('MetaSel ('Just "_mgifIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgifDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrIded (TFBlockDecl ())]) :*: S1 ('MetaSel ('Just "_mgifBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FunctionStatement)))) :+: C1 ('MetaCons "MGIDefParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f ParamOver))))) :+: (C1 ('MetaCons "MGIContAss" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgicaStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgicaDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgicaAssign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetAssign)))) :+: (C1 ('MetaCons "MGICMos" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgicmR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_mgicmDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgicmInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GICMos)))) :+: C1 ('MetaCons "MGIEnable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgieR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgie1_0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgieStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgieDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgieInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIEnable))))))))) :+: (((C1 ('MetaCons "MGIMos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgimR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgimN_P") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgimDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgimInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIMos)))) :+: (C1 ('MetaCons "MGINIn" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgininType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NInputType) :*: S1 ('MetaSel ('Just "_mgininN") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgininStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgininDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mgininInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GINIn))))) :+: C1 ('MetaCons "MGINOut" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mginoR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mginoStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength)) :*: (S1 ('MetaSel ('Just "_mginoDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mginoInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GINOut)))))) :+: (C1 ('MetaCons "MGIPassEn" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgipeR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgipe1_0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgipeDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mgipeInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIPassEn)))) :+: (C1 ('MetaCons "MGIPass" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgipsR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgipsInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIPass))) :+: C1 ('MetaCons "MGIPull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgiplUp_down") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_mgiplStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: S1 ('MetaSel ('Just "_mgiplInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIPull))))))) :+: ((C1 ('MetaCons "MGIUDPInst" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgiudpiUDP") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_mgiudpiStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength)) :*: (S1 ('MetaSel ('Just "_mgiudpiDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mgiudpiInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f UDPInst)))) :+: (C1 ('MetaCons "MGIModInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgimiMod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgimiParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ParamAssign) :*: S1 ('MetaSel ('Just "_mgimiInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f ModInst)))) :+: C1 ('MetaCons "MGIUnknownInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgiuiType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgiuiParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Either Expr (Expr, Expr)))) :*: S1 ('MetaSel ('Just "_mgiuiInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f UknInst)))))) :+: ((C1 ('MetaCons "MGIInitial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrStmt)) :+: C1 ('MetaCons "MGIAlways" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrStmt))) :+: (C1 ('MetaCons "MGILoopGen" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgilgInitIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgilgInitValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr) :*: S1 ('MetaSel ('Just "_mgilgCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr))) :*: (S1 ('MetaSel ('Just "_mgilgUpdIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgilgUpdValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr) :*: S1 ('MetaSel ('Just "_mgilgBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GenerateBlock)))) :+: C1 ('MetaCons "MGICondItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModGenCondItem)))))))

Methods

from :: ModGenItem f -> Rep (ModGenItem f) x #

to :: Rep (ModGenItem f) x -> ModGenItem f #

(Show1 f, forall a. Show a => Show (f a)) => Show (ModGenItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

(Eq1 f, forall a. Eq a => Eq (f a)) => Eq (ModGenItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: ModGenItem f -> ModGenItem f -> Bool #

(/=) :: ModGenItem f -> ModGenItem f -> Bool #

type Rep (ModGenItem f) Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep (ModGenItem f) = D1 ('MetaData "ModGenItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((((C1 ('MetaCons "MGINetInit" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mginiType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetType) :*: S1 ('MetaSel ('Just "_mginiDrive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength)) :*: (S1 ('MetaSel ('Just "_mginiProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mginiInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetInit)))) :+: (C1 ('MetaCons "MGINetDecl" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgindType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetType) :*: (S1 ('MetaSel ('Just "_mgindProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mgindDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetDecl)))) :+: C1 ('MetaCons "MGITriD" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgitdDrive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgitdProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mgitdInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetInit)))))) :+: (C1 ('MetaCons "MGITriC" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgitcCharge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChargeStrength) :*: (S1 ('MetaSel ('Just "_mgitcProp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetProp) :*: S1 ('MetaSel ('Just "_mgitcDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetDecl)))) :+: (C1 ('MetaCons "MGIBlockDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BlockDecl (Compose f Identified) (Either [Range2] CExpr)))) :+: C1 ('MetaCons "MGIGenVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Identifier)))))) :+: ((C1 ('MetaCons "MGITask" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgitAuto") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgitIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :*: (S1 ('MetaSel ('Just "_mgitDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrIded (TFBlockDecl Dir)]) :*: S1 ('MetaSel ('Just "_mgitBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MybStmt))) :+: (C1 ('MetaCons "MGIFunc" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgifAuto") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgifType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (ComType ())))) :*: (S1 ('MetaSel ('Just "_mgifIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgifDecl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [AttrIded (TFBlockDecl ())]) :*: S1 ('MetaSel ('Just "_mgifBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FunctionStatement)))) :+: C1 ('MetaCons "MGIDefParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f ParamOver))))) :+: (C1 ('MetaCons "MGIContAss" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgicaStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgicaDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgicaAssign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f NetAssign)))) :+: (C1 ('MetaCons "MGICMos" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgicmR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_mgicmDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgicmInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GICMos)))) :+: C1 ('MetaCons "MGIEnable" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgieR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgie1_0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgieStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgieDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgieInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIEnable))))))))) :+: (((C1 ('MetaCons "MGIMos" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgimR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgimN_P") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgimDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay3)) :*: S1 ('MetaSel ('Just "_mgimInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIMos)))) :+: (C1 ('MetaCons "MGINIn" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgininType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NInputType) :*: S1 ('MetaSel ('Just "_mgininN") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgininStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: (S1 ('MetaSel ('Just "_mgininDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mgininInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GINIn))))) :+: C1 ('MetaCons "MGINOut" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mginoR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mginoStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength)) :*: (S1 ('MetaSel ('Just "_mginoDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mginoInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GINOut)))))) :+: (C1 ('MetaCons "MGIPassEn" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgipeR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgipe1_0") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "_mgipeDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mgipeInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIPassEn)))) :+: (C1 ('MetaCons "MGIPass" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgipsR") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "_mgipsInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIPass))) :+: C1 ('MetaCons "MGIPull" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgiplUp_down") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "_mgiplStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength) :*: S1 ('MetaSel ('Just "_mgiplInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f GIPull))))))) :+: ((C1 ('MetaCons "MGIUDPInst" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgiudpiUDP") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_mgiudpiStrength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DriveStrength)) :*: (S1 ('MetaSel ('Just "_mgiudpiDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Delay2)) :*: S1 ('MetaSel ('Just "_mgiudpiInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f UDPInst)))) :+: (C1 ('MetaCons "MGIModInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgimiMod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgimiParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ParamAssign) :*: S1 ('MetaSel ('Just "_mgimiInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f ModInst)))) :+: C1 ('MetaCons "MGIUnknownInst" 'PrefixI 'True) (S1 ('MetaSel ('Just "_mgiuiType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgiuiParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Either Expr (Expr, Expr)))) :*: S1 ('MetaSel ('Just "_mgiuiInst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f UknInst)))))) :+: ((C1 ('MetaCons "MGIInitial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrStmt)) :+: C1 ('MetaCons "MGIAlways" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AttrStmt))) :+: (C1 ('MetaCons "MGILoopGen" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_mgilgInitIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgilgInitValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr) :*: S1 ('MetaSel ('Just "_mgilgCond") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr))) :*: (S1 ('MetaSel ('Just "_mgilgUpdIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Just "_mgilgUpdValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CExpr) :*: S1 ('MetaSel ('Just "_mgilgBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GenerateBlock)))) :+: C1 ('MetaCons "MGICondItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ModGenCondItem)))))))

data ModuleItem Source #

Module item: body of module | Caution: if MIPort sign is False then it can be overriden by a MGINetDecl/Init

Instances

Instances details
Data ModuleItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

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

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

toConstr :: ModuleItem -> Constr #

dataTypeOf :: ModuleItem -> DataType #

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

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

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

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

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleItem -> m ModuleItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleItem -> m ModuleItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleItem -> m ModuleItem #

Generic ModuleItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Show ModuleItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ModuleItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModuleItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data ModuleBlock Source #

Module block TODO: remember whether the module is a module or macromodule because implementation dependent

Instances

Instances details
Data ModuleBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleBlock -> c ModuleBlock #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleBlock #

toConstr :: ModuleBlock -> Constr #

dataTypeOf :: ModuleBlock -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModuleBlock) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleBlock) #

gmapT :: (forall b. Data b => b -> b) -> ModuleBlock -> ModuleBlock #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleBlock -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleBlock -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleBlock -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleBlock -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleBlock -> m ModuleBlock #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleBlock -> m ModuleBlock #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleBlock -> m ModuleBlock #

Generic ModuleBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Show ModuleBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ModuleBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ModuleBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data SigLevel Source #

Signal level

Constructors

L0 
L1 
LX 
LQ 
LB 

Instances

Instances details
Data SigLevel Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SigLevel -> c SigLevel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SigLevel #

toConstr :: SigLevel -> Constr #

dataTypeOf :: SigLevel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SigLevel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SigLevel) #

gmapT :: (forall b. Data b => b -> b) -> SigLevel -> SigLevel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SigLevel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SigLevel -> r #

gmapQ :: (forall d. Data d => d -> u) -> SigLevel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SigLevel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SigLevel -> m SigLevel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SigLevel -> m SigLevel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SigLevel -> m SigLevel #

Bounded SigLevel Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Enum SigLevel Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic SigLevel Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep SigLevel 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SigLevel = D1 ('MetaData "SigLevel" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "L0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "L1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LB" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: SigLevel -> Rep SigLevel x #

to :: Rep SigLevel x -> SigLevel #

Show SigLevel Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq SigLevel Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SigLevel Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SigLevel = D1 ('MetaData "SigLevel" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "L0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "L1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LB" 'PrefixI 'False) (U1 :: Type -> Type))))

data ZOX Source #

Constructors

ZOXZ 
ZOXO 
ZOXX 

Instances

Instances details
Data ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZOX -> c ZOX #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZOX #

toConstr :: ZOX -> Constr #

dataTypeOf :: ZOX -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZOX) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZOX) #

gmapT :: (forall b. Data b => b -> b) -> ZOX -> ZOX #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZOX -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZOX -> r #

gmapQ :: (forall d. Data d => d -> u) -> ZOX -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ZOX -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZOX -> m ZOX #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZOX -> m ZOX #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZOX -> m ZOX #

Bounded ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

minBound :: ZOX #

maxBound :: ZOX #

Enum ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

succ :: ZOX -> ZOX #

pred :: ZOX -> ZOX #

toEnum :: Int -> ZOX #

fromEnum :: ZOX -> Int #

enumFrom :: ZOX -> [ZOX] #

enumFromThen :: ZOX -> ZOX -> [ZOX] #

enumFromTo :: ZOX -> ZOX -> [ZOX] #

enumFromThenTo :: ZOX -> ZOX -> ZOX -> [ZOX] #

Generic ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Associated Types

type Rep ZOX 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep ZOX = D1 ('MetaData "ZOX" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ZOXZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZOXO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZOXX" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: ZOX -> Rep ZOX x #

to :: Rep ZOX x -> ZOX #

Show ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

showsPrec :: Int -> ZOX -> ShowS #

show :: ZOX -> String #

showList :: [ZOX] -> ShowS #

NFData ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

rnf :: ZOX -> () #

Eq ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

(==) :: ZOX -> ZOX -> Bool #

(/=) :: ZOX -> ZOX -> Bool #

Ord ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

compare :: ZOX -> ZOX -> Ordering #

(<) :: ZOX -> ZOX -> Bool #

(<=) :: ZOX -> ZOX -> Bool #

(>) :: ZOX -> ZOX -> Bool #

(>=) :: ZOX -> ZOX -> Bool #

max :: ZOX -> ZOX -> ZOX #

min :: ZOX -> ZOX -> ZOX #

type Rep ZOX Source # 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep ZOX = D1 ('MetaData "ZOX" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ZOXZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZOXO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZOXX" 'PrefixI 'False) (U1 :: Type -> Type)))

data CombRow Source #

Combinatorial table row

Constructors

CombRow 

Instances

Instances details
Data CombRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CombRow -> c CombRow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CombRow #

toConstr :: CombRow -> Constr #

dataTypeOf :: CombRow -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CombRow) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CombRow) #

gmapT :: (forall b. Data b => b -> b) -> CombRow -> CombRow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CombRow -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CombRow -> r #

gmapQ :: (forall d. Data d => d -> u) -> CombRow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CombRow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CombRow -> m CombRow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CombRow -> m CombRow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CombRow -> m CombRow #

Generic CombRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep CombRow 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep CombRow = D1 ('MetaData "CombRow" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CombRow" 'PrefixI 'True) (S1 ('MetaSel ('Just "_crInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SigLevel)) :*: S1 ('MetaSel ('Just "_crOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZOX)))

Methods

from :: CombRow -> Rep CombRow x #

to :: Rep CombRow x -> CombRow #

Show CombRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq CombRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: CombRow -> CombRow -> Bool #

(/=) :: CombRow -> CombRow -> Bool #

type Rep CombRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep CombRow = D1 ('MetaData "CombRow" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CombRow" 'PrefixI 'True) (S1 ('MetaSel ('Just "_crInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SigLevel)) :*: S1 ('MetaSel ('Just "_crOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZOX)))

data Edge Source #

Edge specifier

Constructors

EdgePos_neg !Bool 
EdgeDesc 

Fields

Instances

Instances details
Data Edge Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Edge -> c Edge #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Edge #

toConstr :: Edge -> Constr #

dataTypeOf :: Edge -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Edge) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Edge) #

gmapT :: (forall b. Data b => b -> b) -> Edge -> Edge #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Edge -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Edge -> r #

gmapQ :: (forall d. Data d => d -> u) -> Edge -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Edge -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Edge -> m Edge #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Edge -> m Edge #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Edge -> m Edge #

Generic Edge Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Edge 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Edge = D1 ('MetaData "Edge" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "EdgePos_neg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "EdgeDesc" 'PrefixI 'True) (S1 ('MetaSel ('Just "_edFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigLevel) :*: S1 ('MetaSel ('Just "_edTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigLevel)))

Methods

from :: Edge -> Rep Edge x #

to :: Rep Edge x -> Edge #

Show Edge Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> Edge -> ShowS #

show :: Edge -> String #

showList :: [Edge] -> ShowS #

Eq Edge Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: Edge -> Edge -> Bool #

(/=) :: Edge -> Edge -> Bool #

type Rep Edge Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Edge = D1 ('MetaData "Edge" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "EdgePos_neg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "EdgeDesc" 'PrefixI 'True) (S1 ('MetaSel ('Just "_edFrom") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigLevel) :*: S1 ('MetaSel ('Just "_edTo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigLevel)))

data SeqIn Source #

Seqential table inputs: a list of input levels with at most 1 edge specifier

Instances

Instances details
Data SeqIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SeqIn -> c SeqIn #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SeqIn #

toConstr :: SeqIn -> Constr #

dataTypeOf :: SeqIn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SeqIn) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SeqIn) #

gmapT :: (forall b. Data b => b -> b) -> SeqIn -> SeqIn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SeqIn -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SeqIn -> r #

gmapQ :: (forall d. Data d => d -> u) -> SeqIn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SeqIn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SeqIn -> m SeqIn #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SeqIn -> m SeqIn #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SeqIn -> m SeqIn #

Generic SeqIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

from :: SeqIn -> Rep SeqIn x #

to :: Rep SeqIn x -> SeqIn #

Show SeqIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> SeqIn -> ShowS #

show :: SeqIn -> String #

showList :: [SeqIn] -> ShowS #

Eq SeqIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: SeqIn -> SeqIn -> Bool #

(/=) :: SeqIn -> SeqIn -> Bool #

type Rep SeqIn Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data SeqRow Source #

Sequential table row

Constructors

SeqRow 

Instances

Instances details
Data SeqRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SeqRow -> c SeqRow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SeqRow #

toConstr :: SeqRow -> Constr #

dataTypeOf :: SeqRow -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SeqRow) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SeqRow) #

gmapT :: (forall b. Data b => b -> b) -> SeqRow -> SeqRow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SeqRow -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SeqRow -> r #

gmapQ :: (forall d. Data d => d -> u) -> SeqRow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SeqRow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SeqRow -> m SeqRow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SeqRow -> m SeqRow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SeqRow -> m SeqRow #

Generic SeqRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep SeqRow 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SeqRow = D1 ('MetaData "SeqRow" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SeqRow" 'PrefixI 'True) (S1 ('MetaSel ('Just "_srowInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SeqIn) :*: (S1 ('MetaSel ('Just "_srowState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigLevel) :*: S1 ('MetaSel ('Just "_srowNext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ZOX)))))

Methods

from :: SeqRow -> Rep SeqRow x #

to :: Rep SeqRow x -> SeqRow #

Show SeqRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq SeqRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: SeqRow -> SeqRow -> Bool #

(/=) :: SeqRow -> SeqRow -> Bool #

type Rep SeqRow Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep SeqRow = D1 ('MetaData "SeqRow" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "SeqRow" 'PrefixI 'True) (S1 ('MetaSel ('Just "_srowInput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SeqIn) :*: (S1 ('MetaSel ('Just "_srowState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SigLevel) :*: S1 ('MetaSel ('Just "_srowNext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ZOX)))))

data PrimTable Source #

Primitive transition table

Constructors

CombTable !(NonEmpty CombRow) 
SeqTable 

Fields

Instances

Instances details
Data PrimTable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimTable -> c PrimTable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimTable #

toConstr :: PrimTable -> Constr #

dataTypeOf :: PrimTable -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimTable) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimTable) #

gmapT :: (forall b. Data b => b -> b) -> PrimTable -> PrimTable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimTable -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimTable -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrimTable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimTable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimTable -> m PrimTable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimTable -> m PrimTable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimTable -> m PrimTable #

Generic PrimTable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep PrimTable 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PrimTable = D1 ('MetaData "PrimTable" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CombTable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty CombRow))) :+: C1 ('MetaCons "SeqTable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ZOX)) :*: S1 ('MetaSel ('Just "_stRow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SeqRow))))
Show PrimTable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq PrimTable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PrimTable Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PrimTable = D1 ('MetaData "PrimTable" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CombTable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty CombRow))) :+: C1 ('MetaCons "SeqTable" 'PrefixI 'True) (S1 ('MetaSel ('Just "_stInit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ZOX)) :*: S1 ('MetaSel ('Just "_stRow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty SeqRow))))

data PrimPort Source #

Primitive port type

Instances

Instances details
Data PrimPort Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimPort -> c PrimPort #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimPort #

toConstr :: PrimPort -> Constr #

dataTypeOf :: PrimPort -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimPort) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimPort) #

gmapT :: (forall b. Data b => b -> b) -> PrimPort -> PrimPort #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimPort -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimPort -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrimPort -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimPort -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimPort -> m PrimPort #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimPort -> m PrimPort #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimPort -> m PrimPort #

Generic PrimPort Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep PrimPort 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PrimPort = D1 ('MetaData "PrimPort" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "PPInput" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PPOutput" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PPReg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PPOutReg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)))))

Methods

from :: PrimPort -> Rep PrimPort x #

to :: Rep PrimPort x -> PrimPort #

Show PrimPort Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq PrimPort Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PrimPort Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PrimPort = D1 ('MetaData "PrimPort" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "PPInput" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PPOutput" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PPReg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PPOutReg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe CExpr)))))

data PrimitiveBlock Source #

Primitive block

Instances

Instances details
Data PrimitiveBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimitiveBlock -> c PrimitiveBlock #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimitiveBlock #

toConstr :: PrimitiveBlock -> Constr #

dataTypeOf :: PrimitiveBlock -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimitiveBlock) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimitiveBlock) #

gmapT :: (forall b. Data b => b -> b) -> PrimitiveBlock -> PrimitiveBlock #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveBlock -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveBlock -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrimitiveBlock -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimitiveBlock -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimitiveBlock -> m PrimitiveBlock #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveBlock -> m PrimitiveBlock #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveBlock -> m PrimitiveBlock #

Generic PrimitiveBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep PrimitiveBlock 
Instance details

Defined in Verismith.Verilog2005.AST

Show PrimitiveBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq PrimitiveBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep PrimitiveBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data Dot1Ident Source #

Library prefixed cell

Constructors

Dot1Ident 

Instances

Instances details
Data Dot1Ident Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dot1Ident -> c Dot1Ident #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dot1Ident #

toConstr :: Dot1Ident -> Constr #

dataTypeOf :: Dot1Ident -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dot1Ident) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dot1Ident) #

gmapT :: (forall b. Data b => b -> b) -> Dot1Ident -> Dot1Ident #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dot1Ident -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dot1Ident -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dot1Ident -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dot1Ident -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dot1Ident -> m Dot1Ident #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dot1Ident -> m Dot1Ident #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dot1Ident -> m Dot1Ident #

Generic Dot1Ident Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Dot1Ident 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Dot1Ident = D1 ('MetaData "Dot1Ident" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Dot1Ident" 'PrefixI 'True) (S1 ('MetaSel ('Just "_d1iLib") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)) :*: S1 ('MetaSel ('Just "_d1iCell") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)))
Show Dot1Ident Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Dot1Ident Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Dot1Ident Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Dot1Ident = D1 ('MetaData "Dot1Ident" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Dot1Ident" 'PrefixI 'True) (S1 ('MetaSel ('Just "_d1iLib") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)) :*: S1 ('MetaSel ('Just "_d1iCell") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)))

data Cell_inst Source #

Cell or instance

Instances

Instances details
Data Cell_inst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cell_inst -> c Cell_inst #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cell_inst #

toConstr :: Cell_inst -> Constr #

dataTypeOf :: Cell_inst -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cell_inst) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell_inst) #

gmapT :: (forall b. Data b => b -> b) -> Cell_inst -> Cell_inst #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell_inst -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell_inst -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cell_inst -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cell_inst -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cell_inst -> m Cell_inst #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell_inst -> m Cell_inst #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell_inst -> m Cell_inst #

Generic Cell_inst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Cell_inst 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Cell_inst = D1 ('MetaData "Cell_inst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CICell" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Dot1Ident)) :+: C1 ('MetaCons "CIInst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Identifier))))
Show Cell_inst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Cell_inst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Cell_inst Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Cell_inst = D1 ('MetaData "Cell_inst" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "CICell" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Dot1Ident)) :+: C1 ('MetaCons "CIInst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty Identifier))))

data LLU Source #

Liblist or Use

Constructors

LLULiblist ![ByteString] 
LLUUse 

Instances

Instances details
Data LLU Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LLU -> c LLU #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LLU #

toConstr :: LLU -> Constr #

dataTypeOf :: LLU -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LLU) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LLU) #

gmapT :: (forall b. Data b => b -> b) -> LLU -> LLU #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LLU -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LLU -> r #

gmapQ :: (forall d. Data d => d -> u) -> LLU -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LLU -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LLU -> m LLU #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LLU -> m LLU #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LLU -> m LLU #

Generic LLU Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep LLU 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep LLU = D1 ('MetaData "LLU" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "LLULiblist" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ByteString])) :+: C1 ('MetaCons "LLUUse" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lluUIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Dot1Ident) :*: S1 ('MetaSel ('Just "_lluUConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))

Methods

from :: LLU -> Rep LLU x #

to :: Rep LLU x -> LLU #

Show LLU Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> LLU -> ShowS #

show :: LLU -> String #

showList :: [LLU] -> ShowS #

Eq LLU Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: LLU -> LLU -> Bool #

(/=) :: LLU -> LLU -> Bool #

type Rep LLU Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep LLU = D1 ('MetaData "LLU" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "LLULiblist" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ByteString])) :+: C1 ('MetaCons "LLUUse" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lluUIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Dot1Ident) :*: S1 ('MetaSel ('Just "_lluUConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))

data ConfigItem Source #

Items in a config block

Constructors

ConfigItem 

Fields

Instances

Instances details
Data ConfigItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfigItem -> c ConfigItem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfigItem #

toConstr :: ConfigItem -> Constr #

dataTypeOf :: ConfigItem -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfigItem) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfigItem) #

gmapT :: (forall b. Data b => b -> b) -> ConfigItem -> ConfigItem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfigItem -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfigItem -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConfigItem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfigItem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfigItem -> m ConfigItem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigItem -> m ConfigItem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigItem -> m ConfigItem #

Generic ConfigItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ConfigItem 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ConfigItem = D1 ('MetaData "ConfigItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ConfigItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ciCell_inst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Cell_inst) :*: S1 ('MetaSel ('Just "_ciLLU") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LLU)))
Show ConfigItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ConfigItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ConfigItem Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ConfigItem = D1 ('MetaData "ConfigItem" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ConfigItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ciCell_inst") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Cell_inst) :*: S1 ('MetaSel ('Just "_ciLLU") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LLU)))

data ConfigBlock Source #

Config Block: Identifier, Design lines, Configuration items

Constructors

ConfigBlock 

Instances

Instances details
Data ConfigBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfigBlock -> c ConfigBlock #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfigBlock #

toConstr :: ConfigBlock -> Constr #

dataTypeOf :: ConfigBlock -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConfigBlock) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfigBlock) #

gmapT :: (forall b. Data b => b -> b) -> ConfigBlock -> ConfigBlock #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfigBlock -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfigBlock -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConfigBlock -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfigBlock -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfigBlock -> m ConfigBlock #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigBlock -> m ConfigBlock #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfigBlock -> m ConfigBlock #

Generic ConfigBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep ConfigBlock 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ConfigBlock = D1 ('MetaData "ConfigBlock" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ConfigBlock" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_cbIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_cbDesign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Dot1Ident])) :*: (S1 ('MetaSel ('Just "_cbBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ConfigItem]) :*: S1 ('MetaSel ('Just "_cbDef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ByteString]))))
Show ConfigBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq ConfigBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ConfigBlock Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep ConfigBlock = D1 ('MetaData "ConfigBlock" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "ConfigBlock" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_cbIdent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Just "_cbDesign") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Dot1Ident])) :*: (S1 ('MetaSel ('Just "_cbBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ConfigItem]) :*: S1 ('MetaSel ('Just "_cbDef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ByteString]))))

data Verilog2005 Source #

Internal representation of Verilog2005 AST

Instances

Instances details
Data Verilog2005 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Verilog2005 -> c Verilog2005 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Verilog2005 #

toConstr :: Verilog2005 -> Constr #

dataTypeOf :: Verilog2005 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Verilog2005) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verilog2005) #

gmapT :: (forall b. Data b => b -> b) -> Verilog2005 -> Verilog2005 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Verilog2005 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Verilog2005 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Verilog2005 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Verilog2005 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Verilog2005 -> m Verilog2005 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Verilog2005 -> m Verilog2005 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Verilog2005 -> m Verilog2005 #

Monoid Verilog2005 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Semigroup Verilog2005 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Generic Verilog2005 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Associated Types

type Rep Verilog2005 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Verilog2005 = D1 ('MetaData "Verilog2005" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Verilog2005" 'PrefixI 'True) (S1 ('MetaSel ('Just "_vModule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ModuleBlock]) :*: (S1 ('MetaSel ('Just "_vPrimitive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PrimitiveBlock]) :*: S1 ('MetaSel ('Just "_vConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ConfigBlock]))))
Show Verilog2005 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq Verilog2005 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Verilog2005 Source # 
Instance details

Defined in Verismith.Verilog2005.AST

type Rep Verilog2005 = D1 ('MetaData "Verilog2005" "Verismith.Verilog2005.AST" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (C1 ('MetaCons "Verilog2005" 'PrefixI 'True) (S1 ('MetaSel ('Just "_vModule") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ModuleBlock]) :*: (S1 ('MetaSel ('Just "_vPrimitive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [PrimitiveBlock]) :*: S1 ('MetaSel ('Just "_vConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [ConfigBlock]))))

data SystemFunction Source #

Instances

Instances details
Data SystemFunction Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SystemFunction -> c SystemFunction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SystemFunction #

toConstr :: SystemFunction -> Constr #

dataTypeOf :: SystemFunction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SystemFunction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SystemFunction) #

gmapT :: (forall b. Data b => b -> b) -> SystemFunction -> SystemFunction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SystemFunction -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SystemFunction -> r #

gmapQ :: (forall d. Data d => d -> u) -> SystemFunction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SystemFunction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SystemFunction -> m SystemFunction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SystemFunction -> m SystemFunction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SystemFunction -> m SystemFunction #

Show SystemFunction Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Eq SystemFunction Source # 
Instance details

Defined in Verismith.Verilog2005.AST

data Logic Source #

Constructors

LAnd 
LOr 
LNand 
LNor 

Instances

Instances details
Data Logic Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Logic -> c Logic #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Logic #

toConstr :: Logic -> Constr #

dataTypeOf :: Logic -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Logic) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Logic) #

gmapT :: (forall b. Data b => b -> b) -> Logic -> Logic #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Logic -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Logic -> r #

gmapQ :: (forall d. Data d => d -> u) -> Logic -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Logic -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Logic -> m Logic #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Logic -> m Logic #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Logic -> m Logic #

Show Logic Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

showsPrec :: Int -> Logic -> ShowS #

show :: Logic -> String #

showList :: [Logic] -> ShowS #

Eq Logic Source # 
Instance details

Defined in Verismith.Verilog2005.AST

Methods

(==) :: Logic -> Logic -> Bool #

(/=) :: Logic -> Logic -> Bool #

data BXZ Source #

Constructors

BXZ0 
BXZ1 
BXZX 
BXZZ 

Instances

Instances details
Data BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BXZ -> c BXZ #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BXZ #

toConstr :: BXZ -> Constr #

dataTypeOf :: BXZ -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BXZ) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BXZ) #

gmapT :: (forall b. Data b => b -> b) -> BXZ -> BXZ #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BXZ -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BXZ -> r #

gmapQ :: (forall d. Data d => d -> u) -> BXZ -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BXZ -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BXZ -> m BXZ #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BXZ -> m BXZ #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BXZ -> m BXZ #

Bounded BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

minBound :: BXZ #

maxBound :: BXZ #

Enum BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

succ :: BXZ -> BXZ #

pred :: BXZ -> BXZ #

toEnum :: Int -> BXZ #

fromEnum :: BXZ -> Int #

enumFrom :: BXZ -> [BXZ] #

enumFromThen :: BXZ -> BXZ -> [BXZ] #

enumFromTo :: BXZ -> BXZ -> [BXZ] #

enumFromThenTo :: BXZ -> BXZ -> BXZ -> [BXZ] #

Generic BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Associated Types

type Rep BXZ 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep BXZ = D1 ('MetaData "BXZ" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "BXZ0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BXZ1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BXZX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BXZZ" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: BXZ -> Rep BXZ x #

to :: Rep BXZ x -> BXZ #

Show BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

showsPrec :: Int -> BXZ -> ShowS #

show :: BXZ -> String #

showList :: [BXZ] -> ShowS #

NFData BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

rnf :: BXZ -> () #

Eq BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

(==) :: BXZ -> BXZ -> Bool #

(/=) :: BXZ -> BXZ -> Bool #

Ord BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

compare :: BXZ -> BXZ -> Ordering #

(<) :: BXZ -> BXZ -> Bool #

(<=) :: BXZ -> BXZ -> Bool #

(>) :: BXZ -> BXZ -> Bool #

(>=) :: BXZ -> BXZ -> Bool #

max :: BXZ -> BXZ -> BXZ #

min :: BXZ -> BXZ -> BXZ #

type Rep BXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep BXZ = D1 ('MetaData "BXZ" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((C1 ('MetaCons "BXZ0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BXZ1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BXZX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BXZZ" 'PrefixI 'False) (U1 :: Type -> Type)))

data OXZ Source #

Constructors

OXZ0 
OXZ1 
OXZ2 
OXZ3 
OXZ4 
OXZ5 
OXZ6 
OXZ7 
OXZX 
OXZZ 

Instances

Instances details
Data OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OXZ -> c OXZ #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OXZ #

toConstr :: OXZ -> Constr #

dataTypeOf :: OXZ -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OXZ) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OXZ) #

gmapT :: (forall b. Data b => b -> b) -> OXZ -> OXZ #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OXZ -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OXZ -> r #

gmapQ :: (forall d. Data d => d -> u) -> OXZ -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OXZ -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OXZ -> m OXZ #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OXZ -> m OXZ #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OXZ -> m OXZ #

Bounded OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

minBound :: OXZ #

maxBound :: OXZ #

Enum OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

succ :: OXZ -> OXZ #

pred :: OXZ -> OXZ #

toEnum :: Int -> OXZ #

fromEnum :: OXZ -> Int #

enumFrom :: OXZ -> [OXZ] #

enumFromThen :: OXZ -> OXZ -> [OXZ] #

enumFromTo :: OXZ -> OXZ -> [OXZ] #

enumFromThenTo :: OXZ -> OXZ -> OXZ -> [OXZ] #

Generic OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Associated Types

type Rep OXZ 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep OXZ = D1 ('MetaData "OXZ" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "OXZ0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZ1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OXZ2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OXZ3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZ4" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "OXZ5" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZ6" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OXZ7" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OXZX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZZ" 'PrefixI 'False) (U1 :: Type -> Type)))))

Methods

from :: OXZ -> Rep OXZ x #

to :: Rep OXZ x -> OXZ #

Show OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

showsPrec :: Int -> OXZ -> ShowS #

show :: OXZ -> String #

showList :: [OXZ] -> ShowS #

NFData OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

rnf :: OXZ -> () #

Eq OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

(==) :: OXZ -> OXZ -> Bool #

(/=) :: OXZ -> OXZ -> Bool #

Ord OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

compare :: OXZ -> OXZ -> Ordering #

(<) :: OXZ -> OXZ -> Bool #

(<=) :: OXZ -> OXZ -> Bool #

(>) :: OXZ -> OXZ -> Bool #

(>=) :: OXZ -> OXZ -> Bool #

max :: OXZ -> OXZ -> OXZ #

min :: OXZ -> OXZ -> OXZ #

type Rep OXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep OXZ = D1 ('MetaData "OXZ" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) (((C1 ('MetaCons "OXZ0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZ1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OXZ2" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OXZ3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZ4" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "OXZ5" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZ6" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OXZ7" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OXZX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OXZZ" 'PrefixI 'False) (U1 :: Type -> Type)))))

data HXZ Source #

Constructors

HXZ0 
HXZ1 
HXZ2 
HXZ3 
HXZ4 
HXZ5 
HXZ6 
HXZ7 
HXZ8 
HXZ9 
HXZA 
HXZB 
HXZC 
HXZD 
HXZE 
HXZF 
HXZX 
HXZZ 

Instances

Instances details
Data HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HXZ -> c HXZ #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HXZ #

toConstr :: HXZ -> Constr #

dataTypeOf :: HXZ -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HXZ) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HXZ) #

gmapT :: (forall b. Data b => b -> b) -> HXZ -> HXZ #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HXZ -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HXZ -> r #

gmapQ :: (forall d. Data d => d -> u) -> HXZ -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HXZ -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HXZ -> m HXZ #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HXZ -> m HXZ #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HXZ -> m HXZ #

Bounded HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

minBound :: HXZ #

maxBound :: HXZ #

Enum HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

succ :: HXZ -> HXZ #

pred :: HXZ -> HXZ #

toEnum :: Int -> HXZ #

fromEnum :: HXZ -> Int #

enumFrom :: HXZ -> [HXZ] #

enumFromThen :: HXZ -> HXZ -> [HXZ] #

enumFromTo :: HXZ -> HXZ -> [HXZ] #

enumFromThenTo :: HXZ -> HXZ -> HXZ -> [HXZ] #

Generic HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Associated Types

type Rep HXZ 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep HXZ = D1 ('MetaData "HXZ" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((((C1 ('MetaCons "HXZ0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZ2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ3" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HXZ4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ5" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZ6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HXZ7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ8" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HXZ9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZA" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HXZD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HXZX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZZ" 'PrefixI 'False) (U1 :: Type -> Type))))))

Methods

from :: HXZ -> Rep HXZ x #

to :: Rep HXZ x -> HXZ #

Show HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

showsPrec :: Int -> HXZ -> ShowS #

show :: HXZ -> String #

showList :: [HXZ] -> ShowS #

NFData HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

rnf :: HXZ -> () #

Eq HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

(==) :: HXZ -> HXZ -> Bool #

(/=) :: HXZ -> HXZ -> Bool #

Ord HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

Methods

compare :: HXZ -> HXZ -> Ordering #

(<) :: HXZ -> HXZ -> Bool #

(<=) :: HXZ -> HXZ -> Bool #

(>) :: HXZ -> HXZ -> Bool #

(>=) :: HXZ -> HXZ -> Bool #

max :: HXZ -> HXZ -> HXZ #

min :: HXZ -> HXZ -> HXZ #

type Rep HXZ Source # 
Instance details

Defined in Verismith.Verilog2005.Token

type Rep HXZ = D1 ('MetaData "HXZ" "Verismith.Verilog2005.Token" "verismith-1.1.0-FUTsgQc3KWmLTdTSx0Se1T" 'False) ((((C1 ('MetaCons "HXZ0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZ2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ3" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HXZ4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ5" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZ6" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HXZ7" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZ8" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HXZ9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZA" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZC" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HXZD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HXZF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HXZX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HXZZ" 'PrefixI 'False) (U1 :: Type -> Type))))))