01.
Note
10 April 2020 03:47
Category Sub category Code Note
Range Selection Range(Selection, Selection.End(xlDown)).Select Selcet Multiple Cell - From selected cell to down full selection
Range Selection Range(Selection, Selection.End(xlToRight)).Select Selcet Multiple Cell - From selected cell to Right full selection
Sheets Sheets Worksheets("NewData#1").Activate Activate sheets by using tab name
Range Selection Selection.Copy To copy all the selection (current region)
Range Selection Selection.End(xlDown).Select Selcet SINGLE Cell - From selected cell to go down & select single
last down cell
Range Offset ActiveCell.Offset(1, 0).Select Goes onecell down from active cell
Range Selection ActiveSheet.Paste Paste Value from copy
Macro KB shortcut clrl+t+m+r To create the macro from xcel sheets
Macro KB shortcut clrl +f8 To see the code
Macro KB shortcut Press space and underscore, " _" To continue the lone line break down into small lines. Uncheck the
auto syntax check from options
Macro KB shortcut Tools > Options> auto list members check it. It is intelisense
Range last row Range("A4", "b" & Cells(Rows.Count, 1).End(xlUp).Row)
Udemy - Unlock Excel VBA and Excel Macros Page 1
Rough
14 April 2020 02:34
10.2
Option Explicit
Sub NEXT_LOOP_STEP() Sub counter_if_exercise()
Dim i As Integer
Dim i As Long Dim LastRow As Integer
Dim lastrow As Long Const FirstRow As Byte = 2
Dim Myvalue As Double Dim Division As String
Const startrow As Byte = 10 Dim remu As Long
Dim newvalue As Long
Range("H10").Select Range("E:F").Clear
lastrow = Range("A" & startrow).End(xlDown).Row Range("E1").Value = "Remunaration Package"
Range("f1").Value = "Note"
For i = startrow To lastrow
LastRow = Range("B" & FirstRow).End(xlDown).Row
Myvalue = Range("F" & i).Value For i = FirstRow To LastRow
If Myvalue > 100 Then newvalue = (Range("F" & i).Value) * 10 Division = Range("d" & i).Value
remu = Range("b" & i).Value
If Myvalue < 0 Then Exit For
ActiveCell = Myvalue
ActiveCell.Offset(1, 0).Select If Division = "CIB" Then
Range("E" & i).Value = remu * 1.25
Range("F" & i).Value = "Moderate"
ElseIf Range("d" & i).Value = "BDDF" Then
Next i Range("E" & i).Value = remu * 1.35
Range("F" & i).Value = "Good"
ElseIf Range("d" & i).Value = "IRS" Then
End Sub Range("E" & i).Value = remu * 1.5
Range("F" & i).Value = "Very Good"
Else
Range("E" & i).Value = remu * 1.1
Range("F" & i).Value = "Poor"
End If
Next i
Columns.ColumnWidth = 10
Columns.HorizontalAlignment = xlLeft
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 2
4.2 Referring to Ranges & Writing to Cells in VBA
10 April 2020 03:41
'@@@ WITHIN BRACKET @@
• Comma ** , ** with only one set of "" = Single value
• Comma ** , ** with only Multiple set of "" = Multiple value
• Colon : means ( might be select different range based comma , separation = Multiple
value
Sub RefertoCell()
'To clear the cell value
Cells.Clear
'It Will select the Active worksheets
'*****Select Singe Cell*****
'It will select the ONLY A1
Range("A1").Value = "1. 1st Range"
'Do the same thing using cell property, Row, Column
Cells(1, 2) = "2. 1st Cell"
'*****Select range*****
' ":" it will select the continuous cells
Range("A2:C2") = "3. 2nd Select A2 to C2"
' "," It will select separate cells or range
Range("A3:C3,E3:F3").Value = "4. Only A3toC3 & E3toF3, not D3"
Range("A4,E4").Value = "5. Only value in A4 and E4"
'See the Difference between this and other
'this is (" " ," " ) not (",")
'One single full quotation "" with comma select separate value
'Double full quotation (" " ," " ) select full range
Range("A5", "C5") = "6.value in A5 B5 and C5"
'*****Combine Range ,Cell row and column (mostly use in loop)*****
Range("A" & 6, "C" & 6) = "7.value in A6 B6 and C6"
'same as like Range("A5", "C5")
'Combination of range and cells
'same as like Range("A5", "C5")
Range(Cells(7, 1), Cells(7, 3)) = "8.Value in A7 to C7"
' Here, first we select the range A4 to C8,
'Then go to from A4 to 5 step down (A8) then A8 to two step right
'Here it is inclusive, count will start from A4 and then A8
Range("A4:C8").Cells(5, 2) = "9.Value will be in B8"
'*****Offset single cell to select one or more cell*****
'Range("A1").Offset(8, 2) = offset single cell
'mean offset start after A1 (start from A2 to 8 rows), here A1 exclusive
Udemy - Unlock Excel VBA and Excel Macros Page 3
Range("A1").Offset(8, 2).Value = "10.Value Will be in C9"
Range("A1").Offset(9, 2).Range("A1:A4").Value = "11.select only Four cell C10 to C13"
'Difference between
'Range("A1").Offset(8, 2).Range ("A1").value - select only one cell C9
'Range("A1").Offset(9, 2).Range ("A1:A4").value select only Four cell C10 to C13
'whether to select one cell or four cell (how many cell) depend on Range ("A1") or (A1:A4)
'*****Offset range or Multiple cell to select one or more cell*****
'Range("A1").Offset(8, 2) = offset single cell
'mean offset start after A1 (from A2 to 8 rows)
Range("A1:B9").Offset(10, 1).Range("A1:A4") = "12.Multiple Range offset and select 4 Rows"
Range("A1:B9").Offset(16, 2).Range("A1:B4") = "13.Multiple Range offset and select 4 Rows"
Range("A1:B9").Offset(15, 0).Range("A1") = "14.Multiple Range offset and select 4 Rows"
'*****Name manager ********
' Put name in cell A10 as TEST
Range("LASTCELL").Value = "15.Name Manager"
' Put name in cell A12 to A14 as TEST
Range("MtpName").Value = "16.Multiple Name Manager"
'*****Row And Column ********
Rows("12:14").RowHeight = 30 'It will select 12 to 14 row
Range("15:15,17:17").RowHeight = 30
'it will skip row 16.
'Same concepts applied for the Columns
Columns("E:F").ColumnWidth = 10
' cells.columns.autofit or Rows.AutoFit
Rows.AutoFit
Columns.AutoFit
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 4
Udemy - Unlock Excel VBA and Excel Macros Page 5
*4.3 Most Useful Range Properties & Methods
11 April 2020 03:42
Udemy - Unlock Excel VBA and Excel Macros Page 6
4.4 Methods to Find the Last Row of your Range
10 April 2020 03:46
Sub FindTheLastRow()
'ROWS = IT WILL GIVE THE VALUE
'ROW = IT WILL GIVE THE CELL ADDRESS NUMBER LIKE A =1, B =2
'Same as for Columns and Column
'*********** FIND THE LAST ROW ***********
'This method is good if I know the cell of start value and No empty cell extits
Range("K6").Value = Range("A4").End(xlDown).Row
Range("l6").Value = Range("A4").End(xlDown).Rows
'Assume we have GAPS in the middle
Range("K6").Value = Range("A10000").End(xlUp).Row
'now suppose my data set has value more than 10000
'So I will go to the last row in the excel and then jump up
'Range("A" & Rows.Count) = it,s count how many row I have in excel
Range("K6").Value = Range("A" & Rows.Count).End(xlUp).Row
'*********** FIND LAST EMPTY ROW ***********
Range("K7").Value = Range("A" & Rows.Count).End(xlUp).Row + 1
'Range("K7").Value = Range("A4").End(xlDown).Row + 1
'*********** FIND LAST COLUMNS ***********
'Range("K8").Value = Range("A4").End(xlToRight).Column
Range("l8").Value = Range("A4").End(xlToRight).Columns
Range("K8").Value = Cells(4, Columns.Count).End(xlToLeft).Column
'*********** Current Region ***********
Range("K9").Value = Range("A4").CurrentRegion.Address
'*********** Count Rows and columns***********
Range("K10").Value = Range("A4").CurrentRegion.Rows.Count
Range("K13").Value = Range("A4").CurrentRegion.Columns.Count
'******Special Cells - last cell **********
Range("K11").Value = Cells.SpecialCells(xlCellTypeLastCell).Row
Range("K12").Value = Cells.SpecialCells(xlCellTypeLastCell).Column
'******Select all(applicable if you have empty cell) **********
Range("A4", "A" & Cells(Rows.Count, 1).End(xlUp).Row).Interior.Color =
VBA.ColorConstants.vbGreen
Udemy - Unlock Excel VBA and Excel Macros Page 7
Range("A4", "A" & Cells(Rows.Count, 1).End(xlUp).Row).EntireRow.Interior.Color =
Excel.Constants.xlNone
Range("A4", "A" & Cells(Rows.Count, 1).End(xlUp).Row).Interior.Color = VBA.ColorConstants.vbBlue
Range("A4", "A" & Cells(Rows.Count, 1).End(xlUp).Row).EntireRow.Interior.Color =
Excel.Constants.xlNone
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 8
4.5 Copying & resizing a variably sized range
11 April 2020 02:43
Sub Copy_Variable()
'**************
'Copy method
'**************
'Under this Method everything will be carried over
'format, formula etc everything
Range("I3").CurrentRegion.Clear
Newdata01.Range("A3").CurrentRegion.Copy Range("I3")
'**********************
'PasteSpecial method
'**********************
Range("A15").CurrentRegion.Clear
' If I want copy only value not comments or formats
' Enter Space after Pastespecial
Range("A15").CurrentRegion.Clear
Newdata01.Range("A3").CurrentRegion.Copy
Range("A15").PasteSpecial xlPasteValues
Range("A15").PasteSpecial xlPasteComments
Range("A15").PasteSpecial xlPasteValuesAndNumberFormats
' You have to put pastespecial twice for the values and comments
' Each line of the pastespecial do one job
'Like for value and number format
Range("A15").PasteSpecial xlPasteValuesAndNumberFormats
'**************************************
' Resize Property with copy Method
'**************************************
' if I don't want header
'? Range("A3").CurrentRegion.Offset(1,0).Address
' $A$4:$F$10
' but my data is until A9 to F9, So i want to remove A10 to F10
' So RESIZE property will be used
'Print Newdata01.Range("A3").CurrentRegion.Offset(1, 0).Resize(Range("A3").CurrentRegion.Rows.Count - 1).Address
'$A$4:$F$9
' ********* use SPACE and UNDERSCORE to cut and continue the line ************
Range("I16").CurrentRegion.Clear
Newdata01.Range("A3").CurrentRegion.Offset(1, 0) _
.Resize(Range("A3").CurrentRegion.Rows.Count - 1) _
.Copy Range("I16")
'or
Range("I16").CurrentRegion.Clear
Newdata01.Range("A3").CurrentRegion.Offset(1, 0) _
.Resize(Range("A3").CurrentRegion.Rows.Count - 1).Copy _
Range("I16").PasteSpecial xlPasteValues
Range("I16").PasteSpecial xlPasteComments
Range("I16").PasteSpecial xlPasteValuesAndNumberFormats
'********Appliation cut copy mode ******
'Appliation cut copy mode should be false in order to remove copy selection
Application.CutCopyMode = False
Udemy - Unlock Excel VBA and Excel Macros Page 9
Application.CutCopyMode = False
'******** If we add more line in the copy region it will paste new line as well under all 3 method
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 10
4.6 Properly Referencing Worksheets
11 April 2020 00:24
Sub ProperlyReferencingWorksheets()
'.Usedrange is a property of active sheets
' Mean if I use .usedrange It will always refer as active Sheest
'.usedrange is different from range
' refer Worksheets as sheet name
' Suppose sheets name = note
Worksheets("Note").Select
Worksheets("Note").Range("A17") = "Sheet Name"
Range("A17").Clear
' refer Worksheets as CODE name
' Suppose CODE name = notecr
NoteCr.Range("A18") = "Code Name"
Range("A18").Clear
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 11
4.7 Properly Referencing Workbooks
11 April 2020 01:35
Sub ReferenceWorksheet()
' ThisWorkbook means not the active workbooks, ITs mean the Workbook where VBA code is written
' The moment I use the code name for the SHEETS, VBA assume that it is thisworkbook
Workbooks("Note for the course.xlsm").Sheets("Note").Range("A20").Value = "Lucky"
'Same as
NoteCr.Range("A21").Value = "Lucky"
' Debug Print will give the answer in immediate window
' Use to check whether code is okay or not
Debug.Print ActiveWorkbook.FullName 'location with name
Debug.Print ActiveWorkbook.Path ' Name of the folder
Debug.Print ActiveWorkbook.Name ' name only
Debug.Print ActiveSheet.Name
'Select Workbook by Name
'Suppose Workbook name "Note for the course.xlsm"
Workbooks("Note for the course.xlsm").Activate
Workbooks("Note for the course.xlsm").Sheets("Note").Range("A20").Value = "Lucky"
' Copy one workbook from another workbook
' This will only work if both workbooks are open
NoteCr.Range("A1").CurrentRegion.Copy Workbooks("Teste.xlsx").Sheets(1).Range("A1")
Workbooks("Teste.xlsx").Sheets(1).Range("A1").CurrentRegion.Clear
' Copy one workbook from another workbook
' ***If Paste Workbooks are not open***
Application.Workbooks.Open "D:\Teste.xlsx"
Workbooks("Teste.xlsx").Sheets(1).Range("A1").CurrentRegion.Clear
NoteCr.Range("A1").CurrentRegion.Copy Workbooks("Teste.xlsx").Sheets(1).Range("A1")
Cells.Rows.AutoFit
Cells.Columns.AutoFit
' In order to close the WB ( without variable)
' Here paste WB is the active WB
' True means save changes
ActiveWorkbook.Close True
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 12
Udemy - Unlock Excel VBA and Excel Macros Page 13
*4.9 Project Save Hard-coded Copy & Macro-free version
of workbook
11 April 2020 03:41
Udemy - Unlock Excel VBA and Excel Macros Page 14
5.2 Data Types for Better Performance
11 April 2020 03:43
• By Default VBA use data type Variant which changes depending on the data types
• Smaller memory used smaller Range used like, Byte use 1 byte memory and range of it is 0 to
255.
• Double is used for when requires high and accurate precision and declaring percentages.
• Object - used to declare cell as RANGE, sheet as WORKSHEETS, or declare WORKBOOKS as
variable
• Variant could be handy when you have a variable that really changing between different data
types, then it's makes sense to use VARIANT as data types
Udemy - Unlock Excel VBA and Excel Macros Page 15
5.3 Declaring Variables, Arrays & Constants (Role of
Option Explicit)
11 April 2020 03:59
• 'HOW TO DECLARE VARIABLE ?
'First Declare Variable
'Format = DIM "VariableName" AS "DATA TYPE"
'Example = DIM mytext AS string
'DIM mytext
' If I did not put anything as data type, VBA will use VARIANT by default as data type
' In Variable name you can use underscore, nothing else like, symbols or space.
' Dim meansDimension
'Second Assign value for the Variable
'Format = let "VariableName" = "Value"
'Example = let mytext = "MACRO"
'Let can be omitted
'For String data type, you have to put " "
'Example
Sub Variable_Define()
Dim lastcolumn As Integer
Let lastcolumn = Columns.Count
Debug.Print lastcolumn
Dim lastRow As Long
Let lastRow = Rows.Count
Debug.Print lastRow
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 16
Udemy - Unlock Excel VBA and Excel Macros Page 17
5.4 Using Object Variables (Set statement)
11 April 2020 05:22
Udemy - Unlock Excel VBA and Excel Macros Page 18
6.2 With & End With for Easier Code Writing
11 April 2020 06:14
Udemy - Unlock Excel VBA and Excel Macros Page 19
6.3 For Each to Loop Through Collections (sheets, ranges
etc.) in one go
26 April 2020 12:19
'Structure
' Dim Sh as Worksheet
'For Each Sh IN thisworkbook.worksheets
'Sh.protect " test"
'Next
'Dim __ as ____
' For Each ___ In _____
'____________
'Next
Option Explicit
Sub protect_WS()
Dim sh As Worksheet
For Each sh In ThisWorkbook.Worksheets
sh.Protect
Debug.Print sh.Name
Next
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 20
Udemy - Unlock Excel VBA and Excel Macros Page 21
6.4 IF Then (Else, ElseIF) for Conditional Outcomes
26 April 2020 12:37
FORMULA
STRUCTURE
IF **FIRST CONDITION** THEN
RESULT IF FIRST CONDITION TRUE
ELSEIF **SEOND CONDITION** THEN
RESULT IF SECOND CONDITION TRUE
ELSE
RESULT IF BOTH CONDITION ARE FALSE
END IF
Sub if_function()
If Range("F4") > 24000 Then
Range("G4").Value = "Higher than 240000"
Udemy - Unlock Excel VBA and Excel Macros Page 22
Range("G4").Value = "Higher than 240000"
Else: Range("G4").Value = "Less than 24000"
End If
If Range("f5").Value >= 10000 And Range("f5").Value <= 30000 Then
Range("G5").Value = "In between 10000 and 30000"
Else: Range("G5").Value = "outside range"
End If
If Range("f6").Value >= 10000 And Range("f6").Value <= 30000 Then
Range("G6").Value = "Only If"
End If
End Sub
COMBINE IF AND FOR EACH
Sub Combine_IF_and_Foreach()
Dim Sh As Worksheet
For Each Sh In ThisWorkbook.Worksheets
If Sh.Name = "Sheet1" And Sh.Range("A1").Value = "Copy data to Summary Tab" Then
Sh.Unprotect
ElseIf Sh.Name = "a" And Sh.Range("A1").Value = "Empty" Then
Sh.Unprotect "TEST"
End If
Debug.Print Sh.Name
Next
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 23
Udemy - Unlock Excel VBA and Excel Macros Page 24
6.5 Select Case as Alternative for Many IF Statements
26 April 2020 16:17
Sub caseSte()
Select Case Range("A16").Value
Case 0 To 2000
Range("b16").Value = "Very bad"
Case 2001 To 4000
Range("b16").Value = "bad"
Case 4001 To 6000
Range("b16").Value = "Average"
Case 6001 To 8000
Range("b16").Value = "Good"
Case Is > 8000
Range("b16").Value = "Excellent"
Case Else
Range("b16").Value = "ATTENTION POINT"
End Select
Select Case Range("a17").Value
Case 2000 To 4000, 8000 To 10000
Range("b17").Value = "Very bad"
Case Else
Range("b17").Value = "ATTENTION POINT"
End Select
Udemy - Unlock Excel VBA and Excel Macros Page 25
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 26
11.2. One Dimensional Arrays (and transferring back to
sheet)
28 April 2020 00:08
Option Explicit
Sub monthArray()
' Dim monthArray(1 To 12) As String
' Dim I As Byte
'
' For I = 1 To 12
' monthArray(I) = Range("A" & I + 4) ' here I equal 1
'Next I
'or
'Dim monthArray(5 To 16) As String
'Dim I As Byte
'
'For I = 5 To 16
'monthArray(I) = Range("A" & I).Value ' here I equal 5
'
'Next I
' if you think your value can be change ,so you can use name manager
Dim monthArray(1 To 12) As String
Dim I As Byte
For I = 1 To 12
monthArray(I) = Range("myMonth").Cells(I, 1).Value
Next I
'write array back to excel
' by default it gives value to horizontal
Range("C5:N5").Value = monthArray
' check following one, it's will give only JAN in all cell
Range("C6:c17").Value = monthArray
' if you want by vertical way, have to use transpose
Udemy - Unlock Excel VBA and Excel Macros Page 27
Range("D6:D17").Value = Excel.WorksheetFunction.Transpose(monthArray)
End Sub
Sub lowerboundandHigher()
Dim MonthArray(1 To 12) As String
Dim I As Byte
Dim r As Long
'************** This Part Put the value for Month Array**********
For I = 1 To 12
MonthArray(I) = Range("mymonth").Cells(I, 1).Value
Next I
'************** This Part Put the value for Month Array**********
'************** This Part put value after 4 rows**********
For I = LBound(MonthArray) To UBound(MonthArray)
Range("E7").Offset(r).Value = MonthArray(I)
r=r+5
Next I
End Sub
Udemy - Unlock Excel VBA and Excel Macros Page 28
Udemy - Unlock Excel VBA and Excel Macros Page 29