Consulting

Results 1 to 10 of 10

Thread: VBA to convert formulas to value

  1. #1

    VBA to convert formulas to value

    Hi

    Please help Urgent!!!!!


    Could any one please help me in creating a VBA for converting formulas to value of any entire row if a certain criteria matches.




    For example: In the attached sheet I want to covert the formulas of an entire row if the "Status" in D column in "Complete".


    Thank you!!
    Attached Files Attached Files

  2. #2
    VBAX Guru mancubus's Avatar
    Joined
    Dec 2010
    Location
    "Where I lay my head is home" :D
    Posts
    2,644
    try with a copy of original file

    Sub vbax_54491_Formulaz_To_Valz_On_Condition()
    
        Dim cll As Range
        
        With Worksheets("MySheet") 'change MySheet to suit
            .AutoFilterMode = False
            .Cells(1).AutoFilter Field:=4, Criteria1:="=Complete"
            For Each cll In .UsedRange.Offset(1).SpecialCells(12)
                If cll.HasFormula Then cll.Value = cll.Value
            Next
            .AutoFilterMode = False
        End With
    
    End Sub
    PLS DO NOT PM; OPEN A THREAD INSTEAD!!!

    1) Posting Code
    [CODE]PasteYourCodeHere[/CODE]
    (or paste your code, select it, click # button)

    2) Uploading File(s)
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) (multiple files can be selected while holding Ctrl key) / Upload Files / Done
    Replace company specific / sensitive / confidential data. Include so many rows and sheets etc in the uploaded workbook to enable the helpers visualize the data and table structure. Helpers do not need the entire workbook.

    3) Testing the Codes
    always back up your files before testing the codes.

    4) Marking the Thread as Solved
    from Thread Tools (on the top right corner, above the first message)

  3. #3
    Can you help me to do this without auto filter?

  4. #4
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location
    I'm not sure what disadvantage there would be to using AutoFilter, but maybe this is more what you were thinking?

    Option Explicit
      
    Sub example()
    Dim rngFound As Range
    Dim rng2Search As Range
    Dim lRowLookingAt As Long
      
      With Sheet1 '<--- Use whatever the real sheet's CodeName is
        Set rngFound = RangeFound(.Range("A:D"))
        If Not rngFound Is Nothing Then
          If Not rngFound.Row < 2 Then
            For lRowLookingAt = rngFound.Row To 2 Step -1
              If .Cells(lRowLookingAt, 4).Value = "Complete" Then
                .Cells(lRowLookingAt, 4).Offset(0, -2).Resize(, 2).Value = .Cells(lRowLookingAt, 4).Offset(0, -2).Resize(, 2).Value
              End If
            Next
          End If
        End If
      End With
      
    End Sub
      
    Function RangeFound(SearchRange As Range, _
                        Optional ByVal FindWhat As String = "*", _
                        Optional StartingAfter As Range, _
                        Optional LookAtTextOrFormula As XlFindLookIn = xlValues, _
                        Optional LookAtWholeOrPart As XlLookAt = xlPart, _
                        Optional SearchRowCol As XlSearchOrder = xlByRows, _
                        Optional SearchUpDn As XlSearchDirection = xlPrevious, _
                        Optional bMatchCase As Boolean = False) As Range
        
        If StartingAfter Is Nothing Then
            Set StartingAfter = SearchRange.Cells(1)
        End If
        
        Set RangeFound = SearchRange.Find(What:=FindWhat, _
                                          After:=StartingAfter, _
                                          LookIn:=LookAtTextOrFormula, _
                                          LookAt:=LookAtWholeOrPart, _
                                          SearchOrder:=SearchRowCol, _
                                          SearchDirection:=SearchUpDn, _
                                          MatchCase:=bMatchCase)
    End Function
    Hope that helps,

    Mark

  5. #5
    VBAX Guru mancubus's Avatar
    Joined
    Dec 2010
    Location
    "Where I lay my head is home" :D
    Posts
    2,644
    Quote Originally Posted by talkvinith View Post
    Can you help me to do this without auto filter?
    what is wrong with autofilter.
    Last edited by mancubus; 12-10-2015 at 02:12 AM.
    PLS DO NOT PM; OPEN A THREAD INSTEAD!!!

    1) Posting Code
    [CODE]PasteYourCodeHere[/CODE]
    (or paste your code, select it, click # button)

    2) Uploading File(s)
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) (multiple files can be selected while holding Ctrl key) / Upload Files / Done
    Replace company specific / sensitive / confidential data. Include so many rows and sheets etc in the uploaded workbook to enable the helpers visualize the data and table structure. Helpers do not need the entire workbook.

    3) Testing the Codes
    always back up your files before testing the codes.

    4) Marking the Thread as Solved
    from Thread Tools (on the top right corner, above the first message)

  6. #6
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    I don't like 'Urgent'.
    I don't like exclamation marks either.

    Sub M_snb()
       sn = Cells(1).CurrentRegion
    
       For j = 1 To UBound(sn)
          If LCase(sn(j, 4)) = "complete" Then Cells(1).CurrentRegion.Rows(j) = Application.Index(sn, j)
       Next
    End Sub

  7. #7
    Thank all...!! GTO your coding is really working fine.

    A final help if possible.

    I want to remove the name in A column if the D column status is "Verification Completed" or Verification not Required" and can you able to add the coding to the previous macro itself.


    Thanks Again!!
    Attached Files Attached Files

  8. #8
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location

    Here you go. I assumed we only want to do the second check if the first one passes. Change to suit....

    Option Explicit
     
    Sub example()
    Dim rngFound As Range
    Dim rng2Search As Range
    Dim lRowLookingAt As Long
    With Sheet1 '<--- Use whatever the real sheet's CodeName is
    Set rngFound = RangeFound(.Range("A:E"))
    If Not rngFound Is Nothing Then
    If Not rngFound.Row < 2 Then
    For lRowLookingAt = rngFound.Row To 2 Step -1
    If .Cells(lRowLookingAt, 5).Value = "Complete" Then 
    .Cells(lRowLookingAt, 5).Offset(0, -3).Resize(, 3).Value = .Cells(lRowLookingAt, 5).Offset(0, -3).Resize(, 3).Value
    If (.Cells(lRowLookingAt, 4).Value = "Verification Completed" Or .Cells(lRowLookingAt, 4).Value = "Verification not Required") Then
    .Cells(lRowLookingAt, 1).Value = vbNullString
    End If 
    End If
    Next
    End If
    End If
    End With
    End Sub
     
    Function RangeFound(SearchRange As Range, _
     Optional ByVal FindWhat As String = "*", _
     Optional StartingAfter As Range, _
    Optional LookAtTextOrFormula As XlFindLookIn = xlValues, _
    Optional LookAtWholeOrPart As XlLookAt = xlPart, _
    Optional SearchRowCol As XlSearchOrder = xlByRows, _
    Optional SearchUpDn As XlSearchDirection = xlPrevious, _
    Optional bMatchCase As Boolean = False As Range
    IF StartingAfter Is Nothing Then
    Set StartingAfter = SearchRange.Cells(1)
    End If
    Set RangeFound = SearchRange.Find(What:=FindWhat, _
    After:=StartingAfter, _
    LookIn:=LookAtTextOrFormula, _
    LookAt:=LookAtWholeOrPart, _
    SearchOrder:=SearchRowCol, _
    SearchDirection:=SearchUpDn, _
    MatchCase:=bMatchCase)
    End Function
    [/COLOR]

  9. #9
    Thanks You!!

  10. #10
    Knowledge Base Approver VBAX Guru GTO's Avatar
    Joined
    Sep 2008
    Posts
    3,368
    Location
    You are very welcome :-)

Tags for this Thread

Posting Permissions

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