Hello Avinash
Originally Posted by
sumanjjj
1.5% to .15 why i am unable to understand the same
I also do not understand....
1.5% is 1.5/100 = .015
Richard Buttrey ( https://www.excelforum.com/excel-pro...ml#post5190581 ) probably made typo mistake... just typo mistake - not important
Sheet1.Range("D2") = Sheet1.Range("B2") * .15 * 56 is wrong
Sheet1.Range("D2") = Sheet1.Range("B2") * .015 * 56 is correct
Originally Posted by
sumanjjj
i have data upto 100 or 200 rows it can be more all it depends i have to do the same process till the end of the data
So we need to make Lr dynamic, ( http://www.excelfox.com/forum/showth...ll=1#post11466 )
For example …. Sample.xlsx : -
http://www.excelfox.com/forum/showth...ll=1#post11474
Originally Posted by
kaja
, formula will be added by me in the code, put that formula in C2 and drag it the result will be shown by the formula in column C, …
…
Multiply the value of B2 by 1.5%, then multiply that result by 56 and then paste the result in D2
Originally Posted by
fixer
Multiply the value of B2 by 1.5%, then multiply that result by 56 and then paste the result in D2(i need only result in the cell no formulas…..formula will be added by me in the code, put that formula in …. drag it …….. the result will be shown by the formula )
note- 1st row contains headers so ignore the first row
The file will be located in C:\Users\sk\Desktop and file name is sample.xlsx
file is not opened so we have to open the file by vba and do the process and save it and close it
vba will be added in a seperate file process.xlsm
both files are located in same place
i need vba to do the same
So, I think requirement is
The file will be located in C:\Users\sk\Desktop and file name is sample.xlsx, file is not opened so we have to open the file by vba
Multiply the value of B2 by 1.5%, then multiply that result by 56 and then paste the result in D2..formula will be added by me in the code, put that formula in ….
drag it …….. the result will be shown by the formula
I need only result in the cell no formulas…
do the process and save it and close it
note- 1st row contains headers so ignore the first row
vba will be added in a seperate file process.xlsm
both files are located in same place
i need vba to do the same
Using macro recorder, record macro
Record Macro.JPG : https://imgur.com/I2gMvi9
This is the macro recorded by the macro recorder:-
Code:
Sub Makro4()
'
' Makro4 Makro
'
' file is not opened so we have to open the file by vba
Workbooks.Open Filename:="F:\Excel0202015Jan2016\ExcelFox\vixer\sample.xlsx"
' Multiply the value of B2 by 1.5%, then multiply that result by 56 and then paste the result in D2..formula will be added by me in the code, put that formula in …
Range("D2").Select
ActiveCell.FormulaR1C1 = "=RC[-2]*(1.5/100)*56"
' drag it
Range("D2").Select
Selection.AutoFill Destination:=Range("D2:D10"), Type:=xlFillDefault
' I need only result in the cell no formulas
Range("D2:D10").Select
Selection.Copy
Selection.PasteSpecial Paste:=xlPasteValues, Operation:=xlNone, SkipBlanks _
:=False, Transpose:=False
Application.CutCopyMode = False
' save it and close it
Windows("sample.xlsx").Activate
ActiveWindow.Close savechanges:=True
End Sub
Stop macro recording.JPG : https://imgur.com/F0ygnd2
Here is a final macro written by me :-
Code:
'
Sub Vixer9a() ' http://www.excelfox.com/forum/showthread.php/2369-Calculation-by-vba https://www.mrexcel.com/forum/excel-questions/1109256-add-calculation-vba.html http://www.vbaexpress.com/forum/showthread.php?65832-Formula-by-vba[/url] https://www.excelforum.com/excel-pro...on-by-vba.html
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 = "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 ' 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)
' make Lr1 dynamic .... http://www.excelfox.com/forum/showth...ll=1#post11474 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("C" & Ws1.Rows.Count).End(xlUp).Row
Rem 3 The Process ..."....
'3(i) ....Multiply the value of B2 by 1.5%, then multiply that result by 56 and then paste the result in D2.. formula will be added by me in the code, put that formula in
Ws1.Range("D2").Value = "=B2*(1.5/100)*56"
'3(ii) ....drag it
Ws1.Range("D2").AutoFill Destination:=Ws1.Range("D2:D" & Lr1 & ""), Type:=xlFillDefault
'3(iii) I need only result in the cell no formulas
Ws1.Range("D2:D" & Lr1 & "").Copy
Ws1.Range("D2:D" & Lr1 & "").PasteSpecial Paste:=xlPasteValues
Let Application.CutCopyMode = False
Rem 4 save it and close it
Wb1.Save
Wb1.Close
End Sub
Alan
( see also here:
http://www.excelfox.com/forum/showth...ll=1#post11473
http://www.excelfox.com/forum/showth...ll=1#post11474 )
Ref
Artik http://www.vbaexpress.com/forum/show...l=1#post394129
Bookmarks