Skip to content

Commit

Permalink
Redesign Annotation Processing
Browse files Browse the repository at this point in the history
This redesigns annotation processing to no longer rely on the AnnotationTypes enum to identify
an annotation, allowing us to separate the scoping of an annotation from it's type.

Additionally this explicitly stores metainformation on annotations in Attributes on the specific
annotation type. This metainformation is used to automatically register annotations for the
code pane parsing process.

These changes have far-reaching implications for how annotations are used, most of them addressed
in this commit. The parsing of annotations through the VBA API is not correctly dealt with.
  • Loading branch information
Vogel612 committed Aug 26, 2019
1 parent 870cbdf commit bdd8c6d
Show file tree
Hide file tree
Showing 85 changed files with 646 additions and 736 deletions.
6 changes: 5 additions & 1 deletion Rubberduck.API/VBA/Parser.cs
Expand Up @@ -25,6 +25,7 @@
using Rubberduck.Root;
using Rubberduck.VBEditor.ComManagement.TypeLibs;
using Rubberduck.VBEditor.SourceCodeHandling;
using Rubberduck.Parsing.Annotations;

namespace Rubberduck.API.VBA
{
Expand Down Expand Up @@ -106,6 +107,8 @@ internal Parser(object vbe) : this()
var preprocessorErrorListenerFactory = new PreprocessingParseErrorListenerFactory();
var preprocessorParser = new VBAPreprocessorParser(preprocessorErrorListenerFactory, preprocessorErrorListenerFactory);
var preprocessor = new VBAPreprocessor(preprocessorParser, compilationsArgumentsCache);
// FIXME inject annotation types to allow Rubberduck api users to access Annotations from VBA code
var annotationProcessor = new VBAParserAnnotationFactory(new List<Type>());
var mainParseErrorListenerFactory = new MainParseErrorListenerFactory();
var mainTokenStreamParser = new VBATokenStreamParser(mainParseErrorListenerFactory, mainParseErrorListenerFactory);
var tokenStreamProvider = new SimpleVBAModuleTokenStreamProvider();
Expand Down Expand Up @@ -139,7 +142,8 @@ internal Parser(object vbe) : this()
var moduleParser = new ModuleParser(
codePaneSourceCodeHandler,
attributesSourceCodeHandler,
stringParser);
stringParser,
annotationProcessor);
var parseRunner = new ParseRunner(
_state,
parserStateManager,
Expand Down
Expand Up @@ -49,7 +49,7 @@ public AttributeValueOutOfSyncInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
.Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation));
var results = new List<DeclarationInspectionResult>();
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document))
{
Expand Down
Expand Up @@ -46,8 +46,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
foreach (var declaration in State.AllUserDeclarations)
{
var duplicateAnnotations = declaration.Annotations
.GroupBy(annotation => annotation.AnnotationType)
.Where(group => !group.First().AllowMultiple && group.Count() > 1);
.GroupBy(annotation => annotation.GetType())
.Where(group => !group.First().MetaInformation.AllowMultiple && group.Count() > 1);

issues.AddRange(duplicateAnnotations.Select(duplicate =>
{
Expand Down
Expand Up @@ -52,7 +52,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var annotations = State.AllAnnotations;

var unboundAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation)
.Where(annotation => !annotation.MetaInformation.Target.HasFlag(AnnotationTarget.General)
|| annotation.AnnotatedLine == null);
var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations);

Expand Down
Expand Up @@ -48,10 +48,12 @@ public MissingAnnotationArgumentInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
// FIXME don't actually use listeners here, iterate the Annotations instead
// FIXME don't maintain a separate list for annotations that require arguments, instead use AnnotationAttribute to store that information
return (from result in Listener.Contexts
let context = (VBAParser.AnnotationContext)result.Context
where context.annotationName().GetText() == AnnotationType.Ignore.ToString()
|| context.annotationName().GetText() == AnnotationType.Folder.ToString()
where context.annotationName().GetText() == "Ignore"
|| context.annotationName().GetText() == "Folder"
where context.annotationArgList() == null
select new QualifiedContextInspectionResult(this,
string.Format(InspectionResults.MissingAnnotationArgumentInspection,
Expand Down
Expand Up @@ -48,7 +48,7 @@ public MissingAttributeInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
.Where(declaration => declaration.Annotations.Any(annotation => annotation is IAttributeAnnotation));
var results = new List<DeclarationInspectionResult>();
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document
&& !decl.IsIgnoringInspectionResultFor(AnnotationName)))
Expand Down
Expand Up @@ -39,7 +39,7 @@ public ModuleWithoutFolderInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var modulesWithoutFolderAnnotation = State.DeclarationFinder.UserDeclarations(Parsing.Symbols.DeclarationType.Module)
.Where(w => w.Annotations.All(a => a.AnnotationType != AnnotationType.Folder))
.Where(w => !w.Annotations.OfType<FolderAnnotation>().Any())
.ToList();

return modulesWithoutFolderAnnotation
Expand Down
Expand Up @@ -58,15 +58,13 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarations = State.AllUserDeclarations
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member) &&
declaration.Annotations.Any(annotation =>annotation.AnnotationType == AnnotationType.Obsolete));
declaration.Annotations.OfType<ObsoleteAnnotation>().Any());

var issues = new List<IdentifierReferenceInspectionResult>();

foreach (var declaration in declarations)
{
var replacementDocumentation =
((ObsoleteAnnotation) declaration.Annotations.First(annotation =>
annotation.AnnotationType == AnnotationType.Obsolete)).ReplacementDocumentation;
var replacementDocumentation = declaration.Annotations.OfType<ObsoleteAnnotation>().First().ReplacementDocumentation;

issues.AddRange(declaration.References.Select(reference =>
new IdentifierReferenceInspectionResult(this,
Expand Down
Expand Up @@ -39,15 +39,15 @@ public override void Fix(IInspectionResult result, IRewriteSession rewriteSessio
}
else
{
var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues);
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues);
var (newAnnotation, newAnnotationValues) = _attributeAnnotationProvider.ModuleAttributeAnnotation(attributeName, attributeValues);
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotation, newAnnotationValues);
}
}
else
{
var attributeBaseName = AttributeBaseName(attributeName, declaration);
var (newAnnotationType, newAnnotationValues) = _attributeAnnotationProvider.MemberAttributeAnnotation(attributeBaseName, attributeValues);
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotationType, newAnnotationValues);
var (newAnnotation, newAnnotationValues) = _attributeAnnotationProvider.MemberAttributeAnnotation(attributeBaseName, attributeValues);
_annotationUpdater.UpdateAnnotation(rewriteSession, oldAnnotation, newAnnotation, newAnnotationValues);
}
}

