Skip to content

Commit 1d47b07

Browse files
committed
Clean up the flawed trace implementation
Convert trace into a stream to avoid caching all trace in memory Overload the Serialize button to serialize both the project declaration and the COM safe's contents/trace logs Provide some safety around the tracing and fix various one-off errors
1 parent df89aaf commit 1d47b07

File tree

5 files changed

+218
-35
lines changed

5 files changed

+218
-35
lines changed

Rubberduck.Core/UI/Command/MenuItems/CommandBars/SerializeProjectsCommandMenuItem.cs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -76,6 +76,16 @@ protected override void OnExecute(object parameter)
7676
Logger.Warn($"Serializing {library.Path}.");
7777
_serializationProvider.SerializeProject(library);
7878
}
79+
80+
#if DEBUG
81+
//Dumb hack cos I'm too lazy to wire up another button...
82+
var traceDirectory = Path.Combine(Path.GetDirectoryName(_serializationProvider.Target), "COM Trace");
83+
if (!Directory.Exists(traceDirectory))
84+
{
85+
Directory.CreateDirectory(traceDirectory);
86+
}
87+
Rubberduck.VBEditor.ComManagement.ComSafeManager.GetCurrentComSafe().Serialize(traceDirectory);
88+
#endif
7989
}
8090
}
8191
}

Rubberduck.VBEEditor/ComManagement/ComSafeBase.cs

Lines changed: 167 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -5,74 +5,219 @@
55

66
#if DEBUG
77
using System.Diagnostics;
8+
using System.IO;
89
using System.Runtime.InteropServices;
910
#endif
1011

