Skip to content

Commit

Permalink
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck i…
Browse files Browse the repository at this point in the history
…nto next
  • Loading branch information
ThunderFrame committed Jun 4, 2016
2 parents 44eb5af + 760ec98 commit 9137c48
Show file tree
Hide file tree
Showing 23 changed files with 303 additions and 168 deletions.
2 changes: 1 addition & 1 deletion RetailCoder.VBE/App.cs
Original file line number Diff line number Diff line change
Expand Up @@ -150,7 +150,7 @@ public void Startup()
_appMenus.Initialize();
_hooks.HookHotkeys(); // need to hook hotkeys before we localize menus, to correctly display ShortcutTexts
_appMenus.Localize();
Task.Delay(1000).ContinueWith(t => UiDispatcher.Invoke(() => _parser.State.OnParseRequested(this))).ConfigureAwait(false);
Task.Delay(1000).ContinueWith(t => UiDispatcher.Invoke(() => _parser.State.OnParseRequested(this)));
UpdateLoggingLevel();
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,13 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;

namespace Rubberduck.Inspections
{
public class FunctionReturnValueNotUsedInspectionResult : InspectionResultBase
{
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
private QualifiedMemberName _memberName;

public FunctionReturnValueNotUsedInspectionResult(
IInspection inspection,
Expand Down Expand Up @@ -49,5 +49,10 @@ public override string Description
return string.Format(InspectionsUI.FunctionReturnValueNotUsedInspectionResultFormat, Target.IdentifierName);
}
}

public override NavigateCodeEventArgs GetNavigationArgs()
{
return new NavigateCodeEventArgs(Target);
}
}
}
12 changes: 8 additions & 4 deletions RetailCoder.VBE/Inspections/IdentifierNotUsedInspectionResult.cs
Original file line number Diff line number Diff line change
Expand Up @@ -2,20 +2,19 @@
using Antlr4.Runtime;
using Rubberduck.Common;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using Rubberduck.VBEditor;

namespace Rubberduck.Inspections
{
public class IdentifierNotUsedInspectionResult : InspectionResultBase
{
private readonly Declaration _target;
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;

public IdentifierNotUsedInspectionResult(IInspection inspection, Declaration target,
ParserRuleContext context, QualifiedModuleName qualifiedName)
: base(inspection, qualifiedName, context)
: base(inspection, qualifiedName, context, target)
{
_target = target;
_quickFixes = new CodeInspectionQuickFix[]
{
new RemoveUnusedDeclarationQuickFix(context, QualifiedSelection),
Expand All @@ -28,9 +27,14 @@ public override string Description
{
get
{
return string.Format(InspectionsUI.IdentifierNotUsedInspectionResultFormat, _target.DeclarationType.ToLocalizedString(), _target.IdentifierName);
return string.Format(InspectionsUI.IdentifierNotUsedInspectionResultFormat, Target.DeclarationType.ToLocalizedString(), Target.IdentifierName);
}
}

public override NavigateCodeEventArgs GetNavigationArgs()
{
return new NavigateCodeEventArgs(Target);
}
}

/// <summary>
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using Rubberduck.VBEditor;

namespace Rubberduck.Inspections
Expand Down Expand Up @@ -30,6 +31,11 @@ public override string Description
return string.Format(InspectionsUI.ImplicitPublicMemberInspectionResultFormat, Target.IdentifierName);
}
}

public override NavigateCodeEventArgs GetNavigationArgs()
{
return new NavigateCodeEventArgs(Target);
}
}

public class SpecifyExplicitPublicModifierQuickFix : CodeInspectionQuickFix
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
&& ProcedureTypes.Contains(item.DeclarationType)
&& !item.IsTypeSpecified
let issue = new {Declaration = item, QualifiedContext = new QualifiedContext<ParserRuleContext>(item.QualifiedName, item.Context)}
select new ImplicitVariantReturnTypeInspectionResult(this, issue.Declaration.IdentifierName, issue.QualifiedContext);
select new ImplicitVariantReturnTypeInspectionResult(this, issue.Declaration.IdentifierName, issue.QualifiedContext, item);
return issues;
}
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,9 @@
using Antlr4.Runtime;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.Nodes;
using Rubberduck.UI;
using Rubberduck.VBEditor;

namespace Rubberduck.Inspections
Expand All @@ -12,8 +14,8 @@ public sealed class ImplicitVariantReturnTypeInspectionResult : InspectionResult
private readonly string _identifierName;
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;

