Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types used for precise syntax highlighting.
Synopsis
- data Aspect
- data NameKind
- data OtherAspect
- data Aspects = Aspects {}
- data DefinitionSite = DefinitionSite {}
- data TokenBased
- newtype File = File {}
- type HighlightingInfo = CompressedFile
- parserBased :: Aspects
- singleton :: Ranges -> Aspects -> File
- several :: [Ranges] -> Aspects -> File
- merge :: File -> File -> File
- smallestPos :: File -> Maybe Int
- toMap :: File -> IntMap Aspects
- newtype CompressedFile = CompressedFile {}
- compressedFileInvariant :: CompressedFile -> Bool
- compress :: File -> CompressedFile
- decompress :: CompressedFile -> File
- noHighlightingInRange :: Ranges -> CompressedFile -> CompressedFile
- singletonC :: Ranges -> Aspects -> CompressedFile
- severalC :: [Ranges] -> Aspects -> CompressedFile
- splitAtC :: Int -> CompressedFile -> (CompressedFile, CompressedFile)
- selectC :: Range -> CompressedFile -> CompressedFile
- smallestPosC :: CompressedFile -> Maybe Int
- mergeC :: CompressedFile -> CompressedFile -> CompressedFile
Files
Syntactic aspects of the code. (These cannot overlap.)
Comment | |
Keyword | |
String | |
Number | |
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 |
NameKind
s are figured out during scope checking.
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. |
data OtherAspect Source #
Other aspects, generated by type checking.
(These can overlap with each other and with Aspect
s.)
Error | |
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
Meta information which can be associated with a character/character range.
Aspects | |
|
data DefinitionSite Source #
DefinitionSite | |
|
Instances
Eq DefinitionSite Source # | |
Defined in Agda.Interaction.Highlighting.Precise (==) :: DefinitionSite -> DefinitionSite -> Bool # (/=) :: DefinitionSite -> DefinitionSite -> Bool # | |
Show DefinitionSite Source # | |
Defined in Agda.Interaction.Highlighting.Precise showsPrec :: Int -> DefinitionSite -> ShowS # show :: DefinitionSite -> String # showList :: [DefinitionSite] -> ShowS # | |
EmbPrj DefinitionSite Source # | |
data TokenBased Source #
Is the highlighting "token-based", i.e. based only on information from the lexer?
Instances
A File
is a mapping from file positions to meta information.
The first position in the file has number 1.
type HighlightingInfo = CompressedFile Source #
Syntax highlighting information.
Creation
parserBased :: Aspects Source #
A variant of mempty
with tokenBased
set to
NotOnlyTokenBased
.
singleton :: Ranges -> Aspects -> File Source #
is a file whose positions are those in singleton
rs mrs
,
and in which every position is associated with m
.
Merging
Inspection
toMap :: File -> IntMap Aspects Source #
Convert the File
to a map from file positions (counting from 1)
to meta information.
Compressed files
newtype CompressedFile Source #
Instances
Eq CompressedFile Source # | |
Defined in Agda.Interaction.Highlighting.Precise (==) :: CompressedFile -> CompressedFile -> Bool # (/=) :: CompressedFile -> CompressedFile -> Bool # | |
Show CompressedFile Source # | |
Defined in Agda.Interaction.Highlighting.Precise showsPrec :: Int -> CompressedFile -> ShowS # show :: CompressedFile -> String # showList :: [CompressedFile] -> ShowS # | |
Semigroup CompressedFile Source # | |
Defined in Agda.Interaction.Highlighting.Precise (<>) :: CompressedFile -> CompressedFile -> CompressedFile # sconcat :: NonEmpty CompressedFile -> CompressedFile # stimes :: Integral b => b -> CompressedFile -> CompressedFile # | |
Monoid CompressedFile Source # | |
Defined in Agda.Interaction.Highlighting.Precise mappend :: CompressedFile -> CompressedFile -> CompressedFile # mconcat :: [CompressedFile] -> CompressedFile # | |
EmbPrj CompressedFile Source # | |
compressedFileInvariant :: CompressedFile -> Bool Source #
Invariant for compressed files.
Note that these files are not required to be maximally
compressed, because ranges are allowed to be empty, and the
Aspects
s in adjacent ranges are allowed to be equal.
compress :: File -> CompressedFile Source #
Compresses a file by merging consecutive positions with equal meta information into longer ranges.
decompress :: CompressedFile -> File Source #
Decompresses a compressed file.
noHighlightingInRange :: Ranges -> CompressedFile -> CompressedFile Source #
Clear any highlighting info for the given ranges. Used to make sure unsolved meta highlighting overrides error highlighting.
Creation
singletonC :: Ranges -> Aspects -> CompressedFile Source #
is a file whose positions are those in singletonC
rs mrs
,
and in which every position is associated with m
.
severalC :: [Ranges] -> Aspects -> CompressedFile Source #
Like singletonR
, but with a list of Ranges
instead of a
single one.
splitAtC :: Int -> CompressedFile -> (CompressedFile, CompressedFile) Source #
splitAtC p f
splits the compressed file f
into (f1, f2)
,
where all the positions in f1
are < p
, and all the positions
in f2
are >= p
.
selectC :: Range -> CompressedFile -> CompressedFile Source #
Inspection
smallestPosC :: CompressedFile -> Maybe Int Source #
Returns the smallest position, if any, in the CompressedFile
.
Merge
mergeC :: CompressedFile -> CompressedFile -> CompressedFile Source #
Merges compressed files.