VBA Session 1 — Introduction to VBA

Macros, the VBE, and cross‑platform basics (Win/Mac)

Juan F. Imbet

Paris Dauphine University-PSL

Welcome

  • Course: Intro to VBA and Python (10 sessions × ~3 h)
  • Today: General Introduction
  • Goal: Build confidence to automate simple tasks in Excel using VBA

Information

  • Juan F. Imbet, Assistant Professor of Finance.
  • juan.imbet@dauphine.psl.eu
  • Office: P606
  • Office hours by appointment

Bit about me

  • Engineering background, PhD in Finance (Pompeu Fabra University)
  • Research in Asset Pricing, Corporate Finance, Asset Management, and Computational Finance.
  • Teaching in Finance Theory, Programming, and Artificial Intelligence.
  • Consulting Private Equity Firms in implementing AI enhanced investment processes.

Grading

  • Group Project 40% (topic joint with Aymeric Kalife’s class, 100% Python)
  • Final Exam 50% (less focus on exact syntax, more on concepts and problem solving)
  • Class Participation 10%

What is VBA?

  • Visual Basic for Applications (VBA) is a programming language embedded inside Office apps (Excel, Word, PowerPoint, Access).
  • Runs inside the host application process (Excel), giving access to its Object Model: e.g. Application → Workbooks → Worksheets → Range.
  • Great for automating repetitive tasks, building custom functions and UI (forms, buttons), and integrating with files and data.
  • Cross‑platform note: VBA exists on Windows and Mac, but some integrations are Windows‑only. Companies use VBA almost exclusively on Windows.
  • Mac users can still run most VBA code.

How VBA relates to Windows vs Mac

  • Windows: Excel exposes rich automation via COM/ActiveX; VBA can call Windows APIs and Office libraries broadly.
  • COM/ActiveX is a Windows feature that enables inter-application communication and advanced integrations.
  • Mac: Same VBA language and Excel Object Model for most tasks; no COM/ActiveX, some features differ (File dialogs, Add‑ins, some APIs).
  • Bitness matters on Windows (32/64‑bit Office).

Why learn VBA in 2025?

  • Excel remains the lingua franca of business.
  • Quick wins: automate reports, cleanup, formatting.
  • Bridges to other tools (Power Query, Python via xlwings, etc.).

Disadvantages of VBA

  • Old language (from 1993); lacks modern features (e.g., no classes, limited error handling).
  • Not easy to debug or test.
  • Grammar is not the most friendly.

Macro security mindset

  • A Macro is the common name for some VBA code embedded in an Office document.
  • Macros can run code; treat files like executables.
  • Only enable content from trusted sources.
  • Use signed macros in corporate environments.
  • A signed macro is one that has been digitally signed with a certificate to verify its authenticity.

Windows (Trust Center): File → Options → Trust Center → Trust Center Settings → Macro Settings
Recommended for learning: “Disable all macros with notification” + add a Trusted Location for your course folder.
Consider enabling Protected View for files from the internet; unblock via file Properties → Unblock.

Mac (Trust Center): Excel → Preferences → Security & Privacy
Similar options: enable with notification; manage access to Visual Basic project if prompted.

Enable Developer tab (Windows)

  1. File → Options → Customize Ribbon
  2. Under Main Tabs, check Developer and click OK

Enable Developer tab (Mac)

  1. Excel → Preferences → Ribbon & Toolbar
  2. Select Main Tabs and check Developer
  3. Click Save; the Developer tab appears

Excel UI tour (Win/Mac)

  • Windows screenshot: Excel workbook with the Ribbon showing the Developer tab
  • Mac screenshot: Excel for Mac with Developer tab visible
  • Callouts: Record Macro button, Visual Basic button, Macros list

Excel for Windows UI

Excel for Mac UI

Recording a macro (Win/Mac)

