| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Types
Synopsis
- data Module = Module {
- name :: !ModuleName
- imports :: ![Import]
- declarationNames :: ![ModuleName]
- definitions :: ![TypeDefinition]
- sourceFile :: !FilePath
- newtype ModuleName = ModuleName Text
- newtype Import = Import Module
- newtype DefinitionName = DefinitionName {}
- data TypeDefinition = TypeDefinition !DefinitionName !TypeData
- data ImportedTypeDefinition = ImportedTypeDefinition {
- sourceModule :: !ModuleName
- name :: !DefinitionName
- typeData :: !TypeData
- newtype TypeTag = TypeTag Text
- newtype TypeVariable = TypeVariable Text
- newtype ConstructorName = ConstructorName Text
- newtype FieldName = FieldName Text
- newtype EnumerationIdentifier = EnumerationIdentifier Text
- data TagType
- data TypeData
- data EmbeddedConstructor = EmbeddedConstructor !ConstructorName !(Maybe DefinitionReference)
- data StructType
- = PlainStruct ![StructField]
- | GenericStruct ![TypeVariable] ![StructField]
- data UnionType
- = PlainUnion ![Constructor]
- | GenericUnion ![TypeVariable] ![Constructor]
- data Constructor = Constructor !ConstructorName !(Maybe FieldType)
- data StructField = StructField !FieldName !FieldType
- data EnumerationValue = EnumerationValue !EnumerationIdentifier !LiteralTypeValue
- data FieldType
- data DefinitionReference
- = DefinitionReference !TypeDefinition
- | ImportedDefinitionReference !ModuleName !TypeDefinition
- | AppliedGenericReference ![FieldType] !TypeDefinition
- | AppliedImportedGenericReference !ModuleName !AppliedTypes !TypeDefinition
- | DeclarationReference !ModuleName !DefinitionName
- | GenericDeclarationReference !ModuleName !DefinitionName !AppliedTypes
- newtype AppliedTypes = AppliedTypes [FieldType]
- data BasicTypeValue
- data ComplexTypeValue
- data LiteralTypeValue
Documentation
Constructors
| Module | |
Fields
| |
newtype ModuleName Source #
Constructors
| ModuleName Text |
Instances
| Eq ModuleName Source # | |
Defined in Types | |
| Ord ModuleName Source # | |
Defined in Types Methods compare :: ModuleName -> ModuleName -> Ordering # (<) :: ModuleName -> ModuleName -> Bool # (<=) :: ModuleName -> ModuleName -> Bool # (>) :: ModuleName -> ModuleName -> Bool # (>=) :: ModuleName -> ModuleName -> Bool # max :: ModuleName -> ModuleName -> ModuleName # min :: ModuleName -> ModuleName -> ModuleName # | |
| Show ModuleName Source # | |
Defined in Types Methods showsPrec :: Int -> ModuleName -> ShowS # show :: ModuleName -> String # showList :: [ModuleName] -> ShowS # | |
newtype DefinitionName Source #
Constructors
| DefinitionName | |
Fields | |
Instances
| Eq DefinitionName Source # | |
Defined in Types Methods (==) :: DefinitionName -> DefinitionName -> Bool # (/=) :: DefinitionName -> DefinitionName -> Bool # | |
| Show DefinitionName Source # | |
Defined in Types Methods showsPrec :: Int -> DefinitionName -> ShowS # show :: DefinitionName -> String # showList :: [DefinitionName] -> ShowS # | |
data TypeDefinition Source #
Constructors
| TypeDefinition !DefinitionName !TypeData |
Instances
| Eq TypeDefinition Source # | |
Defined in Types Methods (==) :: TypeDefinition -> TypeDefinition -> Bool # (/=) :: TypeDefinition -> TypeDefinition -> Bool # | |
| Show TypeDefinition Source # | |
Defined in Types Methods showsPrec :: Int -> TypeDefinition -> ShowS # show :: TypeDefinition -> String # showList :: [TypeDefinition] -> ShowS # | |
data ImportedTypeDefinition Source #
Constructors
| ImportedTypeDefinition | |
Fields
| |
Instances
| Eq ImportedTypeDefinition Source # | |
Defined in Types Methods (==) :: ImportedTypeDefinition -> ImportedTypeDefinition -> Bool # (/=) :: ImportedTypeDefinition -> ImportedTypeDefinition -> Bool # | |
| Show ImportedTypeDefinition Source # | |
Defined in Types Methods showsPrec :: Int -> ImportedTypeDefinition -> ShowS # show :: ImportedTypeDefinition -> String # showList :: [ImportedTypeDefinition] -> ShowS # | |
newtype TypeVariable Source #
Constructors
| TypeVariable Text |
Instances
| Eq TypeVariable Source # | |
Defined in Types | |
| Show TypeVariable Source # | |
Defined in Types Methods showsPrec :: Int -> TypeVariable -> ShowS # show :: TypeVariable -> String # showList :: [TypeVariable] -> ShowS # | |
newtype ConstructorName Source #
Constructors
| ConstructorName Text |
Instances
| Eq ConstructorName Source # | |
Defined in Types Methods (==) :: ConstructorName -> ConstructorName -> Bool # (/=) :: ConstructorName -> ConstructorName -> Bool # | |
| Show ConstructorName Source # | |
Defined in Types Methods showsPrec :: Int -> ConstructorName -> ShowS # show :: ConstructorName -> String # showList :: [ConstructorName] -> ShowS # | |
newtype EnumerationIdentifier Source #
Constructors
| EnumerationIdentifier Text |
Instances
| Eq EnumerationIdentifier Source # | |
Defined in Types Methods (==) :: EnumerationIdentifier -> EnumerationIdentifier -> Bool # (/=) :: EnumerationIdentifier -> EnumerationIdentifier -> Bool # | |
| Show EnumerationIdentifier Source # | |
Defined in Types Methods showsPrec :: Int -> EnumerationIdentifier -> ShowS # show :: EnumerationIdentifier -> String # showList :: [EnumerationIdentifier] -> ShowS # | |
Defines what type tag field a union should have as well as the type tag location.
Constructors
| EmbeddedTypeTag FieldName | The union has the type tag with the rest of the payload. |
| StandardTypeTag FieldName | The union has the type tag outside of the payload, wrapping it. |
Constructors
| Struct !StructType | |
| Union !FieldName !UnionType | |
| EmbeddedUnion !FieldName ![EmbeddedConstructor] | |
| UntaggedUnion ![FieldType] | |
| Enumeration ![EnumerationValue] | |
| DeclaredType !ModuleName ![TypeVariable] |
data EmbeddedConstructor Source #
Constructors
| EmbeddedConstructor !ConstructorName !(Maybe DefinitionReference) |
Instances
| Eq EmbeddedConstructor Source # | |
Defined in Types Methods (==) :: EmbeddedConstructor -> EmbeddedConstructor -> Bool # (/=) :: EmbeddedConstructor -> EmbeddedConstructor -> Bool # | |
| Show EmbeddedConstructor Source # | |
Defined in Types Methods showsPrec :: Int -> EmbeddedConstructor -> ShowS # show :: EmbeddedConstructor -> String # showList :: [EmbeddedConstructor] -> ShowS # | |
data StructType Source #
Constructors
| PlainStruct ![StructField] | |
| GenericStruct ![TypeVariable] ![StructField] |
Instances
| Eq StructType Source # | |
Defined in Types | |
| Show StructType Source # | |
Defined in Types Methods showsPrec :: Int -> StructType -> ShowS # show :: StructType -> String # showList :: [StructType] -> ShowS # | |
Constructors
| PlainUnion ![Constructor] | |
| GenericUnion ![TypeVariable] ![Constructor] |
data Constructor Source #
Constructors
| Constructor !ConstructorName !(Maybe FieldType) |
Instances
| Eq Constructor Source # | |
Defined in Types | |
| Show Constructor Source # | |
Defined in Types Methods showsPrec :: Int -> Constructor -> ShowS # show :: Constructor -> String # showList :: [Constructor] -> ShowS # | |
data StructField Source #
Constructors
| StructField !FieldName !FieldType |
Instances
| Eq StructField Source # | |
Defined in Types | |
| Show StructField Source # | |
Defined in Types Methods showsPrec :: Int -> StructField -> ShowS # show :: StructField -> String # showList :: [StructField] -> ShowS # | |
data EnumerationValue Source #
Constructors
| EnumerationValue !EnumerationIdentifier !LiteralTypeValue |
Instances
| Eq EnumerationValue Source # | |
Defined in Types Methods (==) :: EnumerationValue -> EnumerationValue -> Bool # (/=) :: EnumerationValue -> EnumerationValue -> Bool # | |
| Show EnumerationValue Source # | |
Defined in Types Methods showsPrec :: Int -> EnumerationValue -> ShowS # show :: EnumerationValue -> String # showList :: [EnumerationValue] -> ShowS # | |
data DefinitionReference Source #
Constructors
Instances
| Eq DefinitionReference Source # | |
Defined in Types Methods (==) :: DefinitionReference -> DefinitionReference -> Bool # (/=) :: DefinitionReference -> DefinitionReference -> Bool # | |
| Show DefinitionReference Source # | |
Defined in Types Methods showsPrec :: Int -> DefinitionReference -> ShowS # show :: DefinitionReference -> String # showList :: [DefinitionReference] -> ShowS # | |
newtype AppliedTypes Source #
Constructors
| AppliedTypes [FieldType] |
Instances
| Eq AppliedTypes Source # | |
Defined in Types | |
| Show AppliedTypes Source # | |
Defined in Types Methods showsPrec :: Int -> AppliedTypes -> ShowS # show :: AppliedTypes -> String # showList :: [AppliedTypes] -> ShowS # | |
data BasicTypeValue Source #
Instances
| Eq BasicTypeValue Source # | |
Defined in Types Methods (==) :: BasicTypeValue -> BasicTypeValue -> Bool # (/=) :: BasicTypeValue -> BasicTypeValue -> Bool # | |
| Show BasicTypeValue Source # | |
Defined in Types Methods showsPrec :: Int -> BasicTypeValue -> ShowS # show :: BasicTypeValue -> String # showList :: [BasicTypeValue] -> ShowS # | |
data ComplexTypeValue Source #
Constructors
| SliceType FieldType | |
| ArrayType Integer FieldType | |
| OptionalType FieldType | |
| PointerType FieldType |
Instances
| Eq ComplexTypeValue Source # | |
Defined in Types Methods (==) :: ComplexTypeValue -> ComplexTypeValue -> Bool # (/=) :: ComplexTypeValue -> ComplexTypeValue -> Bool # | |
| Show ComplexTypeValue Source # | |
Defined in Types Methods showsPrec :: Int -> ComplexTypeValue -> ShowS # show :: ComplexTypeValue -> String # showList :: [ComplexTypeValue] -> ShowS # | |
data LiteralTypeValue Source #
Constructors
| LiteralString !Text | |
| LiteralInteger !Integer | |
| LiteralFloat !Float | |
| LiteralBoolean !Bool |
Instances
| Eq LiteralTypeValue Source # | |
Defined in Types Methods (==) :: LiteralTypeValue -> LiteralTypeValue -> Bool # (/=) :: LiteralTypeValue -> LiteralTypeValue -> Bool # | |
| Show LiteralTypeValue Source # | |
Defined in Types Methods showsPrec :: Int -> LiteralTypeValue -> ShowS # show :: LiteralTypeValue -> String # showList :: [LiteralTypeValue] -> ShowS # | |