Skip to content

Commit

Permalink
Merge pull request #2214 from retailcoder/next
Browse files Browse the repository at this point in the history
Code Inspection fixes
  • Loading branch information
retailcoder committed Sep 4, 2016
2 parents 86012c3 + b035f68 commit 6aa9466
Show file tree
Hide file tree
Showing 19 changed files with 140 additions and 51 deletions.
2 changes: 1 addition & 1 deletion RetailCoder.VBE/Rubberduck.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -1472,4 +1472,4 @@
<Target Name="AfterBuild">
</Target>
-->
</Project>
</Project>
6 changes: 3 additions & 3 deletions RetailCoder.VBE/Settings/CodeInspectionConfigProvider.cs
Original file line number Diff line number Diff line change
Expand Up @@ -15,14 +15,14 @@ public CodeInspectionConfigProvider(IPersistanceService<CodeInspectionSettings>

public CodeInspectionSettings Create()
{
var prototype = new CodeInspectionSettings(GetDefaultCodeInspections(), new WhitelistedIdentifierSetting[] { });
return _persister.Load(prototype) ?? prototype;
var prototype = new CodeInspectionSettings(GetDefaultCodeInspections(), new WhitelistedIdentifierSetting[] { }, true);
return _persister.Load(prototype) ?? prototype;
}

public CodeInspectionSettings CreateDefaults()
{
//This no longer sucks.
return new CodeInspectionSettings(GetDefaultCodeInspections(), new WhitelistedIdentifierSetting[] {});
return new CodeInspectionSettings(GetDefaultCodeInspections(), new WhitelistedIdentifierSetting[] {}, true);
}

public void Save(CodeInspectionSettings settings)
Expand Down
8 changes: 6 additions & 2 deletions RetailCoder.VBE/Settings/CodeInspectionSettings.cs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ public interface ICodeInspectionSettings
{
HashSet<CodeInspectionSetting> CodeInspections { get; set; }
WhitelistedIdentifierSetting[] WhitelistedIdentifiers { get; set; }
bool RunInspectionsOnSuccessfulParse { get; set; }
}

[XmlType(AnonymousType = true)]
Expand All @@ -22,14 +23,17 @@ public class CodeInspectionSettings : ICodeInspectionSettings
[XmlArrayItem("WhitelistedIdentifier", IsNullable = false)]
public WhitelistedIdentifierSetting[] WhitelistedIdentifiers { get; set; }

public CodeInspectionSettings() : this(new HashSet<CodeInspectionSetting>(), new WhitelistedIdentifierSetting[] {})
public bool RunInspectionsOnSuccessfulParse { get; set; }

public CodeInspectionSettings() : this(new HashSet<CodeInspectionSetting>(), new WhitelistedIdentifierSetting[] {}, true)
{
}

public CodeInspectionSettings(HashSet<CodeInspectionSetting> inspections, WhitelistedIdentifierSetting[] whitelistedNames)
public CodeInspectionSettings(HashSet<CodeInspectionSetting> inspections, WhitelistedIdentifierSetting[] whitelistedNames, bool runInspectionsOnParse)
{
CodeInspections = inspections;
WhitelistedIdentifiers = whitelistedNames;
RunInspectionsOnSuccessfulParse = runInspectionsOnParse;
}

public CodeInspectionSetting GetSetting(Type inspection)
Expand Down
7 changes: 5 additions & 2 deletions RetailCoder.VBE/Settings/ConfigurationLoader.cs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,11 @@ public class ConfigurationChangedEventArgs : EventArgs
{
public bool LanguageChanged { get; private set; }
public bool InspectionSettingsChanged { get; private set; }
public bool RunInspectionsOnReparse { get; private set; }

public ConfigurationChangedEventArgs(bool languageChanged, bool inspectionSettingsChanged)
public ConfigurationChangedEventArgs(bool runInspections, bool languageChanged, bool inspectionSettingsChanged)
{
RunInspectionsOnReparse = runInspections;
LanguageChanged = languageChanged;
InspectionSettingsChanged = inspectionSettingsChanged;
}
Expand Down Expand Up @@ -82,6 +84,7 @@ public void SaveConfiguration(Configuration toSerialize)
var langChanged = _generalProvider.Create().Language.Code != toSerialize.UserSettings.GeneralSettings.Language.Code;
var oldInspectionSettings = _inspectionProvider.Create().CodeInspections.Select(s => Tuple.Create(s.Name, s.Severity));
var newInspectionSettings = toSerialize.UserSettings.CodeInspectionSettings.CodeInspections.Select(s => Tuple.Create(s.Name, s.Severity));
var inspectOnReparse = toSerialize.UserSettings.CodeInspectionSettings.RunInspectionsOnSuccessfulParse;

_generalProvider.Save(toSerialize.UserSettings.GeneralSettings);
_hotkeyProvider.Save(toSerialize.UserSettings.HotkeySettings);
Expand All @@ -90,7 +93,7 @@ public void SaveConfiguration(Configuration toSerialize)
_unitTestProvider.Save(toSerialize.UserSettings.UnitTestSettings);
_indenterProvider.Save(toSerialize.UserSettings.IndenterSettings);

OnSettingsChanged(new ConfigurationChangedEventArgs(langChanged, !oldInspectionSettings.SequenceEqual(newInspectionSettings)));
OnSettingsChanged(new ConfigurationChangedEventArgs(inspectOnReparse, langChanged, !oldInspectionSettings.SequenceEqual(newInspectionSettings)));
}

public event EventHandler<ConfigurationChangedEventArgs> SettingsChanged;
Expand Down
19 changes: 13 additions & 6 deletions RetailCoder.VBE/UI/Inspections/InspectionResultsViewModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,9 @@ public sealed class InspectionResultsViewModel : ViewModelBase, INavigateSelecti
_openSettingsCommand = new DelegateCommand(LogManager.GetCurrentClassLogger(), OpenSettings);

_configService.SettingsChanged += _configService_SettingsChanged;

// todo: remove I/O work in constructor
_runInspectionsOnReparse = _configService.LoadConfiguration().UserSettings.CodeInspectionSettings.RunInspectionsOnSuccessfulParse;

_setInspectionTypeGroupingCommand = new DelegateCommand(LogManager.GetCurrentClassLogger(), param =>
{
Expand All @@ -67,11 +70,12 @@ public sealed class InspectionResultsViewModel : ViewModelBase, INavigateSelecti
}

private void _configService_SettingsChanged(object sender, ConfigurationChangedEventArgs e)
{
{
if (e.InspectionSettingsChanged)
{
RefreshInspections();
}
_runInspectionsOnReparse = e.RunInspectionsOnReparse;
}

private ObservableCollection<ICodeInspectionResult> _results = new ObservableCollection<ICodeInspectionResult>();
Expand Down Expand Up @@ -238,32 +242,35 @@ public bool CanQuickFix

private async void ExecuteRefreshCommandAsync()
{
CanRefresh = _vbe.HostApplication() != null && _state.IsDirty();
CanRefresh = _vbe.HostApplication() != null;
if (!CanRefresh)
{
return;
}
await Task.Yield();

IsBusy = true;

_state.OnParseRequested(this);
}

private bool CanExecuteRefreshCommand(object parameter)
{
return !IsBusy && _state.IsDirty();
return !IsBusy;
}

private bool _runInspectionsOnReparse;
private void _state_StateChanged(object sender, EventArgs e)
{
if (_state.Status != ParserState.Ready)
{
IsBusy = false;
return;
}

RefreshInspections();
if (sender == this || _runInspectionsOnReparse)
{
RefreshInspections();
}
}

private async void RefreshInspections()
Expand Down
18 changes: 18 additions & 0 deletions RetailCoder.VBE/UI/RubberduckUI.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

6 changes: 6 additions & 0 deletions RetailCoder.VBE/UI/RubberduckUI.fr.resx
Original file line number Diff line number Diff line change
Expand Up @@ -1571,4 +1571,10 @@ Tous ceux qui nous ont donné une étoile ou un "like"
<data name="CodeExplorer_ShowSignaturesToolTip" xml:space="preserve">
<value>Activer/désactiver les signatures</value>
</data>
<data name="CodeInspectionSettings_Misc" xml:space="preserve">
<value>Autres options</value>
</data>
<data name="CodeInspectionSettings_Misc_RunInspectionsOnSuccessfulParse" xml:space="preserve">
<value>Exécuter les inspections automatiquement</value>
</data>
</root>
6 changes: 6 additions & 0 deletions RetailCoder.VBE/UI/RubberduckUI.resx
Original file line number Diff line number Diff line change
Expand Up @@ -1775,4 +1775,10 @@ All our stargazers, likers &amp; followers, for the warm fuzzies
<data name="CodeExplorer_ExpandSubnodesToolTip" xml:space="preserve">
<value>Expand node and all child nodes</value>
</data>
<data name="CodeInspectionSettings_Misc" xml:space="preserve">
<value>Miscellaneous</value>
</data>
<data name="CodeInspectionSettings_Misc_RunInspectionsOnSuccessfulParse" xml:space="preserve">
<value>Run inspections automatically on successful parse</value>
</data>
</root>
21 changes: 20 additions & 1 deletion RetailCoder.VBE/UI/Settings/InspectionSettings.xaml
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@
xmlns:controls="clr-namespace:Rubberduck.UI.Controls"
xmlns:themes="clr-namespace:Microsoft.Windows.Themes;assembly=PresentationFramework.Aero"
mc:Ignorable="d"
d:DesignHeight="300" d:DesignWidth="300"
d:DesignWidth="300"
d:DataContext="{d:DesignInstance {x:Type settings:InspectionSettingsViewModel}, IsDesignTimeCreatable=False}">
<UserControl.Resources>
<converters:CodeInspectionSeverityEnumToTextConverter x:Key="CodeInspectionSeverityEnumToText" />
Expand Down Expand Up @@ -399,6 +399,25 @@
</DataGrid.Columns>
</DataGrid>
</Border>
<Label Background="DarkGray"
Foreground="White"
FontWeight="SemiBold"
Content="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeInspectionSettings_Misc}"
Margin="0,5,0,3">
<Label.Style>
<Style>
<Style.Resources>
<Style TargetType="{x:Type Border}">
<Setter Property="CornerRadius" Value="5"/>
</Style>
</Style.Resources>
</Style>
</Label.Style>
</Label>
<StackPanel>
<CheckBox IsChecked="{Binding RunInspectionsOnSuccessfulParse}"
Content="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeInspectionSettings_Misc_RunInspectionsOnSuccessfulParse}" />
</StackPanel>
</StackPanel>
</ScrollViewer>
</Grid>
Expand Down
19 changes: 19 additions & 0 deletions RetailCoder.VBE/UI/Settings/InspectionSettingsViewModel.cs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,8 @@ public InspectionSettingsViewModel(Configuration config)
WhitelistedIdentifierSettings = new ObservableCollection<WhitelistedIdentifierSetting>(
config.UserSettings.CodeInspectionSettings.WhitelistedIdentifiers.OrderBy(o => o.Identifier).Distinct());

RunInspectionsOnSuccessfulParse = config.UserSettings.CodeInspectionSettings.RunInspectionsOnSuccessfulParse;

if (InspectionSettings.GroupDescriptions != null)
{
InspectionSettings.GroupDescriptions.Add(new PropertyGroupDescription("TypeLabel"));
Expand Down Expand Up @@ -51,6 +53,21 @@ public ListCollectionView InspectionSettings
}
}

private bool _runInspectionsOnSuccessfulParse;

public bool RunInspectionsOnSuccessfulParse
{
get { return _runInspectionsOnSuccessfulParse; }
set
{
if (_runInspectionsOnSuccessfulParse != value)
{
_runInspectionsOnSuccessfulParse = value;
OnPropertyChanged();
}
}
}

private ObservableCollection<WhitelistedIdentifierSetting> _whitelistedNameSettings;
public ObservableCollection<WhitelistedIdentifierSetting> WhitelistedIdentifierSettings
{
Expand All @@ -69,6 +86,7 @@ public void UpdateConfig(Configuration config)
{
config.UserSettings.CodeInspectionSettings.CodeInspections = new HashSet<CodeInspectionSetting>(InspectionSettings.SourceCollection.OfType<CodeInspectionSetting>());
config.UserSettings.CodeInspectionSettings.WhitelistedIdentifiers = WhitelistedIdentifierSettings.Distinct().ToArray();
config.UserSettings.CodeInspectionSettings.RunInspectionsOnSuccessfulParse = _runInspectionsOnSuccessfulParse;
}

public void SetToDefaults(Configuration config)
Expand All @@ -82,6 +100,7 @@ public void SetToDefaults(Configuration config)
}

WhitelistedIdentifierSettings = new ObservableCollection<WhitelistedIdentifierSetting>();
RunInspectionsOnSuccessfulParse = true;
}

private CommandBase _addWhitelistedNameCommand;
Expand Down
13 changes: 10 additions & 3 deletions RetailCoder.VBE/UI/SourceControl/ChangesView.xaml
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@
<TabItem.Resources>
<BitmapImage x:Key="CheckImage" UriSource="../../Resources/tick.png" />
<BitmapImage x:Key="UndoImage" UriSource="../../Resources/arrow-circle-left.png" />

<BitmapImage x:Key="AddImage" UriSource="../../Resources/plus-circle.png" />

<converters:CommitActionsToTextConverter x:Key="CommitActionToText" />
<converters:CommitActionTextToEnum x:Key="CommitActionValueToEnum" />
<converters:ChangeTypesToTextConverter x:Key="ChangeTypesToText" />
Expand Down Expand Up @@ -218,8 +219,14 @@
<Button Command="{Binding IncludeChangesToolbarButtonCommand}"
CommandParameter="{Binding ElementName=UntrackFilesGrid, Path=SelectedItem}"
IsEnabled="{Binding ElementName=UntrackFilesGrid, Path=SelectedItem, Converter={StaticResource HasSelectedItems}}"
Content="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=SourceControl_IncludeFileButton}"
Height="22" />
Height="22">
<StackPanel Orientation="Horizontal">
<Image Source="{StaticResource AddImage}" />
<TextBlock Text="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=SourceControl_IncludeFileButton}"
Margin="2,0"
VerticalAlignment="Center" />
</StackPanel>
</Button>
</ToolBar>
</ToolBarTray>
<DataGrid ItemsSource="{Binding UntrackedFiles}"
Expand Down
12 changes: 6 additions & 6 deletions Rubberduck.Parsing/VBA/RubberduckParser.cs
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ private void ReparseRequested(object sender, EventArgs e)
if (!_isTestScope)
{
Cancel();
Task.Run(() => ParseAll(_cancellationTokens[0]));
Task.Run(() => ParseAll(sender, _cancellationTokens[0]));
}
else
{
Expand Down Expand Up @@ -142,15 +142,15 @@ public void Parse(CancellationTokenSource token)

if (State.Status < ParserState.Error)
{
State.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
State.SetStatusAndFireStateChanged(this, ParserState.ResolvedDeclarations);
Task.WaitAll(ResolveReferencesAsync(token.Token));
}
}

/// <summary>
/// Starts parsing all components of all unprotected VBProjects associated with the VBE-Instance passed to the constructor of this parser instance.
/// </summary>
private void ParseAll(CancellationTokenSource token)
private void ParseAll(object requestor, CancellationTokenSource token)
{
State.RefreshProjects(_vbe);

Expand Down Expand Up @@ -202,10 +202,10 @@ private void ParseAll(CancellationTokenSource token)
{
if (componentsRemoved) // trigger UI updates
{
State.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
State.SetStatusAndFireStateChanged(requestor, ParserState.ResolvedDeclarations);
}

State.SetStatusAndFireStateChanged(State.Status);
State.SetStatusAndFireStateChanged(requestor, State.Status);
return;
}

Expand Down Expand Up @@ -276,7 +276,7 @@ private void ParseAll(CancellationTokenSource token)

if (State.Status < ParserState.Error)
{
State.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
State.SetStatusAndFireStateChanged(requestor, ParserState.ResolvedDeclarations);
ResolveReferencesAsync(token.Token);
}
}
Expand Down

0 comments on commit 6aa9466

Please sign in to comment.