Windows

  • Developer → Record Macro
  • Name, choose storage (This Workbook/Personal)
  • Do actions → Stop → inspect in VBE
  • Use “Use Relative References” for relative actions
  • Naming: start with a letter; verbs like FormatHeader
  • Quick edit: Developer → Macros → Edit

Mac

  • Developer → Record Macro (similar flow)
  • Some shortcuts/dialogs differ slightly
  • Relative References also available
  • Prefer shape/button over keyboard shortcut (conflicts)
  • Storage mirrors Windows; Personal Macro Workbook exists

Relative References

  • Relative References toggle (Windows/Mac) controls whether recorded actions use absolute cell references (e.g., Range("A1")) or relative to the active cell (e.g., ActiveCell.Offset(0, 0)).
  • Use the Use Relative References button on the Developer tab before starting to record.

The Visual Basic Editor (VBE)

  • Open with Alt+F11 (Windows) or Option+F11 (Mac)
  • Project Explorer, Properties Window, Code Pane
  • Modules vs ThisWorkbook vs Sheet objects
  • Insert a Module: VBE → Insert → Module (stores your Sub procedures)
  • Run code: press F5 in VBE, or assign to a shape/button on the sheet

Opening the VBE (step‑by‑step)

  • Windows: Use Alt+F11, or Ribbon → Developer → Visual Basic
  • Mac: Use Option+F11, or Ribbon → Developer → Visual Basic
  • Verify the Project Explorer (left) and Properties (bottom‑left); if hidden: View → Project Explorer, View → Properties Window
  • Use View menu to show/hide panes if your layout differs.

Hello, world (VBA)

  • Macros start with a Sub procedure, and end with End Sub.
  • VBA has reserved words (e.g., Sub, Dim, If, Then, End); case-insensitive but prefer standard casing.
 Sub HelloWorld()
     MsgBox "Hello from VBA!"
 End Sub
  • How to run it: place cursor inside HelloWorld and press F5 (or click Run ▶)
  • Assign to a button: Insert → Shapes → pick a shape → right‑click → Assign Macro → choose HelloWorld

Procedures, variables, and types

Sub procedures and variables

Sub MyTask()
    ' your steps here
End Sub

Sub Boxes()
    Dim total As Long ' variable declaration
    total = 42
    MsgBox total
End Sub
  • Sub = a routine you can run; lives in a Module
  • Dim name As Type declares storage

Types and Option Explicit

  • Common types: Integer, Long, Double, String, Boolean, Date
  • Variant can hold anything (flexible but slower)
  • Prefer explicit types for clarity and speed
  • Not all types are available on Mac.
  • The Option Explicit statement forces variable declaration, reducing typos and bugs.
Option Explicit ' require declarations
Sub Safer()
    Dim count As Long
    count = 10
    MsgBox count
End Sub
  • Option Explicit → fewer typos, clearer code

Scope and lifetime

  • What variables are visible where, and how long they last.
  • Public vs Private: controls visibility across modules
  • Public = visible everywhere; Private = only inside the module
  • Const for constants, variables that are not meant to change.
  • Constants are stored more efficiently in memory since their values do not change.
  • Sub procedures can also be declared as Public or Private.
  • If no declaration is given, Sub procedures are Public by default.
  • Enum for named integer constants.
  • Defining variables outside any procedure makes them module-level (retain value while module is loaded).

Example

Option Explicit

Public Const VAT As Double = 0.20 ' project-wide constant (in a standard module)
Private totalRuns As Long          ' module-level state

Public Sub RunTask()
    totalRuns = totalRuns + 1
    Dim localMsg As String ' procedure scope
    localMsg = "Run #" & totalRuns
    Debug.Print localMsg
End Sub

Private Function Hidden() As Boolean ' not visible outside module
    Hidden = True
End Function

Public Sub Remember()
    Static last As Long ' retains value across calls
    last = last + 1
    Debug.Print last
End Sub

Public Enum Status
    stPending = 0
    stDone = 1
    stError = 2
