Skip to content

Commit 2b7711c

Browse files
authored
Merge pull request #2112 from Hosch250/Issue1681
Get the website working again
2 parents a87bb84 + 0d65142 commit 2b7711c

File tree

71 files changed

+732
-723
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

71 files changed

+732
-723
lines changed

RetailCoder.VBE/API/ParserState.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -63,12 +63,12 @@ public void Initialize(VBE vbe)
6363
throw new InvalidOperationException("ParserState is already initialized.");
6464
}
6565

66-
_state = new RubberduckParserState(vbe, new Sinks(vbe));
66+
_state = new RubberduckParserState(new Sinks(vbe));
6767
_state.StateChanged += _state_StateChanged;
6868

6969
Func<IVBAPreprocessor> preprocessorFactory = () => new VBAPreprocessor(double.Parse(vbe.Version, CultureInfo.InvariantCulture));
7070
_attributeParser = new AttributeParser(new ModuleExporter(), preprocessorFactory);
71-
_parser = new RubberduckParser(_state, _attributeParser, preprocessorFactory,
71+
_parser = new RubberduckParser(vbe, _state, _attributeParser, preprocessorFactory,
7272
new List<ICustomDeclarationLoader> { new DebugDeclarations(_state), new FormEventDeclarations(_state), new AliasDeclarations(_state) });
7373
}
7474

RetailCoder.VBE/Inspections/IParseTreeInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,6 @@ public ParseTreeResults()
2525
public IEnumerable<QualifiedContext> ObsoleteLetContexts;
2626
public IEnumerable<QualifiedContext> ArgListsWithOneByRefParam;
2727
public IEnumerable<QualifiedContext> EmptyStringLiterals;
28-
public IEnumerable<QualifiedContext<VBAParser.AnnotationContext>> MalformedAnnotations;
28+
public IEnumerable<QualifiedContext> MalformedAnnotations;
2929
}
3030
}

RetailCoder.VBE/Inspections/MalformedAnnotationInspection.cs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -27,16 +27,18 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2727

2828
var results = new List<MalformedAnnotationInspectionResult>();
2929

30-
foreach (var context in ParseTreeResults.MalformedAnnotations)
30+
foreach (var result in ParseTreeResults.MalformedAnnotations)
3131
{
32-
if (context.Context.annotationName().GetText() == AnnotationType.Ignore.ToString() ||
33-
context.Context.annotationName().GetText() == AnnotationType.Folder.ToString())
32+
var context = (VBAParser.AnnotationContext)result.Context;
33+
34+
if (context.annotationName().GetText() == AnnotationType.Ignore.ToString() ||
35+
context.annotationName().GetText() == AnnotationType.Folder.ToString())
3436
{
35-
if (context.Context.annotationArgList() == null)
37+
if (context.annotationArgList() == null)
3638
{
3739
results.Add(new MalformedAnnotationInspectionResult(this,
38-
new QualifiedContext<VBAParser.AnnotationContext>(context.ModuleName,
39-
context.Context)));
40+
new QualifiedContext<VBAParser.AnnotationContext>(result.ModuleName,
41+
context)));
4042
}
4143
}
4244
}

RetailCoder.VBE/Sinks.cs

