rubberduck-vba / Rubberduck

Every programmer needs a rubberduck. COM add-in for the VBA & VB6 IDE (VBE).
https://rubberduckvba.com
GNU General Public License v3.0
1.92k stars 302 forks source link

MS Access leaves a ghost process #3905

Closed daFreeMan closed 6 years ago

daFreeMan commented 6 years ago

Win10, Office 2016 64-bit.

Open Access, open VBE, parse project, close Access. MSACCESS.EXE remains in Task Manager.

RubberduckLog.txt

Vogel612 commented 6 years ago

Apart from a few SLL mode failures for parsing, the log looks pretty clean

MDoerner commented 6 years ago

After having a short look at the log file, I think the problem is that a parse still has been running when RD has been shut down.

daFreeMan commented 6 years ago

Reproduced the hang. Reran with trace log. Was sure to wait until the parse had completed. Shut down VBE, then exited Access. Last time I just closed Access & let it close down the VBE. RubberduckLog.txt

MDoerner commented 6 years ago

Hm, the toolwindows seem to not close down, which basically means that they never get a WM_CLOSE message.

daFreeMan commented 6 years ago

Knowing is half the battle. That sounds like progress to me!!

bclothier commented 6 years ago

FYI I cannot replicate this on Access 2016 x32 on Windows 10 but I can on Access 2010 x32 on Windows 7.... and only if I've parsed.

daFreeMan commented 6 years ago

My old machine was Win7 Office2010 x32 and yes, I had it very consistently on that one, too.

Vogel612 commented 6 years ago

Can confirm clean exit on Access 2016 on Windows 10

bclothier commented 6 years ago

I'm sure there's a setting at play. Maybe having a window visible at startup?

Or it may depend on code (e.g. exceptions from inspection => dirty exit), maybe?

daFreeMan commented 6 years ago

That could be it. I do have a form auto-run and it's usually open when I exit.

daFreeMan commented 6 years ago

I tested closing out the default form and I'm still getting a zombie. :(

I saw in #3614 that there was a note about closing Access with an RD tool window docked, which I normally do with my CE.

I opened my Access project, undocked the CE then closed the project. I reopened my project, parsed, then closed the VBE followed by Access itself. I'm still getting a zombie.

daFreeMan commented 6 years ago

For the record:

I left a zombie running over night. It shrunk from about 117MB of RAM used to about 11MB of RAM used. I created a 1.3GB(!!!) dump file from Task Manager - as I did so, it grew to over 500MB RAM used. It has since settled back down to about 13MB RAM.

The dump file is being shared via Dropbox with the devs (at) rubberduckvba (dot) com.

retailcoder commented 6 years ago

@daFreeMan that would probably be the CLR eventually coming to the realization that it's time to perform garbage collection of whatever was left behind :+1:

daFreeMan commented 6 years ago

Due to HIPAA regulations, it's incredibly difficult to get a file off our work network. Also, it's possible that there might be some HIPPA data visible in the dump file. To mitigate the issue and prevent me getting myself fired, I'm going to attempt to reproduce the issue at home and load the dump file from there.

MDoerner commented 6 years ago

Althouggh I cannot reproduce this ecaxt issue, I get a never ending sequence of access violations on shutdown when running in the debugger.

After some investigation, I found out that this behaviour started with PR #3857.

dermoench42 commented 6 years ago

Can confirm sometimes an unclean shutdown on current Windows10 / Office 2016 64bit in an VirtualBox.

mostly after using some rubberduck functionality e.g. 'indent' current module.

An MS Access ghost task remains an if restarting some 10 seconds later, Rubberduck won't come up - only the virgin VBE.

After killing the ghost and restarting Access Rubberduck comes up, but displays the 'first start after install' message: "Would You like to see the chanlog..." or similar.

But maybe it is related to the 'refresh' - on my db it took around a minute to finish.

When closing access while rubberduck is refreshing, the cpuload of the ghost task stays hi for this minute and then goes down to zero. But the process doesn't disappear. And again when restarting access rubberduck won't appear.

ervin

Version 2.2.0.3468 OS: Microsoft Windows NT 10.0.17134.0, x64 Host Product: Microsoft Office 2016 x64 Host Version: 16.0.10228.20080 Host Executable: MSACCESS.EXE

bclothier commented 6 years ago

I can confirm that behavior was present with the stable version. However, in latest prereleases, the behavior does not seem to exhibit anymore. Can anyone else confirm if one download the latest pre-release, that it solves the issue?

Inarion commented 6 years ago