End Enum

Debugging

  • Large programs rarely run perfectly the first time.
  • Understanding the values that variables take at different points in execution is key to finding and fixing bugs.
  • To write something in the debugging output window, use Debug.Print.
  • This output can be viewed in the Immediate Window (Ctrl+G in Windows or Cmd+G in Mac).

Referencing cells

  • VBA can access and manipulate Excel cells directly.
  • Absolute reference example uses the Range object.
  • Relative reference example uses ActiveCell and Offset.
  • ActiveCell is the currently selected cell in the active worksheet.
  • Offset is used to refer to a cell that is a specific number of rows and columns away from another cell.
Sub SetA1()
    Range("A1").Value = "Hi"
End Sub
  • Qualify with Worksheets(“Sheet1”).Range(“A1”) to be precise
  • Qualify fully when multiple workbooks: Workbooks("Book1.xlsx").Worksheets("Sheet1").Range("A1")
  • Cells(row, col) uses numbers: Cells(1, 1) is A1; can combine: Range(Cells(1,1), Cells(10,2))
  • Useful for loops.

Selecting vs directly writing

  • Avoid Select/Activate when possible; write directly

Do this

Worksheets("Sheet1").Range("A1").Value = "Direct write"
With Worksheets("Sheet1")
    .Range("B1").Value = "With block"
    .Cells(2, 1).Value = 123
End With

Not this

Worksheets("Sheet1").Select
Range("A1").Select
Selection.Value = "Indirect write"
Range("B1").Select
ActiveCell.Value = "Indirect with ActiveCell"

Conditionals

If…Then

If Range("A1").Value > 0 Then
    MsgBox "Positive"
Else
    MsgBox "Non‑positive"
End If
  • Great for simple conditions and ranges

Select Case

Select Case Range("B1").Value
    Case "A", "B": MsgBox "Group 1"
    Case "C": MsgBox "Group 2"
    Case Else: MsgBox "Other"
End Select
  • Cleaner than nested Ifs for discrete categories

Loops: Do it repeatedly

  • You need to define the variable that controls the loop.
Dim i As Long
For i = 1 To 10
    Cells(i, 1).Value = i
Next i

Dim c As Range
For Each c In Range("A1:A10")
    c.Value = c.Value & "!" ' The & concatenates strings
Next c

Dim k As Long
k = 1
Do While k <= 10
    Cells(k, 2).Value = k * 2
    k = k + 1
Loop

Dim tries As Long
tries = 0
Do
    tries = tries + 1
Loop Until tries >= 10
  • For ... Next: use a counter variable for numeric ranges
  • For Each ... Next: iterate items in a collection (Worksheets, Shapes, or cells in a Range)
  • Do While/Do Until: loop while/until a condition is satisfied (see next slide)

Debugging essentials

  • Breakpoints (click left margin), the code execution will pause there.
  • Step Into F8, Step Over Shift+F8, Step Out Ctrl+Shift+F8
  • Immediate window Ctrl+G: evaluate (? Range("A1").Value) or call procedures
  • Debug.Print for tracing; Stop statement to break programmatically

How to inspect variables live

  • Use the Locals window (View → Locals Window) to see all local variables and their current values when paused at a breakpoint.
  • Not all variables may have their values shown in the Locals window, especially if they are complex objects or if the code is not currently within the scope where the variable is defined.
Sub Trace()
   Dim c As Long
    For c = 1 To 10
        c = c + 1
    Next c
End Sub
  • Tip: Reproduce fast; isolate into small test Subs; comment out non-essential code while debugging

Do While / Do Until

Dim r As Long
r = 1
Do While Cells(r, 1).Value <> ""
    Cells(r, 2).Value = Len(Cells(r, 1).Value)
    r = r + 1
Loop
  • Do While condition ... Loop: runs while condition is True
  • Do Until condition ... Loop: runs until condition becomes True
  • Prefer guard rails: increment counters, add max-iteration safety to avoid infinite loops
