Page 2 of 3 FirstFirst 123 LastLast
Results 11 to 20 of 25

Thread: Apply formula Calculation by VBA Value ="to Forumula"

  1. #11
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0

    calculation by vba

    vba is placed in a seperate file c.xlsm
    both files are located in a same place
    there is a file name sample1.xlsx
    open sample1.xlsx
    in column N we have to use the formula =H2/M2 and paste the result in values in column N of sample1.xlsx
    and in coulmn Q we have to use the formula =N2*P2 and paste the result in values in column Q of sample1.xlsx
    and save and close the sample1.xlsx


    note we have to use the formula till the end of the data (till the column H has data )
    example if column H has data till H17 then we have to use the formula till
    N17 & Q17

    so plz have a look sir and help me in solving this problem by vba macro sir

  2. #12
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Hello Avinash
    Similar to here
    http://www.excelfox.com/forum/showth...ll=1#post11472
    Also is similar to many of your posts and questions
    So I have merged Threads


    …..note we have to use the formula till the end of the data (till the column H has data )
    example if column H has data till H17 then we have to use the formula till
    N17 & Q17

    Code:
    ' make Lr1 dynamic .... http://www.excelfox.com/forum/showthread.php/2345-Appendix-Thread-(-Codes-for-other-Threads-HTML-Tables-etc-)?p=11474&viewfull=1#post11474
     Let Lr1 = Ws1.Range("H" & Ws1.Rows.Count).End(xlUp).Row
     


    both files are located in a same place
    ___there is a file name sample1.xlsx

    MyPath = ThisWorkbook.Path
    ___strWb1 = "sample.xlsx"



    Merged with Sub Vixer9c() from http://www.excelfox.com/forum/showth...ulation-by-vba http://www.excelfox.com/forum/showth...ll=1#post11479


    ( I did all this from memory on computer at father in law not with Excel so maybe some error is )


    10c is like 9c .. It is "fixed vector applied across a range" ( https://teylyn.com/2017/03/21/dollarsigns/#comment-191 , http://www.excelfox.com/forum/showth...ll=1#post11479 )


    Code:
    Sub Vixer10c() ' http://www.excelfox.com/forum/showthread.php/2420-calculation-by-vba?p=12523#post12523
    'Sub Vixer9c() ' demo for   fixed vector applied across a range
    Rem 1 Workbook and worksheets info
    '1a) Workbook info
    '                                                                                Dim Wbm As Workbook: Set Wbm = ThisWorkbook ' The workbook containing macro
    Dim Wb1 As Workbook ' This will be set later when the workbook is opened
    Dim MyPath As String: Let MyPath = ThisWorkbook.Path '  "both files are located in a same place                                                                                                                                      ."C:\Users\sk\Desktop"....The file will be located in C:\Users\sk\Desktop ....
    Dim strWb1 As String: Let strWb1 = "sample.xlsx" '                                                          " ....and file name is sample.xlsx
    '1b) Worksheets info
    Dim Ws1 As Worksheet ' This will be set later when the workbook is opened)
    Dim Lr1 As Long '     note we have to use the formula till the end of the data (till the column H has data )                                                                                                                     Let Lr1 = 10 for sample file  , but we will determine it dynamically after opening the file
    Rem 2 Open file   "..... file is not opened so we have to open the file by vba
    '                                                                                                                                  Workbooks.Open Filename:="F:\Excel0202015Jan2016\ExcelFox\vixer\sample.xlsx"
    'Workbooks.Open Filename:=ThisWorkbook.Path & "\" & strWb1  '  ...both files are located in same place
     Workbooks.Open Filename:=MyPath & "\" & strWb1              '                                                                      ...file will be located in C:\Users\sk\Desktop
     Set Wb1 = ActiveWorkbook ' The workbook just opened will now be the current active workbook
     Set Ws1 = Wb1.Worksheets.Item(1)
    
    ' note we have to use the formula till the end of the data (till the column H has data )         make Lr1 dynamic .... http://www.excelfox.com/forum/showthread.php/2345-Appendix-Thread-(-Codes-for-other-Threads-HTML-Tables-etc-)?p=11474&viewfull=1#post11474
     Let Lr1 = Ws1.Range("H" & Ws1.Rows.Count).End(xlUp).Row
    Rem 3 The Process ..."....
    'In column N we have to use the formula =H2/M2                        .....and paste the result in values in column N
     Ws1.Range("N2:N" & Lr1 & "").Value = "=H2/M2"
    'I need only result in the cell no formulas
     Ws1.Range("N2:N" & Lr1 & "").Value = Ws1.Range("N2:N" & Lr1 & "").Value '.....paste the result in values in column N
    'in coulmn Q we have to use the formula =N2*P2                         ......and paste the result in values in column Q
     Ws1.Range("Q2:Q" & Lr1 & "").Value = "=N2*P2"
    'I need only result in the cell no formulas
     Ws1.Range("Q2:Q" & Lr1 & "").Value = Ws1.Range("Q2:Q" & Lr1 & "").Value
                                                            '        '3(i)(ii) ....Multiply the value of B2 by 1.5%, then multiply that result by 56 and then paste the result in D2..   ....drag it formula will be added by me in the code, put that formula in
                                                            '         Ws1.Range("D2:D" & Lr1 & "").Value = "=B2*(1.5/100)*56"
                                                            '        '3(iii) I need only result in the cell no formulas
                                                            '         Let Ws1.Range("D2:D" & Lr1 & "").Value = Ws1.Range("D2:D" & Lr1 & "").Value
    Rem 4 and save and close the sample1.xlsx    ... save it and close it
     Wb1.Save
     Wb1.Close
    'End Sub
    End Sub
    




    Alan
    Attached Files Attached Files
    Last edited by DocAElstein; 03-02-2020 at 05:31 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  3. #13
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    Code:
    Sub calculation()
      Dim wb1 As Workbook, Ws1 As Worksheet, lr1 As Long
      Set wb1 = Workbooks.Open(ThisWorkbook.Path & "\FundsCheck.xlsb")
      Set Ws1 = wb1.Worksheets.Item(1)
      Let lr1 = Ws1.Range("H" & Ws1.Rows.Count).End(xlUp).Row
       Ws1.Range("N2:N" & lr1 & "").Value = "=H2/M2"
       Ws1.Range("N2:N" & lr1 & "").Value = Ws1.Range("N2:N" & lr1 & "").Value
       Ws1.Range("Q2:Q" & lr1 & "").Value = "=N2*P2"
       Ws1.Range("Q2:Q" & lr1 & "").Value = Ws1.Range("Q2:Q" & lr1 & "").Value
       wb1.Save
       wb1.Close
    End Sub
    I used this code and i met with an error this code is if perfect but what this code is doing is suppose coulmn H has data till h20 then this formula is giving the result till n20 and q20 in values but after that also after n20 and q20 also formula is used
    Last edited by DocAElstein; 03-02-2020 at 05:22 PM.

  4. #14
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0

  5. #15
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    Doc Sir ur code is perfect no doubt in it i got where the mistake started on more macro was causing an error i got the issue
    Thnx Alot Doc sir for ur long lasting support sir have a great day sir

  6. #16
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0

    convert formula result to values by macro

    I have a data in cloumn I,column J,column K that data is the result of the formulas i have used
    what i need i need to convert that formula result to values by a macro
    all files are located in a same path
    vba is palced in a seperate file
    macro.xlsm
    and file that has formulas is 2.xls

  7. #17
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    See here:
    http://www.excelfox.com/forum/showth...ll=1#post11479
    http://www.excelfox.com/forum/showth...ll=1#post12540


    To convert formulas in a range, Rng, to values …

    Rng.Value = Rng.Value

    To convert formulas in a range, Rng1, to values …

    Rng1.Value = Rng1.Value

    To convert formulas in a range, Rng2, to values …

    Rng2.Value = Rng2.Value




    _____ Workbook: macro.xlsm ( Using Excel 2007 32 bit )
    Row\Col
    H
    I
    J
    K
    L
    1
    =1
    =2
    =3
    2
    ="a" ="b"
    =1+6
    3
    Worksheet: Tabelle3


    Code:
    Sub RngFormulasToValues()
     Range("I2:K2").Value = Range("I2:K2").Value
    End Sub

    _____ Workbook: macro.xlsm ( Using Excel 2007 32 bit )
    Row\Col
    H
    I
    J
    K
    L
    1
    =1
    =2
    =3
    2
    a b
    7
    3
    Worksheet: Tabelle3


    Code:
    Sub RngFormulasToValues()
     Range("I1:K2").Value = Range("I1:K2").Value
    End Sub

    _____ Workbook: macro.xlsm ( Using Excel 2007 32 bit )
    Row\Col
    H
    I
    J
    K
    L
    1
    1
    2
    3
    2
    a b
    7
    3
    Worksheet: Tabelle3
    Last edited by DocAElstein; 03-17-2020 at 09:17 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  8. #18
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    Code:
    Sub STEP6()
     Dim w1 As Workbook
     Set w1 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\Upstox\Merge.xlsx") ' change the file path
    w1.Worksheets.Item(1).Columns("I:K").Copy
    w1.Worksheets.Item(1).Columns("I:K").PasteSpecial Paste:=xlPasteValuesAndNumberFormats
    w1.Save
    w1.Close
    End Sub


    Doc Sir I made this
    correct the code if its wrong
    Thnx Doc Sir for ur Great Guidance Sir

  9. #19
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    This will work:.._

    Code:
    Sub STEP6()
     Dim w1 As Workbook
     Set w1 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\Upstox\Merge.xlsx") ' change the file path
    
    ' convert formula result to values  ---   Copy  3145728 cells                            3145728 Cells in 3 Whole columns.JPG :  https://imgur.com/kQYSQfg
    w1.Worksheets.Item(1).Columns("I:K").Copy
    w1.Worksheets.Item(1).Columns("I:K").PasteSpecial Paste:=xlPasteValuesAndNumberFormats
    
    
    w1.Save
    w1.Close
    End Sub
    _...This will also work…._

    Code:
    Sub STEP6()
     Dim w1 As Workbook
     Set w1 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\Upstox\Merge.xlsx") ' change the file path
    
    ' convert formula result to values  ---   Copy  3145728 cells                            3145728 Cells in 3 Whole columns.JPG :  https://imgur.com/kQYSQfg
    w1.Worksheets.Item(1).Columns("I:K").Value = w1.Worksheets.Item(1).Columns("I:K").Value
    
    
    w1.Save
    w1.Close
    End Sub
    
    _.........But it is not good - you copy 3 x 1048576 = 3145728 cells
    3145728 Cells in 3 Whole columns.JPG : https://imgur.com/kQYSQfg
    Attachment 2795

    _.................This is better:-

    3 x Lr Cells.JPG : https://imgur.com/LaIBKQL
    Attachment 2796

    Code:
    Sub STEP6()
     Dim w1 As Workbook
     Set w1 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\Upstox\Merge.xlsx") ' change the file path
    Dim Lr As Long: Let Lr = w1.Worksheets.Item(1).Range("K" & w1.Worksheets.Item(1).Rows.Count & "").End(xlUp).Row
     
    ' convert formula result to values   ----    3 x Lr cells                                 3 x Lr Cells.JPG : https://imgur.com/LaIBKQL
     w1.Worksheets.Item(1).Range("I1:K" & Lr & "").Value = w1.Worksheets.Item(1).Range("I1:K" & Lr & "").Value
    
    
    Wb1.Save
    Wb1.Close
    End Sub

    _......................................This is best

    Code:
    Sub STEP6()
     Dim Wb1 As Workbook, Ws1 As Worksheet
     Set Wb1 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\Upstox\Merge.xlsx") ' change the file path
     Set Ws1 = Wb1.Worksheets.Item(1)
    Dim Lr As Long: Let Lr = Ws1.Range("K" & Ws1.Rows.Count & "").End(xlUp).Row
     
    ' convert formula result to values   ----    3 x Lr cells                                 3 x Lr Cells.JPG : https://imgur.com/LaIBKQL
     Ws1.Range("I1:K" & Lr & "").Value = Ws1.Range("I1:K" & Lr & "").Value
    
    
    Wb1.Save
    Wb1.Close
    End Sub
    
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  10. #20
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    Thnx Doc Sir

Similar Threads

  1. TAT Calculation
    By pramodagroiya in forum Excel Help
    Replies: 5
    Last Post: 05-30-2016, 12:27 PM
  2. On Going Calculation
    By justme1052 in forum Excel Help
    Replies: 2
    Last Post: 12-31-2013, 02:06 AM
  3. Replies: 5
    Last Post: 10-21-2013, 04:43 PM
  4. Calculation with different condition in a cell
    By LalitPandey87 in forum Excel Help
    Replies: 5
    Last Post: 04-04-2012, 08:38 AM

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
  •