Lines changed: 26 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -11,18 +11,22 @@ namespace Rubberduck
1111
{
1212
public class ProjectEventArgs : EventArgs, IProjectEventArgs
1313
{
14-
public ProjectEventArgs(string projectId)
14+
public ProjectEventArgs(string projectId, VBProject project)
1515
{
1616
_projectId = projectId;
17+
_project = project;
1718
}
1819

1920
private readonly string _projectId;
2021
public string ProjectId { get { return _projectId; } }
22+
23+
private readonly VBProject _project;
24+
public VBProject Project { get { return _project; } }
2125
}
2226

2327
public class ProjectRenamedEventArgs : ProjectEventArgs, IProjectRenamedEventArgs
2428
{
25-
public ProjectRenamedEventArgs(string projectId, string oldName) : base(projectId)
29+
public ProjectRenamedEventArgs(string projectId, VBProject project, string oldName) : base(projectId, project)
2630
{
2731
_oldName = oldName;
2832
}
@@ -33,27 +37,28 @@ public ProjectRenamedEventArgs(string projectId, string oldName) : base(projectI
3337

3438
public class ComponentEventArgs : EventArgs, IComponentEventArgs
3539
{
36-
public ComponentEventArgs(string projectId, string componentName, vbext_ComponentType type)
40+
public ComponentEventArgs(string projectId, VBProject project, VBComponent component)
3741
{
3842
_projectId = projectId;
39-
_componentName = componentName;
40-
_type = type;
43+
_project = project;
44+
_component = component;
4145
}
4246

4347
private readonly string _projectId;
4448
public string ProjectId { get { return _projectId; } }
4549

46-
private readonly string _componentName;
47-
public string ComponentName { get { return _componentName; } }
50+
private readonly VBProject _project;
51+
public VBProject Project { get { return _project; } }
52+
53+
private readonly VBComponent _component;
54+
public VBComponent Component { get { return _component; } }
4855

49-
private readonly vbext_ComponentType _type;
50-
public vbext_ComponentType Type { get { return _type; } }
5156
}
5257

5358
public class ComponentRenamedEventArgs : ComponentEventArgs, IComponentRenamedEventArgs
5459
{
55-
public ComponentRenamedEventArgs(string projectId, string componentName, vbext_ComponentType type, string oldName)
56-
: base(projectId, componentName, type)
60+
public ComponentRenamedEventArgs(string projectId, VBProject project, VBComponent component, string oldName)
61+
: base(projectId, project, component)
5762
{
5863
_oldName = oldName;
5964
}
@@ -108,7 +113,7 @@ private void _sink_ProjectActivated(object sender, DispatcherEventArgs<VBProject
108113
var handler = ProjectActivated;
109114
if (handler != null)
110115
{
111-
handler(sender, new ProjectEventArgs(projectId));
116+
handler(sender, new ProjectEventArgs(projectId, e.Item));
112117
}
113118
});
114119
}
@@ -127,7 +132,7 @@ private void _sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
127132
var handler = ProjectAdded;
128133
if (handler != null)
129134
{
130-
handler(sender, new ProjectEventArgs(projectId));
135+
handler(sender, new ProjectEventArgs(projectId, e.Item));
131136
}
132137
});
133138
}
@@ -144,7 +149,7 @@ private void _sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject>
144149
var handler = ProjectRemoved;
145150
if (handler != null)
146151
{
147-
handler(sender, new ProjectEventArgs(projectId));
152+
handler(sender, new ProjectEventArgs(projectId, e.Item));
148153
}
149154
});
150155
}
@@ -161,7 +166,7 @@ private void _sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBPr
161166
var handler = ProjectRenamed;
162167
if (handler != null)
163168
{
164-
handler(sender, new ProjectRenamedEventArgs(projectId, oldName));
169+
handler(sender, new ProjectRenamedEventArgs(projectId, e.Item, oldName));
165170
}
166171
});
167172
}
@@ -228,12 +233,11 @@ private void ComponentsSink_ComponentActivated(object sender, DispatcherEventArg
228233
if (!IsEnabled) { return; }
229234

230235
var projectId = e.Item.Collection.Parent.HelpFile;
231-
var componentName = e.Item.Name;
232236

233237
var handler = ComponentActivated;
234238
if (handler != null)
235239
{
236-
handler(sender, new ComponentEventArgs(projectId, componentName, e.Item.Type));
240+
handler(sender, new ComponentEventArgs(projectId, e.Item.Collection.Parent, e.Item));
237241
}
238242
}
239243

@@ -247,7 +251,7 @@ private void ComponentsSink_ComponentAdded(object sender, DispatcherEventArgs<VB
247251
var handler = ComponentAdded;
248252
if (handler != null)
249253
{
250-
handler(sender, new ComponentEventArgs(projectId, componentName, e.Item.Type));
254+
handler(sender, new ComponentEventArgs(projectId, e.Item.Collection.Parent, e.Item));
251255
}
252256
}
253257

@@ -261,7 +265,7 @@ private void ComponentsSink_ComponentReloaded(object sender, DispatcherEventArgs
261265
var handler = ComponentReloaded;
262266
if (handler != null)
263267
{
264-
handler(sender, new ComponentEventArgs(projectId, componentName, e.Item.Type));
268+
handler(sender, new ComponentEventArgs(projectId, e.Item.Collection.Parent, e.Item));
265269
}
266270
}
267271

@@ -275,7 +279,7 @@ private void ComponentsSink_ComponentRemoved(object sender, DispatcherEventArgs<
275279
var handler = ComponentRemoved;
276280
if (handler != null)
277281
{
278-
handler(sender, new ComponentEventArgs(projectId, componentName, e.Item.Type));
282+
handler(sender, new ComponentEventArgs(projectId, e.Item.Collection.Parent, e.Item));
279283
}
280284
}
281285

@@ -290,7 +294,7 @@ private void ComponentsSink_ComponentRenamed(object sender, DispatcherRenamedEve
290294
var handler = ComponentRenamed;
291295
if (handler != null)
292296
{
293-
handler(sender, new ComponentRenamedEventArgs(projectId, componentName, e.Item.Type, oldName));
297+
handler(sender, new ComponentRenamedEventArgs(projectId, e.Item.Collection.Parent, e.Item, e.OldName));
294298
}
295299
}
296300

@@ -304,7 +308,7 @@ private void ComponentsSink_ComponentSelected(object sender, DispatcherEventArgs
304308
var handler = ComponentSelected;
305309
if (handler != null)
306310
{
307-
handler(sender, new ComponentEventArgs(projectId, componentName, e.Item.Type));
311+
handler(sender, new ComponentEventArgs(projectId, e.Item.Collection.Parent, e.Item));
308312
}
309313
}
310314
#endregion

RetailCoder.VBE/UI/SourceControl/SourceControlViewViewModel.cs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -126,8 +126,8 @@ private void ComponentAdded(object sender, IComponentEventArgs e)
126126
return;
127127
}
128128

