| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Agda.Syntax.Common.Aspect
Synopsis
- data Induction
- data Aspect
- data NameKind
- data OtherAspect
- data Aspects = Aspects {
- aspect :: Maybe Aspect
- otherAspects :: Set OtherAspect
- note :: String
- definitionSite :: Maybe DefinitionSite
- tokenBased :: !TokenBased
- data DefinitionSite = DefinitionSite {
- defSiteModule :: TopLevelModuleName
- defSitePos :: Int
- defSiteHere :: Bool
- defSiteAnchor :: Maybe String
- data TokenBased
Documentation
Constructors
| Inductive | |
| CoInductive |
Instances
| PatternMatchingAllowed Induction Source # | |
Defined in Agda.Syntax.Common Methods patternMatchingAllowed :: Induction -> Bool Source # | |
| Pretty Induction Source # | |
| HasRange Induction Source # | |
| KillRange Induction Source # | |
Defined in Agda.Syntax.Common Methods | |
| EmbPrj Induction Source # | |
| Show Induction Source # | |
| NFData Induction Source # | |
Defined in Agda.Syntax.Common.Aspect | |
| Eq Induction Source # | |
| Ord Induction Source # | |
Defined in Agda.Syntax.Common.Aspect | |
Constructors
| Comment | |
| Keyword | |
| String | |
| Number | |
| Hole | |
| Symbol | Symbols like forall, =, ->, etc. |
| PrimitiveType | Things like Set and Prop. |
| Name (Maybe NameKind) Bool | Is the name an operator part? |
| Pragma | Text occurring in pragmas that does not have a more specific aspect. |
| Background | Non-code contents in literate Agda |
| Markup | Delimiters used to separate the Agda code blocks from the other contents in literate Agda |
Instances
| EmbPrj Aspect Source # | |
| Semigroup Aspect Source # |
|
| Generic Aspect Source # | |
| Show Aspect Source # | |
| NFData Aspect | |
Defined in Agda.Interaction.Highlighting.Precise | |
| Eq Aspect Source # | |
| type Rep Aspect Source # | |
Defined in Agda.Syntax.Common.Aspect type Rep Aspect = D1 ('MetaData "Aspect" "Agda.Syntax.Common.Aspect" "Agda-2.6.3.20230930-inplace" 'False) (((C1 ('MetaCons "Comment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Keyword" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Hole" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Symbol" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrimitiveType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NameKind)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: (C1 ('MetaCons "Pragma" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Background" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Markup" 'PrefixI 'False) (U1 :: Type -> Type))))) | |
NameKinds are figured out during scope checking.
Constructors
| Bound | Bound variable. |
| Generalizable | Generalizable variable. (This includes generalizable variables that have been generalized). |
| Constructor Induction | Inductive or coinductive constructor. |
| Datatype | |
| Field | Record field. |
| Function | |
| Module | Module name. |
| Postulate | |
| Primitive | Primitive. |
| Record | Record type. |
| Argument | Named argument, like x in {x = v} |
| Macro | Macro. |
Instances
| EmbPrj NameKind Source # | |
| Semigroup NameKind Source # | Some |
| Generic NameKind Source # | |
| Show NameKind Source # | |
| NFData NameKind Source # | |
Defined in Agda.Syntax.Common.Aspect | |
| Eq NameKind Source # | |
| type Rep NameKind Source # | |
Defined in Agda.Syntax.Common.Aspect type Rep NameKind = D1 ('MetaData "NameKind" "Agda.Syntax.Common.Aspect" "Agda-2.6.3.20230930-inplace" 'False) (((C1 ('MetaCons "Bound" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Generalizable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Constructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Induction)))) :+: (C1 ('MetaCons "Datatype" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Field" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Function" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Module" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Postulate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Primitive" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Record" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Argument" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Macro" 'PrefixI 'False) (U1 :: Type -> Type))))) | |
data OtherAspect Source #
Other aspects, generated by type checking.
(These can overlap with each other and with Aspects.)
Constructors
| Error | |
| ErrorWarning | A warning that is considered fatal in the end. |
| DottedPattern | |
| UnsolvedMeta | |
| UnsolvedConstraint | Unsolved constraint not connected to meta-variable. This could for instance be an emptyness constraint. |
| TerminationProblem | |
| PositivityProblem | |
| Deadcode | Used for highlighting unreachable clauses, unreachable RHS (because of an absurd pattern), etc. |
| ShadowingInTelescope | Used for shadowed repeated variable names in telescopes. |
| CoverageProblem | |
| IncompletePattern | When this constructor is used it is probably a good idea to
include a |
| TypeChecks | Code which is being type-checked. |
| MissingDefinition | Function declaration without matching definition NB: We put CatchallClause last so that it is overwritten by other, more important, aspects in the emacs mode. |
| CatchallClause | |
| ConfluenceProblem |
Instances
| EmbPrj OtherAspect Source # | |
Defined in Agda.TypeChecking.Serialise.Instances.Highlighting Methods icode :: OtherAspect -> S Int32 Source # icod_ :: OtherAspect -> S Int32 Source # value :: Int32 -> R OtherAspect Source # | |
| Bounded OtherAspect Source # | |
Defined in Agda.Syntax.Common.Aspect | |
| Enum OtherAspect Source # | |
Defined in Agda.Syntax.Common.Aspect Methods succ :: OtherAspect -> OtherAspect pred :: OtherAspect -> OtherAspect toEnum :: Int -> OtherAspect fromEnum :: OtherAspect -> Int enumFrom :: OtherAspect -> [OtherAspect] enumFromThen :: OtherAspect -> OtherAspect -> [OtherAspect] enumFromTo :: OtherAspect -> OtherAspect -> [OtherAspect] enumFromThenTo :: OtherAspect -> OtherAspect -> OtherAspect -> [OtherAspect] | |
| Generic OtherAspect Source # | |
Defined in Agda.Syntax.Common.Aspect Associated Types type Rep OtherAspect :: Type -> Type | |
| Show OtherAspect Source # | |
Defined in Agda.Syntax.Common.Aspect Methods showsPrec :: Int -> OtherAspect -> ShowS show :: OtherAspect -> String showList :: [OtherAspect] -> ShowS | |
| NFData OtherAspect | |
Defined in Agda.Interaction.Highlighting.Precise Methods rnf :: OtherAspect -> () | |
| Eq OtherAspect Source # | |
Defined in Agda.Syntax.Common.Aspect | |
| Ord OtherAspect Source # | |
Defined in Agda.Syntax.Common.Aspect Methods compare :: OtherAspect -> OtherAspect -> Ordering (<) :: OtherAspect -> OtherAspect -> Bool (<=) :: OtherAspect -> OtherAspect -> Bool (>) :: OtherAspect -> OtherAspect -> Bool (>=) :: OtherAspect -> OtherAspect -> Bool max :: OtherAspect -> OtherAspect -> OtherAspect min :: OtherAspect -> OtherAspect -> OtherAspect | |
| type Rep OtherAspect Source # | |
Defined in Agda.Syntax.Common.Aspect type Rep OtherAspect = D1 ('MetaData "OtherAspect" "Agda.Syntax.Common.Aspect" "Agda-2.6.3.20230930-inplace" 'False) (((C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorWarning" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DottedPattern" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnsolvedMeta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnsolvedConstraint" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TerminationProblem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PositivityProblem" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Deadcode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ShadowingInTelescope" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CoverageProblem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IncompletePattern" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TypeChecks" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MissingDefinition" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CatchallClause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConfluenceProblem" 'PrefixI 'False) (U1 :: Type -> Type))))) | |
Syntactic aspects of the code. (These cannot overlap.)
Meta information which can be associated with a character/character range.
Constructors
| Aspects | |
Fields
| |
Instances
data DefinitionSite Source #
Constructors
| DefinitionSite | |
Fields
| |
Instances
| EmbPrj DefinitionSite Source # | |
Defined in Agda.TypeChecking.Serialise.Instances.Highlighting Methods icode :: DefinitionSite -> S Int32 Source # icod_ :: DefinitionSite -> S Int32 Source # value :: Int32 -> R DefinitionSite Source # | |
| Semigroup DefinitionSite Source # | |
Defined in Agda.Interaction.Highlighting.Precise Methods (<>) :: DefinitionSite -> DefinitionSite -> DefinitionSite # sconcat :: NonEmpty DefinitionSite -> DefinitionSite stimes :: Integral b => b -> DefinitionSite -> DefinitionSite | |
| Generic DefinitionSite Source # | |
Defined in Agda.Syntax.Common.Aspect Associated Types type Rep DefinitionSite :: Type -> Type | |
| Show DefinitionSite Source # | |
Defined in Agda.Syntax.Common.Aspect Methods showsPrec :: Int -> DefinitionSite -> ShowS show :: DefinitionSite -> String showList :: [DefinitionSite] -> ShowS | |
| NFData DefinitionSite | |
Defined in Agda.Interaction.Highlighting.Precise Methods rnf :: DefinitionSite -> () | |
| Eq DefinitionSite Source # | |
Defined in Agda.Syntax.Common.Aspect Methods (==) :: DefinitionSite -> DefinitionSite -> Bool (/=) :: DefinitionSite -> DefinitionSite -> Bool | |
| type Rep DefinitionSite Source # | |
Defined in Agda.Syntax.Common.Aspect type Rep DefinitionSite = D1 ('MetaData "DefinitionSite" "Agda.Syntax.Common.Aspect" "Agda-2.6.3.20230930-inplace" 'False) (C1 ('MetaCons "DefinitionSite" 'PrefixI 'True) ((S1 ('MetaSel ('Just "defSiteModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TopLevelModuleName) :*: S1 ('MetaSel ('Just "defSitePos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "defSiteHere") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "defSiteAnchor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))) | |
data TokenBased Source #
Is the highlighting "token-based", i.e. based only on information from the lexer?
Constructors
| TokenBased | |
| NotOnlyTokenBased |