Consulting

Results 1 to 10 of 10

Thread: VBA errors

  1. #1
    VBAX Newbie
    Joined
    Mar 2014
    Posts
    4
    Location

    VBA errors

    Hello all!

    I'm fairly new to the forums and to vba also.

    My issue is that it jumps the yes part of an If ( the Sub PROM () IF) and i don't really know why, and also that after it does it gives the error "Overflow"

    Dim p as Long
    ------------------------------
    Sub PROJECT ()
        Dim n As Integer, i As Integer, j As Integer
        Dim y(100) As Integer, sum As Long, p As Long, sum2 As Long, a As Long
        n = InputBox(" Please enter the total of values to evaluate (12)", "VALUE")
        
        If n < 2 Then
            MsgBox "Incorrect value, please enter a value that is higher than 2", vbCritical, "ERROR"
            Call PROJECT
            Else
            i = 0
            sum = 0
            Call PROM
            j = 0
            sum2 = 0
            Call EXP
            a = Sqr(sum2 / (n - 1))
        End If
    
    End Sub
    ------------------------------------------------
    Sub PROM()
        Dim i As Integer, n As Integer
        Dim sum As Long, y(100) As Integer
            If i <= n - 1 Then
                y(i) = InputBox("Please enter a value", "Value")
                sum = sum + y(i)
                i = i + 1
                Call PROM
                Else
                p = sum / n
            End If
    End Sub
    ----------------------------
    Sub EXP()
        Dim j As Integer, n As Integer
        Dim sum2 As Long, y(100) As Integer
        If j <= n - 1 Then
            sum2 = sum2 + (y(j) - p) ^ 2
            j = j + 1
            Call EXP
        End If
    End Sub
    Also this is still a work in progress, i still need to finish the output part of the program... i have a giant mess here haha.

  2. #2
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location
    Greetings cybotzu and welcome to vbaexpress

    My issue is that it jumps the yes part of an If ( the Sub PROM () IF) and i don't really know why, and also that after it does it gives the error "Overflow"
    Okay, let us step through the lines likely to be executing:


    Option ExplicitDim p As Long
    You have one variable declared at module level. So this is the only variable that will retain its value between procedures.

    Sub PROJECT()
        Dim n As Integer, i As Integer, j As Integer
        Dim y(100) As Integer, sum As Long, p As Long, sum2 As Long, a As Long
        n = InputBox(" Please enter the total of values to evaluate (12)", "VALUE")
         
        If n < 2 Then
            MsgBox "Incorrect value, please enter a value that is higher than 2", vbCritical, "ERROR"
            Call PROJECT
        Else
            i = 0
            sum = 0
            Call PROM
            j = 0
            sum2 = 0
            Call EXP
            a = Sqr(sum2 / (n - 1))
        End If
         
    End Sub
    In the above, assuming we typed a number of 2 or greater, we end up calling PROM().

    Sub PROM()
        Dim i As Integer, n As Integer
        Dim sum As Long, y(100) As Integer
    
        If i <= n - 1 Then
            y(i) = InputBox("Please enter a value", "Value")
            sum = sum + y(i)
            i = i + 1
            Call PROM
        Else
            p = sum / n
        End If
    End Sub
    In PROM(), 'i' has a value of 0, as does 'n'. This is because both are declared local to the procedure, and Integer/Long variables default to 0. So... we are really testing:

    If 0 <= 0-1 Or simplified, If 0 <= -1 which of course it will not be.

    Hence, the Else gets executed, and we have p = sum / n, or that is, p = 0 / 0. So you see, you end up with a divided by zero error.

    Does that makes sense?

    Mark

  3. #3
    VBAX Newbie
    Joined
    Mar 2014
    Posts
    4
    Location
    Quote Originally Posted by GTO View Post
    Greetings cybotzu and welcome to vbaexpress



    Okay, let us step through the lines likely to be executing:


    Option ExplicitDim p As Long
    You have one variable declared at module level. So this is the only variable that will retain its value between procedures.

    Sub PROJECT()
        Dim n As Integer, i As Integer, j As Integer
        Dim y(100) As Integer, sum As Long, p As Long, sum2 As Long, a As Long
        n = InputBox(" Please enter the total of values to evaluate (12)", "VALUE")
         
        If n < 2 Then
            MsgBox "Incorrect value, please enter a value that is higher than 2", vbCritical, "ERROR"
            Call PROJECT
        Else
            i = 0
            sum = 0
            Call PROM
            j = 0
            sum2 = 0
            Call EXP
            a = Sqr(sum2 / (n - 1))
        End If
         
    End Sub
    In the above, assuming we typed a number of 2 or greater, we end up calling PROM().

    Sub PROM()
        Dim i As Integer, n As Integer
        Dim sum As Long, y(100) As Integer
    
        If i <= n - 1 Then
            y(i) = InputBox("Please enter a value", "Value")
            sum = sum + y(i)
            i = i + 1
            Call PROM
        Else
            p = sum / n
        End If
    End Sub
    In PROM(), 'i' has a value of 0, as does 'n'. This is because both are declared local to the procedure, and Integer/Long variables default to 0. So... we are really testing:

    If 0 <= 0-1 Or simplified, If 0 <= -1 which of course it will not be.

    Hence, the Else gets executed, and we have p = sum / n, or that is, p = 0 / 0. So you see, you end up with a divided by zero error.

    Does that makes sense?

    Mark
    Actually yes, yes it does but i thought by having the first If that makes 'n' bigger than than 2 then i had no problem when it went to the second If which was i <= n-1 unless the real problem here is because im declaring them wrong?

  4. #4
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,728
    Location
    In addition, to Mark's $4.75 of comments (he raised his rates again) , here's my $.02



    'always a good idea (read in Help)
    Option Explicit
    'global variables only when necessary
    'hard to debug
    'using functions with passed parameters would most liekly be easier
    Dim p As Long
    Sub PROJECT()
        'IMHO more descriptive variable names will make it easier for others
        '    and in 6-8 months for you to figure out since it will be 'self documenting'
        '    ex. Dim NumberOfVariables as Long, NumbersArray(100) as Long, etc.
        Dim n As Integer, i As Integer, j As Integer
        'these are Dim-ed as Long, but that's just a fancy name for a really big number WITH NO DECIMALS
        '    At a minimum you'd what variable a to be  'As Double'
        'Also as (100), the y indexes begin at 0 and go to 100. Just if you're not aware
        '   You could use Option Base 1, or be explicit Dim y(1 to 100) if you want
        '   (read Help about using LBound and UBound when you get a chance)
        'You have y(100) Dim-ed in this sub, as well as in the 2 lowere level subs
        '   Each of them will be different (read about Scope in the Help), but just having the same name
        Dim y(100) As Integer, sum As Long, p As Long, sum2 As Long, a As Long
        
        'more user-friendly to provide acceptable range, and how to just exit
        'This is the way I'm used to doing it but there are many others
        n = -1
        On Error Resume Next
        n = InputBox(" Please enter the total of values to evaluate (2 - 12)," & vbCrLf & vbCrLf & _
               "or [Cancel] to exit", "VALUE")
        On Error GoTo 0
        If n = -1 Then Exit Sub
        
        'n = InputBox(" Please enter the total of values to evaluate (12)", "VALUE")
         
        If n < 2 Then
            MsgBox "Incorrect value, please enter a value that is higher than 2", vbCritical, "ERROR"
            
            'I REALLY doubt that you want recursion here (sub calling itself)
            'it might never happen, but if you enter 1 multiple times and single step you'll see
            '   (there are times when you might want to use recursion, so I'm not sure)
            Call PROJECT
        
        Else
            'These are NOT the same i and sum as used in PROM and EXP (Scope again)
            i = 0
            sum = 0
            Call PROM
            j = 0
            sum2 = 0
            Call EXP
            a = Sqr(sum2 / (n - 1))
        End If
         
    End Sub
    Sub PROM()
        'i starts as 0 and so does n
        Dim i As Integer, n As Integer
        Dim sum As Long, y(100) As Integer
        
        'if 0 <= 0 - 1 then ....
        If i <= n - 1 Then
            y(i) = InputBox("Please enter a value", "Value")
            sum = sum + y(i)
            i = i + 1
            Call PROM   'Recursion desired???
        Else
            p = sum / n
        End If
    End Sub
    Sub EXP()
        Dim j As Integer, n As Integer
        Dim sum2 As Long, y(100) As Integer
        If j <= n - 1 Then
            sum2 = sum2 + (y(j) - p) ^ 2
            j = j + 1
            Call EXP    'Recursion desired????
        End If
    End Sub
    Paul

  5. #5
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,728
    Location
    So just a simple example of some concepts to consider if you want ...

    1. Variable Scope
    2. Functions with passed and returned paramenters
    3. Self documenting (IMHO) variable names
    4. Parameter validation (2 - 12). I left as repeated code for the example, but normally it should be modularized into a single validation function, called 2 times


    Option Explicit
    Sub Proj()
        Dim FirstNumber As Long, SecondNumber As Long
        Dim DividedBy As Double
        
        'get first number. must be between 2 and 12
        Do
            FirstNumber = -1
            On Error Resume Next
            FirstNumber = InputBox(" Please enter FirstNumber (2 - 12)," & vbCrLf & vbCrLf & _
                "or [Cancel] to exit", "VALUE")
            On Error GoTo 0
            If FirstNumber = -1 Then Exit Sub
        Loop Until FirstNumber >= 2 And FirstNumber <= 12
        
        'get second number. must be between 2 and 12
        Do
            SecondNumber = -1
            On Error Resume Next
            SecondNumber = InputBox(" Please enter SecondNumber (2 - 12)," & vbCrLf & vbCrLf & _
                "or [Cancel] to exit", "VALUE")
            On Error GoTo 0
            If SecondNumber = -1 Then Exit Sub
        Loop Until SecondNumber >= 2 And SecondNumber <= 12
        
        DividedBy = DivideOneByTwo(FirstNumber, SecondNumber)
        MsgBox DividedBy
    End Sub
    Function DivideOneByTwo(num1 As Long, num2 As Long) As Double
        'should never happen but just in case
        If num2 <> 0# Then
            DivideOneByTwo = num1 / num2
        Else
            DivideOneByTwo = 99999.9999
        End If
    End Function

    Paul

  6. #6
    VBAX Newbie
    Joined
    Mar 2014
    Posts
    4
    Location
    Quote Originally Posted by Paul_Hossler View Post
    In addition, to Mark's $4.75 of comments (he raised his rates again) , here's my $.02

    Paul
    In advance thanks to both of you for taking your time to help this helpless "coder" , that was really helpful paul i have a few questions though, oh and sorry about the dims haha sorry for making it 1000 times harder lol, ok um i still dont understand why the i = 0 and sum = 0 are the not the same used in the recursions i made, and why n starts at 0 since i did the input value of n.

  7. #7
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,728
    Location
    I believe you're asking about the 'Scope' of the variable

    Example

    In One the N is Dim-ed within the sub (it's scope), and all references in that sub use THAT variable
    In Two, the N is not Dim-ed, so the module level N is in scope and is still set to 0
    In Three, the N is dim-ed as a string so within that module the string N is used


    Option Explicit
    
    
    'module level variable
    Dim N As Long
    
    Sub One()
        'procedure level variable
        Dim N As Long
        N = 100
        'Type mis-match error on below
        'N = "No Good"
        MsgBox N
    End Sub
    
    
    Sub Two()
        'uses the module level variable
        MsgBox N
    End Sub
    
    Sub Three()
        'procedure level variable
        Dim N As String
        N = "Hello"
        MsgBox N
    End Sub
    Last edited by Paul_Hossler; 04-27-2014 at 10:57 AM.
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  8. #8
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    Sub M_snb()
        For j = 1 To 2
            Do
                 y = InputBox("Please enter (2 - 12)," & vbCrLf & vbCrLf & "or [Cancel] to exit", "Number " & j)
            Loop Until (y > 1 And y < 13) Or y = ""
            If y = "" Then Exit Sub
            If j = 1 Then x = y
        Next
        
        If x <> "" And y <> "" Then MsgBox F_divide(x, y)
    End Sub
    
    Function F_divide(x, y)
        F_divide = x / y
    End Function

  9. #9
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location
    Quote Originally Posted by Paul_Hossler View Post
    In addition, to Mark's $4.75 of comments (he raised his rates again) , here's my $.02
    Shucks, I wouldn't dare - lest I'd price myself right out of the market with the little bit I gave.

    Quote Originally Posted by cybotzu View Post
    In advance thanks to both of you for taking your time to help this helpless "coder" , that was really helpful paul i have a few questions though, oh and sorry about the dims haha sorry for making it 1000 times harder lol, ok um i still dont understand why the i = 0 and sum = 0 are the not the same used in the recursions i made, and why n starts at 0 since i did the input value of n.
    Paul has given very nice/thorough answers, so just a couple of links and one further suggestion, in case the variables' scope still contains any mystery (I remember how hard it was for me to wrap my head around some of this when starting out.).

    http://www.excel-easy.com/vba/exampl...ble-scope.html
    http://support.microsoft.com/kb/141693
    http://www.cpearson.com/Excel/Scope.aspx

    I admit I scanned/read through quickly, but I believe I have them listed in order: shorter/easier to longer/more in-depth. Paul's example at #7 really covers it, I just included the links as at least for me, the more I read about a particular "thing", the more likely I am to "get" what the writer is trying to teach. Anyways, my one suggestion would be to take the time to familiarize yourself with the Locals and Immediate Windows. Particularly the Locals Window will show you what is happening as you step through (okay, I guess it is two suggestions; as I'd definitely suggest F8'ing it through Paul's example and your original code, so you can see what is happening each step of the way).

    Hope that helps,

    Mark

  10. #10
    VBAX Newbie
    Joined
    Mar 2014
    Posts
    4
    Location
    Sorry, for the late reply im working on it at the moment with all the useful information you guys gave me will update as soon as possible! see if i got it correctly haha

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •