Consulting

Page 1 of 3 1 2 3 LastLast
Results 1 to 20 of 44

Thread: Is there a VBA that will search all formulas in a sheet or book

  1. #1
    VBAX Regular
    Joined
    Sep 2015
    Location
    East Texas
    Posts
    87
    Location

    Is there a VBA that will search all formulas in a sheet or book

    You all were so kind to find me a Macro that compares my conditional formatting which has been so beneficial plus it finds all my #REF! errors and I know where to go to fix them as it gives me everything on an output sheet.

    Is there a VBA that would do the same thing for formulas that are written in cells and perhaps tell me if they are correct or not as a bonus? Basically go through my sheet(s) and record all the formulas I am using on an "output" sheet

    Thanks

  2. #2
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    This creates a new sheet for each existing sheet and places the formulas, as Text, into the same cell on the new sheet as they are in the existing sheet. AFAIK, there is now way to use VBA to see if the formulas are good.

    Option Explicit
    
    Sub ListFormulas()
    Dim Mysheets As Object
    Dim Sht As Worksheet
    Dim FormSht As Worksheet
    Dim Cel As Range
    
    Set Mysheets = Application.Worksheets
    
    'UnComment next line after passes testing
    'Application.ScreenUpdating = False
    
    For Each Sht In Mysheets
      Worksheets.Add After:=Sheets(Sht.Name)
      ActiveSheet.Name = Sht.Name & "_Formulas"
      Set FormSht = ActiveSheet
      
      For Each Cel In Sht.UsedRange
        If InStr(Cel.Formula, "=") = 1 Then _
          FormSht.Range(Cel.Address) = "'" & Cel.Formula
      Next Cel
    Next Sht
    
    Application.ScreenUpdating = True
    End Sub
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  3. #3
    Mac Moderator VBAX Guru mikerickson's Avatar
    Joined
    May 2007
    Location
    Davis CA
    Posts
    2,778
    The built in Error Checking routines should be able to flag any cell with a bad formula.

  4. #4
    VBAX Regular
    Joined
    Sep 2015
    Location
    East Texas
    Posts
    87
    Location
    Thanks for replying Sam. I am trying to run the code from a book of 18 sheets. It does the 1st sheet perfectly and then I get a run time error for the "sheet name" After it runs the 1st sheet the Macro places a blank sheet with this error. Is there a way to fix this? This will do exactly like I need. I am not sure why it says sheet 6. As you can see its actually sheet 4 (not sure if that matters, I have it in a Module) OR if this is what its suppose to do....what do I do?

    Thanks

    Run Time Error.jpg Blank sheet 6.jpg
    Attached Images Attached Images
    Last edited by Larbec; 10-12-2015 at 05:13 AM.

  5. #5
    VBAX Master Aflatoon's Avatar
    Joined
    Sep 2009
    Location
    UK
    Posts
    1,720
    Location
    Wouldn't it be easier to just copy the sheet, remove any constants and then replace = with '= instead:
    Sub ListFormulas()
        Dim Mysheets              As Object
        Dim Sht                   As Worksheet
    
    
        Set Mysheets = Application.Worksheets
    
    
        'UnComment next line after passes testing
        Application.ScreenUpdating = False
    
    
        For Each Sht In Mysheets
            Sht.Copy After:=Sht
            ActiveSheet.Name = Sht.Name & "_Formulas"
            On Error Resume Next
            With ActiveSheet.UsedRange
                .SpecialCells(xlCellTypeConstants).Clear
                .Replace "=", "'="
            End With
            On Error GoTo 0
        Next Sht
    
    
        Application.ScreenUpdating = True
    End Sub
    Be as you wish to seem

  6. #6
    VBAX Regular
    Joined
    Sep 2015
    Location
    East Texas
    Posts
    87
    Location
    Thanks for helping! This actually copies the 1st sheet and made a duplicate and then another sheet with the formulas and then stops

    copy sheet.jpg

  7. #7
    VBAX Master Aflatoon's Avatar
    Joined
    Sep 2009
    Location
    UK
    Posts
    1,720
    Location
    That's because you already have a sheet called "Drawn Numbers_Formulas" - probably from running SamT's code. Delete that before running the code I just posted.
    Be as you wish to seem

  8. #8
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,730
    Location
    I'd just start with something straight forward like this


    Option Explicit
    Sub ListFormulas()
        Dim wsFormulas As Worksheet, ws As Worksheet
        Dim rFormulas As Range, rCell As Range
        Dim iOut As Long
        
        Application.ScreenUpdating = False
        
        
        'delete existing
        On Error Resume Next
        Application.DisplayAlerts = False
        Worksheets("Formulas").Delete
        Application.DisplayAlerts = True
        On Error GoTo 0
        
        'add new one
        Worksheets.Add.Name = "Formulas"
        Set wsFormulas = Worksheets("Formulas")
        
        'add headers
        iOut = 1
        With wsFormulas
            .Cells(iOut, 1).Value = "Sheet Name"
            .Cells(iOut, 2).Value = "Cell Address"
            .Cells(iOut, 3).Value = "Formula"
        End With
        iOut = iOut + 1
        'go through the sheets looking for formulas
        For Each ws In ActiveWorkbook.Worksheets
            With ws
                If .Name = "Formulas" Then GoTo NextSheet
                
                Set rFormulas = Nothing
                On Error Resume Next
                Set rFormulas = .UsedRange.SpecialCells(xlCellTypeFormulas)
                On Error GoTo 0
                
                If rFormulas Is Nothing Then GoTo NextSheet
                
                For Each rCell In rFormulas.Cells
                    wsFormulas.Cells(iOut, 1).Value = rCell.Parent.Name
                    wsFormulas.Cells(iOut, 2).Value = rCell.Address
                    
                    If IsError(rCell.Value) Then wsFormulas.Cells(iOut, 3).Interior.Color = vbRed
                    
                    wsFormulas.Cells(iOut, 3).Value = "'" & rCell.Formula
                                
                    iOut = iOut + 1
                Next
                    
                
            End With
    NextSheet:
        Next
        
        Application.ScreenUpdating = True
    End Sub
    Attached Files Attached Files
    ---------------------------------------------------------------------------------------------------------------------

    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

  9. #9
    VBAX Regular
    Joined
    Sep 2015
    Location
    East Texas
    Posts
    87
    Location
    Quote Originally Posted by Aflatoon View Post
    That's because you already have a sheet called "Drawn Numbers_Formulas" - probably from running SamT's code. Delete that before running the code I just posted.
    I did not have a 2nd sheet when I ran it. When I put the new code as suggested I get this?

    invalid sheet name.jpg

  10. #10
    VBAX Regular
    Joined
    Sep 2015
    Location
    East Texas
    Posts
    87
    Location
    Paul,

    Thanks for chiming in and helping us

    I am running this and see what results we get. I have some errands 2while it runs and will report back. It seems to be taking a longer time than the one above. Perhaps that is normal

  11. #11
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Remove all the sheets added by this thread's code.

    Insert one sheet. Put this code in that sheet's Code Page and run it.
    Option Explicit
    
    
     
    Sub Test1()
        
    Dim Mysheets As Object
    Dim i As Long
    
    Set Mysheets = Application.Worksheets
    On Error GoTo ErrHandler
    For i = 1 To Mysheets.Count
      Cells(i, "A").Value = Mysheets(i).Name
    Next i
    
    Set Mysheets = Nothing
    
    Exit Sub
    ErrHandler:
    MsgBox "Count is " & i & ", Name is " & Mysheets(i).Name
        
        Application.ScreenUpdating = True
    End Sub
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  12. #12
    VBAX Master Aflatoon's Avatar
    Joined
    Sep 2009
    Location
    UK
    Posts
    1,720
    Location
    Tried my code in Paul's workbook without error. Here's another version to test:

    Sub ListFormulas()    Dim Mysheets              As Object
        Dim n                     As Long
        
    
    
        'UnComment next line after passes testing
        Application.ScreenUpdating = False
    
    
    
    
        For n = 1 To ThisWorkbook.Sheets.Count
            Sheets(n).Copy after:=ThisWorkbook.Sheets(ThisWorkbook.Sheets.Count)
            ActiveSheet.Name = Sheets(n).Name & "_Formulas"
            On Error Resume Next
            With ActiveSheet.UsedRange
                .SpecialCells(xlCellTypeConstants).Clear
                .Replace "=", "'="
            End With
            On Error GoTo 0
        Next n
    
    
    
    
        Application.ScreenUpdating = True
    End Sub
    Be as you wish to seem

  13. #13
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,646
    or

    Sub M_snb()
        For Each sh In Sheets
           sh.Activate
           ActiveWindow.DisplayFormulas = True
        Next
    End Sub

  14. #14
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    Option Explicit
     
    Sub Test1()
        
    Dim Mysheets As Object
    Dim i As Long
    
    Set Mysheets = Application.Worksheets
    On Error GoTo ErrHandler
    For i = 1 To Mysheets.Count
      Cells(i, "A").Value = Mysheets(i).Name
    Next i
    
    Set Mysheets = Nothing
    
    Exit Sub
    ErrHandler:
    MsgBox "Count is " & i & ", Name is " & Mysheets(i).Name
        
        Application.ScreenUpdating = True
    End Sub
    Sub ListFormulas()
        Dim Mysheets As Object
        Dim Sht As Worksheet
        Dim FormSht As Worksheet
        Dim Cel As Range
         
        Set Mysheets = Application.Worksheets
         
         'UnComment next line after passes testing
         'Application.ScreenUpdating = False
         
        For Each Sht In Mysheets
            Worksheets.Add After:=Sheets(Sht.Name)
            ActiveSheet.Name = Sht.Name & "_Formulas"
            Set FormSht = ActiveSheet
             
            For Each Cel In Sht.UsedRange
                If InStr(Cel.Formula, "=") = 1 Then _
                FormSht.Range(Cel.Address) = "'" & Cel.Formula
            Next Cel
        Next Sht
         
        Application.ScreenUpdating = True
    End Sub
    Sub DeleteFormulaListSheets()
    
    Dim i As Long
    Application.DisplayAlerts = False
    Application.EnableEvents = False
    
    On Error GoTo CleanEnd
    
    For i = Sheets.Count To 1 Step -1
    If InStr(Sheets(i).Name, "_Formulas") > 0 Then Sheets(i).Delete
    Next i
    
    CleanEnd:
    Application.DisplayAlerts = True
    Application.EnableEvents = True
    End Sub
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  15. #15
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,730
    Location
    @Aflatoon --

    It would seem that would generate a '_Formulas' sheet for every worksheet?

    I took the OP's request #1 to mean a single output sheet

    Basically go through my sheet(s) and record all the formulas I am using on an "output" sheet
    ---------------------------------------------------------------------------------------------------------------------

    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

  16. #16
    VBAX Master Aflatoon's Avatar
    Joined
    Sep 2009
    Location
    UK
    Posts
    1,720
    Location
    Yes - I was basically following SamT's logic but thought it would be quite slow looping through cells one by one, and this seemed a faster option. It would be as easy to just highlight them in-place IMO.
    Be as you wish to seem

  17. #17
    Moderator VBAX Sage SamT's Avatar
    Joined
    Oct 2006
    Location
    Near Columbia
    Posts
    7,814
    Location
    I assumed that the OP had many sheets and would want to compare the Formulas to the Sheet they applied to in an easy manner.

    The probable Ideal would to use both methods. Run a sheet by sheet Procedure, then run Paul's Simple_List Procedure

    And Aflatoon, I agree that yours is going to be faster.
    I expect the student to do their homework and find all the errrors I leeve in.


    Please take the time to read the Forum FAQ

  18. #18
    VBAX Regular
    Joined
    Sep 2015
    Location
    East Texas
    Posts
    87
    Location
    Quote Originally Posted by SamT View Post
    I assumed that the OP had many sheets and would want to compare the Formulas to the Sheet they applied to in an easy manner.

    The probable Ideal would to use both methods. Run a sheet by sheet Procedure, then run Paul's Simple_List Procedure

    And Aflatoon, I agree that yours is going to be faster.

    SamT,

    You are correct, I want to be able to compare each sheet. Let me fully explain. I have 5 books. 1 book has 17 sheets. Out of the 17 sheets 1o are supposed to be the same and I know they are not. I have corrected most of the CF but not the formulas. In my other 4 books they have 32 sheets with 3000 rows and 27 columns so its a lot to go through. Out of the 32 sheets 18 should be the same. Hope this makes sense.

    I am a somewhat of a newbie with Macros and I am sorry to say I am very confused which Macro to use at this point lol. I do know how to use the modules and get them to run though

    I noticed that some have a red shade. Does this mean I have errors in those formulas? If so, should I do a new post on suggestions how to correct them keeping in mind this is somewhat new to me but I want to learn and be self sufficient to be able to help others down the road as you are helping me

    Again, thanks for all the help y'all are giving me as this has already proven to find mistakes at a glance now for me

    Red shade.jpg

    Here is an example: All the Games should have the same formulas and CF on them that I am trying to verify

    sheets the same.jpg
    Last edited by Larbec; 10-12-2015 at 08:47 AM. Reason: add snip

  19. #19
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,730
    Location
    It looks that the results were from my suggestion

    If you check G3 on DrawnNumbers, it should show some sort of error

    The only way I know to determine that there's an error is like this, and I marked them in red

    If IsError(rCell.Value) Then wsFormulas.Cells(iOut, 3).Interior.Color = vbRed
    Others may have better ideas
    ---------------------------------------------------------------------------------------------------------------------

    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

  20. #20
    VBAX Regular
    Joined
    Sep 2015
    Location
    East Texas
    Posts
    87
    Location
    Quote Originally Posted by SamT View Post
    I assumed that the OP had many sheets and would want to compare the Formulas to the Sheet they applied to in an easy manner.

    The probable Ideal would to use both methods. Run a sheet by sheet Procedure, then run Paul's Simple_List Procedure

    And Aflatoon, I agree that yours is going to be faster.
    I totally agree i see benefits both ways THANK YOU BOTH!

Posting Permissions

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