module Helium.Syntax.UHA_Syntax where
data Alternative = Alternative_Hole (Range) (Integer)
| Alternative_Feedback (Range) (String) (Alternative)
| Alternative_Alternative (Range) (Pattern) (RightHandSide)
| Alternative_Empty (Range)
type Alternatives = [Alternative]
data AnnotatedType = AnnotatedType_AnnotatedType (Range) (Bool) (Type)
type AnnotatedTypes = [AnnotatedType]
data Body = Body_Hole (Range) (Integer)
| Body_Body (Range) (ImportDeclarations) (Declarations)
data Constructor = Constructor_Constructor (Range) (Name) (AnnotatedTypes)
| Constructor_Infix (Range) (AnnotatedType) (Name) (AnnotatedType)
| Constructor_Record (Range) (Name) (FieldDeclarations)
type Constructors = [Constructor]
data ContextItem = ContextItem_ContextItem (Range) (Name) (Types)
type ContextItems = [ContextItem]
data Declaration = Declaration_Hole (Range) (Integer)
| Declaration_Type (Range) (SimpleType) (Type)
| Declaration_Data (Range) (ContextItems) (SimpleType) (Constructors) (Names)
| Declaration_Newtype (Range) (ContextItems) (SimpleType) (Constructor) (Names)
| Declaration_Class (Range) (ContextItems) (SimpleType) (MaybeDeclarations)
| Declaration_Instance (Range) (ContextItems) (Name) (Types) (MaybeDeclarations)
| Declaration_Default (Range) (Types)
| Declaration_FunctionBindings (Range) (FunctionBindings)
| Declaration_PatternBinding (Range) (Pattern) (RightHandSide)
| Declaration_TypeSignature (Range) (Names) (Type)
| Declaration_Fixity (Range) (Fixity) (MaybeInt) (Names)
| Declaration_Empty (Range)
type Declarations = [Declaration]
data Export = Export_Variable (Range) (Name)
| Export_TypeOrClass (Range) (Name) (MaybeNames)
| Export_TypeOrClassComplete (Range) (Name)
| Export_Module (Range) (Name)
type Exports = [Export]
data Expression = Expression_Hole (Range) (Integer)
| Expression_Feedback (Range) (String) (Expression)
| Expression_MustUse (Range) (Expression)
| Expression_Literal (Range) (Literal)
| Expression_Variable (Range) (Name)
| Expression_Constructor (Range) (Name)
| Expression_Parenthesized (Range) (Expression)
| Expression_NormalApplication (Range) (Expression) (Expressions)
| Expression_InfixApplication (Range) (MaybeExpression) (Expression) (MaybeExpression)
| Expression_If (Range) (Expression) (Expression) (Expression)
| Expression_Lambda (Range) (Patterns) (Expression)
| Expression_Case (Range) (Expression) (Alternatives)
| Expression_Let (Range) (Declarations) (Expression)
| Expression_Do (Range) (Statements)
| Expression_List (Range) (Expressions)
| Expression_Tuple (Range) (Expressions)
| Expression_Comprehension (Range) (Expression) (Qualifiers)
| Expression_Typed (Range) (Expression) (Type)
| Expression_RecordConstruction (Range) (Name) (RecordExpressionBindings)
| Expression_RecordUpdate (Range) (Expression) (RecordExpressionBindings)
| Expression_Enum (Range) (Expression) (MaybeExpression) (MaybeExpression)
| Expression_Negate (Range) (Expression)
| Expression_NegateFloat (Range) (Expression)
type Expressions = [Expression]
data FieldDeclaration = FieldDeclaration_FieldDeclaration (Range) (Names) (AnnotatedType)
type FieldDeclarations = [FieldDeclaration]
data Fixity = Fixity_Infixl (Range)
| Fixity_Infixr (Range)
| Fixity_Infix (Range)
data FunctionBinding = FunctionBinding_Hole (Range) (Integer)
| FunctionBinding_Feedback (Range) (String) (FunctionBinding)
| FunctionBinding_FunctionBinding (Range) (LeftHandSide) (RightHandSide)
type FunctionBindings = [FunctionBinding]
data GuardedExpression = GuardedExpression_GuardedExpression (Range) (Expression) (Expression)
type GuardedExpressions = [GuardedExpression]
data Import = Import_Variable (Range) (Name)
| Import_TypeOrClass (Range) (Name) (MaybeNames)
| Import_TypeOrClassComplete (Range) (Name)
data ImportDeclaration = ImportDeclaration_Import (Range) (Bool) (Name) (MaybeName) (MaybeImportSpecification)
| ImportDeclaration_Empty (Range)
type ImportDeclarations = [ImportDeclaration]
data ImportSpecification = ImportSpecification_Import (Range) (Bool) (Imports)
type Imports = [Import]
data LeftHandSide = LeftHandSide_Function (Range) (Name) (Patterns)
| LeftHandSide_Infix (Range) (Pattern) (Name) (Pattern)
| LeftHandSide_Parenthesized (Range) (LeftHandSide) (Patterns)
data Literal = Literal_Int (Range) (String)
| Literal_Char (Range) (String)
| Literal_Float (Range) (String)
| Literal_String (Range) (String)
data MaybeDeclarations = MaybeDeclarations_Nothing
| MaybeDeclarations_Just (Declarations)
data MaybeExports = MaybeExports_Nothing
| MaybeExports_Just (Exports)
data MaybeExpression = MaybeExpression_Nothing
| MaybeExpression_Just (Expression)
data MaybeImportSpecification = MaybeImportSpecification_Nothing
| MaybeImportSpecification_Just (ImportSpecification)
data MaybeInt = MaybeInt_Nothing
| MaybeInt_Just (Int)
data MaybeName = MaybeName_Nothing
| MaybeName_Just (Name)
data MaybeNames = MaybeNames_Nothing
| MaybeNames_Just (Names)
data Module = Module_Module (Range) (MaybeName) (MaybeExports) (Body)
data Name = Name_Identifier (Range) (Strings) (String)
| Name_Operator (Range) (Strings) (String)
| Name_Special (Range) (Strings) (String)
type Names = [Name]
data Pattern = Pattern_Hole (Range) (Integer)
| Pattern_Literal (Range) (Literal)
| Pattern_Variable (Range) (Name)
| Pattern_Constructor (Range) (Name) (Patterns)
| Pattern_Parenthesized (Range) (Pattern)
| Pattern_InfixConstructor (Range) (Pattern) (Name) (Pattern)
| Pattern_List (Range) (Patterns)
| Pattern_Tuple (Range) (Patterns)
| Pattern_Record (Range) (Name) (RecordPatternBindings)
| Pattern_Negate (Range) (Literal)
| Pattern_As (Range) (Name) (Pattern)
| Pattern_Wildcard (Range)
| Pattern_Irrefutable (Range) (Pattern)
| Pattern_Successor (Range) (Name) (Literal)
| Pattern_NegateFloat (Range) (Literal)
type Patterns = [Pattern]
data Position = Position_Position (String) (Int) (Int)
| Position_Unknown
data Qualifier = Qualifier_Guard (Range) (Expression)
| Qualifier_Let (Range) (Declarations)
| Qualifier_Generator (Range) (Pattern) (Expression)
| Qualifier_Empty (Range)
type Qualifiers = [Qualifier]
data Range = Range_Range (Position) (Position)
data RecordExpressionBinding = RecordExpressionBinding_RecordExpressionBinding (Range) (Name) (Expression)
type RecordExpressionBindings = [RecordExpressionBinding]
data RecordPatternBinding = RecordPatternBinding_RecordPatternBinding (Range) (Name) (Pattern)
type RecordPatternBindings = [RecordPatternBinding]
data RightHandSide = RightHandSide_Expression (Range) (Expression) (MaybeDeclarations)
| RightHandSide_Guarded (Range) (GuardedExpressions) (MaybeDeclarations)
data SimpleType = SimpleType_SimpleType (Range) (Name) (Names)
data Statement = Statement_Expression (Range) (Expression)
| Statement_Let (Range) (Declarations)
| Statement_Generator (Range) (Pattern) (Expression)
| Statement_Empty (Range)
type Statements = [Statement]
type Strings = [(String)]
data Type = Type_Application (Range) (Bool) (Type) (Types)
| Type_Variable (Range) (Name)
| Type_Constructor (Range) (Name)
| Type_Qualified (Range) (ContextItems) (Type)
| Type_Forall (Range) (Names) (Type)
| Type_Exists (Range) (Names) (Type)
| Type_Parenthesized (Range) (Type)
type Types = [Type]