public ImplicitVariantReturnTypeInspectionResult(IInspection inspection, string identifierName, QualifiedContext<ParserRuleContext> qualifiedContext)
: base(inspection, qualifiedContext.ModuleName, qualifiedContext.Context)
public ImplicitVariantReturnTypeInspectionResult(IInspection inspection, string identifierName, QualifiedContext<ParserRuleContext> qualifiedContext, Declaration target)
: base(inspection, qualifiedContext.ModuleName, qualifiedContext.Context, target)
{
_identifierName = identifierName;
_quickFixes = new CodeInspectionQuickFix[]
Expand All @@ -33,6 +35,11 @@ public override string Description
_identifierName);
}
}

public override NavigateCodeEventArgs GetNavigationArgs()
{
return new NavigateCodeEventArgs(Target);
}
}

public class SetExplicitVariantReturnTypeQuickFix : CodeInspectionQuickFix
Expand Down
2 changes: 1 addition & 1 deletion RetailCoder.VBE/Inspections/InspectionResultBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,7 @@ public override string ToString()
QualifiedSelection.Selection.StartLine);
}

public NavigateCodeEventArgs GetNavigationArgs()
public virtual NavigateCodeEventArgs GetNavigationArgs()
{
return new NavigateCodeEventArgs(QualifiedSelection);
}
Expand Down
17 changes: 3 additions & 14 deletions RetailCoder.VBE/Inspections/Inspector.cs
Original file line number Diff line number Diff line change
Expand Up @@ -55,11 +55,8 @@ public async Task<IEnumerable<ICodeInspectionResult>> FindIssuesAsync(Rubberduck
return new ICodeInspectionResult[] { };
}

await Task.Yield();

state.OnStatusMessageUpdate(RubberduckUI.CodeInspections_Inspecting);
UpdateInspectionSeverity();
//OnReset();

var allIssues = new ConcurrentBag<ICodeInspectionResult>();

Expand All @@ -72,31 +69,23 @@ public async Task<IEnumerable<ICodeInspectionResult>> FindIssuesAsync(Rubberduck

var inspections = _inspections.Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow)
.Select(inspection =>
new Task(() =>
Task.Run(() =>
{
token.ThrowIfCancellationRequested();
var inspectionResults = inspection.GetInspectionResults();
var results = inspectionResults as IEnumerable<InspectionResultBase> ?? inspectionResults;
if (results.Any())
{
//OnIssuesFound(results);
foreach (var inspectionResult in results)
{
allIssues.Add(inspectionResult);
}
}
})).ToArray();

foreach (var inspection in inspections)
{
inspection.Start();
}
})).ToList();

Task.WaitAll(inspections);
await Task.WhenAll(inspections);
state.OnStatusMessageUpdate(RubberduckUI.ResourceManager.GetString("ParserState_" + state.Status)); // should be "Ready"

return allIssues;
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
using Antlr4.Runtime;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;

namespace Rubberduck.Inspections
{
Expand Down Expand Up @@ -33,5 +34,10 @@ public override string Description
return string.Format(InspectionsUI.NonReturningFunctionInspectionResultFormat, Target.IdentifierName);
}
}