Expand Down
8 changes: 4 additions & 4 deletions Rubberduck.CodeAnalysis/QuickFixes/IgnoreOnceQuickFix.cs
Expand Up @@ -52,17 +52,17 @@ private void FixNonModule(IInspectionResult result, IRewriteSession rewriteSessi
.OfType<IgnoreAnnotation>()
.FirstOrDefault();

var annotationType = AnnotationType.Ignore;
var annotationInfo = typeof(IgnoreAnnotation).GetCustomAttributes(false).OfType<AnnotationAttribute>().Single();
if (existingIgnoreAnnotation != null)
{
var annotationValues = existingIgnoreAnnotation.InspectionNames.ToList();
annotationValues.Insert(0, result.Inspection.AnnotationName);
_annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationType, annotationValues);
_annotationUpdater.UpdateAnnotation(rewriteSession, existingIgnoreAnnotation, annotationInfo, annotationValues);
}
else
{
var annotationValues = new List<string> { result.Inspection.AnnotationName };
_annotationUpdater.AddAnnotation(rewriteSession, new QualifiedContext(module, result.Context), annotationType, annotationValues);
_annotationUpdater.AddAnnotation(rewriteSession, new QualifiedContext(module, result.Context), annotationInfo, annotationValues);
}
}

Expand All @@ -73,7 +73,7 @@ private void FixModule(IInspectionResult result, IRewriteSession rewriteSession)
.OfType<IgnoreModuleAnnotation>()
.FirstOrDefault();

