| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Agda.Syntax.Common.Aspect
Synopsis
- data Induction
- data Aspect
- data NameKind
- data OtherAspect
- data Aspects = Aspects {}
- data DefinitionSite = DefinitionSite {}
- data TokenBased
Documentation
Constructors
| Inductive | |
| CoInductive |
Instances
| PatternMatchingAllowed Induction Source # | |
Defined in Agda.Syntax.Common Methods | |
| Pretty Induction Source # | |
| HasRange Induction Source # | |
| KillRange Induction Source # | |
Defined in Agda.Syntax.Common Methods | |
| EmbPrj Induction Source # | |
| NFData Induction Source # | |
Defined in Agda.Syntax.Common.Aspect | |
| Show Induction Source # | |
| Eq Induction Source # | |
| Ord Induction Source # | |
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
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 # | |||||
| NFData NameKind Source # | |||||
Defined in Agda.Syntax.Common.Aspect | |||||
| Semigroup NameKind Source # | Some | ||||
| Generic NameKind Source # | |||||
Defined in Agda.Syntax.Common.Aspect Associated Types
| |||||
| Show NameKind Source # | |||||
| 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.7.20250510-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. |
| InstanceProblem | Unusable instance etc. |
| CosmeticProblem | Nothing serious, just a beauty flaw. |
| CatchallClause | |
| ConfluenceProblem |
Instances
| EmbPrj OtherAspect Source # | |||||
| NFData OtherAspect Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise Methods rnf :: OtherAspect -> () # | |||||
| 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
| |||||
| Show OtherAspect Source # | |||||
Defined in Agda.Syntax.Common.Aspect Methods showsPrec :: Int -> OtherAspect -> ShowS # show :: OtherAspect -> String # showList :: [OtherAspect] -> ShowS # | |||||
| 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.7.20250510-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 "InstanceProblem" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CosmeticProblem" '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
| EncodeTCM Doc Source # | |||||
| Underscore Doc Source # | |||||
Defined in Agda.Syntax.Common | |||||
| ReportS Doc Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods reportS :: MonadDebug m => VerboseKey -> VerboseLevel -> Doc -> m () Source # | |||||
| TraceS Doc Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods traceS :: MonadDebug m => VerboseKey -> VerboseLevel -> Doc -> m c -> m c Source # | |||||
| EmbPrj Aspects Source # | |||||
| EmbPrj Doc Source # | |||||
| NFData Aspects Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise | |||||
| Monoid Aspects Source # | |||||
| Semigroup Aspects Source # | |||||
| Generic Aspects Source # | |||||
Defined in Agda.Syntax.Common.Aspect Associated Types
| |||||
| Show Aspects Source # | |||||
| Eq Aspects Source # | |||||
| ToJSON Doc Source # | |||||
| IsBasicRangeMap Aspects PositionMap Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise Methods singleton :: Ranges -> Aspects -> PositionMap Source # toMap :: PositionMap -> IntMap Aspects Source # toList :: PositionMap -> [(Range, Aspects)] Source # coveringRange :: PositionMap -> Maybe Range Source # | |||||
| IsBasicRangeMap Aspects RangePair Source # | |||||
| Convert PositionMap (RangeMap Aspects) Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise | |||||
| IsBasicRangeMap Aspects (DelayedMerge PositionMap) Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise Methods singleton :: Ranges -> Aspects -> DelayedMerge PositionMap Source # toMap :: DelayedMerge PositionMap -> IntMap Aspects Source # toList :: DelayedMerge PositionMap -> [(Range, Aspects)] Source # coveringRange :: DelayedMerge PositionMap -> Maybe Range Source # | |||||
| IsBasicRangeMap Aspects (DelayedMerge RangePair) Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise | |||||
| ReportS (TCM Doc) Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods reportS :: MonadDebug m => VerboseKey -> VerboseLevel -> TCM Doc -> m () Source # | |||||
| ReportS [Doc] Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods reportS :: MonadDebug m => VerboseKey -> VerboseLevel -> [Doc] -> m () Source # | |||||
| ReportS [TCM Doc] Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods reportS :: MonadDebug m => VerboseKey -> VerboseLevel -> [TCM Doc] -> m () Source # | |||||
| TraceS (TCM Doc) Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods traceS :: MonadDebug m => VerboseKey -> VerboseLevel -> TCM Doc -> m c -> m c Source # | |||||
| TraceS [Doc] Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods traceS :: MonadDebug m => VerboseKey -> VerboseLevel -> [Doc] -> m c -> m c Source # | |||||
| TraceS [TCM Doc] Source # | |||||
Defined in Agda.TypeChecking.Monad.Debug Methods traceS :: MonadDebug m => VerboseKey -> VerboseLevel -> [TCM Doc] -> m c -> m c Source # | |||||
| Null (TCM Doc) Source # | |||||
| Semigroup (TCM Doc) Source # | This instance is more specific than a generic instance
| ||||
| Convert (DelayedMerge PositionMap) (RangeMap Aspects) Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise Methods convert :: DelayedMerge PositionMap -> RangeMap Aspects Source # | |||||
| Convert (DelayedMerge RangePair) (RangeMap Aspects) Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise | |||||
| Convert (RangeMap Aspects) (RangeMap Aspects) Source # | |||||
| Monad m => Null (PureConversionT m Doc) Source # | |||||
Defined in Agda.TypeChecking.Conversion.Pure | |||||
| type Rep Aspects Source # | |||||
Defined in Agda.Syntax.Common.Aspect type Rep Aspects = D1 ('MetaData "Aspects" "Agda.Syntax.Common.Aspect" "Agda-2.7.20250510-inplace" 'False) (C1 ('MetaCons "Aspects" 'PrefixI 'True) ((S1 ('MetaSel ('Just "aspect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Aspect)) :*: S1 ('MetaSel ('Just "otherAspects") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set OtherAspect))) :*: (S1 ('MetaSel ('Just "note") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "definitionSite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DefinitionSite)) :*: S1 ('MetaSel ('Just "tokenBased") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TokenBased))))) | |||||
data DefinitionSite Source #
Constructors
| DefinitionSite | |
Fields
| |
Instances
| EmbPrj DefinitionSite Source # | |||||
| NFData DefinitionSite Source # | |||||
Defined in Agda.Interaction.Highlighting.Precise Methods rnf :: DefinitionSite -> () # | |||||
| 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
Methods from :: DefinitionSite -> Rep DefinitionSite x # to :: Rep DefinitionSite x -> DefinitionSite # | |||||
| Show DefinitionSite Source # | |||||
Defined in Agda.Syntax.Common.Aspect Methods showsPrec :: Int -> DefinitionSite -> ShowS # show :: DefinitionSite -> String # showList :: [DefinitionSite] -> ShowS # | |||||
| 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.7.20250510-inplace" 'False) (C1 ('MetaCons "DefinitionSite" 'PrefixI 'True) ((S1 ('MetaSel ('Just "defSiteModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TopLevelModuleName' Range)) :*: 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 |
Instances
| EncodeTCM TokenBased Source # | |
Defined in Agda.Interaction.Highlighting.JSON | |
| EmbPrj TokenBased Source # | |
| Monoid TokenBased Source # | |
Defined in Agda.Interaction.Highlighting.Precise Methods mempty :: TokenBased # mappend :: TokenBased -> TokenBased -> TokenBased # mconcat :: [TokenBased] -> TokenBased # | |
| Semigroup TokenBased Source # | |
Defined in Agda.Interaction.Highlighting.Precise Methods (<>) :: TokenBased -> TokenBased -> TokenBased # sconcat :: NonEmpty TokenBased -> TokenBased # stimes :: Integral b => b -> TokenBased -> TokenBased # | |
| Show TokenBased Source # | |
Defined in Agda.Syntax.Common.Aspect Methods showsPrec :: Int -> TokenBased -> ShowS # show :: TokenBased -> String # showList :: [TokenBased] -> ShowS # | |
| Eq TokenBased Source # | |
Defined in Agda.Syntax.Common.Aspect | |
| ToJSON TokenBased Source # | |
Defined in Agda.Interaction.Highlighting.JSON Methods toJSON :: TokenBased -> Value # toEncoding :: TokenBased -> Encoding # toJSONList :: [TokenBased] -> Value # toEncodingList :: [TokenBased] -> Encoding # omitField :: TokenBased -> Bool # | |