1112
namespace Rubberduck.VBEditor.ComManagement
1213
{
1314
public abstract class ComSafeBase : IComSafe
1415
{
15-
#if DEBUG
16-
protected IEnumerable<string> Trace = null;
17-
#endif
18-
1916
public abstract void Add(ISafeComWrapper comWrapper);
2017

18+
public abstract bool TryRemove(ISafeComWrapper comWrapper);
19+
2120
//We do not use GetHashCode because subclasses of SafeComWrapper<T> overwrite this method
2221
//and we need to distinguish between individual instances.
2322
protected int GetComWrapperObjectHashCode(ISafeComWrapper comWrapper)
2423
{
2524
return RuntimeHelpers.GetHashCode(comWrapper);
2625
}
2726

28-
public abstract bool TryRemove(ISafeComWrapper comWrapper);
29-
27+
private bool _disposed;
3028
public void Dispose()
3129
{
3230
Dispose(true);
31+
32+
#if DEBUG
33+
if (_disposed)
34+
{
35+
return;
36+
}
37+
38+
_disposed = true;
39+
40+
lock (_streamLock)
41+
{
42+
try
43+
{
44+
if (_traceStream == null)
45+
{
46+
return;
47+
}
48+
49+
_traceStream.Close();
50+
if (string.IsNullOrWhiteSpace(_directory))
51+
{
52+
File.Delete(_traceFilePath);
53+
}
54+
else
55+
{
56+
File.Move(_traceFilePath,
57+
Path.Combine(_directory,
58+
Path.GetFileNameWithoutExtension(_traceFilePath) + " final.csv"));
59+
}
60+
}
61+
finally
62+
{
63+
_traceStream?.Dispose();
64+
_traceStream = null;
65+
}
66+
}
67+
#endif
3368
}
3469

3570
protected abstract void Dispose(bool disposing);
3671

3772
#if DEBUG
73+
private struct TraceData
74+
{
75+
internal int HashCode { get; set; }
76+
internal string IUnknownAddress { get; set; }
77+
internal IEnumerable<string> StackTrace { get; set; }
78+
}
79+
private StreamWriter _traceStream;
80+
private string _traceFilePath;
81+
private string _directory;
82+
private readonly object _streamLock = new object();
83+
84+
/// <summary>
85+
/// The first few stack frames come from the ComSafe and thus are not
86+
/// particularly interesting. Typically, we want to look at the frames
87+
/// outside the ComSafe.
88+
/// </summary>
89+
private const int StackTraceNumberOfElementsToSkipOnRemoval = 6;
90+
private const int StackTrackNumberOfElementsToSkipOnAddUpdate = 8;
91+
private const int StackTraceDepth = 5;
92+
3893
/// <summary>
3994
/// Provide a serialized list of the COM Safe
4095
/// to make it easy to analyze what is inside
4196
/// the COM Safe at the different points of
4297
/// the session's lifetime.
4398
/// </summary>
44-
public void Serialize()
99+
public void Serialize(string targetDirectory)
100+
{
101+
lock (_streamLock)
102+
{
103+
_directory = targetDirectory;
104+
var serializeTime = DateTime.UtcNow;
105+
using (var stream = File.AppendText(Path.Combine(_directory,
106+
$"COM Safe Content Snapshot {serializeTime:yyyyMMddhhmmss}.csv")))
107+
{
108+
stream.WriteLine(
109+
$"Ordinal\tKey\tCOM Wrapper Type\tWrapping Null?\tIUnknown Pointer Address");
110+
var i = 0;
111+
foreach (var kvp in GetWrappers())
112+
{
113+
var line = kvp.Value != null
114+
? $"{i++}\t{kvp.Key}\t\"{kvp.Value.GetType().FullName}\"\t\"{kvp.Value.IsWrappingNullReference}\"\t\"{(kvp.Value.IsWrappingNullReference ? "null" : GetPtrAddress(kvp.Value.Target))}\""
115+
: $"{i++}\t{kvp.Key}\t\"null\"\t\"null\"\t\"null\"";
116+
stream.WriteLine(line);
117+
}
118+
}
119+
120+
if (_traceStream == null)
121+
{
122+
return;
123+
}
124+
125+
_traceStream.Flush();
126+
File.Copy(_traceFilePath, Path.Combine(_directory, $"COM Safe Stack Trace {serializeTime:yyyyMMddhhmmss}.csv"));
127+
}
128+
}
129+
130+
protected void TraceAdd(ISafeComWrapper comWrapper)
131+
{
132+
Trace("Add", comWrapper, StackTrackNumberOfElementsToSkipOnAddUpdate);
133+
}
134+
135+
protected void TraceUpdate(ISafeComWrapper comWrapper)
45136
{
46-
using (var stream = System.IO.File.AppendText($"comSafeOutput {DateTime.UtcNow:yyyyMMddhhmmss}.csv"))
137+
Trace("Update", comWrapper, StackTrackNumberOfElementsToSkipOnAddUpdate);
138+
}
139+
140+
protected void TraceRemove(ISafeComWrapper comWrapper, bool wasRemoved)
141+
{
142+
var activity = wasRemoved ? "Removed" : "Not removed";
143+
Trace(activity, comWrapper, StackTraceNumberOfElementsToSkipOnRemoval);
144+
}
145+
146+
private readonly object _idLock = new object();
147+
private int _id;
148+
private void Trace(string activity, ISafeComWrapper comWrapper, int framesToSkip)
149+
{
150+
lock (_streamLock)
47151
{
48-
stream.WriteLine(
49-
"Ordinal\tKey\tCOM Wrapper Type\tWrapping Null?\tIUnknown Pointer Address\tLevel 1\tLevel 2\tLevel 3");
50-
var i = 0;
51-
foreach (var kvp in GetWrappers())
152+
if (_disposed)
153+
{
154+
return;
155+
}
156+
157+
if (_traceStream == null)
158+
{
159+
var directory = Path.GetTempPath();
160+
_traceFilePath = Path.Combine(directory,
161+
$"COM Safe Stack Trace {DateTime.UtcNow:yyyyMMddhhmmss}.{GetHashCode()}.csv");
162+
_traceStream = File.AppendText(_traceFilePath);
163+
_traceStream.WriteLine(
164+
$"Ordinal\tTimestamp\tActivity\tKey\tIUnknown Pointer Address\t{FrameHeaders()}");
165+
}
166+
167+
int id;
168+
lock (_idLock)
52169
{
53-
var line = kvp.Value != null
54-
? $"{i++}\t{kvp.Key}\t\"{kvp.Value.GetType().FullName}\"\t\"{kvp.Value.IsWrappingNullReference}\"\t\"{(kvp.Value.IsWrappingNullReference ? "null" : GetPtrAddress(kvp.Value))}\"\t\"{string.Join("\"\t\"", Trace)}\""
55-
: $"{i++}\t{kvp.Key}\t\"null\"\t\"null\"\t\"null\"\t\"{string.Join("\"\t\"", Trace)}\"";
56-
stream.WriteLine(line);
170+
id = _id++;
57171
}
172+
173+
var traceData = new TraceData
174+
{
175+
HashCode = GetComWrapperObjectHashCode(comWrapper),
176+
IUnknownAddress = comWrapper.IsWrappingNullReference ? "null" : GetPtrAddress(comWrapper.Target),
177+
StackTrace = GetStackTrace(StackTraceDepth, framesToSkip)
178+
};
179+
180+
var line =
181+
$"{id}\t{DateTime.UtcNow}\t\"{activity}\"\t{traceData.HashCode}\t{traceData.IUnknownAddress}\t\"{string.Join("\"\t\"", traceData.StackTrace)}\"";
182+
_traceStream.WriteLine(line);
183+
}
184+
}
185+
186+
private static string FrameHeaders()
187+
{
188+
var headers = new System.Text.StringBuilder();
189+
for(var i = 1; i <= StackTraceDepth; i++)
190+
{
191+
headers.Append($"Frame {i}\t");
58192
}
193+
194+
return headers.ToString();
59195
}
60196

61197
protected abstract IDictionary<int, ISafeComWrapper> GetWrappers();
62198