var annotationType = AnnotationType.IgnoreModule;
var annotationType = typeof(IgnoreModuleAnnotation).GetCustomAttributes(false).OfType<AnnotationAttribute>().Single();
if (existingIgnoreModuleAnnotation != null)
{
var annotationValues = existingIgnoreModuleAnnotation.InspectionNames.ToList();
Expand Down
Expand Up @@ -20,7 +20,7 @@ public RemoveDuplicatedAnnotationQuickFix(IAnnotationUpdater annotationUpdater)
public override void Fix(IInspectionResult result, IRewriteSession rewriteSession)
{
var duplicateAnnotations = result.Target.Annotations
.Where(annotation => annotation.AnnotationType == result.Properties.AnnotationType)
.Where(annotation => annotation.GetType() == result.Properties.AnnotationType)
.OrderBy(annotation => annotation.Context.Start.StartIndex)
.Skip(1)
.ToList();
Expand Down
Expand Up @@ -52,7 +52,7 @@ public CodeExplorerComponentViewModel(ICodeExplorerNode parent, Declaration decl
Declaration.Attributes.HasPredeclaredIdAttribute(out _);

public bool IsTestModule => Declaration.DeclarationType == DeclarationType.ProceduralModule
&& Declaration.Annotations.Any(annotation => annotation.AnnotationType == AnnotationType.TestModule);
&& Declaration.Annotations.Any(annotation => annotation is TestModuleAnnotation);

public override void Synchronize(ref List<Declaration> updated)
{
Expand Down
Expand Up @@ -51,7 +51,7 @@ public override string NameWithSignature
}

public override bool IsObsolete =>
Declaration.Annotations.Any(annotation => annotation.AnnotationType == AnnotationType.Obsolete);
Declaration.Annotations.Any(annotation => annotation is ObsoleteAnnotation);

public static readonly DeclarationType[] SubMemberTypes =
{
Expand Down
10 changes: 5 additions & 5 deletions Rubberduck.Core/UI/CodeExplorer/Commands/IndentCommand.cs
Expand Up @@ -47,14 +47,14 @@ private bool SpecialEvaluateCanExecute(object parameter)
case CodeExplorerProjectViewModel project:
return _state.AllUserDeclarations
.Any(c => c.DeclarationType.HasFlag(DeclarationType.Module) &&
c.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent) &&
!c.Annotations.Any(a => a is NoIndentAnnotation) &&
c.ProjectId == project.Declaration.ProjectId);
case CodeExplorerCustomFolderViewModel folder:
return folder.Children.OfType<CodeExplorerComponentViewModel>() //TODO - this has the filter applied.
.Select(s => s.Declaration)
.Any(d => d.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent));
.Any(d => !d.Annotations.Any(a => a is NoIndentAnnotation));
case CodeExplorerComponentViewModel model:
return model.Declaration.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent);
return !model.Declaration.Annotations.Any(a => a is NoIndentAnnotation);
case CodeExplorerMemberViewModel member:
return member.QualifiedSelection.HasValue;
default:
Expand All @@ -79,7 +79,7 @@ protected override void OnExecute(object parameter)

var componentDeclarations = _state.AllUserDeclarations.Where(c =>
c.DeclarationType.HasFlag(DeclarationType.Module) &&
c.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent) &&
!c.Annotations.Any(a => a is NoIndentAnnotation) &&
c.ProjectId == declaration.ProjectId);

foreach (var componentDeclaration in componentDeclarations)
Expand All @@ -93,7 +93,7 @@ protected override void OnExecute(object parameter)
{
var components = folder.Children.OfType<CodeExplorerComponentViewModel>() //TODO: this has the filter applied.
.Select(s => s.Declaration)
.Where(d => d.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent))
.Where(d => !d.Annotations.Any(a => a is NoIndentAnnotation))
.Select(d => _state.ProjectsProvider.Component(d.QualifiedName.QualifiedModuleName));

