Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
- type SdfString = ByteString
- type Qstring = String
- type Number = Double
- type Rnumber = Double
- type Dnumber = Int
- type Tsvalue = String
- type Identifier = String
- data DelayFile = DelayFile SdfHeader [Cell]
- data SdfHeader = SdfHeader SdfVersion (Maybe DesignName) (Maybe Date) (Maybe Vendor) (Maybe ProgramName) (Maybe ProgramVersion) (Maybe HierarchyDivider) (Maybe Voltage) (Maybe Process) (Maybe Temperature) (Maybe TimeScale)
- type SdfVersion = Qstring
- type DesignName = Qstring
- type Date = Qstring
- type Vendor = Qstring
- type ProgramName = Qstring
- type ProgramVersion = Qstring
- type HierarchyDivider = Qstring
- type Voltage = Rtriple
- type Process = Qstring
- type Temperature = Rtriple
- type TimeScale = Qstring
- data Cell = Cell Celltype CellInstance (Maybe Correlation) [TimingSpec]
- type Celltype = Qstring
- type CellInstance = [Identifier]
- type Instance = Identifier
- data Correlation = Correlation Qstring (Maybe CorrFactor)
- type CorrFactor = [Number]
- data TimingSpec
- type DelSpec = [Deltype]
- type TcSpec = [TcDef]
- data Deltype
- data InputOutputPath = InputOutputPath PortPath PortPath
- data DelDef
- data NetSpec = NetSpec (Maybe Instance) Identifier
- data TcDef
- data TchkDef
- = TchkDefSetup PortTchk PortTchk Rvalue
- | TchkDefHold PortTchk PortTchk Rvalue
- | TchkDefSetuphold PortTchk PortTchk Rvalue Rvalue
- | TchkDefRecovery PortTchk PortTchk Rvalue
- | TchkDefSkew PortTchk PortTchk Rvalue
- | TchkDefWidth PortTchk Value
- | TchkDefPeriod PortTchk Value
- | TchkDefNochange PortTchk PortTchk Rvalue Rvalue
- data CnsDef
- data PortTchk
- type ConstraintPath = (PortInstance, PortInstance)
- data PortSpec
- data PortEdge = PortEdge EdgeIdentifier PortPath
- type EdgeIdentifier = String
- type PortPath = Port
- type Port = Identifier
- type ScalarPort = Identifier
- type BusPort = Identifier
- data PortInstance = PortInstance (Maybe Instance) Identifier
- type Value = Triple
- type Triple = (Maybe Double, Maybe Double, Maybe Double)
- type Rvalue = Triple
- type Rtriple = Triple
- type RvalueList = [Rvalue]
- type ConditionalPortExpr = String
- type SimpleExpression = String
- type TimingCheckCondition = String
- type ScalarConstant = String
- type UnaryOperator = String
- type InversionOperator = String
- type BinaryOperator = String
- type EqualityOperator = String
Documentation
type SdfString = ByteString Source
This is the parser stream type. We can switch from String to ByteString or other input stream by changing the definition of SdfString
type Identifier = String Source
SdfHeader SdfVersion (Maybe DesignName) (Maybe Date) (Maybe Vendor) (Maybe ProgramName) (Maybe ProgramVersion) (Maybe HierarchyDivider) (Maybe Voltage) (Maybe Process) (Maybe Temperature) (Maybe TimeScale) |
type SdfVersion = Qstring Source
type DesignName = Qstring Source
type ProgramName = Qstring Source
type ProgramVersion = Qstring Source
type HierarchyDivider = Qstring Source
type Temperature = Rtriple Source
type CellInstance = [Identifier] Source
type Instance = Identifier Source
type CorrFactor = [Number] Source
data InputOutputPath Source
type ConstraintPath = (PortInstance, PortInstance) Source
type EdgeIdentifier = String Source
type Port = Identifier Source
type ScalarPort = Identifier Source
type BusPort = Identifier Source
type RvalueList = [Rvalue] Source
type ConditionalPortExpr = String Source
type SimpleExpression = String Source
type TimingCheckCondition = String Source
type ScalarConstant = String Source
type UnaryOperator = String Source
type InversionOperator = String Source
type BinaryOperator = String Source
type EqualityOperator = String Source