VBA
Discuss AutoCAD ActiveX and VBA (Visual Basic for Applications) questions here.
cancel
Showing results for 
Show  only  | Search instead for 
Did you mean: 

ACAD 2015 VBA elockviolation ERROR

14 REPLIES 14
Reply
Message 1 of 15
alexborodulin1
2173 Views, 14 Replies

ACAD 2015 VBA elockviolation ERROR

In autocad 2015 whenever I use VBA application inserting different blocks with attributes autocad works fine for 2, 3 o 4 insertions of blocks. After that when I insert block AutoCAD crashes with error message:

 

internal error: !dbinsert.cpp@1294: elockviolation

 

In previous versions (ACAD2014 or earlier) there were no problem with this VBA application.

Any help will be appreciated.

 

Alex

 

14 REPLIES 14
Message 2 of 15

Hi,

 

can you reproduce that with an emtpy drawing and just the lines for inserting one specific block?

If so it will be very helpful to upload that sample-code, the drawing you use here as empty drawing + the block you try to insert.

If it's part from a complete application and it is not reproducable with a sample it will also be difficult for us here to reproduce what you get.

 

Very important to know also:

  • what os do you have (Win7, Win8, Win8.1 / 32bit or 64bit)?
  • do you insert the block from an external drawing or do you have the blockdefinition already in the drawing where you want to inserted it as blockreference?

 

- alfred -

------------------------------------------------------------------------------------
Alfred NESWADBA
Ingenieur Studio HOLLAUS ... www.hollaus.at ... blog.hollaus.at ... CDay 2024
------------------------------------------------------------------------------------
(not an Autodesk consultant)
Message 3 of 15

The error indicates that you attempted to access the database without first requesting and obtaining permission. Start by making sure you lock the database before attempting to access it. If the lock fails, then something (perhaps an unfinished command) still holds the lock, and your code must either cancel or complete the operation or wait until the database becomes available.

--
Owen Wengerd
ManuSoft
Message 4 of 15

Hi Owen,

 

>> Start by making sure you lock the database

How do you lock a database with VBA?

 

- alfred -

------------------------------------------------------------------------------------
Alfred NESWADBA
Ingenieur Studio HOLLAUS ... www.hollaus.at ... blog.hollaus.at ... CDay 2024
------------------------------------------------------------------------------------
(not an Autodesk consultant)
Message 5 of 15


@Alfred.NESWADBA wrote:

>> Start by making sure you lock the database

How do you lock a database with VBA?


Erm, you can't. I was thinking VB.NET. That makes it a little bit harder to track down the culprit in this case, nevertheless the task remains the same.

--
Owen Wengerd
ManuSoft
Message 6 of 15
epdavid
in reply to: alexborodulin1

Hi,

I had the same problem - same error, did you manage to figure out what's going on?

Thanks Ed

Message 7 of 15
DeGrooteAntea
in reply to: epdavid

At the office we recently updated to Autocad 2015.

When I execute my code (insert line of block, change line or block,...), I to get the elockviolation Error.

How can I solve this for VBA?

Message 8 of 15

Hi,

 

may I repeat my lines:

Can you reproduce that with an emtpy drawing and just the lines for inserting one specific block?

If so it will be very helpful to upload that sample-code, the drawing you use here as empty drawing + the block you try to insert.

 

Otherwise it looks hard to get that isolated as long as nobody else can reproduce that.

 

- alfred -

------------------------------------------------------------------------------------
Alfred NESWADBA
Ingenieur Studio HOLLAUS ... www.hollaus.at ... blog.hollaus.at ... CDay 2024
------------------------------------------------------------------------------------
(not an Autodesk consultant)
Message 9 of 15

The Error was produced with VBA code for block insertion (procedure INSMS1old)

Select client from combobox (form at the bottom of message); name of client gets into name of block and Template.dwg from corresponding folder added to drawing.

 

Sub INSMS1old(B)

 

Dim blockRefObj As AcadBlockReference

