delete layout from dwg when selected in listbox.

delete layout from dwg when selected in listbox.

Anonymous
Not applicable
1,588 Views
17 Replies
Message 1 of 18

delete layout from dwg when selected in listbox.

Anonymous
Not applicable

Hi 

**using autocad 2015 and downloaded the latest VBA engine from autodesk.

I have a vba userform that lists all the layouts in the current dwg. I want to be able to delete the layouts when selected in the list box and i click submit. 

Private Sub SubmitButton_Click()
    Dim MyArray() As Variant
    Dim i As Long
    Dim Cnt As Long
    With Me.Listbox1
        Cnt = 0
        For i = 0 To .ListCount - 1
            If .Selected(i) = False Then
                Cnt = Cnt + 1
                ReDim Preserve MyArray(1 To Cnt)
                MyArray(Cnt) = .List(i)
            End If
        Next i
        If Cnt > 0 Then
            If ThisDrawing.Layouts.Count > UBound(MyArray) Then
                'Application.DisplayAlerts = False
                ThisDrawing.Layouts(MyArray).Delete
                'Application.DisplayAlerts = True
                Call UpdateSheetList
            Else
               'MsgBox "A workbook must contain at least one visible sheet.", vbExclamation
            End If
        Else
           'MsgBox "Please select one or more sheets for deletion...", vbExclamation
        End If
   End With
        'Unload Me
End Sub
Private Sub CancelButton_Click()
'unload form
    Unload Me
End Sub
Private Sub UserForm_Initialize()
    Call UpdateSheetList
End Sub
Private Sub UpdateSheetList()
    Dim PlotLayout As AcadLayout
    Dim PlotLayouts As AcadLayouts
        Listbox1.Clear
    Set PlotLayouts = ThisDrawing.Layouts
        For Each PlotLayout In PlotLayouts
        'ThisDrawing.ActiveLayout = PlotLayout
        Listbox1.AddItem PlotLayout.Name
    Next
End Sub

 I am converting code from Excel so I think that's wehre my hang up is but i get the following code when I run it: invalid call or procedure. It pops up and i can select items but when i click submit it keeps erroring out. 

 

Thanks in advance. 

0 Likes
Accepted solutions (1)
1,589 Views
17 Replies
Replies (17)
Message 2 of 18

Anonymous
Not applicable

try this...

 

For i = 0 To .ListCount - 1
      If .Selected(i) Then ThisDrawing.Layouts(.Item[i]).Delete
Next i

 

i hope this help...

0 Likes
Message 3 of 18

Anonymous
Not applicable

I tried this it just gives me a syntax error. Thanks anyway.

0 Likes
Message 4 of 18

Anonymous
Not applicable
If Cnt > 0 Then
            If ThisDrawing.Layouts.Count > UBound(MyArray) Then
                ThisDrawing.Layouts(MyArray).Delete

  The problem seems to be here ^^^ I get the following error when I run:

     "Run-time error '5': Invalid procedure call or argument"

and it highlights:

ThisDrawing.Layouts(MyArray).Delete

 

0 Likes
Message 5 of 18

Anonymous
Not applicable

your "MyArray" is a variant, containing all the names of Layouts selected for deletion

while the Delete method must acts on a single item of the Layouts collection

 

try cycling through MyArray and use "ThisDrawing.Layouts.item(MyArray(i)).Delete" (were I assumed "i" as the loop counter)

0 Likes
Message 6 of 18

Anonymous
Not applicable

RIVBA

 

This is what i did:

Private Sub SubmitButton_Click()
On Error Resume Next
    Dim i As Long
    With Me.Listbox1
        For i = 0 To .ListCount - 1
            If .Selected(i) Then
                ThisDrawing.layouts.Item((i)).Delete
            End If
        Next i
        'UpdateSheetList
   End With
        'Unload Me
End Sub

 

It seems to work but it only deletes one at a time ie i need to click submit multiple times (but, it removes the selected from the listbox) is there a way to delete all selected items?

0 Likes
Message 7 of 18

Anonymous
Not applicable

or all un-selected items (ideally)

0 Likes
Message 8 of 18

Anonymous
Not applicable

just set the listbox "MultiSelect" property to let you select multiple items.