Unfortunately, I can repro the issue even with the latest prerelease. :(

Version 2.2.0.3564
OS: Microsoft Windows NT 6.1.7601 Service Pack 1, x64
Host Product: Microsoft Office 2013 x86
Host Version: 15.0.5023.1000
Host Executable: MSACCESS.EXE

What I did, with both approaches being 100% reproducible for me:


Approach 1:

  1. Launch some DB in Access.
  2. Open the VBE.
  3. Close VBE and Access.

Result: No ghost process.


Approach 2:

  1. Launch some DB in Access.
  2. Open the VBE.
  3. Have RD parse the project.
  4. Close VBE and Access.

Result: Ghost process* that when reused will not have RD loaded. (Reused in that executing an .accdb file or similar will not spawn a new process but seemingly use the existing one)


* I've removed the details of the parser run - if you think it's essential to review those 3.8k lines as well, I can provide them. (Though I'd prefer to not publicly upload them - it's my current project at work.)

Inarion commented 6 years ago

100% reproducible for me

Huh? This is only true with one .accdb. If I try again with a different one, in both approaches Access can cleanly exit... Trace log (without parsing part) of approach 2 with a different .accdb

So maybe the parser log is the crucial part? Please tell me your thoughts.

ThunderFrame commented 6 years ago

@Inarion - Are you waiting for the Inspections to appear before closing Access?

If you take a copy of the ghosting ACCDB, and remove all modules, forms and reports, then close and reopen Access, then parse the trimmed down database, do you get ghosting on exit? And if you then further remove all non-default references, close Access, reopen and parse?

That is, if you whittle the ghosting ACCDB down to being a blank database, does it still cause problems? If it doesn't, then I guess we need to discover which component/reference is causing the problem, by slowly removing items one at a time until we can produce a MCVE.

Inarion commented 6 years ago

Are you waiting for the Inspections to appear before closing Access?

I didn't even open the inspections window - just the initial parse to get RD working. (I clicked the Pending button and waited for the parse to finish, then closed Access.)

As for your other questions: I will try to get these tested today. (If my already melting brain allows for it... it's too goddamn hot...)

bclothier commented 6 years ago

From a quick skimming, I cannot see anything that's significant different between the logs.

I'm fairly sure that this has to do with a inspection that's causing a leak, which would be why it clean exits for a particular file; it depends on its codebase or something like, So we're getting closer with a MCVE in order to fix it.

@MDoerner just making sure - is this a cause for concern? I'm not sure if that's a factor but I doubt it - it's present in both logs:


2018-07-30 10:51:18.0938;WARN-2.2.0.3564;Rubberduck.VBEditor.SafeComWrappers.SafeComWrapper`1;Released COM wrapper of type Rubberduck.VBEditor.SafeComWrappers.Office12.CommandBarControl whose underlying RCW has already been released from outside the SafeComWrapper. New reference count is -1.;
Inarion commented 6 years ago

After some chit-chat and trial and error, the current state of our research suggests that parsing an Access project while any form is open will lead to a ghost process remaining.

MCVE:

  1. Create a new .accdb file from within Access.
  2. Close the automatically created table without saving. (It should disappear.)
  3. Create a new empty form (Create --> Empty form) and save it. (I think saving is crucial here!)
  4. Open the VBE and parse while having the empty form open in Access. (Note there is no actual code in the current project.)
  5. Close Access.

Voilà: Hello, Ghost!

daFreeMan commented 6 years ago

OK, something has definitely improved. I had been getting the ghost process no matter what I did. However, I just installed .3564 this morning (single user, Win10-64, Office16/local-32), and can reproduce the clean exit if I have no forms open during the parse.

I have a form that auto-launches, so for giggles, I changed from Form View to Design View before parsing, but I still get the ghost in that situation.

One distinct difference between the Form View ghost and the Design View ghost - Form View's ghost had a significantly larger memory footprint than did Design Views's. Something like 256MB vs 20MB of RAM consumed. (rough estimates from memory - my memory...)

Additional Note: A parse with the form open is what causes the hang - I closed the form, parsed again, then closed and I still get Mr. Zombie-Ghost.

Here are the three log files, in case they may help the situation: RubberduckLog.Form-Ghost.txt RubberduckLog.FormDesign-Ghost.txt RubberduckLog.NoForm-CleanExit.txt

comintern commented 6 years ago

Linking chat.

ThunderFrame commented 6 years ago

I forget whether a press of the Reset button (the :stop: icon in the VBE) will close an Access Form? If it does, it might be worth having Rubberduck reset and compile the project before parsing.

bclothier commented 6 years ago

No, stopping will not reset the forms opened via the DoCmd.OpenForm. Their state, OTOH, will be messed up.

ThunderFrame commented 6 years ago

Also, IIRC, an Access Form, currently, can only have its controls enumerated if the form is open in design view, but I forget whether Rubberduck even tries to enumerate the controls (or do anything differently) if the form is open in design view.

bclothier commented 6 years ago

Actually, I believe controls can be enumerated in a open form. That's the tricky thing. There is an overlap of what code can run in design state and what code can run in run state; and it's fairly substantial; including enumerating the controls. To ensure you are working with a form in design view and not an open form, requires that you know a bit about Access OM in order to query its design state. I don't believe there is a programmatic equivalent from VBE's OM alone to tell us that.

ThunderFrame commented 6 years ago

Depending upon the Access version, you can get an idea of the design state by interrogating the serialized VBA/Access forms/Reports and other meta) in the MSys tables. The old format is a serialized Compound Binary File Format of IStorages and IStreams, the new format is a table hierarchy of Binary fields (IStreams) and parent fields (IStorages). i.e. Both formats are effectively a hierarchy of IStreams. IIRC, there is sometimes a second hierarchy, when design changes are made. We could potentially interrogate this structure to identify the state of the open forms/reports, but it would take some work to identify what exactly constitutes a changed or in use object.

daFreeMan commented 6 years ago

Mentioned in chat, but putting it here for the permanent record:

My form auto-opens when I launch the .accdb. I prevented that by holding down shift as it opened, opened the form directly in Design Mode, parsed the project, and got a zombie-free shutdown of Access.

A9G-Data-Droid commented 6 years ago

I am not seeing this behavior in v2.2.0.3703-pre. I have a fairly simple project with a few forms and some code that updates tables. I can parse, do some stuff with the duck and close Access. It seems to shutdown gracefully for me.

Inarion commented 6 years ago

@A9G-Data-Droid Can't confirm. As long as any form is open in form view or layout view while parsing, the ghost will linger. If I close all open forms / switch to design mode before parsing, all is fine. (== the ghost is busted)

daFreeMan commented 6 years ago

Unfortunately, I'm with @Inarion - I too am continuing to get the ghost if I parse the project with a form in Form View. If the form is in Design View, all is good.

dermoench42 commented 6 years ago

Today I installed Rubberduck v2.2.0.3749-pre I opened my DB went to the Code Editor, clicked on refresh on the rubberduck explorer window. After some time it displays my db and the modules. Meanwhile I took a look on some modules, found what I wanted to check. Was OK so I closed the vba editor. Closed Access, too. Took a look at the Task Manager and there it was: MS ACCESS running, 628,8MB RAM. For 20 Minutes now. Reopen the same db works, calling the vba editor... Rubberduck splash missing, rubberduck missing.

  1. Test. Do the same as above, but not killing the task. Try to open another database. Hmm, nothing happens at all, but the lockfile (.laccdb) appears and the MS ACCESS task has some cpu load (25%). Open a 3rd db. It appears immediately and also rubberduck, but in an new task, which remains the same way as ghost. There is something in Rubberduck which prevents Access from terminating or freeing the Ressources. ervin
A9G-Data-Droid commented 6 years ago

I found a thread from GetLatestVersionAsync was still running after I had closed Access. This is only one of the stragglers. After I disabled version check I am still seeing the ghost process occasionally. I believe there might be a WPF thread still running as well because I see the XAML debugger still going after Access is closed.

Microsoft.VisualStudio.DesignTools.WpfTap.dll!Microsoft.VisualStudio.DesignTools.WpfTap.Networking.AnonymousPipe.WaitForCondition

Inarion commented 6 years ago

@A9G-Data-Droid It's really easy to reproduce: Have any form (that has been saved at least once) open in form view while RD parses -> Teardown issues and ghost process.

The Version Check doesn't seem to be a problem on my machine, at least deactivating didn't change anything for me.

daFreeMan commented 6 years ago

Unfortunately, I must again agree with @Inarion. Running build .3835, I launched Access, closed my auto-open form, launched the VBE, turned OFF the version check, closed the VBE and Access, relaunched my project leaving the auto-open form open, parsed, closed Access and have a zombie Access process.

Don't let this dissuade you, @A9G-Data-Droid, keep going! Keep digging! Somebody's got to figure this out and it may as well be you!

A9G-Data-Droid commented 6 years ago

Sorry if I was unclear. I have identified at least 2 threads that hang after close. One is the version check and one is a WPF object. The WPF thread remains when version check is disabled.

bclothier commented 6 years ago

Update - I was able to pinpoint the problem down to code explorer, specifically this constructor here:

        public CodeExplorerComponentViewModel(CodeExplorerItemViewModel parent, Declaration declaration, IEnumerable<Declaration> declarations, IProjectsProvider projectsProvider)
        {
...
            var qualifiedModuleName = declaration.QualifiedName.QualifiedModuleName;
            try
            {
                switch (qualifiedModuleName.ComponentType)
                {
                    case ComponentType.Document:
                        var component = _projectsProvider.Component(qualifiedModuleName);
                        string parenthesizedName;
                        using (var properties = component.Properties)
                        using (var nameProperty = properties["Name"])
                        {
                            parenthesizedName = nameProperty.Value.ToString() ?? string.Empty;
                        }
...
            }
            catch
            {
                // gotcha! (this means that the property either doesn't exist or we weren't able to get it for some reason)
            }
        }

When the form is in design view, there is no problem running the constructor and all is good. However, when it's in form view, an exception is thrown.

The first exception is:

+       $exception  {"Function or interface marked as restricted, or the function uses an Automation type not supported in Visual Basic"}   System.Runtime.InteropServices.COMException

thrown on the line using (var properties = component.Properties).

The second exception for the same QMN called again later is:

+       $exception  {"Object doesn't support this property or method"}  System.NotSupportedException

thrown on the line using (var nameProperty = properties["Name"])

I have verified that if we skip the section entirely, Rubberduck is able to parse even when the form is open in form view and will not leave a ghost process. Obviously the exceptions are causing it to leak a COM object and thus we end up with a ghost process.