Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A Haskell syntax model, loosely based on Language.Haskell.Tools.AST
Synopsis
- data Alternative = Alternative {}
- _Alternative :: Name
- _Alternative_pattern :: FieldName
- _Alternative_rhs :: FieldName
- _Alternative_binds :: FieldName
- data Assertion = Assertion {
- assertionName :: Name
- assertionTypes :: [Type]
- _Assertion :: Name
- _Assertion_name :: FieldName
- _Assertion_types :: FieldName
- newtype CaseRhs = CaseRhs {}
- _CaseRhs :: Name
- data Constructor
- _Constructor :: Name
- _Constructor_ordinary :: FieldName
- _Constructor_record :: FieldName
- data Constructor_Ordinary = Constructor_Ordinary {}
- _Constructor_Ordinary :: Name
- _Constructor_Ordinary_name :: FieldName
- _Constructor_Ordinary_fields :: FieldName
- data Constructor_Record = Constructor_Record {}
- _Constructor_Record :: Name
- _Constructor_Record_name :: FieldName
- _Constructor_Record_fields :: FieldName
- data ConstructorWithComments = ConstructorWithComments {}
- _ConstructorWithComments :: Name
- _ConstructorWithComments_body :: FieldName
- _ConstructorWithComments_comments :: FieldName
- data DataDeclaration = DataDeclaration {}
- _DataDeclaration :: Name
- _DataDeclaration_keyword :: FieldName
- _DataDeclaration_context :: FieldName
- _DataDeclaration_head :: FieldName
- _DataDeclaration_constructors :: FieldName
- _DataDeclaration_deriving :: FieldName
- data DataDeclaration_Keyword
- _DataDeclaration_Keyword :: Name
- _DataDeclaration_Keyword_data :: FieldName
- _DataDeclaration_Keyword_newtype :: FieldName
- data DeclarationWithComments = DeclarationWithComments {}
- _DeclarationWithComments :: Name
- _DeclarationWithComments_body :: FieldName
- _DeclarationWithComments_comments :: FieldName
- data Declaration
- _Declaration :: Name
- _Declaration_data :: FieldName
- _Declaration_type :: FieldName
- _Declaration_valueBinding :: FieldName
- _Declaration_typedBinding :: FieldName
- data DeclarationHead
- _DeclarationHead :: Name
- _DeclarationHead_application :: FieldName
- _DeclarationHead_parens :: FieldName
- _DeclarationHead_simple :: FieldName
- data DeclarationHead_Application = DeclarationHead_Application {}
- _DeclarationHead_Application :: Name
- _DeclarationHead_Application_function :: FieldName
- _DeclarationHead_Application_operand :: FieldName
- newtype Deriving = Deriving {
- unDeriving :: [Name]
- _Deriving :: Name
- data Export
- _Export :: Name
- _Export_declaration :: FieldName
- _Export_module :: FieldName
- data Expression
- = ExpressionApplication Expression_Application
- | ExpressionCase Expression_Case
- | ExpressionConstructRecord Expression_ConstructRecord
- | ExpressionDo [Statement]
- | ExpressionIf Expression_If
- | ExpressionInfixApplication Expression_InfixApplication
- | ExpressionLiteral Literal
- | ExpressionLambda Expression_Lambda
- | ExpressionLeftSection Expression_Section
- | ExpressionLet Expression_Let
- | ExpressionList [Expression]
- | ExpressionParens Expression
- | ExpressionPrefixApplication Expression_PrefixApplication
- | ExpressionRightSection Expression_Section
- | ExpressionTuple [Expression]
- | ExpressionTypeSignature Expression_TypeSignature
- | ExpressionUpdateRecord Expression_UpdateRecord
- | ExpressionVariable Name
- _Expression :: Name
- _Expression_application :: FieldName
- _Expression_case :: FieldName
- _Expression_constructRecord :: FieldName
- _Expression_do :: FieldName
- _Expression_if :: FieldName
- _Expression_infixApplication :: FieldName
- _Expression_literal :: FieldName
- _Expression_lambda :: FieldName
- _Expression_leftSection :: FieldName
- _Expression_let :: FieldName
- _Expression_list :: FieldName
- _Expression_parens :: FieldName
- _Expression_prefixApplication :: FieldName
- _Expression_rightSection :: FieldName
- _Expression_tuple :: FieldName
- _Expression_typeSignature :: FieldName
- _Expression_updateRecord :: FieldName
- _Expression_variable :: FieldName
- data Expression_Application = Expression_Application {}
- _Expression_Application :: Name
- _Expression_Application_function :: FieldName
- _Expression_Application_argument :: FieldName
- data Expression_Case = Expression_Case {}
- _Expression_Case :: Name
- _Expression_Case_case :: FieldName
- _Expression_Case_alternatives :: FieldName
- data Expression_ConstructRecord = Expression_ConstructRecord {}
- _Expression_ConstructRecord :: Name
- _Expression_ConstructRecord_name :: FieldName
- _Expression_ConstructRecord_fields :: FieldName
- data Expression_If = Expression_If {}
- _Expression_If :: Name
- _Expression_If_condition :: FieldName
- _Expression_If_then :: FieldName
- _Expression_If_else :: FieldName
- data Expression_InfixApplication = Expression_InfixApplication {}
- _Expression_InfixApplication :: Name
- _Expression_InfixApplication_lhs :: FieldName
- _Expression_InfixApplication_operator :: FieldName
- _Expression_InfixApplication_rhs :: FieldName
- data Expression_Lambda = Expression_Lambda {}
- _Expression_Lambda :: Name
- _Expression_Lambda_bindings :: FieldName
- _Expression_Lambda_inner :: FieldName
- data Expression_Let = Expression_Let {}
- _Expression_Let :: Name
- _Expression_Let_bindings :: FieldName
- _Expression_Let_inner :: FieldName
- data Expression_PrefixApplication = Expression_PrefixApplication {}
- _Expression_PrefixApplication :: Name
- _Expression_PrefixApplication_operator :: FieldName
- _Expression_PrefixApplication_rhs :: FieldName
- data Expression_Section = Expression_Section {}
- _Expression_Section :: Name
- _Expression_Section_operator :: FieldName
- _Expression_Section_expression :: FieldName
- data Expression_TypeSignature = Expression_TypeSignature {}
- _Expression_TypeSignature :: Name
- _Expression_TypeSignature_inner :: FieldName
- _Expression_TypeSignature_type :: FieldName
- data Expression_UpdateRecord = Expression_UpdateRecord {}
- _Expression_UpdateRecord :: Name
- _Expression_UpdateRecord_inner :: FieldName
- _Expression_UpdateRecord_fields :: FieldName
- data Field = Field {}
- _Field :: Name
- _Field_name :: FieldName
- _Field_type :: FieldName
- data FieldWithComments = FieldWithComments {}
- _FieldWithComments :: Name
- _FieldWithComments_field :: FieldName
- _FieldWithComments_comments :: FieldName
- data FieldUpdate = FieldUpdate {}
- _FieldUpdate :: Name
- _FieldUpdate_name :: FieldName
- _FieldUpdate_value :: FieldName
- data Import = Import {}
- _Import :: Name
- _Import_qualified :: FieldName
- _Import_module :: FieldName
- _Import_as :: FieldName
- _Import_spec :: FieldName
- data Import_Spec
- _Import_Spec :: Name
- _Import_Spec_list :: FieldName
- _Import_Spec_hiding :: FieldName
- data ImportModifier
- _ImportModifier :: Name
- _ImportModifier_pattern :: FieldName
- _ImportModifier_type :: FieldName
- data ImportExportSpec = ImportExportSpec {}
- _ImportExportSpec :: Name
- _ImportExportSpec_modifier :: FieldName
- _ImportExportSpec_name :: FieldName
- _ImportExportSpec_subspec :: FieldName
- data ImportExportSpec_Subspec
- _ImportExportSpec_Subspec :: Name
- _ImportExportSpec_Subspec_all :: FieldName
- _ImportExportSpec_Subspec_list :: FieldName
- data Literal
- _Literal :: Name
- _Literal_char :: FieldName
- _Literal_double :: FieldName
- _Literal_float :: FieldName
- _Literal_int :: FieldName
- _Literal_integer :: FieldName
- _Literal_string :: FieldName
- data LocalBinding
- _LocalBinding :: Name
- _LocalBinding_signature :: FieldName
- _LocalBinding_value :: FieldName
- newtype LocalBindings = LocalBindings {}
- _LocalBindings :: Name
- data Module = Module {}
- _Module :: Name
- _Module_head :: FieldName
- _Module_imports :: FieldName
- _Module_declarations :: FieldName
- data ModuleHead = ModuleHead {}
- _ModuleHead :: Name
- _ModuleHead_comments :: FieldName
- _ModuleHead_name :: FieldName
- _ModuleHead_exports :: FieldName
- newtype ModuleName = ModuleName {}
- _ModuleName :: Name
- data Name
- _Name :: Name
- _Name_implicit :: FieldName
- _Name_normal :: FieldName
- _Name_parens :: FieldName
- newtype NamePart = NamePart {
- unNamePart :: String
- _NamePart :: Name
- data Operator
- _Operator :: Name
- _Operator_backtick :: FieldName
- _Operator_normal :: FieldName
- data Pattern
- _Pattern :: Name
- _Pattern_application :: FieldName
- _Pattern_as :: FieldName
- _Pattern_list :: FieldName
- _Pattern_literal :: FieldName
- _Pattern_name :: FieldName
- _Pattern_parens :: FieldName
- _Pattern_record :: FieldName
- _Pattern_tuple :: FieldName
- _Pattern_typed :: FieldName
- _Pattern_wildcard :: FieldName
- data Pattern_Application = Pattern_Application {}
- _Pattern_Application :: Name
- _Pattern_Application_name :: FieldName
- _Pattern_Application_args :: FieldName
- data Pattern_As = Pattern_As {}
- _Pattern_As :: Name
- _Pattern_As_name :: FieldName
- _Pattern_As_inner :: FieldName
- data Pattern_Record = Pattern_Record {}
- _Pattern_Record :: Name
- _Pattern_Record_name :: FieldName
- _Pattern_Record_fields :: FieldName
- data Pattern_Typed = Pattern_Typed {}
- _Pattern_Typed :: Name
- _Pattern_Typed_inner :: FieldName
- _Pattern_Typed_type :: FieldName
- data PatternField = PatternField {}
- _PatternField :: Name
- _PatternField_name :: FieldName
- _PatternField_pattern :: FieldName
- data QualifiedName = QualifiedName {}
- _QualifiedName :: Name
- _QualifiedName_qualifiers :: FieldName
- _QualifiedName_unqualified :: FieldName
- newtype RightHandSide = RightHandSide {}
- _RightHandSide :: Name
- newtype Statement = Statement {}
- _Statement :: Name
- data Type
- _Type :: Name
- _Type_application :: FieldName
- _Type_function :: FieldName
- _Type_infix :: FieldName
- _Type_list :: FieldName
- _Type_parens :: FieldName
- _Type_tuple :: FieldName
- _Type_variable :: FieldName
- data Type_Application = Type_Application {}
- _Type_Application :: Name
- _Type_Application_context :: FieldName
- _Type_Application_argument :: FieldName
- data Type_Function = Type_Function {}
- _Type_Function :: Name
- _Type_Function_domain :: FieldName
- _Type_Function_codomain :: FieldName
- data Type_Infix = Type_Infix {}
- _Type_Infix :: Name
- _Type_Infix_lhs :: FieldName
- _Type_Infix_operator :: FieldName
- _Type_Infix_rhs :: FieldName
- data TypeDeclaration = TypeDeclaration {}
- _TypeDeclaration :: Name
- _TypeDeclaration_name :: FieldName
- _TypeDeclaration_type :: FieldName
- data TypeSignature = TypeSignature {}
- _TypeSignature :: Name
- _TypeSignature_name :: FieldName
- _TypeSignature_type :: FieldName
- data TypedBinding = TypedBinding {}
- _TypedBinding :: Name
- _TypedBinding_typeSignature :: FieldName
- _TypedBinding_valueBinding :: FieldName
- data ValueBinding = ValueBindingSimple ValueBinding_Simple
- _ValueBinding :: Name
- _ValueBinding_simple :: FieldName
- data ValueBinding_Simple = ValueBinding_Simple {}
- _ValueBinding_Simple :: Name
- _ValueBinding_Simple_pattern :: FieldName
- _ValueBinding_Simple_rhs :: FieldName
- _ValueBinding_Simple_localBindings :: FieldName
- newtype Variable = Variable {
- unVariable :: Name
- _Variable :: Name
Documentation
data Alternative Source #
A pattern-matching alternative
Instances
_Alternative :: Name Source #
A type assertion
Assertion | |
|
_Assertion :: Name Source #
The right-hand side of a pattern-matching alternative
CaseRhs | |
|
data Constructor Source #
A data constructor
Instances
_Constructor :: Name Source #
data Constructor_Ordinary Source #
An ordinary (positional) data constructor
Instances
data Constructor_Record Source #
A record-style data constructor
Instances
Read Constructor_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show Constructor_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Constructor_Record -> ShowS # show :: Constructor_Record -> String # showList :: [Constructor_Record] -> ShowS # | |
Eq Constructor_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Constructor_Record -> Constructor_Record -> Bool # (/=) :: Constructor_Record -> Constructor_Record -> Bool # | |
Ord Constructor_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Constructor_Record -> Constructor_Record -> Ordering # (<) :: Constructor_Record -> Constructor_Record -> Bool # (<=) :: Constructor_Record -> Constructor_Record -> Bool # (>) :: Constructor_Record -> Constructor_Record -> Bool # (>=) :: Constructor_Record -> Constructor_Record -> Bool # max :: Constructor_Record -> Constructor_Record -> Constructor_Record # min :: Constructor_Record -> Constructor_Record -> Constructor_Record # |
data ConstructorWithComments Source #
A data constructor together with any comments
Instances
data DataDeclaration Source #
A data type declaration
Instances
Read DataDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show DataDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> DataDeclaration -> ShowS # show :: DataDeclaration -> String # showList :: [DataDeclaration] -> ShowS # | |
Eq DataDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: DataDeclaration -> DataDeclaration -> Bool # (/=) :: DataDeclaration -> DataDeclaration -> Bool # | |
Ord DataDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: DataDeclaration -> DataDeclaration -> Ordering # (<) :: DataDeclaration -> DataDeclaration -> Bool # (<=) :: DataDeclaration -> DataDeclaration -> Bool # (>) :: DataDeclaration -> DataDeclaration -> Bool # (>=) :: DataDeclaration -> DataDeclaration -> Bool # max :: DataDeclaration -> DataDeclaration -> DataDeclaration # min :: DataDeclaration -> DataDeclaration -> DataDeclaration # |
data DataDeclaration_Keyword Source #
The 'data' versus 'newtype keyword
Instances
data DeclarationWithComments Source #
A data declaration together with any comments
Instances
data Declaration Source #
A data or value declaration
DeclarationData DataDeclaration | |
DeclarationType TypeDeclaration | |
DeclarationValueBinding ValueBinding | |
DeclarationTypedBinding TypedBinding |
Instances
_Declaration :: Name Source #
data DeclarationHead Source #
The left-hand side of a declaration
DeclarationHeadApplication DeclarationHead_Application | |
DeclarationHeadParens DeclarationHead | |
DeclarationHeadSimple Name |
Instances
Read DeclarationHead Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show DeclarationHead Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> DeclarationHead -> ShowS # show :: DeclarationHead -> String # showList :: [DeclarationHead] -> ShowS # | |
Eq DeclarationHead Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: DeclarationHead -> DeclarationHead -> Bool # (/=) :: DeclarationHead -> DeclarationHead -> Bool # | |
Ord DeclarationHead Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: DeclarationHead -> DeclarationHead -> Ordering # (<) :: DeclarationHead -> DeclarationHead -> Bool # (<=) :: DeclarationHead -> DeclarationHead -> Bool # (>) :: DeclarationHead -> DeclarationHead -> Bool # (>=) :: DeclarationHead -> DeclarationHead -> Bool # max :: DeclarationHead -> DeclarationHead -> DeclarationHead # min :: DeclarationHead -> DeclarationHead -> DeclarationHead # | |
ToTree DeclarationHead Source # | |
Defined in Hydra.Ext.Haskell.Serde toTree :: DeclarationHead -> Expr Source # |
data DeclarationHead_Application Source #
An application-style declaration head
Instances
A 'deriving' statement
Deriving | |
|
An export statement
data Expression Source #
A data expression
Instances
Read Expression Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Expression # readList :: ReadS [Expression] # readPrec :: ReadPrec Expression # readListPrec :: ReadPrec [Expression] # | |
Show Expression Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
Eq Expression Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Expression -> Expression -> Bool # (/=) :: Expression -> Expression -> Bool # | |
Ord Expression Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Expression -> Expression -> Ordering # (<) :: Expression -> Expression -> Bool # (<=) :: Expression -> Expression -> Bool # (>) :: Expression -> Expression -> Bool # (>=) :: Expression -> Expression -> Bool # max :: Expression -> Expression -> Expression # min :: Expression -> Expression -> Expression # | |
ToTree Expression Source # | |
Defined in Hydra.Ext.Haskell.Serde toTree :: Expression -> Expr Source # |
_Expression :: Name Source #
data Expression_Application Source #
An application expression
Instances
data Expression_Case Source #
A case expression
Instances
Read Expression_Case Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show Expression_Case Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Expression_Case -> ShowS # show :: Expression_Case -> String # showList :: [Expression_Case] -> ShowS # | |
Eq Expression_Case Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Expression_Case -> Expression_Case -> Bool # (/=) :: Expression_Case -> Expression_Case -> Bool # | |
Ord Expression_Case Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Expression_Case -> Expression_Case -> Ordering # (<) :: Expression_Case -> Expression_Case -> Bool # (<=) :: Expression_Case -> Expression_Case -> Bool # (>) :: Expression_Case -> Expression_Case -> Bool # (>=) :: Expression_Case -> Expression_Case -> Bool # max :: Expression_Case -> Expression_Case -> Expression_Case # min :: Expression_Case -> Expression_Case -> Expression_Case # | |
ToTree Expression_Case Source # | |
Defined in Hydra.Ext.Haskell.Serde toTree :: Expression_Case -> Expr Source # |
data Expression_ConstructRecord Source #
A record constructor expression
Instances
data Expression_If Source #
An 'if' expression
Instances
Read Expression_If Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Expression_If # readList :: ReadS [Expression_If] # | |
Show Expression_If Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Expression_If -> ShowS # show :: Expression_If -> String # showList :: [Expression_If] -> ShowS # | |
Eq Expression_If Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Expression_If -> Expression_If -> Bool # (/=) :: Expression_If -> Expression_If -> Bool # | |
Ord Expression_If Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Expression_If -> Expression_If -> Ordering # (<) :: Expression_If -> Expression_If -> Bool # (<=) :: Expression_If -> Expression_If -> Bool # (>) :: Expression_If -> Expression_If -> Bool # (>=) :: Expression_If -> Expression_If -> Bool # max :: Expression_If -> Expression_If -> Expression_If # min :: Expression_If -> Expression_If -> Expression_If # | |
ToTree Expression_If Source # | |
Defined in Hydra.Ext.Haskell.Serde toTree :: Expression_If -> Expr Source # |
data Expression_InfixApplication Source #
An infix application expression
Instances
data Expression_Lambda Source #
A lambda expression
Instances
data Expression_Let Source #
A 'let' expression
Instances
Read Expression_Let Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Expression_Let # readList :: ReadS [Expression_Let] # | |
Show Expression_Let Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Expression_Let -> ShowS # show :: Expression_Let -> String # showList :: [Expression_Let] -> ShowS # | |
Eq Expression_Let Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Expression_Let -> Expression_Let -> Bool # (/=) :: Expression_Let -> Expression_Let -> Bool # | |
Ord Expression_Let Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Expression_Let -> Expression_Let -> Ordering # (<) :: Expression_Let -> Expression_Let -> Bool # (<=) :: Expression_Let -> Expression_Let -> Bool # (>) :: Expression_Let -> Expression_Let -> Bool # (>=) :: Expression_Let -> Expression_Let -> Bool # max :: Expression_Let -> Expression_Let -> Expression_Let # min :: Expression_Let -> Expression_Let -> Expression_Let # |
data Expression_PrefixApplication Source #
A prefix expression
Instances
data Expression_Section Source #
A section expression
Instances
Read Expression_Section Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show Expression_Section Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Expression_Section -> ShowS # show :: Expression_Section -> String # showList :: [Expression_Section] -> ShowS # | |
Eq Expression_Section Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Expression_Section -> Expression_Section -> Bool # (/=) :: Expression_Section -> Expression_Section -> Bool # | |
Ord Expression_Section Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Expression_Section -> Expression_Section -> Ordering # (<) :: Expression_Section -> Expression_Section -> Bool # (<=) :: Expression_Section -> Expression_Section -> Bool # (>) :: Expression_Section -> Expression_Section -> Bool # (>=) :: Expression_Section -> Expression_Section -> Bool # max :: Expression_Section -> Expression_Section -> Expression_Section # min :: Expression_Section -> Expression_Section -> Expression_Section # |
data Expression_TypeSignature Source #
A type signature expression
Instances
data Expression_UpdateRecord Source #
An update record expression
Instances
A field (name/type pair)
data FieldWithComments Source #
A field together with any comments
Instances
data FieldUpdate Source #
A field name and value
Instances
Read FieldUpdate Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS FieldUpdate # readList :: ReadS [FieldUpdate] # readPrec :: ReadPrec FieldUpdate # readListPrec :: ReadPrec [FieldUpdate] # | |
Show FieldUpdate Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> FieldUpdate -> ShowS # show :: FieldUpdate -> String # showList :: [FieldUpdate] -> ShowS # | |
Eq FieldUpdate Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: FieldUpdate -> FieldUpdate -> Bool # (/=) :: FieldUpdate -> FieldUpdate -> Bool # | |
Ord FieldUpdate Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: FieldUpdate -> FieldUpdate -> Ordering # (<) :: FieldUpdate -> FieldUpdate -> Bool # (<=) :: FieldUpdate -> FieldUpdate -> Bool # (>) :: FieldUpdate -> FieldUpdate -> Bool # (>=) :: FieldUpdate -> FieldUpdate -> Bool # max :: FieldUpdate -> FieldUpdate -> FieldUpdate # min :: FieldUpdate -> FieldUpdate -> FieldUpdate # |
_FieldUpdate :: Name Source #
An import statement
data Import_Spec Source #
An import specification
Instances
Read Import_Spec Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Import_Spec # readList :: ReadS [Import_Spec] # readPrec :: ReadPrec Import_Spec # readListPrec :: ReadPrec [Import_Spec] # | |
Show Import_Spec Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Import_Spec -> ShowS # show :: Import_Spec -> String # showList :: [Import_Spec] -> ShowS # | |
Eq Import_Spec Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Import_Spec -> Import_Spec -> Bool # (/=) :: Import_Spec -> Import_Spec -> Bool # | |
Ord Import_Spec Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Import_Spec -> Import_Spec -> Ordering # (<) :: Import_Spec -> Import_Spec -> Bool # (<=) :: Import_Spec -> Import_Spec -> Bool # (>) :: Import_Spec -> Import_Spec -> Bool # (>=) :: Import_Spec -> Import_Spec -> Bool # max :: Import_Spec -> Import_Spec -> Import_Spec # min :: Import_Spec -> Import_Spec -> Import_Spec # |
_Import_Spec :: Name Source #
data ImportModifier Source #
An import modifier (pattern
or 'type')
Instances
Read ImportModifier Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS ImportModifier # readList :: ReadS [ImportModifier] # | |
Show ImportModifier Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> ImportModifier -> ShowS # show :: ImportModifier -> String # showList :: [ImportModifier] -> ShowS # | |
Eq ImportModifier Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: ImportModifier -> ImportModifier -> Bool # (/=) :: ImportModifier -> ImportModifier -> Bool # | |
Ord ImportModifier Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: ImportModifier -> ImportModifier -> Ordering # (<) :: ImportModifier -> ImportModifier -> Bool # (<=) :: ImportModifier -> ImportModifier -> Bool # (>) :: ImportModifier -> ImportModifier -> Bool # (>=) :: ImportModifier -> ImportModifier -> Bool # max :: ImportModifier -> ImportModifier -> ImportModifier # min :: ImportModifier -> ImportModifier -> ImportModifier # |
data ImportExportSpec Source #
An import or export specification
Instances
Read ImportExportSpec Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show ImportExportSpec Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> ImportExportSpec -> ShowS # show :: ImportExportSpec -> String # showList :: [ImportExportSpec] -> ShowS # | |
Eq ImportExportSpec Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: ImportExportSpec -> ImportExportSpec -> Bool # (/=) :: ImportExportSpec -> ImportExportSpec -> Bool # | |
Ord ImportExportSpec Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: ImportExportSpec -> ImportExportSpec -> Ordering # (<) :: ImportExportSpec -> ImportExportSpec -> Bool # (<=) :: ImportExportSpec -> ImportExportSpec -> Bool # (>) :: ImportExportSpec -> ImportExportSpec -> Bool # (>=) :: ImportExportSpec -> ImportExportSpec -> Bool # max :: ImportExportSpec -> ImportExportSpec -> ImportExportSpec # min :: ImportExportSpec -> ImportExportSpec -> ImportExportSpec # |
data ImportExportSpec_Subspec Source #
Instances
A literal value
LiteralChar Int | |
LiteralDouble Double | |
LiteralFloat Float | |
LiteralInt Int | |
LiteralInteger Integer | |
LiteralString String |
data LocalBinding Source #
Instances
Read LocalBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS LocalBinding # readList :: ReadS [LocalBinding] # | |
Show LocalBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> LocalBinding -> ShowS # show :: LocalBinding -> String # showList :: [LocalBinding] -> ShowS # | |
Eq LocalBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: LocalBinding -> LocalBinding -> Bool # (/=) :: LocalBinding -> LocalBinding -> Bool # | |
Ord LocalBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: LocalBinding -> LocalBinding -> Ordering # (<) :: LocalBinding -> LocalBinding -> Bool # (<=) :: LocalBinding -> LocalBinding -> Bool # (>) :: LocalBinding -> LocalBinding -> Bool # (>=) :: LocalBinding -> LocalBinding -> Bool # max :: LocalBinding -> LocalBinding -> LocalBinding # min :: LocalBinding -> LocalBinding -> LocalBinding # |
_LocalBinding :: Name Source #
newtype LocalBindings Source #
Instances
Read LocalBindings Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS LocalBindings # readList :: ReadS [LocalBindings] # | |
Show LocalBindings Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> LocalBindings -> ShowS # show :: LocalBindings -> String # showList :: [LocalBindings] -> ShowS # | |
Eq LocalBindings Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: LocalBindings -> LocalBindings -> Bool # (/=) :: LocalBindings -> LocalBindings -> Bool # | |
Ord LocalBindings Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: LocalBindings -> LocalBindings -> Ordering # (<) :: LocalBindings -> LocalBindings -> Bool # (<=) :: LocalBindings -> LocalBindings -> Bool # (>) :: LocalBindings -> LocalBindings -> Bool # (>=) :: LocalBindings -> LocalBindings -> Bool # max :: LocalBindings -> LocalBindings -> LocalBindings # min :: LocalBindings -> LocalBindings -> LocalBindings # |
data ModuleHead Source #
Instances
Read ModuleHead Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS ModuleHead # readList :: ReadS [ModuleHead] # readPrec :: ReadPrec ModuleHead # readListPrec :: ReadPrec [ModuleHead] # | |
Show ModuleHead Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> ModuleHead -> ShowS # show :: ModuleHead -> String # showList :: [ModuleHead] -> ShowS # | |
Eq ModuleHead Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: ModuleHead -> ModuleHead -> Bool # (/=) :: ModuleHead -> ModuleHead -> Bool # | |
Ord ModuleHead Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: ModuleHead -> ModuleHead -> Ordering # (<) :: ModuleHead -> ModuleHead -> Bool # (<=) :: ModuleHead -> ModuleHead -> Bool # (>) :: ModuleHead -> ModuleHead -> Bool # (>=) :: ModuleHead -> ModuleHead -> Bool # max :: ModuleHead -> ModuleHead -> ModuleHead # min :: ModuleHead -> ModuleHead -> ModuleHead # | |
ToTree ModuleHead Source # | |
Defined in Hydra.Ext.Haskell.Serde toTree :: ModuleHead -> Expr Source # |
_ModuleHead :: Name Source #
newtype ModuleName Source #
Instances
Read ModuleName Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS ModuleName # readList :: ReadS [ModuleName] # readPrec :: ReadPrec ModuleName # readListPrec :: ReadPrec [ModuleName] # | |
Show ModuleName Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> ModuleName -> ShowS # show :: ModuleName -> String # showList :: [ModuleName] -> ShowS # | |
Eq ModuleName Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: ModuleName -> ModuleName -> Bool # (/=) :: ModuleName -> ModuleName -> Bool # | |
Ord ModuleName Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: ModuleName -> ModuleName -> Ordering # (<) :: ModuleName -> ModuleName -> Bool # (<=) :: ModuleName -> ModuleName -> Bool # (>) :: ModuleName -> ModuleName -> Bool # (>=) :: ModuleName -> ModuleName -> Bool # max :: ModuleName -> ModuleName -> ModuleName # min :: ModuleName -> ModuleName -> ModuleName # |
_ModuleName :: Name Source #
data Pattern_Application Source #
Instances
data Pattern_As Source #
Instances
Read Pattern_As Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Pattern_As # readList :: ReadS [Pattern_As] # readPrec :: ReadPrec Pattern_As # readListPrec :: ReadPrec [Pattern_As] # | |
Show Pattern_As Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Pattern_As -> ShowS # show :: Pattern_As -> String # showList :: [Pattern_As] -> ShowS # | |
Eq Pattern_As Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Pattern_As -> Pattern_As -> Bool # (/=) :: Pattern_As -> Pattern_As -> Bool # | |
Ord Pattern_As Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Pattern_As -> Pattern_As -> Ordering # (<) :: Pattern_As -> Pattern_As -> Bool # (<=) :: Pattern_As -> Pattern_As -> Bool # (>) :: Pattern_As -> Pattern_As -> Bool # (>=) :: Pattern_As -> Pattern_As -> Bool # max :: Pattern_As -> Pattern_As -> Pattern_As # min :: Pattern_As -> Pattern_As -> Pattern_As # |
_Pattern_As :: Name Source #
data Pattern_Record Source #
Instances
Read Pattern_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Pattern_Record # readList :: ReadS [Pattern_Record] # | |
Show Pattern_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Pattern_Record -> ShowS # show :: Pattern_Record -> String # showList :: [Pattern_Record] -> ShowS # | |
Eq Pattern_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Pattern_Record -> Pattern_Record -> Bool # (/=) :: Pattern_Record -> Pattern_Record -> Bool # | |
Ord Pattern_Record Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Pattern_Record -> Pattern_Record -> Ordering # (<) :: Pattern_Record -> Pattern_Record -> Bool # (<=) :: Pattern_Record -> Pattern_Record -> Bool # (>) :: Pattern_Record -> Pattern_Record -> Bool # (>=) :: Pattern_Record -> Pattern_Record -> Bool # max :: Pattern_Record -> Pattern_Record -> Pattern_Record # min :: Pattern_Record -> Pattern_Record -> Pattern_Record # |
data Pattern_Typed Source #
Instances
Read Pattern_Typed Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Pattern_Typed # readList :: ReadS [Pattern_Typed] # | |
Show Pattern_Typed Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Pattern_Typed -> ShowS # show :: Pattern_Typed -> String # showList :: [Pattern_Typed] -> ShowS # | |
Eq Pattern_Typed Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Pattern_Typed -> Pattern_Typed -> Bool # (/=) :: Pattern_Typed -> Pattern_Typed -> Bool # | |
Ord Pattern_Typed Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Pattern_Typed -> Pattern_Typed -> Ordering # (<) :: Pattern_Typed -> Pattern_Typed -> Bool # (<=) :: Pattern_Typed -> Pattern_Typed -> Bool # (>) :: Pattern_Typed -> Pattern_Typed -> Bool # (>=) :: Pattern_Typed -> Pattern_Typed -> Bool # max :: Pattern_Typed -> Pattern_Typed -> Pattern_Typed # min :: Pattern_Typed -> Pattern_Typed -> Pattern_Typed # |
data PatternField Source #
Instances
Read PatternField Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS PatternField # readList :: ReadS [PatternField] # | |
Show PatternField Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> PatternField -> ShowS # show :: PatternField -> String # showList :: [PatternField] -> ShowS # | |
Eq PatternField Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: PatternField -> PatternField -> Bool # (/=) :: PatternField -> PatternField -> Bool # | |
Ord PatternField Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: PatternField -> PatternField -> Ordering # (<) :: PatternField -> PatternField -> Bool # (<=) :: PatternField -> PatternField -> Bool # (>) :: PatternField -> PatternField -> Bool # (>=) :: PatternField -> PatternField -> Bool # max :: PatternField -> PatternField -> PatternField # min :: PatternField -> PatternField -> PatternField # |
_PatternField :: Name Source #
data QualifiedName Source #
Instances
Read QualifiedName Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS QualifiedName # readList :: ReadS [QualifiedName] # | |
Show QualifiedName Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> QualifiedName -> ShowS # show :: QualifiedName -> String # showList :: [QualifiedName] -> ShowS # | |
Eq QualifiedName Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: QualifiedName -> QualifiedName -> Bool # (/=) :: QualifiedName -> QualifiedName -> Bool # | |
Ord QualifiedName Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: QualifiedName -> QualifiedName -> Ordering # (<) :: QualifiedName -> QualifiedName -> Bool # (<=) :: QualifiedName -> QualifiedName -> Bool # (>) :: QualifiedName -> QualifiedName -> Bool # (>=) :: QualifiedName -> QualifiedName -> Bool # max :: QualifiedName -> QualifiedName -> QualifiedName # min :: QualifiedName -> QualifiedName -> QualifiedName # |
newtype RightHandSide Source #
Instances
Read RightHandSide Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS RightHandSide # readList :: ReadS [RightHandSide] # | |
Show RightHandSide Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> RightHandSide -> ShowS # show :: RightHandSide -> String # showList :: [RightHandSide] -> ShowS # | |
Eq RightHandSide Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: RightHandSide -> RightHandSide -> Bool # (/=) :: RightHandSide -> RightHandSide -> Bool # | |
Ord RightHandSide Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: RightHandSide -> RightHandSide -> Ordering # (<) :: RightHandSide -> RightHandSide -> Bool # (<=) :: RightHandSide -> RightHandSide -> Bool # (>) :: RightHandSide -> RightHandSide -> Bool # (>=) :: RightHandSide -> RightHandSide -> Bool # max :: RightHandSide -> RightHandSide -> RightHandSide # min :: RightHandSide -> RightHandSide -> RightHandSide # | |
ToTree RightHandSide Source # | |
Defined in Hydra.Ext.Haskell.Serde toTree :: RightHandSide -> Expr Source # |
_Statement :: Name Source #
TypeApplication Type_Application | |
TypeFunction Type_Function | |
TypeInfix Type_Infix | |
TypeList Type | |
TypeParens Type | |
TypeTuple [Type] | |
TypeVariable Name |
data Type_Application Source #
Instances
Read Type_Application Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show Type_Application Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Type_Application -> ShowS # show :: Type_Application -> String # showList :: [Type_Application] -> ShowS # | |
Eq Type_Application Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Type_Application -> Type_Application -> Bool # (/=) :: Type_Application -> Type_Application -> Bool # | |
Ord Type_Application Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Type_Application -> Type_Application -> Ordering # (<) :: Type_Application -> Type_Application -> Bool # (<=) :: Type_Application -> Type_Application -> Bool # (>) :: Type_Application -> Type_Application -> Bool # (>=) :: Type_Application -> Type_Application -> Bool # max :: Type_Application -> Type_Application -> Type_Application # min :: Type_Application -> Type_Application -> Type_Application # |
data Type_Function Source #
Instances
Read Type_Function Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Type_Function # readList :: ReadS [Type_Function] # | |
Show Type_Function Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Type_Function -> ShowS # show :: Type_Function -> String # showList :: [Type_Function] -> ShowS # | |
Eq Type_Function Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Type_Function -> Type_Function -> Bool # (/=) :: Type_Function -> Type_Function -> Bool # | |
Ord Type_Function Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Type_Function -> Type_Function -> Ordering # (<) :: Type_Function -> Type_Function -> Bool # (<=) :: Type_Function -> Type_Function -> Bool # (>) :: Type_Function -> Type_Function -> Bool # (>=) :: Type_Function -> Type_Function -> Bool # max :: Type_Function -> Type_Function -> Type_Function # min :: Type_Function -> Type_Function -> Type_Function # |
data Type_Infix Source #
Instances
Read Type_Infix Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS Type_Infix # readList :: ReadS [Type_Infix] # readPrec :: ReadPrec Type_Infix # readListPrec :: ReadPrec [Type_Infix] # | |
Show Type_Infix Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> Type_Infix -> ShowS # show :: Type_Infix -> String # showList :: [Type_Infix] -> ShowS # | |
Eq Type_Infix Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: Type_Infix -> Type_Infix -> Bool # (/=) :: Type_Infix -> Type_Infix -> Bool # | |
Ord Type_Infix Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: Type_Infix -> Type_Infix -> Ordering # (<) :: Type_Infix -> Type_Infix -> Bool # (<=) :: Type_Infix -> Type_Infix -> Bool # (>) :: Type_Infix -> Type_Infix -> Bool # (>=) :: Type_Infix -> Type_Infix -> Bool # max :: Type_Infix -> Type_Infix -> Type_Infix # min :: Type_Infix -> Type_Infix -> Type_Infix # |
_Type_Infix :: Name Source #
data TypeDeclaration Source #
Instances
Read TypeDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show TypeDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> TypeDeclaration -> ShowS # show :: TypeDeclaration -> String # showList :: [TypeDeclaration] -> ShowS # | |
Eq TypeDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: TypeDeclaration -> TypeDeclaration -> Bool # (/=) :: TypeDeclaration -> TypeDeclaration -> Bool # | |
Ord TypeDeclaration Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: TypeDeclaration -> TypeDeclaration -> Ordering # (<) :: TypeDeclaration -> TypeDeclaration -> Bool # (<=) :: TypeDeclaration -> TypeDeclaration -> Bool # (>) :: TypeDeclaration -> TypeDeclaration -> Bool # (>=) :: TypeDeclaration -> TypeDeclaration -> Bool # max :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration # min :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration # |
data TypeSignature Source #
Instances
Read TypeSignature Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS TypeSignature # readList :: ReadS [TypeSignature] # | |
Show TypeSignature Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> TypeSignature -> ShowS # show :: TypeSignature -> String # showList :: [TypeSignature] -> ShowS # | |
Eq TypeSignature Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: TypeSignature -> TypeSignature -> Bool # (/=) :: TypeSignature -> TypeSignature -> Bool # | |
Ord TypeSignature Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: TypeSignature -> TypeSignature -> Ordering # (<) :: TypeSignature -> TypeSignature -> Bool # (<=) :: TypeSignature -> TypeSignature -> Bool # (>) :: TypeSignature -> TypeSignature -> Bool # (>=) :: TypeSignature -> TypeSignature -> Bool # max :: TypeSignature -> TypeSignature -> TypeSignature # min :: TypeSignature -> TypeSignature -> TypeSignature # |
data TypedBinding Source #
Instances
Read TypedBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS TypedBinding # readList :: ReadS [TypedBinding] # | |
Show TypedBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> TypedBinding -> ShowS # show :: TypedBinding -> String # showList :: [TypedBinding] -> ShowS # | |
Eq TypedBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: TypedBinding -> TypedBinding -> Bool # (/=) :: TypedBinding -> TypedBinding -> Bool # | |
Ord TypedBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: TypedBinding -> TypedBinding -> Ordering # (<) :: TypedBinding -> TypedBinding -> Bool # (<=) :: TypedBinding -> TypedBinding -> Bool # (>) :: TypedBinding -> TypedBinding -> Bool # (>=) :: TypedBinding -> TypedBinding -> Bool # max :: TypedBinding -> TypedBinding -> TypedBinding # min :: TypedBinding -> TypedBinding -> TypedBinding # |
_TypedBinding :: Name Source #
data ValueBinding Source #
Instances
Read ValueBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast readsPrec :: Int -> ReadS ValueBinding # readList :: ReadS [ValueBinding] # | |
Show ValueBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> ValueBinding -> ShowS # show :: ValueBinding -> String # showList :: [ValueBinding] -> ShowS # | |
Eq ValueBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: ValueBinding -> ValueBinding -> Bool # (/=) :: ValueBinding -> ValueBinding -> Bool # | |
Ord ValueBinding Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: ValueBinding -> ValueBinding -> Ordering # (<) :: ValueBinding -> ValueBinding -> Bool # (<=) :: ValueBinding -> ValueBinding -> Bool # (>) :: ValueBinding -> ValueBinding -> Bool # (>=) :: ValueBinding -> ValueBinding -> Bool # max :: ValueBinding -> ValueBinding -> ValueBinding # min :: ValueBinding -> ValueBinding -> ValueBinding # | |
ToTree ValueBinding Source # | |
Defined in Hydra.Ext.Haskell.Serde toTree :: ValueBinding -> Expr Source # |
_ValueBinding :: Name Source #
data ValueBinding_Simple Source #
Instances
Read ValueBinding_Simple Source # | |
Defined in Hydra.Ext.Haskell.Ast | |
Show ValueBinding_Simple Source # | |
Defined in Hydra.Ext.Haskell.Ast showsPrec :: Int -> ValueBinding_Simple -> ShowS # show :: ValueBinding_Simple -> String # showList :: [ValueBinding_Simple] -> ShowS # | |
Eq ValueBinding_Simple Source # | |
Defined in Hydra.Ext.Haskell.Ast (==) :: ValueBinding_Simple -> ValueBinding_Simple -> Bool # (/=) :: ValueBinding_Simple -> ValueBinding_Simple -> Bool # | |
Ord ValueBinding_Simple Source # | |
Defined in Hydra.Ext.Haskell.Ast compare :: ValueBinding_Simple -> ValueBinding_Simple -> Ordering # (<) :: ValueBinding_Simple -> ValueBinding_Simple -> Bool # (<=) :: ValueBinding_Simple -> ValueBinding_Simple -> Bool # (>) :: ValueBinding_Simple -> ValueBinding_Simple -> Bool # (>=) :: ValueBinding_Simple -> ValueBinding_Simple -> Bool # max :: ValueBinding_Simple -> ValueBinding_Simple -> ValueBinding_Simple # min :: ValueBinding_Simple -> ValueBinding_Simple -> ValueBinding_Simple # |