look through VBA help file to carefully choose the proper option of three available (actually one is for single selection, so there you'll choose between two of them).

you can do this at design time but also at run time, adding a codeline like

me.ListBox1.MultiSelect=fmMultiSelectMulti

 

0 Likes
Message 9 of 18

Anonymous
Not applicable

Sorry I should have specified it is already a multi select. I can select all the ones i want but on submit it only deletes one of them. Everything works great except it just deletes one sheet at a time Smiley Frustrated

0 Likes
Message 10 of 18

Anonymous
Not applicable
Maybe that "on error resume next" is hiding something wrong. Comment it out and debug.
You may want to send your dwg and the complete code for us to be more effective.
0 Likes
Message 11 of 18

Ed__Jobe
Mentor
Mentor

You're working with a list from the list of selected items in the listbox. That list has an index all its own. It does not match the index of ThisDrawing.Layouts. Furthermore, once you delete a layout, the index has to reinitialize, so you can't count on the index numbers to be the same as before and just iterate the list as you delete items. In the listbox, you have the layout names. Try deleting layouts by their indexed name, rather than their numerical index.

Ed


Did you find this post helpful? Feel free to Like this post.
Did your question get successfully answered? Then click on the ACCEPT SOLUTION button.
How to post your code.

EESignature

0 Likes
Message 12 of 18

Anonymous
Not applicable

Below is the complete code in use. It works with any autocad drawing. I've been just useing a new drawing nothing in it and adding layers and testing. 

 

Private Sub SubmitButton_Click()
'On Error Resume Next
    Dim i As Long
    With Me.Listbox1
        For i = 0 To .ListCount - 1
            If .Selected(i) Then
                ThisDrawing.Layouts.Item((i)).Delete
            End If
        Next i
        UpdateSheetList
   End With
        'Unload Me
End Sub
Private Sub CancelButton_Click()
'unload form
    Unload Me
End Sub
Private Sub UserForm_Initialize()
    Call UpdateSheetList
End Sub
Private Sub UpdateSheetList()
    Dim Lyt As AcadLayout
    Dim Lyts As AcadLayouts
        Listbox1.Clear
    Set Lyts = ThisDrawing.Layouts
        For Each Lyt In Lyts
        Listbox1.AddItem Lyt.Name
    Next
End Sub

 

0 Likes
Message 13 of 18

Anonymous
Not applicable

eljobe's one is your point.

 

try debugging and while inside the "For i = 0 To .ListCount - 1" loop, go to the Immediate Window and type

?ThisDrawing.Layouts.Item(i).Name

and then press enter

 

then do the same with

?Me.ListBox1.List(i)

to see if they match.

and they generally won't, unless that listbox has been filled following the Layouts order. but even then, after the first deletion, those two collections won't have one indexing number point the same layout name.

 

so you have to use

ThisDrawing.Layouts.Item(.List(i)).Delete

 to have ListBox's "List()" property give you the Layout name to use in Layouts "Item()" property.

 

or go back to your fisrt posted code solution where you used "MyArray" array to store to be deleted Layouts names and loop through it using

ThisDrawing.Layouts.item(MyArray(i)).Delete

 

 

 

Message 14 of 18

Anonymous
Not applicable

think we are on to something, but i dont get what you mean by "go to immediate window" when i add that code it says the "name" part is an "invalid use of property"

 

sorry for my ignorance. 

0 Likes
Message 15 of 18

Ed__Jobe
Mentor
Mentor

The Immediate window is another IDE window that allows you to type vba and have it execute immediately. Its also where the output from Debug.Print goes to. To show the window, View>Immediate Window or Ctrl+G.

 

Type:

Debug.Print ThisDrawing.Layouts(0).Name {Enter}

 

In a new, unnamed dwg, this will return "Layout1".

 

You can also code ThisDrawing.Layouts("Layout1").Delete, provided other layouts exist. The point is that you can refer to the layout by its name as well. You have the names stored in your listbox and can refer to them with ListBox1.Selected(0). This should evaluate to a string that can be used in the Delete line.

 

ThisDrawing.Layouts("Layout1").Delete becomes ThisDrawing.Layouts(ListBox1.Selected(i)).Delete where i is the index number that points to the listbox item where "Layout1" was selected. Note that I've left off the Item method since this is the default method for the Layouts collection.

Ed


Did you find this post helpful? Feel free to Like this post.
Did your question get successfully answered? Then click on the ACCEPT SOLUTION button.
How to post your code.

EESignature

Message 16 of 18

Anonymous
Not applicable

this makes sense to me but i'm not able to put it into code. Truthfully while I get the concept I'm still learning the syntax and how it all works together. can you show me what this would look like.

 

You guys are awesome. 🙂

0 Likes
Message 17 of 18

Ed__Jobe
Mentor
Mentor
Accepted solution
If .Selected(i) Then
                ThisDrawing.Layouts.Item(Listbox1.List(i,0)).Delete
            End If

Ed


Did you find this post helpful? Feel free to Like this post.
Did your question get successfully answered? Then click on the ACCEPT SOLUTION button.
How to post your code.

EESignature

Message 18 of 18

Anonymous
Not applicable

awesome !! it works. I was close i was writing it as:

 

ThisDrawing.Layouts.Item(.List(i)).Delete

 

 

so in your verision its saying for each item in listbox1 list that's selected delete. 

 

is that an over simplication. Thanks again!! 

0 Likes