Dim tries As Long
tries = 0
Do
    tries = tries + 1
    If tries > 1000 Then Exit Do ' safety
    ' ... work ...
Loop Until Application.CountA(Range("A1:A10")) = 10
  • Tip: Choose For when you know counts, For Each for collections, Do While/Until for condition-driven loops

InputBox and MsgBox

Dim name As String
name = InputBox("Your name?")
MsgBox "Hi " & name
  • Simple UI for quick interactions

Advanced: prompt for a Range safely

Sub PickRange()
    Dim rng As Range
    On Error Resume Next
    Set rng = Application.InputBox("Select a range", Type:=8)
    On Error GoTo 0
    If rng Is Nothing Then
        MsgBox "No selection"
    Else
        MsgBox "You picked " & rng.Address
    End If
End Sub

Arrays (static vs dynamic)

  • An array is a collection of values indexed by number.
  • Static arrays have fixed size; Dynamic arrays can be resized with ReDim.
' Static array (fixed size)
Dim a(1 To 5) As Long
a(1) = 10

' Dynamic array (resize later)
Dim b() As Double
ReDim b(1 To 3)
b(3) = 1.23
ReDim Preserve b(1 To 5) ' keep existing values
ReDim b(1 To 2) ' loses existing values
  • Static arrays: fastest, but fixed bounds
  • Dynamic arrays: ReDim to set size; ReDim Preserve to keep values.
  • Bounds defaults: if unspecified, VBA uses zero-based indexing; prefer explicit 1 To N for clarity
  • Many programming languages use zero-based indexing; VBA defaults to zero-based if no bounds are specified, but using 1 To N is clearer for Excel users.

Collections and Dictionary

  • Two main collection types: Collection (built-in) and Scripting.Dictionary (Windows).
  • Collections have no fixed size; Dictionaries map keys to values.
' Collection (built-in)
Dim coll As New Collection
coll.Add "Alice"
coll.Add "Bob"
Dim item As Variant
For Each item In coll
    Debug.Print item
Next

' Scripting.Dictionary (Windows)
Dim dict As Object
Set dict = CreateObject("Scripting.Dictionary")
dict("FR") = "France"
dict("ES") = "Spain"
If dict.Exists("FR") Then Debug.Print dict("FR")
  • Collection: ordered, allows duplicates, 1-based indexing via Item
  • Dictionary: key→value map, fast lookup; on Mac, available via AppleScript support but often easiest to simulate with Collection or use array lookups
  • Tip: For portability, prefer Collection or arrays unless you really need keyed lookup
  • Dim vs Set', Dim declares a variable;Set` assigns an object reference.
  • An object reference points to an instance of an object (like a Collection or Dictionary).

Object references

  • If you modify an object through one reference, the changes are reflected when accessing it through another reference.

Example

Dim coll1 As New Collection
Dim coll2 As Collection
Set coll2 = coll1 ' coll2 now references the same Collection as coll1
coll1.Add "Item1"
Debug.Print coll2.Count ' Outputs 1, as coll2 references the same Collection

Subs vs Functions (User Defined Functions - UDFs)

' Sub performs actions
Sub ClearData()
    Worksheets("Sheet1").Range("A2:D1000").ClearContents
End Sub

' Function returns a value (UDF) name the variable that captures the return value as the function name
Public Function AddTax(amount As Double, rate As Double) As Double
    AddTax = amount * (1 + rate)
End Function
  • Sub: run from VBE, buttons, or macros dialog; can modify workbook state
  • Function: returns a value; can be used in worksheet cells as a UDF
  • UDF caveats: should be pure (function of inputs only); avoid side effects (changing sheets)
  • For security UDFs are not allowed to modify the Excel environment (e.g., changing cell values, formatting, or interacting with other applications). They should only compute and return values based on their input parameters.

