Safe Haskell | None |
---|---|
Language | Haskell98 |
Documentation
type T_Alternative = Alternative Source
type T_Alternatives = Alternatives Source
type T_AnnotatedType = AnnotatedType Source
type T_AnnotatedTypes = AnnotatedTypes Source
sem_Body_Hole :: T_Range -> Integer -> T_Body Source
sem_Body_Body :: T_Range -> T_ImportDeclarations -> T_Declarations -> T_Body Source
type T_Constructor = Constructor Source
sem_Constructor_Infix :: T_Range -> T_AnnotatedType -> T_Name -> T_AnnotatedType -> T_Constructor Source
type T_Constructors = Constructors Source
type T_ContextItem = ContextItem Source
sem_ContextItem_ContextItem :: T_Range -> T_Name -> T_Types -> T_ContextItem Source
type T_ContextItems = ContextItems Source
type T_Declaration = Declaration Source
sem_Declaration_Type :: T_Range -> T_SimpleType -> T_Type -> T_Declaration Source
sem_Declaration_Data :: T_Range -> T_ContextItems -> T_SimpleType -> T_Constructors -> T_Names -> T_Declaration Source
sem_Declaration_Newtype :: T_Range -> T_ContextItems -> T_SimpleType -> T_Constructor -> T_Names -> T_Declaration Source
sem_Declaration_Class :: T_Range -> T_ContextItems -> T_SimpleType -> T_MaybeDeclarations -> T_Declaration Source
sem_Declaration_Instance :: T_Range -> T_ContextItems -> T_Name -> T_Types -> T_MaybeDeclarations -> T_Declaration Source
sem_Declaration_TypeSignature :: T_Range -> T_Names -> T_Type -> T_Declaration Source
sem_Declaration_Fixity :: T_Range -> T_Fixity -> T_MaybeInt -> T_Names -> T_Declaration Source
type T_Declarations = Declarations Source
sem_Export :: Export -> T_Export Source
wrap_Export :: T_Export -> Inh_Export -> Syn_Export Source
sem_Export_Variable :: T_Range -> T_Name -> T_Export Source
sem_Export_TypeOrClass :: T_Range -> T_Name -> T_MaybeNames -> T_Export Source
sem_Export_Module :: T_Range -> T_Name -> T_Export Source
sem_Exports :: Exports -> T_Exports Source
wrap_Exports :: T_Exports -> Inh_Exports -> Syn_Exports Source
sem_Exports_Cons :: T_Export -> T_Exports -> T_Exports Source
type T_Expression = Expression Source
sem_Expression_Hole :: T_Range -> Integer -> T_Expression Source
sem_Expression_Feedback :: T_Range -> String -> T_Expression -> T_Expression Source
sem_Expression_InfixApplication :: T_Range -> T_MaybeExpression -> T_Expression -> T_MaybeExpression -> T_Expression Source
sem_Expression_If :: T_Range -> T_Expression -> T_Expression -> T_Expression -> T_Expression Source
sem_Expression_Lambda :: T_Range -> T_Patterns -> T_Expression -> T_Expression Source
sem_Expression_Typed :: T_Range -> T_Expression -> T_Type -> T_Expression Source
sem_Expression_RecordConstruction :: T_Range -> T_Name -> T_RecordExpressionBindings -> T_Expression Source
sem_Expression_RecordUpdate :: T_Range -> T_Expression -> T_RecordExpressionBindings -> T_Expression Source
sem_Expression_Enum :: T_Range -> T_Expression -> T_MaybeExpression -> T_MaybeExpression -> T_Expression Source
type T_Expressions = Expressions Source
sem_FieldDeclaration_FieldDeclaration :: T_Range -> T_Names -> T_AnnotatedType -> T_FieldDeclaration Source
wrap_FieldDeclarations :: T_FieldDeclarations -> Inh_FieldDeclarations -> Syn_FieldDeclarations Source
sem_FieldDeclarations_Cons :: T_FieldDeclaration -> T_FieldDeclarations -> T_FieldDeclarations Source
sem_Fixity :: Fixity -> T_Fixity Source
wrap_Fixity :: T_Fixity -> Inh_Fixity -> Syn_Fixity Source
sem_FunctionBinding_FunctionBinding :: T_Range -> T_LeftHandSide -> T_RightHandSide -> T_FunctionBinding Source
wrap_GuardedExpression :: T_GuardedExpression -> Inh_GuardedExpression -> Syn_GuardedExpression Source
sem_GuardedExpression_GuardedExpression :: T_Range -> T_Expression -> T_Expression -> T_GuardedExpression Source
wrap_GuardedExpressions :: T_GuardedExpressions -> Inh_GuardedExpressions -> Syn_GuardedExpressions Source
sem_GuardedExpressions_Cons :: T_GuardedExpression -> T_GuardedExpressions -> T_GuardedExpressions Source
sem_Import :: Import -> T_Import Source
wrap_Import :: T_Import -> Inh_Import -> Syn_Import Source
sem_Import_Variable :: T_Range -> T_Name -> T_Import Source
sem_Import_TypeOrClass :: T_Range -> T_Name -> T_MaybeNames -> T_Import Source
wrap_ImportDeclaration :: T_ImportDeclaration -> Inh_ImportDeclaration -> Syn_ImportDeclaration Source
sem_ImportDeclaration_Import :: T_Range -> Bool -> T_Name -> T_MaybeName -> T_MaybeImportSpecification -> T_ImportDeclaration Source
wrap_ImportDeclarations :: T_ImportDeclarations -> Inh_ImportDeclarations -> Syn_ImportDeclarations Source
sem_ImportDeclarations_Cons :: T_ImportDeclaration -> T_ImportDeclarations -> T_ImportDeclarations Source
wrap_ImportSpecification :: T_ImportSpecification -> Inh_ImportSpecification -> Syn_ImportSpecification Source
sem_Imports :: Imports -> T_Imports Source
wrap_Imports :: T_Imports -> Inh_Imports -> Syn_Imports Source
sem_Imports_Cons :: T_Import -> T_Imports -> T_Imports Source
type T_Judgement = [(Name, Tp)] -> (Tp, Core_Judgement, Judgement, Expression, Names) Source
data Inh_Judgement Source
Inh_Judgement | |
|
data Syn_Judgement Source
type T_LeftHandSide = LeftHandSide Source
sem_LeftHandSide_Function :: T_Range -> T_Name -> T_Patterns -> T_LeftHandSide Source
sem_LeftHandSide_Infix :: T_Range -> T_Pattern -> T_Name -> T_Pattern -> T_LeftHandSide Source
sem_Literal :: Literal -> T_Literal Source
wrap_Literal :: T_Literal -> Inh_Literal -> Syn_Literal Source
sem_Literal_Int :: T_Range -> String -> T_Literal Source
sem_Literal_Char :: T_Range -> String -> T_Literal Source
sem_Literal_Float :: T_Range -> String -> T_Literal Source
sem_Literal_String :: T_Range -> String -> T_Literal Source
wrap_MaybeDeclarations :: T_MaybeDeclarations -> Inh_MaybeDeclarations -> Syn_MaybeDeclarations Source
type T_MaybeExports = MaybeExports Source
wrap_MaybeImportSpecification :: T_MaybeImportSpecification -> Inh_MaybeImportSpecification -> Syn_MaybeImportSpecification Source
sem_MaybeInt :: MaybeInt -> T_MaybeInt Source
type T_MaybeInt = MaybeInt Source
sem_MaybeInt_Just :: Int -> T_MaybeInt Source
type T_MaybeName = MaybeName Source
type T_MaybeNames = MaybeNames Source
sem_Module :: Module -> T_Module Source
wrap_Module :: T_Module -> Inh_Module -> Syn_Module Source
sem_Module_Module :: T_Range -> T_MaybeName -> T_MaybeExports -> T_Body -> T_Module Source
wrap_Names :: T_Names -> Inh_Names -> Syn_Names Source
sem_Names_Cons :: T_Name -> T_Names -> T_Names Source
sem_Pattern :: Pattern -> T_Pattern Source
wrap_Pattern :: T_Pattern -> Inh_Pattern -> Syn_Pattern Source
sem_Pattern_Hole :: T_Range -> Integer -> T_Pattern Source
sem_Pattern_Literal :: T_Range -> T_Literal -> T_Pattern Source
sem_Pattern_Variable :: T_Range -> T_Name -> T_Pattern Source
sem_Pattern_Constructor :: T_Range -> T_Name -> T_Patterns -> T_Pattern Source
sem_Pattern_List :: T_Range -> T_Patterns -> T_Pattern Source
sem_Pattern_Tuple :: T_Range -> T_Patterns -> T_Pattern Source
sem_Pattern_Negate :: T_Range -> T_Literal -> T_Pattern Source
sem_Patterns :: Patterns -> T_Patterns Source
type T_Patterns = Patterns Source
sem_Patterns_Cons :: T_Pattern -> T_Patterns -> T_Patterns Source
sem_Position :: Position -> T_Position Source
type T_Position = Position Source
sem_Position_Position :: String -> Int -> Int -> T_Position Source
type T_Qualifier = Qualifier Source
sem_Qualifier_Generator :: T_Range -> T_Pattern -> T_Expression -> T_Qualifier Source
type T_Qualifiers = Qualifiers Source
wrap_Range :: T_Range -> Inh_Range -> Syn_Range Source
sem_Range_Range :: T_Position -> T_Position -> T_Range Source
wrap_RecordExpressionBinding :: T_RecordExpressionBinding -> Inh_RecordExpressionBinding -> Syn_RecordExpressionBinding Source
sem_RecordExpressionBinding_RecordExpressionBinding :: T_Range -> T_Name -> T_Expression -> T_RecordExpressionBinding Source
wrap_RecordExpressionBindings :: T_RecordExpressionBindings -> Inh_RecordExpressionBindings -> Syn_RecordExpressionBindings Source
sem_RecordExpressionBindings_Cons :: T_RecordExpressionBinding -> T_RecordExpressionBindings -> T_RecordExpressionBindings Source
wrap_RecordPatternBinding :: T_RecordPatternBinding -> Inh_RecordPatternBinding -> Syn_RecordPatternBinding Source
sem_RecordPatternBinding_RecordPatternBinding :: T_Range -> T_Name -> T_Pattern -> T_RecordPatternBinding Source
wrap_RecordPatternBindings :: T_RecordPatternBindings -> Inh_RecordPatternBindings -> Syn_RecordPatternBindings Source
sem_RecordPatternBindings_Cons :: T_RecordPatternBinding -> T_RecordPatternBindings -> T_RecordPatternBindings Source
type T_RightHandSide = RightHandSide Source
sem_RightHandSide_Expression :: T_Range -> T_Expression -> T_MaybeDeclarations -> T_RightHandSide Source
sem_RightHandSide_Guarded :: T_Range -> T_GuardedExpressions -> T_MaybeDeclarations -> T_RightHandSide Source
type T_SimpleJudgement = [(Name, Tp)] -> [(String, Tp)] -> (Core_Judgement, SimpleJudgement, [(String, Tp)], Names) Source
type T_SimpleJudgements = [(Name, Tp)] -> [(String, Tp)] -> (Core_Judgements, SimpleJudgements, [(String, Tp)], Names) Source
type T_SimpleType = SimpleType Source
sem_SimpleType_SimpleType :: T_Range -> T_Name -> T_Names -> T_SimpleType Source
type T_Statement = Statement Source
sem_Statement_Generator :: T_Range -> T_Pattern -> T_Expression -> T_Statement Source
type T_Statements = Statements Source
sem_Strings :: Strings -> T_Strings Source
wrap_Strings :: T_Strings -> Inh_Strings -> Syn_Strings Source
sem_Strings_Cons :: String -> T_Strings -> T_Strings Source
sem_Type_Variable :: T_Range -> T_Name -> T_Type Source
sem_Type_Constructor :: T_Range -> T_Name -> T_Type Source
sem_Type_Qualified :: T_Range -> T_ContextItems -> T_Type -> T_Type Source
sem_Type_Parenthesized :: T_Range -> T_Type -> T_Type Source
sem_TypeRule :: TypeRule -> T_TypeRule Source
type T_TypeRule = [(Name, Tp)] -> [(String, Tp)] -> (Expression, Tp, Core_TypeRule, TypeRule, [(String, Tp)], Names) Source
data Inh_TypeRule Source
Inh_TypeRule | |
|
data Syn_TypeRule Source
wrap_Types :: T_Types -> Inh_Types -> Syn_Types Source
sem_Types_Cons :: T_Type -> T_Types -> T_Types Source
data Inh_TypingStrategy Source
data Syn_TypingStrategy Source
type T_UserStatement = [((String, Maybe String), MessageBlock)] -> Names -> [(Name, Tp)] -> ConstraintInfo -> TypeConstraints ConstraintInfo -> Predicates -> (Core_UserStatement, Names, UserStatement, Names, TypeConstraints ConstraintInfo, Predicates) Source
data Inh_UserStatement Source
sem_UserStatement_Equal :: T_Type -> T_Type -> String -> T_UserStatement Source
sem_UserStatement_Pred :: T_Name -> T_Type -> String -> T_UserStatement Source
type T_UserStatements = [((String, Maybe String), MessageBlock)] -> Names -> [(Name, Tp)] -> ConstraintInfo -> TypeConstraints ConstraintInfo -> Predicates -> (Core_UserStatements, Names, UserStatements, Names, TypeConstraints ConstraintInfo, Predicates) Source
data Inh_UserStatements Source
data Syn_UserStatements Source