Rubberduck icon indicating copy to clipboard operation
Rubberduck copied to clipboard

Supporting Autodesk Inventor

Open inventordev opened this issue 1 year ago • 7 comments

Hello,

I'm trying to support Autodesk Inventor.

Some of declaration throw the exceptions and they cause "Resolver Error". I determined the declarations that causing the error and wrote the code to discard them.

// TypeAnnotationPass.cs
        public void Execute(IReadOnlyCollection<QualifiedModuleName> modules)
        {
            var toDetermineAsTypeDeclaration = _declarationFinder
                                                .FindDeclarationsWithNonBaseAsType()
                                                .Where(decl => decl.AsTypeDeclaration == null 
                                                        || modules.Contains(decl.QualifiedName.QualifiedModuleName));
            foreach (var declaration in toDetermineAsTypeDeclaration)
            {
+               if (declaration.CustomFolder == "Inventor" && 
+                   declaration.AsTypeName == "Circle")
+               {
+                   continue;
+               }
                AnnotateType(declaration);
            }
        }

How can I properly address this issue?

Thanks,

inventordev avatar Jul 09 '22 13:07 inventordev

I found the interesting thread. https://stackoverflow.com/questions/22986017/undocumented-vba-special-keywords-circle-and-scale

Here is a test code and the errors happen with a vanilla Excel VBA.

Sub test()
    Dim Circle As Object ' Error
    Dim Scale as Object ' Error
    Dim Line As Object ' OK
    Dim Point As Object ' OK
End Sub

"Circle" seems to be a special keyword and Rubberduck may be confused because Inventor has a class named "Circle".

inventordev avatar Jul 10 '22 00:07 inventordev

I think you are right with your analysis. To deal with this, one probably has to amend the parser and the resolver in analogy with how we did it to enable the Object.Print statement from VB6.

MDoerner avatar Jul 10 '22 06:07 MDoerner

Hi @inventordev , I have applied this patch to the lastest Rubberduck source code, but Rubberduck still crashes on load with Inventor 2020. Which version of Inventor are you using?

ls-2037 avatar Aug 09 '22 20:08 ls-2037

Hi, I'm using Inventor 2022. I'll try with 2020 later.

inventordev avatar Aug 10 '22 00:08 inventordev

Inventor 2020 cause an error when booting VBE as you said...

inventordev avatar Aug 10 '22 01:08 inventordev

NLog.LogManager.Configuration was null if Inventor 2020 was used and this caused the error. I don't know why it was null or who should have initialized this object.

inventordev avatar Aug 10 '22 05:08 inventordev

Hi @inventordev , I have been using this patch with Inventor 2022 and it does allow Rubberduck to work. However, I often get an "Unexpected Error" from Rubberduck during refresh when I have Inventor files open. Have you had any similar issues?

ls-2037 avatar Jan 16 '23 16:01 ls-2037