The Workbook, Worksheet and WorksheetFunction objects

  • Each workbook and worksheet has its own code module (ThisWorkbook, Sheet1, etc.)
  • They allow access to events (open, close, change, etc.)
  • They also allow access to standard excel formulas.
  • Use ThisWorkbook to refer to the workbook containing the code.
  • Some common events:
    • Workbook_Open: runs when the workbook opens
    • Workbook_BeforeClose: runs before the workbook closes
    • Worksheet_Change: runs when a cell value changes in that sheet
  • This is the main reason why Office applications ask to enable macros when opening files with VBA code.
Private Sub Workbook_Open()
    MsgBox "Welcome!"
End Sub

Access to standard Excel formulas

Sub UseExcelFunction()
    Dim result As Double
    result = Application.WorksheetFunction.Sum(Range("A1:A10"))
    MsgBox "Sum is " & result
End Sub
---

## Win vs Mac differences (overview)

- Shortcuts (Alt vs Option), some dialogs differ
- File system paths differ
- Many object model calls are the same

Details that matter:
- Paths: Windows uses `C:\Users\...\file.xlsx`; Mac uses `/Users/you/file.xlsx`; combine with `Application.PathSeparator`
- File dialogs: `Application.FileDialog(msoFileDialogFilePicker)` works on both, but filters and default folders behave slightly differently
- API calls: Windows allows `Declare PtrSafe Function` to call Win32 APIs; Mac lacks Win32 — avoid OS API calls for portability
- Add‑ins: `.xlam` works both; COM add‑ins are Windows‑only

---

## Error handling basics

```vb
Sub DoWork()
    On Error GoTo CleanUp ' jump to CleanUp on error
    ' ... risky code here ...

Done:
    ' What to do when done
    Exit Sub

CleanUp:
    MsgBox "Error " & Err.Number & ": " & Err.Description, vbExclamation, "DoWork"
    Resume Done
End Sub
  • Start simple; add structure as you grow

Variable Types

  • Integer: -32,768 to 32,767 (2 bytes)
  • Long: -2,147,483,648 to 2,147,483,647 (4 bytes)
  • Single: Single-precision floating point (4 bytes)
  • Double: Double-precision floating point (8 bytes)
  • String: Text (up to ~2 billion characters)
  • Boolean: True/False (2 bytes)
  • Date: Dates and times (8 bytes)
  • Variant: Can hold any type; default if no type specified (16 bytes + data)
  • Prefer explicit types for clarity and performance; Variant is flexible but slower and uses more memory
  • Not all types are available on Mac.

Your first serious program (exercise in class)

  • For your first exercise you are going to estimate the value of \(\pi\) using a Monte Carlo method.
  • Imagin e a square of side 2 (from -1 to 1 in both x and y) that contains a circle of radius 1.
  • The area of the square is 4, and the area of the circle is \(\pi\).
  • You are going to randomly generate points in the square, and count how many fall inside the circle as a fraction of the total points.
  • This fraction multiplied by 4 will give you an estimate of \(\pi\).

Your task - Create a UDF EstimatePi(n As Long) As Double that takes the number of random points to generate as input, and returns the estimate of \(\pi\). - Use x = Rnd to generate random numbers between 0 and 1; scale it to -1 to 1. - Return the estimate. - Your function should be available in the worksheet as e.g. =EstimatePi(10000).

Function EstimatePi(n As Long) As Double
    Dim inside As Long
    Dim i As Long
    Dim x As Double, y As Double
    inside = 0
    'Randomize 'Optional Initialize random number generator
    For i = 1 To n
        x = Rnd * 2 - 1 ' Random x in [-1, 1]
        y = Rnd * 2 - 1 ' Random y in [-1, 1]
        If x * x + y * y <= 1 Then
            inside = inside + 1
        End If
    Next i
    EstimatePi = (inside / n) * 4 ' Estimate of pi
End Function