| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Language.Bluespec.Classic.AST.Type
Synopsis
- data Type
- data TyVar = TyVar {}
- data TyCon
- data TISort
- = TItype Integer Type
- | TIdata {
- tidata_cons :: [Id]
- tidata_enum :: Bool
- | TIstruct StructSubType [Id]
- | TIabstract
- data StructSubType
- = SStruct
- | SClass
- | SDataCon { }
- | SInterface [IfcPragma]
- | SPolyWrap {
- spolywrap_id :: Id
- spolywrap_ctor :: Maybe Id
- spolywrap_field :: Id
- type CType = Type
- data Kind
- data PartialKind
- newtype CTypeclass = CTypeclass Id
- data CPred = CPred {
- cpred_tc :: CTypeclass
- cpred_args :: [CType]
- data CQType = CQType [CPred] CType
- baseKVar :: Int
- cTNum :: Integer -> Position -> CType
- isTConArrow :: TyCon -> Bool
- isTConPair :: TyCon -> Bool
- leftCon :: CType -> Maybe Id
Documentation
Representation of types
Constructors
| TVar TyVar | type variable |
| TCon TyCon | type constructor |
| TAp Type Type | type-level application |
| TGen Position Int | quantified type variable used in type schemes |
| TDefMonad Position | not used after CVParserImperative |
Instances
| Show Type Source # | |
| Eq Type Source # | |
| Ord Type Source # | |
| HasKind Type Source # | |
| HasPosition Type Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods getPosition :: Type -> Position Source # | |
| Pretty Type Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods pPrintPrec :: PrettyLevel -> Rational -> Type -> Doc # pPrintList :: PrettyLevel -> [Type] -> Doc # | |
Representation of a type variable
Constructors
| TyVar | |
Instances
| Show TyVar Source # | |
| Eq TyVar Source # | |
| Ord TyVar Source # | |
| HasKind TyVar Source # | |
| HasPosition TyVar Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods getPosition :: TyVar -> Position Source # | |
| Pretty TyVar Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods pPrintPrec :: PrettyLevel -> Rational -> TyVar -> Doc # pPrintList :: PrettyLevel -> [TyVar] -> Doc # | |
Representation of a type constructor
Constructors
| TyCon | A constructor for a type of value kind |
| TyNum | A constructor for a type of numeric kind |
Fields
| |
| TyStr | A constructor for a type of string kind |
Fields
| |
Instances
| Show TyCon Source # | |
| Eq TyCon Source # | |
| Ord TyCon Source # | |
| HasKind TyCon Source # | |
| HasPosition TyCon Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods getPosition :: TyCon -> Position Source # | |
| Pretty TyCon Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods pPrintPrec :: PrettyLevel -> Rational -> TyCon -> Doc # pPrintList :: PrettyLevel -> [TyCon] -> Doc # | |
Constructors
| TItype Integer Type | |
| TIdata | |
Fields
| |
| TIstruct StructSubType [Id] | |
| TIabstract | |
data StructSubType Source #
Constructors
| SStruct | |
| SClass | |
| SDataCon | |
Fields | |
| SInterface [IfcPragma] | |
| SPolyWrap | |
Fields
| |
Instances
Representation of kinds
Constructors
| KStar | kind of a simple value type |
| KNum | kind of a simple numeric type |
| KStr | kind of a simple string type |
| Kfun Kind Kind | kind of type constructors (type-level function) |
| KVar Int | generated kind variable (used only during kind inference) |
data PartialKind Source #
Constructors
| PKNoInfo | |
| PKStar | |
| PKNum | |
| PKStr | |
| PKfun PartialKind PartialKind |
Instances
| Show PartialKind Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods showsPrec :: Int -> PartialKind -> ShowS # show :: PartialKind -> String # showList :: [PartialKind] -> ShowS # | |
| Eq PartialKind Source # | |
Defined in Language.Bluespec.Classic.AST.Type | |
| Ord PartialKind Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods compare :: PartialKind -> PartialKind -> Ordering # (<) :: PartialKind -> PartialKind -> Bool # (<=) :: PartialKind -> PartialKind -> Bool # (>) :: PartialKind -> PartialKind -> Bool # (>=) :: PartialKind -> PartialKind -> Bool # max :: PartialKind -> PartialKind -> PartialKind # min :: PartialKind -> PartialKind -> PartialKind # | |
| Pretty PartialKind Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods pPrintPrec :: PrettyLevel -> Rational -> PartialKind -> Doc # pPrint :: PartialKind -> Doc # pPrintList :: PrettyLevel -> [PartialKind] -> Doc # | |
newtype CTypeclass Source #
A named typeclass
Constructors
| CTypeclass Id |
Instances
| Show CTypeclass Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods showsPrec :: Int -> CTypeclass -> ShowS # show :: CTypeclass -> String # showList :: [CTypeclass] -> ShowS # | |
| Eq CTypeclass Source # | |
Defined in Language.Bluespec.Classic.AST.Type | |
| Ord CTypeclass Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods compare :: CTypeclass -> CTypeclass -> Ordering # (<) :: CTypeclass -> CTypeclass -> Bool # (<=) :: CTypeclass -> CTypeclass -> Bool # (>) :: CTypeclass -> CTypeclass -> Bool # (>=) :: CTypeclass -> CTypeclass -> Bool # max :: CTypeclass -> CTypeclass -> CTypeclass # min :: CTypeclass -> CTypeclass -> CTypeclass # | |
| HasPosition CTypeclass Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods getPosition :: CTypeclass -> Position Source # | |
| Pretty CTypeclass Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods pPrintPrec :: PrettyLevel -> Rational -> CTypeclass -> Doc # pPrint :: CTypeclass -> Doc # pPrintList :: PrettyLevel -> [CTypeclass] -> Doc # | |
Representation of the provisos and other class constraints
Constructors
| CPred | |
Fields
| |
Instances
| Show CPred Source # | |
| Eq CPred Source # | |
| Ord CPred Source # | |
| HasPosition CPred Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods getPosition :: CPred -> Position Source # | |
| Pretty CPred Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods pPrintPrec :: PrettyLevel -> Rational -> CPred -> Doc # pPrintList :: PrettyLevel -> [CPred] -> Doc # | |
Instances
| Show CQType Source # | |
| Eq CQType Source # | |
| Ord CQType Source # | |
| HasPosition CQType Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods getPosition :: CQType -> Position Source # | |
| Pretty CQType Source # | |
Defined in Language.Bluespec.Classic.AST.Type Methods pPrintPrec :: PrettyLevel -> Rational -> CQType -> Doc # pPrintList :: PrettyLevel -> [CQType] -> Doc # | |
isTConArrow :: TyCon -> Bool Source #
isTConPair :: TyCon -> Bool Source #