foreach (var component in components)
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Core/UI/Command/NoIndentAnnotationCommand.cs
Expand Up @@ -29,7 +29,7 @@ private bool SpecialEvaluateCanExecute(object parameter)
return pane != null
&& !pane.IsWrappingNullReference
&& target != null
&& target.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent);
&& !target.Annotations.Any(a => a is NoIndentAnnotation);
}
}

Expand Down
Expand Up @@ -105,7 +105,7 @@ public override object Convert(object value, Type targetType, object parameter,
return value is ICodeExplorerNode node &&
node.Declaration != null &&
DeclarationIcons.ContainsKey(node.Declaration.DeclarationType)
? node.Declaration.Annotations.Any(a => a.AnnotationType == AnnotationType.TestMethod)
? node.Declaration.Annotations.Any(a => a is TestMethodAnnotation)
? TestMethodIcon
: DeclarationIcons[node.Declaration.DeclarationType]
: ExceptionIcon;
Expand Down
Expand Up @@ -47,7 +47,7 @@ private bool SpecialEvaluateCanExecute(object parameter)

var testModules = _state.AllUserDeclarations.Where(d =>
d.DeclarationType == DeclarationType.ProceduralModule &&
d.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule));
d.Annotations.Any(a => a is TestModuleAnnotation));

try
{
Expand Down
Expand Up @@ -41,7 +41,7 @@ private bool SpecialEvaluateCanExecute(object parameter)
}
var testModules = _state.AllUserDeclarations.Where(d =>
d.DeclarationType == DeclarationType.ProceduralModule &&
d.Annotations.Any(a => a.AnnotationType == AnnotationType.TestModule));
d.Annotations.Any(a => a is TestModuleAnnotation));

try
{
Expand Down
5 changes: 3 additions & 2 deletions Rubberduck.Core/UI/UnitTesting/TestExplorerViewModel.cs
Expand Up @@ -10,6 +10,7 @@
using Rubberduck.Common;
using Rubberduck.Interaction.Navigation;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources;
Expand Down Expand Up @@ -374,7 +375,7 @@ private void ExecuteIgnoreTestCommand(object parameter)
{
var rewriteSession = RewritingManager.CheckOutCodePaneSession();

AnnotationUpdater.AddAnnotation(rewriteSession, _mousedOverTestMethod.Declaration, Parsing.Annotations.AnnotationType.IgnoreTest);
AnnotationUpdater.AddAnnotation(rewriteSession, _mousedOverTestMethod.Declaration, typeof(IgnoreTestAnnotation).GetCustomAttributes(false).OfType<AnnotationAttribute>().Single());

rewriteSession.TryRewrite();
}
Expand All @@ -383,7 +384,7 @@ private void ExecuteUnignoreTestCommand(object parameter)
{
var rewriteSession = RewritingManager.CheckOutCodePaneSession();
var ignoreTestAnnotations = _mousedOverTestMethod.Declaration.Annotations
.Where(iannotations => iannotations.AnnotationType == Parsing.Annotations.AnnotationType.IgnoreTest);
.Where(iannotations => iannotations is IgnoreTestAnnotation);

foreach (var ignoreTestAnnotation in ignoreTestAnnotations)
{
Expand Down
23 changes: 21 additions & 2 deletions Rubberduck.JunkDrawer/Output/StringExtensions.cs
Expand Up @@ -15,13 +15,32 @@ public static string Capitalize(this string input)
tokens[0] = CultureInfo.CurrentUICulture.TextInfo.ToTitleCase(tokens[0]);
return string.Join(" ", tokens);
}

public static string CapitalizeFirstLetter(this string input)
{
{
if (input.Length == 0)
{
return string.Empty;
}
return input.Capitalize().Substring(0, 1) + input.Substring(1);
}
}

public static string UnQuote(this string input)
{
if (input[0] == '"' && input[input.Length - 1] == '"')
{
return input.Substring(1, input.Length - 2);
}
return input;
}

public static string EnQuote(this string input)
{
if (input[0] == '"' && input[input.Length - 1] == '"')
{
return input;
}
return $"\"{input}\"";
}
}
}

0 comments on commit bdd8c6d

Please sign in to comment.