Differences in Error Handling between VBA and OOo Basic

I have been looking at the difference in how OOo Basic (OOB) and VBA handle errors.  I started from the basis of a whitepaper that I wrote (see Error Handling in VBScript – Part I) and which explains how VBA and VBscript error handling really works. Incidentally this is not how it is described in the Microsoft documentation.  I used a test that I included in the paper as my starting point. (By the way, of the couple of dozen guys who I know have tried it, not one correctly predicted the answer).  Here is the code for the test.

' 
' VBA Version. To convert to OOo Basic remove the "Debug." objects 
' 
Dim a, b, c 
b = "*": c = b 
On Error Resume Next 
' Note that 1/0 generates error 11 -- division by zero 
' Note thAt a(2) generates error 9 -- subscript out of range 
a = Array(0, 1) 
b = 1 / a(0): Debug.Print "(a) = ", b, Err Err.Clear 
c = a(2): Debug.Print "(b) = ", c, Err 
b = 1 / c: Debug.Print "(c) = ", b, Err 
b = 1 / a(2): Debug.Print "(d) = ", b, Err 
Debug.Print "(e) =", b, Err
Debug.Print "(f) = ", a(2), Err 
b = a(0): Debug.Print "(g) = ", b, Err 
Blah a, 2, True, False: Debug.Print "(h) = ", a(2), Err 
Blah a, 2, False, True: Debug.Print "(i) = ", a(2), Err 
Blah a, 2, False, False: Debug.Print "(j) = ", a(2), Err 
Blah a, 1, True, False: Debug.Print "Final Status = ", a(1), Err
 ... 
Sub Blah(a, i, trap, cont)
  Dim b, c
  If trap Then On Error GoTo 0
  If cont Then On Error Resume Next
  b = a(i)
  c = 1 / b
End Sub

Now .Number is the default parameter of Err (we are talking VBA and not VB.Net), so Err works both in VBA and OOB. Also OOB doesn’t throw the error on Err.Clear because of the On Error Resume Next. The output for VBA is:

(a) = * 11
(b) = * 9
(c) = * 13
(d) = * 9
(e) = * 9
(g) = 0 9
Final Status = 1 0

And for OOB:

(a) = * 0
(b) = * 0
(c) = * 0
(d) = * 0
(e) = * 0
(f) = (g) = 0 0 
(h) = (i) = (j) = Final Status = 1 0

These, plus stepping through with the IDE and watching the variables tells me that

  1. Both VBA and OOB abort the current statement on Error. (The differences for (f) are due to the fact that VBA assembles the whole line for output, but OOB aborts but leaves part output in the Print buffer which pricked by the next valid Print
  2. Both step to the Error handler label in the case of On Error Goto Label and to the next statement in the case of On Error Resume Next.
  3. Both handle call stack unrolling and catching of errors at a parent in the same way.
  4. The major difference in behaviour is that OOB doesn’t only puts the error details in Err etc. when Resume Next is in force.

So my warming is that if you’ve got used to the VBscript approach of doing Goto-less Error handling then watch out.  IT DOESN’T WORK IN OOB.  However you can implement something approaching this by appending the following default hander to your code and using ErrNo (which needs to be Global) instead [i] except that the On Error and Resume statements do not reset ErrNo. You will need to remember to do this yourself.

On Error Goto ErrRet  ' At head of routine
 ...  
 Exit Sub
' or Function as appropriate at foot of routine
ErrRet:
  ErrNo = Err
  Resume Next

Leave a Reply