Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
10 changes: 10 additions & 0 deletions RetailCoder.VBE/Common/DeclarationExtensions.cs
Original file line number Diff line number Diff line change
Expand Up @@ -216,6 +216,16 @@ public static IEnumerable<Declaration> FindEventHandlers(this IEnumerable<Declar
&& declaration.IdentifierName.StartsWith(control.IdentifierName + "_"));
}

public static IEnumerable<Declaration> FindBuiltInEventHandlers(this IEnumerable<Declaration> declarations)
{
var handlerNames = declarations.Where(declaration => declaration.IsBuiltIn && declaration.DeclarationType == DeclarationType.Event)
.Select(e => e.ParentDeclaration.IdentifierName + "_" + e.IdentifierName);

return declarations.Where(declaration => !declaration.IsBuiltIn
&& declaration.DeclarationType == DeclarationType.Procedure
&& handlerNames.Contains(declaration.IdentifierName));
}

/// <summary>
/// Gets the <see cref="Declaration"/> of the specified <see cref="type"/>,
/// at the specified <see cref="selection"/>.
Expand Down
17 changes: 11 additions & 6 deletions RetailCoder.VBE/Inspections/ParameterNotUsedInspection.cs
Original file line number Diff line number Diff line change
Expand Up @@ -33,13 +33,14 @@ public ParameterNotUsedInspection(VBE vbe, RubberduckParserState state, IMessage

public override IEnumerable<CodeInspectionResultBase> GetInspectionResults()
{
var declarations = UserDeclarations.ToList();
var declarations = Declarations.ToList();

var interfaceMemberScopes = declarations.FindInterfaceMembers().Select(m => m.Scope).ToList();
var interfaceImplementationMemberScopes = declarations.FindInterfaceImplementationMembers().Select(m => m.Scope).ToList();

var parameters = declarations.Where(parameter => !parameter.IsBuiltIn
&& parameter.DeclarationType == DeclarationType.Parameter
var builtInHandlers = declarations.FindBuiltInEventHandlers();

var parameters = declarations.Where(parameter => parameter.DeclarationType == DeclarationType.Parameter
&& !(parameter.Context.Parent.Parent is VBAParser.EventStmtContext)
&& !(parameter.Context.Parent.Parent is VBAParser.DeclareStmtContext));

Expand All @@ -50,9 +51,13 @@ public override IEnumerable<CodeInspectionResultBase> GetInspectionResults()
new RemoveParametersPresenterFactory(editor,
new RemoveParametersDialog(), State, _messageBox), editor);

var issues = from issue in unused.Where(parameter => !IsInterfaceMemberParameter(parameter, interfaceMemberScopes))
let isInterfaceImplementationMember = IsInterfaceMemberImplementationParameter(issue, interfaceImplementationMemberScopes)
select new ParameterNotUsedInspectionResult(this, string.Format(Description, issue.IdentifierName), ((dynamic)issue.Context).ambiguousIdentifier(), issue.QualifiedName, isInterfaceImplementationMember, quickFixRefactoring, State);
var issues = from issue in unused.Where(parameter =>
!IsInterfaceMemberParameter(parameter, interfaceMemberScopes)
&& !builtInHandlers.Contains(parameter.ParentDeclaration))
let isInterfaceImplementationMember = IsInterfaceMemberImplementationParameter(issue, interfaceImplementationMemberScopes)
select new ParameterNotUsedInspectionResult(this, string.Format(Description, issue.IdentifierName),
((dynamic) issue.Context).ambiguousIdentifier(), issue.QualifiedName,
isInterfaceImplementationMember, quickFixRefactoring, State);

return issues.ToList();
}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,9 @@ public override IEnumerable<CodeInspectionResultBase> GetInspectionResults()
{
var usages = UserDeclarations.Where(declaration =>
declaration.DeclarationType == DeclarationType.Variable
&& !UserDeclarations.Any(d => d.DeclarationType == DeclarationType.UserDefinedType
&& d.IdentifierName == declaration.AsTypeName)
&& !declaration.IsSelfAssigned
&& !declaration.References.Any(reference => reference.IsAssignment))
.SelectMany(declaration => declaration.References)
.Where(usage => !usage.IsInspectionDisabled(AnnotationName));
Expand Down
Original file line number Diff line number Diff line change
@@ -1,19 +1,15 @@
using System;
using System.Collections.Generic;
using System.Drawing;
using System.Linq;
using System.Windows.Media.Imaging;
using Microsoft.Vbe.Interop;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using resx = Rubberduck.UI.CodeExplorer.CodeExplorer;

namespace Rubberduck.Navigation.CodeExplorer
{
public class CodeExplorerComponentViewModel : ViewModelBase
public class CodeExplorerComponentViewModel : CodeExplorerItemViewModel
{
private readonly Declaration _declaration;
private readonly IEnumerable<CodeExplorerMemberViewModel> _members;

private static readonly DeclarationType[] MemberTypes =
{
Expand All @@ -34,18 +30,16 @@ public class CodeExplorerComponentViewModel : ViewModelBase
public CodeExplorerComponentViewModel(Declaration declaration, IEnumerable<Declaration> declarations)
{
_declaration = declaration;
_members = declarations.GroupBy(item => item.Scope).SelectMany(grouping =>
_icon = Icons[DeclarationType];
Items = declarations.GroupBy(item => item.Scope).SelectMany(grouping =>
grouping.Where(item => item.ParentDeclaration != null
&& MemberTypes.Contains(item.DeclarationType)
&& item.ParentDeclaration.Equals(declaration))
&& item.ParentScope == declaration.Scope
&& MemberTypes.Contains(item.DeclarationType))
.OrderBy(item => item.QualifiedSelection.Selection.StartLine)
.Select(item => new CodeExplorerMemberViewModel(item, grouping)))
.ToList();
.Select(item => new CodeExplorerMemberViewModel(item, grouping)));

}

public IEnumerable<CodeExplorerMemberViewModel> Members { get { return _members; } }

private bool _isErrorState;
public bool IsErrorState { get { return _isErrorState; } set { _isErrorState = value; OnPropertyChanged(); } }

Expand All @@ -58,7 +52,7 @@ public bool IsTestModule
}
}

public string Name { get { return _declaration.IdentifierName; } }
public override string Name { get { return _declaration.IdentifierName; } }


private vbext_ComponentType ComponentType { get { return _declaration.QualifiedName.QualifiedModuleName.Component.Type; } }
Expand Down Expand Up @@ -93,6 +87,8 @@ private DeclarationType DeclarationType
{ DeclarationType.Document, GetImageSource(resx.document_office) }
};

public BitmapImage Icon { get { return Icons[DeclarationType]; } }
private readonly BitmapImage _icon;
public override BitmapImage CollapsedIcon { get { return _icon; } }
public override BitmapImage ExpandedIcon { get { return _icon; } }
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -2,16 +2,13 @@
using System.Linq;
using System.Windows.Media.Imaging;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using resx = Rubberduck.Properties.Resources;

namespace Rubberduck.Navigation.CodeExplorer
{
public class CodeExplorerCustomFolderViewModel : ViewModelBase
public class CodeExplorerCustomFolderViewModel : CodeExplorerItemViewModel
{
private readonly string _name;
private readonly IEnumerable<CodeExplorerComponentViewModel> _components;

private static readonly DeclarationType[] ComponentTypes =
{
DeclarationType.Class,
Expand All @@ -24,28 +21,30 @@ public CodeExplorerCustomFolderViewModel(string name, IEnumerable<Declaration> d
{
_name = name;

var items = declarations.ToList();
_collapsedIcon = GetImageSource(resx.folder_horizontal);
_expandedIcon = GetImageSource(resx.folder_horizontal_open);

_components = items.GroupBy(item => item.ComponentName)
.SelectMany(grouping =>
grouping.Where(item => ComponentTypes.Contains(item.DeclarationType))
.Select(item => new CodeExplorerComponentViewModel(item, grouping)))
.OrderBy(item => item.Name)
.ToList();
var items = declarations.ToList();

_blueFolderCollapsed = GetImageSource(resx.blue_folder_horizontal);
_blueFolderExpanded = GetImageSource(resx.blue_folder_horizontal_open);
var parents = items.GroupBy(item => item.ComponentName).OrderBy(item => item.Key).ToList();
foreach (var component in parents)
{
var moduleName = component.Key;
var parent = items.Single(item =>
ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName);
var members = items.Where(item =>
!ComponentTypes.Contains(item.DeclarationType) && item.ComponentName == moduleName);

AddChild(new CodeExplorerComponentViewModel(parent, members));
}
}

private readonly BitmapImage _blueFolderCollapsed;
public BitmapImage BlueFolderCollapsed { get { return _blueFolderCollapsed; } }

private readonly BitmapImage _blueFolderExpanded;
public BitmapImage BlueFolderExpanded { get { return _blueFolderExpanded; } }

public override string Name { get { return _name; } }

public string Name { get { return _name; } }
private readonly BitmapImage _collapsedIcon;
public override BitmapImage CollapsedIcon { get { return _collapsedIcon; } }

public IEnumerable<CodeExplorerComponentViewModel> Components { get { return _components; } }
private readonly BitmapImage _expandedIcon;
public override BitmapImage ExpandedIcon { get { return _expandedIcon; } }
}
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,40 @@
using System.Collections.Generic;
using System.Linq;
using System.Windows.Media.Imaging;
using Rubberduck.UI;

namespace Rubberduck.Navigation.CodeExplorer
{
public abstract class CodeExplorerItemViewModel : ViewModelBase
{
private IList<CodeExplorerItemViewModel> _items = new List<CodeExplorerItemViewModel>();
public IEnumerable<CodeExplorerItemViewModel> Items { get { return _items; } protected set { _items = value.ToList(); } }

public abstract string Name { get; }
public abstract BitmapImage CollapsedIcon { get; }
public abstract BitmapImage ExpandedIcon { get; }

public CodeExplorerItemViewModel GetChild(string name)
{
foreach (var item in _items)
{
if (item.Name == name)
{
return item;
}
var result = item.GetChild(name);
if (result != null)
{
return result;
}
}

return null;
}

public void AddChild(CodeExplorerItemViewModel item)
{
_items.Add(item);
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -3,12 +3,11 @@
using System.Linq;
using System.Windows.Media.Imaging;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using resx = Rubberduck.UI.CodeExplorer.CodeExplorer;

namespace Rubberduck.Navigation.CodeExplorer
{
public class CodeExplorerMemberViewModel : ViewModelBase
public class CodeExplorerMemberViewModel : CodeExplorerItemViewModel
{
private readonly Declaration _declaration;

Expand All @@ -22,7 +21,7 @@ public class CodeExplorerMemberViewModel : ViewModelBase
new Dictionary<Tuple<DeclarationType, Accessibility>, BitmapImage>
{
{ Tuple.Create(DeclarationType.Constant, Accessibility.Private), GetImageSource(resx.VSObject_Constant_Private)},
{ Tuple.Create(DeclarationType.Constant, Accessibility.Public), GetImageSource(resx.VSObject_Field)},
{ Tuple.Create(DeclarationType.Constant, Accessibility.Public), GetImageSource(resx.VSObject_Constant)},
{ Tuple.Create(DeclarationType.Enumeration, Accessibility.Public), GetImageSource(resx.VSObject_Enum)},
{ Tuple.Create(DeclarationType.Enumeration, Accessibility.Private ), GetImageSource(resx.VSObject_EnumPrivate)},
{ Tuple.Create(DeclarationType.EnumerationMember, Accessibility.Public), GetImageSource(resx.VSObject_EnumItem)},
Expand Down Expand Up @@ -61,24 +60,51 @@ public CodeExplorerMemberViewModel(Declaration declaration, IEnumerable<Declarat
_declaration = declaration;
if (declarations != null)
{
_members = declarations.Where(item => SubMemberTypes.Contains(item.DeclarationType) && item.ParentDeclaration.Equals(declaration))
.Select(item => new CodeExplorerMemberViewModel(item, null))
.OrderBy(item => item.Name);
Items = declarations.Where(item => SubMemberTypes.Contains(item.DeclarationType) && item.ParentDeclaration.Equals(declaration))
.OrderBy(item => item.Selection.StartLine)
.Select(item => new CodeExplorerMemberViewModel(item, null));
}

var modifier = declaration.Accessibility == Accessibility.Global || declaration.Accessibility == Accessibility.Implicit
? Accessibility.Public
: declaration.Accessibility;
var key = Tuple.Create(declaration.DeclarationType, modifier);

_name = DetermineMemberName(declaration);
_icon = Mappings[key];
}

public string Name { get { return _declaration.IdentifierName; } }
private readonly string _name;
public override string Name { get { return _name; } }

private readonly BitmapImage _icon;
public BitmapImage Icon { get { return _icon; } }
private static string DetermineMemberName(Declaration declaration)
{
var type = declaration.DeclarationType;
switch (type)
{
case DeclarationType.PropertyGet:
return declaration.IdentifierName + " (Get)";
case DeclarationType.PropertyLet:
return declaration.IdentifierName + " (Let)";
case DeclarationType.PropertySet:
return declaration.IdentifierName + " (Set)";
case DeclarationType.Variable:
if (declaration.IsArray())
{
return declaration.IdentifierName + "()";
}
return declaration.IdentifierName;
case DeclarationType.Constant:
var valuedDeclaration = (ValuedDeclaration)declaration;
return valuedDeclaration.IdentifierName + " = " + valuedDeclaration.Value;

private readonly IEnumerable<CodeExplorerMemberViewModel> _members;
public IEnumerable<CodeExplorerMemberViewModel> Members { get { return _members; } }
default:
return declaration.IdentifierName;
}
}

private readonly BitmapImage _icon;
public override BitmapImage CollapsedIcon { get { return _icon; } }
public override BitmapImage ExpandedIcon { get { return _icon; } }
}
}
Loading