129-
Logger.Trace("Component {0} added", e.ComponentName);
130-
var fileStatus = Provider.Status().SingleOrDefault(stat => stat.FilePath.Split('.')[0] == e.ComponentName);
129+
Logger.Trace("Component {0} added", e.Component.Name);
130+
var fileStatus = Provider.Status().SingleOrDefault(stat => stat.FilePath.Split('.')[0] == e.Component.Name);
131131
if (fileStatus != null)
132132
{
133133
Provider.AddFile(fileStatus.FilePath);
@@ -143,8 +143,8 @@ private void ComponentRemoved(object sender, IComponentEventArgs e)
143143
return;
144144
}
145145

146-
Logger.Trace("Component {0] removed", e.ComponentName);
147-
var fileStatus = Provider.Status().SingleOrDefault(stat => stat.FilePath.Split('.')[0] == e.ComponentName);
146+
Logger.Trace("Component {0] removed", e.Component.Name);
147+
var fileStatus = Provider.Status().SingleOrDefault(stat => stat.FilePath.Split('.')[0] == e.Component.Name);
148148
if (fileStatus != null)
149149
{
150150
Provider.RemoveFile(fileStatus.FilePath, true);
@@ -160,7 +160,7 @@ private void ComponentRenamed(object sender, IComponentRenamedEventArgs e)
160160
return;
161161
}
162162

163-
Logger.Trace("Component {0} renamed to {1}", e.OldName, e.ComponentName);
163+
Logger.Trace("Component {0} renamed to {1}", e.OldName, e.Component.Name);
164164
var fileStatus = Provider.LastKnownStatus().SingleOrDefault(stat => stat.FilePath.Split('.')[0] == e.OldName);
165165
if (fileStatus != null)
166166
{
@@ -170,11 +170,11 @@ private void ComponentRenamed(object sender, IComponentRenamedEventArgs e)
170170
var fileExt = "." + fileStatus.FilePath.Split('.').Last();
171171

172172
_fileSystemWatcher.EnableRaisingEvents = false;
173-
File.Move(directory + fileStatus.FilePath, directory + e.ComponentName + fileExt);
173+
File.Move(directory + fileStatus.FilePath, directory + e.Component.Name + fileExt);
174174
_fileSystemWatcher.EnableRaisingEvents = true;
175175

176176
Provider.RemoveFile(e.OldName + fileExt, false);
177-
Provider.AddFile(e.ComponentName + fileExt);
177+
Provider.AddFile(e.Component.Name + fileExt);
178178
}
179179
}
180180

Rubberduck.Parsing/ISinks.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ namespace Rubberduck.Parsing
66
public interface IProjectEventArgs
77
{
88
string ProjectId { get; }
9+
VBProject Project { get; }
910
}
1011

1112
public interface IProjectRenamedEventArgs : IProjectEventArgs
@@ -16,8 +17,9 @@ public interface IProjectRenamedEventArgs : IProjectEventArgs
1617
public interface IComponentEventArgs
1718
{
1819
string ProjectId { get; }
19-
string ComponentName { get; }
20-
vbext_ComponentType Type { get; }
20+
21+
VBProject Project { get; }
22+
VBComponent Component { get; }
2123
}
2224

2325
public interface IComponentRenamedEventArgs : IComponentEventArgs

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,8 @@ public class RubberduckParser : IRubberduckParser
2525

2626
private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
2727
= new Dictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
28-
28+
29+
private readonly VBE _vbe;
2930
private readonly RubberduckParserState _state;
3031
private readonly IAttributeParser _attributeParser;
3132
private readonly Func<IVBAPreprocessor> _preprocessorFactory;
@@ -35,12 +36,14 @@ private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationT
3536
private readonly bool _isTestScope;
3637

3738
public RubberduckParser(
39+
VBE vbe,
3840
RubberduckParserState state,
3941
IAttributeParser attributeParser,
4042
Func<IVBAPreprocessor> preprocessorFactory,
4143
IEnumerable<ICustomDeclarationLoader> customDeclarationLoaders,
4244
bool isTestScope = false)
4345
{
46+
_vbe = vbe;
4447
_state = state;
4548
_attributeParser = attributeParser;
4649
_preprocessorFactory = preprocessorFactory;
@@ -73,7 +76,7 @@ private void ReparseRequested(object sender, EventArgs e)
7376
/// </summary>
7477
public void Parse(CancellationTokenSource token)
7578
{
76-
State.RefreshProjects();
79+
State.RefreshProjects(_vbe);
7780

7881
var components = new List<VBComponent>();
7982
foreach (var project in State.Projects)
@@ -149,7 +152,7 @@ public void Parse(CancellationTokenSource token)
149152
/// </summary>
150153
private void ParseAll(CancellationTokenSource token)
151154
{
152-
State.RefreshProjects();
155+
State.RefreshProjects(_vbe);
153156

154157
var components = new List<VBComponent>();
155158
foreach (var project in State.Projects)

0 commit comments

Comments
 (0)