Be more efficient in VBA coding --> efficient VBA looping - excel

could you assist me in writing the code below more efficiently please? I am working on a Master List, where I am copying data from various sources for each month into the columns Z, AC, AF, AI etc. (always separated by 2 columns). Then I copy that cell all the way down to update the values for each row. As you can see in the code below, the only difference from one section of the code to the next is:
Change column (here Z to AC)
Change paths which are stored in different cells (e.g. fromPath changed to fromPath2.
How can I make it more efficient? Any idea would be greatly appreciated.
Take care
' Update Jan 2018
fromPath = Sheets("Filepaths for P25 2017").Range("G2")
vbaPath = Sheets("Filepaths for P25 2017").Range("F2")
vbaFile = Sheets("Filepaths for P25 2017").Range("H2")
Orderlist2017 = Sheets("Filepaths for P25 2017").Range("I2")
With ThisWorkbook.Sheets("Orderlist P25 2017")
Range("Z10").Formula = "=VLookup(C10, '" & vbaPath & vbaFile & Orderlist2017 & "'!C14:Z90, 8, False)"
Range("Z10").Select
Selection.Copy
Range("Y10").Select
Selection.End(xlDown).Select
Range("Z85").Select
Range(Selection, Selection.End(xlUp)).Select
ActiveSheet.Paste
Application.CutCopyMode = False
End With
' Update Feb 2018
fromPath2 = Sheets("Filepaths for P25 2017").Range("G3")
vbaPath2 = Sheets("Filepaths for P25 2017").Range("F3")
vbaFile2 = Sheets("Filepaths for P25 2017").Range("H3")
Orderlist2017 = Sheets("Filepaths for P25 2017").Range("I3")
With ThisWorkbook.Sheets("Orderlist P25 2017")
Range("AC10").Formula = "=VLookup(C10, '" & vbaPath2 & vbaFile2 & Orderlist2017 & "'!C14:Z90, 8, False)"
Range("AC10").Select
Selection.Copy
Range("Y10").Select
Selection.End(xlDown).Select
Range("AC85").Select
Range(Selection, Selection.End(xlUp)).Select
ActiveSheet.Paste
Application.CutCopyMode = False
End With

In my experience, the most effective way to speed up most macros is to turn off screen updating. Also, turning off automatic calculation can help a lot, if your worksheet contains a lot of formulas. I created a method to do this, called "FastMode" which I use in every VBA project I create. At the top of your macro, call it with the parameter set to "True" to make your code run fast, then at the end, call it with "False" to restore the default Excel settings.
Public Sub FastMode(ByVal blnMode As Boolean)
'set workbook to fast mode (or back to normal mode) to speed up any process
'that modifies the worksheets
On Error Resume Next
With Application
Select Case blnMode
Case True
.ScreenUpdating = False
.Calculation = xlCalculationManual
Case False
.ScreenUpdating = True
.Calculation = xlCalculationAutomatic
End Select
End With
End Sub

Try something like this. Untested, but should get you started.
Sub TT()
Dim fromPath, vbaPath, vbaFile, Orderlist2017
Dim shtPaths As Worksheet, shtOrders As Worksheet
Dim i As Long, rngFormula
Set shtPaths = Sheets("Filepaths for P25 2017") 'ThisWorkbook?
Set shtOrders = ThisWorkbook.Sheets("Orderlist P25 2017")
Set rngFormula = shtOrders.Range("Z10") '<< first vlookup goes here
For i = 1 To 12 'for example...
fromPath = shtPaths.Range("G2").Offset(i - 1, 0).Value
vbaPath = shtPaths.Range("F2").Offset(i - 1, 0).Value
vbaFile = shtPaths.Range("H2").Offset(i - 1, 0).Value
Orderlist2017 = shtPaths.Range("I2").Offset(i - 1, 0).Value
'you can assign the formula directly to the required range
' (exactly what you want here is not clear from your posted code...)
rngFormula.Resize(76, 1).Formula = "=VLookup(C10, '" & vbaPath & vbaFile & Orderlist2017 & "'!C$14:Z$90, 8, False)"
Set rngFormula = rngFormula.Offset(0, 2) 'move over two columns
Next i
End Sub

Related

Is there a possible way to add a new row and insert updated formula?

Looking for some help on a small project of mine. VBA coding is not my thing and just started to learn now at a way later age than I'd like.
Backstory:
I work in Business Management and look at a lot of project management finances. I see that it is pretty slow to add a new formula and then drag down the updated formula.
I have been looking how to add a new row that is continuous on top of adding a Concatenate formula to provide a unique ID.
I have done some research and found a file that will be able to add rows with a value of +1 for every row.
Goal(s):
Main Objective-
If someone can help me to update the formula (Concatenate formula on column E), it is a straight copy and paste at this moment so it is not updating based on the new row. Can someone help me revise the code?
Secondary Objective-
Also, it may be a reach but is there code out already that can ask for a text box of some sort to provide more than one new row with the appropriate formulas being copied as well?
Thank you for the help!
Please see the code below:
Sub Button1_Click()
Dim wsS1 As Worksheet
Dim lRows As Long
Dim Iint As Integer
Set wsS1 = Worksheets("Sheet1")
lRows = wsS1.Range("B65536").End(xlUp).Row
If wsS1.Range("B5").Value = "" Then
wsS1.Range("B5").Value = 1
wsS1.Range("G5").Formula = "=IF(AND(D4=""""),"""",IF(AND(D4<>""""),$E4))"
wsS1.Rows(4).EntireRow.Copy
wsS1.Rows(5).PasteSpecial Paste:=xlFormats, Operation:=xlNone, SkipBlanks:= _
False, Transpose:=False
Selection.Interior.ColorIndex = xlNone
Selection.Font.Bold = False
Rows(5).RowHeight = 12.75
End If
For Iint = 5 To lRows
If wsS1.Range("B" & Iint + 1).Value = "" Then
wsS1.Rows(Iint).EntireRow.Copy
wsS1.Rows(Iint + 1).PasteSpecial xlFormats
wsS1.Rows(Iint + 1).PasteSpecial xlFormula
wsS1.Range("G" & Iint + 1).Formula = wsS1.Range("G" & Iint).Formula
wsS1.Range("C" & Iint + 1).Formula = wsS1.Range("C" & Iint).Formula
wsS1.Range("D" & Iint + 1).Formula = wsS1.Range("D" & Iint).Formula
wsS1.Range("E" & Iint + 1).Formula = wsS1.Range("E" & Iint).Formula
wsS1.Range("B" & Iint + 1).Value = wsS1.Range("B" & Iint).Value + 1
End If
Next Iint
End Sub

Compare two Columns and delete the gap Using Macro

I have an Excel file and i want to compare the date in columns A and D and delete the gap between them.
For example based on this picture
enter image description here
Time in column A start at 14:56:23 and in D at 14:56:18. So i want to delete all the data in column D till 14:56:23 so that it will be the same in both A and D.
this problem will be repeated many times so i want to develop a macro to do it.
that is a small program to compare just first two cells in column A and D
Sub Edit_Date_time()
Dim r As Range
Dim l As Range
Set r = Range("A2")
Set l = Range("D2")
If r.Value <> l.Value Then
Range("D2:E2").Select
Selection.Delete Shift:=xlUp
End If
End Sub
the problem is that the cells contain date & time so i can not compare it as values.I have also to expand this code to cover the whole A2 & D2 column not only the first two cells.
Your question has morphed many times, but I am going with the question "how to eliminate rows without matching timestamps" ...
Comparing timestamps can be tricky, even if they are correctly formatted. You would expect 2/17/2016 14:56:29 to be equal to 2/17/2016 14:56:29, but there may be a difference in milliseconds that you cannot see in the string or in the general format. Therefore, you should use a tolerance when determining <, >, or =.
Remember, with timestamps 1.0 = 1 day. So 1/10 of a second is (1/24/60/60/10).
I assume you want to delete pressure rows when those timestamps are earlier than the corresponding temperature timestamps, AND you want to delete temperature rows when those timestamps are earlier than the corresponding pressure timestamps.
This means, worst case, a loop will need to go through the entire data set twice.
I tested code against this data ...
After processing, the yellow cells should align, the orange rows should be deleted. Here are the results I get ...
using this code ...
Sub ParseDateTime()
Dim TRange As Range, PRange As Range
Dim iLoop As Long, LoopEnd As Long
Dim theRow As Long, LastRow As Long
' set the range for the temperature data
LastRow = Sheets("Sheet1").Range("A" & Sheets("Sheet1").Rows.Count).End(xlUp).Row
Set TRange = Sheets("Sheet1").Range("A1:C" & LastRow)
LoopEnd = LastRow
' set the range for the pressure data
LastRow = Sheets("Sheet1").Range("D" & Sheets("Sheet1").Rows.Count).End(xlUp).Row
Set PRange = Sheets("Sheet1").Range("D1:E" & LastRow)
If LastRow > LoopEnd Then LoopEnd = LastRow
' loop through the range
theRow = 1
For iLoop = 2 To 2 * LoopEnd
theRow = theRow + 1
' stop searching when no more data
If TRange(theRow, 1) = "" And PRange(theRow, 1) = "" Then Exit For
' if out of temperature data, eliminate the rest of the pressure data
If TRange(theRow, 1) = "" Then
PRange.Rows(theRow).Delete Shift:=xlUp
theRow = theRow - 1
End If
' if out of pressure data, eliminate the rest of the temperature data
If PRange(theRow, 1) = "" Then
TRange.Rows(theRow).Delete Shift:=xlUp
theRow = theRow - 1
End If
' eliminate pressure rows where the time stamp is earlier than the temperature timestamp
If (TRange(theRow, 1).Value > PRange(theRow, 1).Value) And _
(Abs(TRange(theRow, 1).Value - PRange(theRow, 1).Value) >= (1# / 24# / 60# / 60# / 10#)) Then
PRange.Rows(theRow).Delete Shift:=xlUp
theRow = theRow - 1
Else
' eliminate temperature rows where the time stamp is earlier than the pressure timestamp
If (TRange(theRow, 1).Value < PRange(theRow, 1).Value) And _
(Abs(TRange(theRow, 1).Value - PRange(theRow, 1).Value) >= (1# / 24# / 60# / 60# / 10#)) Then
TRange.Rows(theRow).Delete Shift:=xlUp
theRow = theRow - 1
End If
End If
Next iLoop
End Sub
The redefinition(s) of this question makes it hard to deal with; particularly so as some (now removed) criteria would render some solutions to the current problem impractical.
I remember when your data came from multiple CSV files; some containing temperatures and some containing pressures. In fact there was so much data that it could conceivably 'spill' over to another worksheet. This fact alone renders individual worksheet value comparisons impractical. Even if it all fit on a single worksheet, comparing a million datetimes with a second set of a million datetimes and removing entries that do not fit both categories is going to be an arduous and time-consuming task.
Arduous and time-consuming tasks are best processed 'in-memory'. Repeatedly returning to the worksheet(s) to compare values is going to bog down processing and should be avoided unless absolutely necessary.
This seems like it should be an SQL question where two different sets of CSVs are loaded into two temporary but consolidated database tables and indexed on their respective datetimes. An INNER JOIN could then be performed to build a third table of matching records. Easy-peasy.
But this is an excel / vba question and should be answered in kind.
A VBA Scripting.Dictionary object is like an in-memory database table and comes with a unique primary 'index' called the key. It also has a single additional 'field' of the variant type which can receive any style of value or values that a variant can. Loading two dictionaries with the respective values (one for temperatures and another for the pressures) using the datetimes as the keys would seem to be the most efficient method of combining the two.
Sample data
I started with several CSVs similar to the following.
                                Temperaturen-25.csv                                                        SPS-25.csv
Three temperature CSVs and three pressure CSVs totalled ~300K records (~150K each) with periods of intentionally missing datetimes from each.
Module2 (Code)
Option Explicit
'public constant dictating the maximum number of entries per worksheet (never set higher than Rows.Count-3)
Public Const iMAXROWS As Long = 50000
Sub main()
Dim fp As String, fn As String, tmp As Variant
Dim dt As Variant, tdic As Object, pdic As Object
Dim tpwb As Workbook, a As Long, d As Long, w As Long
'apptggl btggl:=false 'uncomment this when you have finished debugging
'create 2 dictionary objects to receive ALL of the data
Set tdic = CreateObject("Scripting.Dictionary")
Set pdic = CreateObject("Scripting.Dictionary")
tdic.CompareMode = vbBinaryCompare
pdic.CompareMode = vbBinaryCompare
'load the dictionaries using the overwrite method
fp = Environ("TMP") & Chr(92) & "TempPress"
fn = Dir(fp & Chr(92) & "*.csv", vbNormal)
Do While CBool(Len(fn))
Select Case True
Case LCase(fn) Like "*temperaturen*"
'debug.Print "found " & fn
loadTPDictionary CStr(fp & Chr(92) & fn), tdic, 3
Case LCase(fn) Like "*sps*"
'debug.Print "found " & fn
loadTPDictionary CStr(fp & Chr(92) & fn), pdic, 2
Case Else
'do nothing; not temperature or pressure
End Select
'debug.Print tdic.Count & ":" & pdic.Count
fn = Dir
Loop
'debug.Print tdic.Count
'debug.Print pdic.Count
'At this point you have two dictionary object; one for temps and one for pressures
'They have a unique indexed key on their datetime values
'Time to merge the two
'First load all matching pressures into the temperatures
For Each dt In tdic
If pdic.Exists(dt) Then
tdic.Item(dt) = Array(tdic.Item(dt)(0), tdic.Item(dt)(1), tdic.Item(dt)(2), _
pdic.Item(dt)(1), pdic.Item(dt)(0))
End If
Next dt
'Second, get rid of temps that had no matching pressure
For Each dt In tdic
If UBound(tdic.Item(dt)) < 4 Then
tdic.Remove dt
End If
Next dt
'debug.Print tdic.Count
'debug.Print pdic.Count
'At this point the temp dictionary object contains a merged set of matching temps and pressures
'Time to put the values into one or more worksheets
'create a new target workbook and set up the first target worksheet
Set tpwb = Workbooks.Add
With tpwb
For w = 1 To Int(tdic.Count / iMAXROWS) + 1
a = 1: d = 1
'first load an array with the dictionary's values
ReDim tmp(1 To iMAXROWS, 1 To 5)
For Each dt In tdic
If d > (w * iMAXROWS) Then
Exit For
ElseIf d > ((w - 1) * iMAXROWS) Then
tmp(a, 1) = tdic.Item(dt)(0)
tmp(a, 2) = tdic.Item(dt)(1)
tmp(a, 3) = tdic.Item(dt)(2)
tmp(a, 4) = tdic.Item(dt)(3)
tmp(a, 5) = tdic.Item(dt)(4)
a = a + 1
End If
d = d + 1
Next dt
On Error GoTo bm_Need_Worksheet
With .Worksheets(w + 1) '<~~ ignore the original blank worksheet from the new workbook
'dump the values back into the worksheet
.Cells(2, 1).Resize(UBound(tmp, 1), UBound(tmp, 2)) = tmp
'format the datetimes
.Range("A2:A" & UBound(tmp, 1) + 1 & ",E2:E" & UBound(tmp, 1) + 1).NumberFormat = _
"[Color10]mm/dd/yyyy hh:mm:ss"
.Columns("A:E").AutoFit
End With
'clear the variant array
Erase tmp
Next w
'get rid of the original unprepped worksheet created with the new workbook
.Worksheets(1).Delete
'save as a binary workbook due to size considerations
.SaveAs Filename:=fp & Chr(92) & Format(Date, "\T\P\_yyyymmdd\_") & CLng(Timer), _
FileFormat:=xlExcel12, AddToMru:=True
'close savechanges:=false 'uncomment this after debugging
End With
'we got safely here; skip over worksheet creation
GoTo bm_Safe_Exit
bm_Need_Worksheet:
On Error GoTo 0
With tpwb.Worksheets.Add(After:=Sheets(Sheets.Count))
On Error GoTo bm_Need_Worksheet
.Range("A1:E1") = Array("Date and Time", "Temperature 1", "Temperature 2", _
"Pressure", "Date and Time (p)")
.Name = "Temperaturen & Pressure " & w
With .Parent.Windows(1)
.SplitColumn = 0: .SplitRow = 1
.FreezePanes = True
.Zoom = 75
End With
End With
Resume
bm_Safe_Exit:
'discard the dictionary objects
tdic.RemoveAll: Set tdic = Nothing
pdic.RemoveAll: Set pdic = Nothing
'restore the application environment
appTGGL
End Sub
Sub loadTPDictionary(fpn As String, ByRef dict As Object, flds As Long)
Dim f As Long, v As Long, vVALs As Variant, wb As Workbook
Workbooks.OpenText Filename:=fpn, StartRow:=1, DataType:=xlDelimited, _
ConsecutiveDelimiter:=False, _
Comma:=True, Tab:=False, Semicolon:=False, Space:=False, Other:=False, _
FieldInfo:=IIf(flds = 3, Array(Array(1, 3), Array(2, 1), Array(3, 1)), _
Array(Array(1, 3), Array(2, 1)))
With ActiveWorkbook
With Worksheets(1)
'Debug.Print .Cells(1, 1).Value
vVALs = .Range(.Cells(2, 1), .Cells(Rows.Count, flds).End(xlUp)).Value2
End With
.Close SaveChanges:=False
End With
If flds = 3 Then
For v = LBound(vVALs, 1) To UBound(vVALs, 1)
'fastest load method but overwrites duplicate datetime values with the last temp1, temp2
dict.Item(vVALs(v, 1)) = Array(vVALs(v, 1), vVALs(v, 2), vVALs(v, 3))
Next v
Else
For v = LBound(vVALs, 1) To UBound(vVALs, 1)
'fastest load method but overwrites duplicate datetime values with the last pressure
dict.Item(vVALs(v, 1)) = Array(vVALs(v, 1), vVALs(v, 2))
Next v
End If
Erase vVALs
End Sub
Public Sub appTGGL(Optional bTGGL As Boolean = True)
With Application
.ScreenUpdating = bTGGL
.EnableEvents = bTGGL
.DisplayAlerts = bTGGL
.AutoRecover.Enabled = bTGGL 'no interruptions with an auto-save
.Calculation = IIf(bTGGL, xlCalculationAutomatic, xlCalculationManual)
.CutCopyMode = False
.StatusBar = vbNullString
End With
Debug.Print Timer
End Sub
Refer to the in-code comments to follow the program flow. I seriously advise you to start with a smaller sample data set and work through the code using F8 and ctrl+F8. Set some watches on the vars. I've left many Debug.Print statements in that can be uncommented and their information observed through the VBE's Immediate window.
btw, my default workbooks are created with a single worksheet, not three like the default. You might want to adjust the code to remove everything but a single blank Worksheet Object immediately after the creation of a new target Workbook Object if you still open a new workbook with three blank worksheets. New worksheets are created to receive the data and are formatted on creation appropriately.
Results
While the results were produced quickly enough, I thought ~150K records (~135K after processing) were sufficient for testing. These results were split into multiple worksheets because of the iMAXROWS constant I set at 50K per worksheet.
                          TP_20160501_65489.xlsb
150K+150K processed into ~140K consolidated records in ~29 seconds.
You might also wish to seriously consider moving to a database solution.
See Highlight Duplicates and Filter by color alternative for pointers on dealing with large worksheets.

Read Wildcard As Asterisk

I had a piece of code commissioned earlier this week (cheaper to have an expert write it than for me to spend a week trying to!). However, when putting it use I've hit a bit of a snag.
The macro looks at a name on one excel worksheet, matches it to a list of names and associated ID numbers on a different worksheet, then inserts the ID on the first worksheet. This was all fine until I started using it on real data.
Here's some sample data (all of this information is in one cell...):
WARHOL*, Andy
PETO, John F
D3 GRECO, Emilio -20th C
HASELTINE, William Stanley
D3 DALI, Salvador
D3 SOSNO, Sacha
WEGMAN**, WILLIAM
One asterisk means it's a print, two a photograph, D3 a sculpture, and nothing a painting.
When I run the code with this data, it sees * as a wildcard, and so will always insert the ID of the first variation of the artist in the sheet. What I need is a way for the macro to not read it as a wildcard.
I did some research, and found that inserting ~ before * negates the wildcard properties. How would I make my code do this? I've discovered the main issue of having code written by someone else... You might not understand it!
Here is the code:
Public Sub match_data()
'ctrl+r
On Error GoTo errh
Application.ScreenUpdating = False
Application.Calculation = xlCalculationManual
Dim r1, r2, i, exc As Long
Dim fp As Range
Sheets("Data").Activate
r1 = Cells(Rows.Count, "B").End(xlUp).Row
r2 = Sheets("List").Cells(Sheets("List").Rows.Count, "B").End(xlUp).Row
'MsgBox r1 & r2
exc = 0
For i = 2 To r1
If Range("B" & i).Value <> "" Then
With Sheets("List").Range("B2:B" & r2)
Set fp = .Find(Range("B" & i).Value, LookIn:=xlValues, lookat:=xlWhole)
If Not fp Is Nothing Then
Range("B" & i).Interior.Color = xlNone
Range("A" & i).Value = Sheets("List").Range("A" & fp.Row).Value
Else
Range("B" & i).Interior.Color = xlNone
Range("B" & i).Interior.Color = vbYellow
exc = exc + 1
End If
End With
End If
Next i
MsgBox "There are " & exc & " exceptions."
errh:
If Err.Number > 0 Then
MsgBox Err.Description
End If
Application.ScreenUpdating = True
Application.Calculation = xlCalculationAutomatic
End Sub
Oh also, I would need to do this for the list of names and ID's wouldn't I? If so, that only needs doing once, so if you could give me a hint about that too, I'd be so grateful!
Thanks!
PS I know the system we are using at the moment absolutely sucks (definitely not 3rd form normalised!), but we are fast running out of time and money, and need to get our product up and running ASAP!
EDIT: To clarify, here is a pic of the spreadsheets I'm working with... Obviously in cells A14 and A15 I wanted the ID numbers 11 & 12 respectively
Here is one way to tell the stars from the planets:
Sub StaryNight()
Dim s As String, OneStar As String, TwoStar As String, ThreeStar As String
OneStar = "*"
TwoStar = "**"
ThreeStar = "***"
t = Range("A1").Text
ary = Split(t, ",")
s = ary(0)
If Right(s, 3) = ThreeStar Then
MsgBox "scupture"
Exit Sub
ElseIf Right(s, 2) = TwoStar Then
MsgBox "photograph"
Exit Sub
ElseIf Right(s, 1) = OneStar Then
MsgBox "print"
Exit Sub
End If
MsgBox "Painting"
End Sub
Okay, I have solved the problem! I had a play around with changing the variables in the Find and Replace box.
If I put ~* in both the find AND replace boxes, and uncheck Match entire cell contents, I can replace all of the * with ~* (really don't understand that but oh well!)
So I do this on the Data worksheet, but NOT on the List worksheet, run the macro as normal and the problem is solved!

Reduce Macro Time

I have been worked on a VBA code for past couple of days and everything seems to be working fine till one fine day when I added the below code to it. It marco executed time increased to such an extent that I myself don't when it is going to complete. I have waited for almost 2 hours but it continues to run.
This datasheet that I have is about 15 MB in size and contains around 47,000 rows with 25 columns filled with data. I have running this code to delete rows basis the multiple criteria on Columns "H".
Here is the code. Any help to reduce the runtime is highly appreciated.
Thanks...
Application.ScreenUpdating = False
Application.EnableEvents = False
Application.Calculation = xlCalculationManual
Application.DisplayStatusBar = False
Workbooks("Vivar_Template_Blank.xlsx").Sheets("Main & PCO Working").Activate
Dim ws As Worksheet, i&, lastRow&, value$
Set ws = ActiveWorkbook.ActiveSheet
lastRow = ws.Range("H" & ws.Rows.Count).End(xlUp).Row
For i = lastRow5 To 2 Step -1
value = ws.Cells(i, 8).value
If Not (value Like "*Supplier Name*" _
Or value Like "*[PO]Supplier (Common Supplier)*" _
Or value Like "*ACCENTURE LLP*" _
Or value Like "*COGNIZANT TECHNOLOGY SOLUTIONS US CORP*" _
Or value Like "*INFOSYS LIMITED*" _
Or value Like "*INFOSYS TECHNOLOGIES LTD*" _
Or value Like "*INTERNATIONAL BUSINESS MACHINES CORP DBA IBM CORP*" _
Or value Like "*MINDTREE LIMITED*" _
Or value Like "*SYNTEL INC*" _
Or value Like "*TATA AMERICA INTERNATIONAL CORPORATION*") _
Then
ws.Rows(i).Delete
End If
Next
Application.EnableEvents = True
Application.ScreenUpdating = True
Application.Calculation = xlCalculationAutomatic
Application.DisplayStatusBar = True
Or is not short-circuited so each Like expression will be executed, an alternative to halt on the first match (you don't actually need Like in this case, you can use the more efficient InStr):
Dim lookup(9) As String
lookup(0) = "Supplier Name"
lookup(1) = "[PO]Supplier (Common Supplier)"
lookup(2) = "ACCENTURE LLP"
lookup(3) = "COGNIZANT TECHNOLOGY SOLUTIONS US CORP"
lookup(4) = "INFOSYS LIMITED"
lookup(5) = "INFOSYS TECHNOLOGIES LTD"
lookup(6) = "INTERNATIONAL BUSINESS MACHINES CORP DBA IBM CORP"
lookup(7) = "MINDTREE LIMITED"
lookup(8) = "SYNTEL INC"
lookup(9) = "TATA AMERICA INTERNATIONAL CORPORATION"
For i = lastRow5 To 2 Step -1
value = ws.Cells(i, 8).value
For j = 0 To UBound(lookup)
If InStr(Value, lookup(j)) Then
ws.Rows(i).Delete
Exit For
End If
Next
Next
If any values are empty or there is a large distribution of a constant non-matching value, you should check and exclude them first.
Deleting Rows (Row by Row) is slow , try to use Union and delete all Rows by one time.
Application.ScreenUpdating = False
Application.EnableEvents = False
Application.Calculation = xlCalculationManual
Application.DisplayStatusBar = False
Workbooks("Vivar_Template_Blank.xlsx").Sheets("Main & PCO Working").Activate
Dim ws As Worksheet, i&, lastRow&, value$
Dim uRng As Range
Set ws = ActiveWorkbook.ActiveSheet
lastRow = ws.Range("H" & ws.Rows.Count).End(xlUp).Row
For i = lastRow5 To 2 Step -1 ' !!! maybe lastRow not lastRow5 because there is no value for lastRow5 in your code!!!
value = ws.Cells(i, 8).value
If Not (value Like "*Supplier Name*" _
Or value Like "*[PO]Supplier (Common Supplier)*" _
Or value Like "*ACCENTURE LLP*" _
Or value Like "*COGNIZANT TECHNOLOGY SOLUTIONS US CORP*" _
Or value Like "*INFOSYS LIMITED*" _
Or value Like "*INFOSYS TECHNOLOGIES LTD*" _
Or value Like "*INTERNATIONAL BUSINESS MACHINES CORP DBA IBM CORP*" _
Or value Like "*MINDTREE LIMITED*" _
Or value Like "*SYNTEL INC*" _
Or value Like "*TATA AMERICA INTERNATIONAL CORPORATION*") _
Then
'ws.Rows(i).Delete
If uRng Is Nothing Then
Set uRng = ws.Rows(i)
Else
Set uRng = Union(uRng, ws.Rows(i))
End If
End If
Next
If Not uRng Is Nothing Then uRng.Delete
Application.EnableEvents = True
Application.ScreenUpdating = True
Application.Calculation = xlCalculationAutomatic
Application.DisplayStatusBar = True
You could build a set of nested if/else constructs such that your logic terminates when the first true condition is encountered.
If Not (value Like "*Supplier Name*") then
ws.Rows(i).Delete
else if value Like "*[PO]Supplier (Common Supplier)*" then
ws.Rows(i).Delete
else if ...
End If
After you do this, another level of optimization would be to order the 'if' statements from most prevalent to least, thereby reducing the number of expected comparisons.

VBA code optimization

I have a set of VBA codes which work really perfectly with around of 20 000 x 16 cells.
However, I need to use the codes with max 80 000 x 16 cells.
I have identified two types of codes which run really slow:
c = 2 'this is the first row where your data will output
d = 2 'this is the first row where you want to check for data
Application.ScreenUpdating = False
Do Until Range("A" & c) = "" 'This will loop until column U is empty, set the column to whatever you want
'but it cannot have blanks in it, or it will stop looping. Choose a column that is
'always going to have data in it.
ws1.Range("U" & d).FormulaR1C1 = "=RC[-20] & RIGHT(""0000"" & RC[-14], 6)"
c = c + 1 'Advances a and b when there is a matching case
d = d + 1
Loop
Application.ScreenUpdating = True
End Sub
Sub OpenValue()
Dim l As Integer
Dim k As Integer
Dim m As Integer
m = Sheets("Input").Range("AC:AC").End(xlDown).Row
For l = 2 To m
If Range("AC" & l) = "Delievered" Then
Range("AD" & l) = 0
ElseIf Range("AC" & l) = "Cancelled" Then
Range("AD" & l) = 0
Else
Range("AD" & l) = Val(Range("Z" & l)) * Val(Range("J" & l))
End If
Next
End Sub
What can I do to poptimize them ....
The link provided by #GSerg is an awesome way to cut the running time of your script down. I found myself using:
Application.ScreenUpdating set to False
Application.Calculation set to xlCalculationManual
Application.EnableEvents set to False
Application.DisplayAlerts set to False
so often that I combined them into a single public subroutine. #Garys-Student provided the inspiration:
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'INPUT : True or False (i.e. fast or slow)
'DESCRIPTION : this sub turns off screen updating and alarms then
' sets calculations to manual
'
Public Sub GoFast(OnOrOff As Boolean)
Dim CalcMode As XlCalculation
CalcMode = Application.Calculation
With Application
.ScreenUpdating = Not OnOrOff
.EnableEvents = Not OnOrOff
.DisplayAlerts = Not OnOrOff
If OnOrOff Then
.Calculation = xlCalculationManual
Else
.Calculation = CalcMode
End If
End With
End Sub
In practice, you can now add the one-liner:
Call GoFast(True)
at the beginning of your script as part of the setup, then add:
Call GoFast(False)
at the end of your script as part of the teardown. Modify as you see fit!
The Do Until can be replaced with a one liner:
ws1.Range("A2", ws1.Range("A2").End(xlDown)).Offset(0,20).FormulaR1C1 = _
"=RC[-20] & RIGHT(""0000"" & RC[-14], 6)"
Note that this will fail if A3 is empty. If you have headers in row 1 you can change the second A2 to A1.
For the other Sub I'm not sure if you are doing something special with Val but if not you could change it to something similar:
Sub OpenValue()
Dim r As Range
Set r = Sheets("Input").Range("AD2:AD" & Sheets("Input").Range("AC1").End(xlDown).Row)
With r
.FormulaR1C1 = "=IF(OR(RC[-1]=""Delivered"",RC[-1]=""Cancelled""),0,RC10*RC26"
'If you want these as values uncomment the following lines
'.Calculate
'.Copy
'.PasteSpecial xlPasteValues
End With
End Sub
Sprinkle Application stuff around if needed (Calculation, ScreenUpdating, DisplayAlerts, EnableEvents).
Why is this faster:
To put it simply, VBA and Excel have to open a 'channel' to communicate between each other and this costs some time. So looping through a Range and adding formulas one-by-one is much slower for large ranges than doing it all at once since you'll only open the 'channel' once.

Resources