63-
protected static IEnumerable<string> GetStackTrace(int frames, int offset)
199+
private static IEnumerable<string> GetStackTrace(int frames, int framesToSkip)
64200
{
65201
var list = new List<string>();
66202
var trace = new StackTrace();
67-
if ((trace.FrameCount - offset) < frames)
203+
if (trace.FrameCount < (frames + framesToSkip))
204+
{
205+
frames = trace.FrameCount;
206+
}
207+
else
68208
{
69-
frames = (trace.FrameCount - offset);
209+
frames += framesToSkip;
70210
}
71211

72-
for (var i = 1; i <= frames; i++)
212+
framesToSkip -= 1;
213+
frames -= 1;
214+
215+
for (var i = framesToSkip; i < frames; i++)
73216
{
74-
var frame = trace.GetFrame(i + offset);
75-
var typeName = frame.GetMethod().DeclaringType?.FullName ?? string.Empty;
217+
var frame = trace.GetFrame(i);
218+
var type = frame.GetMethod().DeclaringType;
219+
220+
var typeName = type?.FullName ?? string.Empty;
76221
var methodName = frame.GetMethod().Name;
77222

78223
var qualifiedName = $"{typeName}{(typeName.Length > 0 ? "::" : string.Empty)}{methodName}";

Rubberduck.VBEEditor/ComManagement/IComSafe.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,5 +7,8 @@ public interface IComSafe: IDisposable
77
{
88
void Add(ISafeComWrapper comWrapper);
99
bool TryRemove(ISafeComWrapper comWrapper);
10+
#if DEBUG
11+
void Serialize(string targetDirectory);
12+
#endif
1013
}
1114
}

Rubberduck.VBEEditor/ComManagement/StrongComSafe.cs

Lines changed: 19 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -15,16 +15,19 @@ public override void Add(ISafeComWrapper comWrapper)
1515
{
1616
if (comWrapper != null)
1717
{
18-
#if DEBUG
19-
Trace = GetStackTrace(3, 3);
20-
#endif
2118
_comWrapperCache.AddOrUpdate(
2219
comWrapper,
23-
key => 1,
20+
key =>
21+
{
22+
#if DEBUG
23+
TraceAdd(comWrapper);
24+
#endif
25+
return 1;
26+
},
2427
(key, value) =>
2528
{
2629
#if DEBUG
27-
System.Diagnostics.Debug.Assert(false);
30+
TraceUpdate(comWrapper);
2831
#endif
2932
return value;
3033
});
@@ -33,7 +36,16 @@ public override void Add(ISafeComWrapper comWrapper)
3336

3437
public override bool TryRemove(ISafeComWrapper comWrapper)
3538
{
36-
return !_disposed && comWrapper != null && _comWrapperCache.TryRemove(comWrapper, out _);
39+
if (_disposed || comWrapper == null)
40+
{
41+
return false;
42+
}
43+
44+
var result = _comWrapperCache.TryRemove(comWrapper, out _);
45+
#if DEBUG
46+
TraceRemove(comWrapper, result);
47+
#endif
48+
return result;
3749
}
3850

3951
private bool _disposed;
@@ -62,3 +74,4 @@ protected override IDictionary<int, ISafeComWrapper> GetWrappers()
6274
#endif
6375
}
6476
}
77+

Rubberduck.VBEEditor/ComManagement/WeakComSafe.cs

Lines changed: 19 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
55

66
#if DEBUG
7-
using System.Diagnostics;
87
using System.Linq;
98
#endif
109

@@ -19,16 +18,19 @@ public override void Add(ISafeComWrapper comWrapper)
1918
{
2019
if (comWrapper != null)
2120
{
22-
#if DEBUG
23-
Trace = GetStackTrace(3, 3);
24-
#endif
2521
_comWrapperCache.AddOrUpdate(
2622
GetComWrapperObjectHashCode(comWrapper),
27-
key => (DateTime.UtcNow, new WeakReference<ISafeComWrapper>(comWrapper)),
23+
key =>
24+
{
25+
#if DEBUG
26+
TraceAdd(comWrapper);
27+
#endif
28+
return (DateTime.UtcNow, new WeakReference<ISafeComWrapper>(comWrapper));
29+
},
2830
(key, value) =>
2931
{
3032
#if DEBUG
31-
Debug.Assert(false);
33+
TraceUpdate(comWrapper);
3234
#endif
3335
return (value.insertTime, new WeakReference<ISafeComWrapper>(comWrapper));
3436
});
@@ -38,7 +40,16 @@ public override void Add(ISafeComWrapper comWrapper)
3840

3941
public override bool TryRemove(ISafeComWrapper comWrapper)
4042
{
41-
return !_disposed && comWrapper != null && _comWrapperCache.TryRemove(GetComWrapperObjectHashCode(comWrapper), out _);
43+
if (_disposed || comWrapper == null)
44+
{
45+
return false;
46+
}
47+
48+
var result = _comWrapperCache.TryRemove(GetComWrapperObjectHashCode(comWrapper), out _);
49+
#if DEBUG
50+
TraceRemove(comWrapper, result);
51+
#endif
52+
return result;
4253
}
4354

4455
private bool _disposed;
@@ -80,3 +91,4 @@ protected override IDictionary<int, ISafeComWrapper> GetWrappers()
8091
#endif
8192
}
8293
}
94+

0 commit comments

Comments
 (0)