public override NavigateCodeEventArgs GetNavigationArgs()
{
return new NavigateCodeEventArgs(Target);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ public class ExtractMethodSelectionValidation : IExtractMethodSelectionValidatio
private IEnumerable<Declaration> _declarations;



public ExtractMethodSelectionValidation(IEnumerable<Declaration> declarations)
{
_declarations = declarations;
Expand Down Expand Up @@ -56,10 +56,15 @@ public bool withinSingleProcedure(QualifiedSelection qualifiedSelection)
{
procStartContext = procStart.Context as VBAParser.SubStmtContext;
}
// TOOD: Doesn't support properties.
if (procStartContext == null)
{
return false;
}
var procEndOfSignature = procStartContext.endOfStatement() as VBAParser.EndOfStatementContext;
var procSignatureLastLine = procEndOfSignature.Start.Line;

return (procEnd as Declaration).QualifiedSelection.Equals((procStart as Declaration).QualifiedSelection)
return (procEnd as Declaration).QualifiedSelection.Equals((procStart as Declaration).QualifiedSelection)
&& (procSignatureLastLine < startLine);

}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,8 @@ public object Convert(object value, Type targetType, object parameter, CultureIn

public object ConvertBack(object value, Type targetType, object parameter, CultureInfo culture)
{
throw new NotImplementedException();
var converter = new InspectionSeverityImageSourceConverter();
return converter.ConvertBack(value, targetType, parameter, culture);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -554,7 +554,7 @@
ItemsSource="{Binding Source={StaticResource ResultsByInspectionType}}"
Visibility="{Binding IsChecked, ElementName=GroupByInspectionType, Converter={StaticResource BoolToVisibility}}">
<DataGrid.Columns>
<DataGridTemplateColumn Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeInspectionResults_Type}">
<DataGridTemplateColumn Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeInspectionResults_Type}" SortDirection="Descending">
<DataGridTemplateColumn.CellTemplate>
<DataTemplate DataType="inspections:ICodeInspectionResult">
<Image Source="{Binding Inspection, Converter={StaticResource InspectionIconConverter}}" Height="16" />
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
using System.Drawing;
using System.Globalization;
using System.IO;
using System.Linq;
using System.Windows.Data;
using System.Windows.Media;
using System.Windows.Media.Imaging;
Expand All @@ -15,7 +16,6 @@ public class InspectionSeverityImageSourceConverter : IValueConverter
private static readonly IDictionary<CodeInspectionSeverity,ImageSource> Icons =
new Dictionary<CodeInspectionSeverity, ImageSource>
{
{ CodeInspectionSeverity.DoNotShow, null },
{ CodeInspectionSeverity.Hint, ToImageSource(Properties.Resources.information_white) },
{ CodeInspectionSeverity.Suggestion, ToImageSource(Properties.Resources.information) },
{ CodeInspectionSeverity.Warning, ToImageSource(Properties.Resources.exclamation) },
Expand All @@ -35,7 +35,7 @@ public object Convert(object value, Type targetType, object parameter, CultureIn

public object ConvertBack(object value, Type targetType, object parameter, CultureInfo culture)
{
throw new NotImplementedException();
return Icons.First(f => f.Value == value).Key;
}

private static ImageSource ToImageSource(Image source)
Expand Down
3 changes: 3 additions & 0 deletions Rubberduck.Parsing/Rubberduck.Parsing.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@
<Reference Include="Antlr4.Runtime.net45">
<HintPath>..\packages\Antlr4.Runtime.4.3.0\lib\net45\Antlr4.Runtime.net45.dll</HintPath>
</Reference>
<Reference Include="Microsoft.Build.Tasks.v4.0" />
<Reference Include="Microsoft.Vbe.Interop, Version=12.0.0.0, Culture=neutral, PublicKeyToken=71e9bce111e9429c">
<SpecificVersion>False</SpecificVersion>
<EmbedInteropTypes>False</EmbedInteropTypes>
Expand Down Expand Up @@ -126,6 +127,8 @@
<Compile Include="Preprocessing\VBAConditionalCompilationParserBaseVisitor.cs" />
<Compile Include="Preprocessing\VBAConditionalCompilationParserListener.cs" />
<Compile Include="Preprocessing\VBAConditionalCompilationParserVisitor.cs" />
<Compile Include="Symbols\ComInformation.cs" />
<Compile Include="Symbols\ComParameter.cs" />
<Compile Include="Symbols\Identifier.cs" />
<Compile Include="Binding\IBindingContext.cs" />
<Compile Include="Binding\IBoundExpression.cs" />
Expand Down
33 changes: 33 additions & 0 deletions Rubberduck.Parsing/Symbols/ComInformation.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,33 @@
using System.Runtime.InteropServices.ComTypes;
using Rubberduck.VBEditor;

namespace Rubberduck.Parsing.Symbols
{
public class ComInformation
{
public ComInformation(TYPEATTR typeAttributes, IMPLTYPEFLAGS implTypeFlags, ITypeInfo typeInfo, string typeName, QualifiedModuleName typeModuleName, Declaration moduleDeclaration, DeclarationType typeDeclarationType)
{
TypeAttributes = typeAttributes;
ImplTypeFlags = implTypeFlags;
TypeInfo = typeInfo;
TypeName = typeName;
TypeQualifiedModuleName = typeModuleName;
ModuleDeclaration = moduleDeclaration;
TypeDeclarationType = typeDeclarationType;
}

public TYPEATTR TypeAttributes { get; internal set; }
public IMPLTYPEFLAGS ImplTypeFlags { get; internal set; }
public ITypeInfo TypeInfo { get; internal set; }

public string TypeName { get; internal set; }
public QualifiedModuleName TypeQualifiedModuleName { get; internal set; }
public Declaration ModuleDeclaration { get; internal set; }
public DeclarationType TypeDeclarationType { get; internal set; }

public override string ToString()
{
return ModuleDeclaration.IdentifierName;
}
}
}
21 changes: 21 additions & 0 deletions Rubberduck.Parsing/Symbols/ComParameter.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
using System;
using System.Collections.Generic;
using System.Linq;
using System.Text;
using System.Threading.Tasks;

namespace Rubberduck.Parsing.Symbols
{
public class ComParameter
{
public bool IsArray { get; set; }
public bool IsByRef { get; set;}
public string Name { get; set;}

public ComParameter(string name, bool byRef)
{
Name = name;
IsByRef = byRef;
}
}
}

0 comments on commit 9137c48

Please sign in to comment.