Dim insertionPnt(0 To 2) As Double

   insertionPnt(0) = 2#: insertionPnt(1) = 2#: insertionPnt(2) = 0

   If ThisDrawing.ActiveSpace = acModelSpace Then

   Set blockRefObj = ThisDrawing.ModelSpace.InsertBlock(insertionPnt, _

   DRIV & NYAC & "Clients\" & B & "\Template.dwg", 1#, 1#, 1#, 0)

Else:

   Set blockRefObj = ThisDrawing.PaperSpace.InsertBlock(insertionPnt, _

   DRIV & NYAC & "Clients\" & B & "\Template.dwg", 1#, 1#, 1#, 0)

End If

End Sub

 

THE PROBLEM WAS RESOLVED WITH PRIMITIVE SENDCOMMAND...-INSERT

 

Sub INSMS1(B)

Dim blona

blona = DRIV & NYAC & "Clients\" & B & "\Template.dwg"

ThisDrawing.SendCommand ("-insert " & blona & vbCr & "0,0 1 1 0 ")

 

End Sub

 

--------------

Regards,

Alex Borodulin

 

NYacadSymbolsMarksForm.png

Message 10 of 15

I have tested it with an empty drawing. The result is the same. Most of the times i am able to insert the block once, but then i get the lock violation. Using the sendcommand is not realy an option for me because i need to acces the block to be able to update it. Below is a small part of my code. My program is used to interpret CPT-data. First I select a Zero-point (Nulpunt), then i insert a block with an atribute displaying the level. Then I use Plus (or Min) to position the block on the right position (layer separation for CPT). The block is just a line with a text above (the atribute).

 

 

Public NULX As Double
Public NULY As Double
Public SPLITSLIJN As AcadBlockReference
Public DW1 As AcadDocument
Dim NULOK As Boolean
Public LAAGOK As Boolean
Public EINDE As Boolean
Public Const LOCATIE_GRONDONDERZOEK = "M:\"

Public Const PI = 3.14159265358979

#If VBA7 Then
    Public Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
#Else
    Public Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
#End If



Sub PLUS()

        Dim PUNT As Variant
        PUNT = SPLITSLIJN.InsertionPoint
    Dim Attrib As Variant
    Dim DeltaY As Double
    Dim DY As Double
    DeltaY = 0.05

    
    PUNT(1) = PUNT(1) + DeltaY
    DY = PUNT(1) - NULY
    On Error Resume Next 'already lock violation here
        SPLITSLIJN.InsertionPoint = PUNT
        Debug.Print Err.Number
    On Error GoTo 0
    
    Dim PEIL As String
    PEIL = Format(DY, "standard")
    If DY >= 0 Then PEIL = "+" & PEIL
    Attrib = SPLITSLIJN.GetAttributes
    Attrib(0).TextString = PEIL
    SPLITSLIJN.UPDATE
    SPLITSLIJN.InsertionPoint = PUNT

End Sub



Sub NULPUNT()

    Set DW1 = Application.ActiveDocument

        Dim PPUNT As Variant
        On Error Resume Next
        PPUNT = DW1.Utility.GetPoint(, "SELECTEER NULPUNT")
        If GetAsyncKeyState(vbKeyEscape) Then GoTo EINDE
        On Error GoTo 0
        NULX = PPUNT(0)
        NULY = PPUNT(1)
    NULOK = True
EINDE:
End Sub


Sub INVOEGLAAG()
Debug.Print GetAsyncKeyState(vbKeyEscape)

If NULOK = False Then Call NULPUNT

Set DW1 = Application.ActiveDocument
Dim Attrib As Variant
Dim INVOEGPUNT As Variant
    
        On Error Resume Next
        INVOEGPUNT = ThisDrawing.Utility.GetPoint(, "Geef positie laag")
        
        If GetAsyncKeyState(vbKeyEscape) Then GoTo EINDE
        On Error GoTo 0
        Set SPLITSLIJN = ThisDrawing.ModelSpace.InsertBlock(INVOEGPUNT, LOCATIE_GRONDONDERZOEK & "ACADBLOCKS\Laagopbouw.dwg", 1#, 1#, 1#, 0)
        

        LAAGOK = True
        
        

    DY = (INVOEGPUNT(1) - NULY)
    Dim PEIL As String
    PEIL = Format(DY, "standard")
        
    Attrib = SPLITSLIJN.GetAttributes
    
    Attrib(0).TextString = DY
    SPLITSLIJN.UPDATE

EINDE:
End Sub
Message 11 of 15

Hi,

 

Just to make sure: you get the elock-violation at that following code line (and not during the insert)?

 

 On Error Resume Next 'already lock violation here

I'm not sure about the GetAsyncKeyState ... have you ever tried to just get the point and then test for Err.Number <> 0?
I know that this is not exactly the same, but like you use it this should be just a bit different, because that code also handles none-input too:

 

On Error Resume Next
Pnt = ThisDrawing.Utility.GetPoint( , "Point. ")
If Err.Number = 0 then
   ... do your steps, point is given
else
   ... break, no valid point shown
end if

 - alfred -

------------------------------------------------------------------------------------
Alfred NESWADBA
Ingenieur Studio HOLLAUS ... www.hollaus.at ... blog.hollaus.at ... CDay 2024
------------------------------------------------------------------------------------
(not an Autodesk consultant)
Message 12 of 15

Hi Alfred,

 

I get a Lock violation when i want to "move" the block. This is bypassed by the "on error resume next"-statement.

 

The real lock violation happens on the insert of the block. The whole program crashes and I get the following message:

ELock Violation.JPG

 

 

The GetAsyncKeyState is used to exit the code when i press Escape. This code poses no problem.

 

Message 13 of 15

Hi,

 

>> The GetAsyncKeyState is used to exit the code when i press Escape. This code poses no problem.

As it's name contains "Async" I'm not sure if that is thread-safe, that's why I suggested to try my way (which also handles the ESC key + additionally the no-input/just enter).

 

- alfred -

------------------------------------------------------------------------------------
Alfred NESWADBA
Ingenieur Studio HOLLAUS ... www.hollaus.at ... blog.hollaus.at ... CDay 2024
------------------------------------------------------------------------------------
(not an Autodesk consultant)
Message 14 of 15

Hi Alfred,

 

I tried it your way. It handles the escape key as expected. From now on i will use this method, thanks.

However it does not change anything about the lockviolation...

Message 15 of 15

Hi,

 

Do you have verified your code with other drawings and other blocks?

 

>> At the office we recently updated to Autocad 2015.

When you installed AutoCAD 2015, have your also installed the service packs for that?

 

- alfred -

------------------------------------------------------------------------------------
Alfred NESWADBA
Ingenieur Studio HOLLAUS ... www.hollaus.at ... blog.hollaus.at ... CDay 2024
------------------------------------------------------------------------------------
(not an Autodesk consultant)

Can't find what you're looking for? Ask the community or share your knowledge.

Post to forums  

Autodesk Design & Make Report

”Boost