I did a simple DCF Valuation with Python and I thought I try it with Excel and VBA as well. The VBA module:
Converts numbers stored as text (including percentages and values with unit symbols) into actual numeric values.
Searches for key financial items using substring matching.
Computes Free Cash Flow to the Firm (FCFF), forecasts future cash flows, calculates the Weighted Average Cost of Capital (WACC), and ultimately derives an intrinsic share price.
Outputs all assumptions, extracted metrics, and calculation steps neatly into a “valuation” sheet.
Many financial datasets store numbers as text with extra
formatting—such as commas, unit abbreviations (M, B, T), or percentages.
I downloaded my financial statements from stockanalysis.com and I wrote
the following helper function, ParseValue
, to clean and
convert the data into properly formatted numeric values. For instance,
“15%” becomes 0.15 and “12.5M” becomes 12,500,000, also multiplied
figures by 1,000,000 since they were given in million dollars.
Option Explicit
' --- Helper Function: ParseValue ---
' Converts text values with units (e.g., "12.5M", "3.2B", "15%") into a numeric value.
Public Function ParseValue(val As Variant) As Double
Dim s As String, lastChar As String
s = CStr(val)",", "")
s = Replace(s,
s = Trim(s)
If s = "-" Or s = "" Or s = "NA" Or s = "N/A" Then
ParseValue = 0Exit Function
End If
' Handle percentages
If InStr(s, "%") > 0 Then
"%", "")
s = Replace(s, If IsNumeric(s) Then
ParseValue = CDbl(s) / 100Else
ParseValue = 0End If
Exit Function
End If
lastChar = Right(s, 1)Select Case lastChar
"B"
Case If IsNumeric(Left(s, Len(s) - 1)) Then
ParseValue = CDbl(Left(s, Len(s) - 1)) * 1000000000#Else
ParseValue = 0End If
"M"
Case If IsNumeric(Left(s, Len(s) - 1)) Then
ParseValue = CDbl(Left(s, Len(s) - 1)) * 1000000#Else
ParseValue = 0End If
"T"
Case If IsNumeric(Left(s, Len(s) - 1)) Then
ParseValue = CDbl(Left(s, Len(s) - 1)) * 1000000000000#Else
ParseValue = 0End If
Else
Case If IsNumeric(s) Then
' For plain numbers, assume the value is in millions (adjust as needed)
ParseValue = CDbl(s) * 1000000#Else
ParseValue = 0End If
End Select
End Function
Financial items (such as EBIT, Depreciation, or CAPEX) may not be
stored as exact text. The next helper function, GetValue
,
searches for a substring match in column B (starting at row 5) and
returns the corresponding value from column C—after converting it with
ParseValue
.
' --- Helper Function: GetValue ---
' Searches for a cell in column B (starting at row 5) that contains the search string (substring match)
' and returns the numeric value from the corresponding cell in column C.
Public Function GetValue(ws As Worksheet, searchStr As String, Optional secondOccurrence As Boolean = False) As Double
Dim lastRow As Long, r As Long, countFound As Integer
countFound = 0"B").End(xlUp).Row
lastRow = ws.Cells(ws.Rows.Count, For r = 5 To lastRow
Dim cellText As String
"B").Value)
cellText = Trim(ws.Cells(r, ' Check if searchStr appears anywhere in the cell (case-insensitive)
If InStr(1, cellText, searchStr, vbTextCompare) > 0 Then
countFound = countFound + 1If (Not secondOccurrence And countFound = 1) Or (secondOccurrence And countFound = 2) Then
"C").Value)
GetValue = ParseValue(ws.Cells(r, Exit Function
End If
End If
Next r
GetValue = 0End Function
The main subroutine, CalculateDCF
, gathers key metrics
from your three financial statement sheets, performs the DCF
calculations, and then outputs a summary with all assumptions,
equations, and steps neatly into a “valuation” sheet.
' --- Main Subroutine: CalculateDCF ---
' Extracts key metrics from "Income Statement", "Balance Sheet", and "Cash Flow" sheets,
' forecasts Free Cash Flow to the Firm (FCFF), calculates WACC, and computes an intrinsic share price.
' Outputs a formatted summary on a sheet named "valuation".
Public Sub CalculateDCF()
Dim wsFin As Worksheet, wsBal As Worksheet, wsCF As Worksheet, wsVal As Worksheet
Set wsFin = ThisWorkbook.Sheets("Income Statement")
Set wsBal = ThisWorkbook.Sheets("Balance Sheet")
Set wsCF = ThisWorkbook.Sheets("Cash Flow")
' --- Create (or clear) the "valuation" sheet ---
On Error Resume Next
Set wsVal = ThisWorkbook.Sheets("valuation")
On Error GoTo 0
If wsVal Is Nothing Then
Set wsVal = ThisWorkbook.Sheets.Add(After:=ThisWorkbook.Sheets(ThisWorkbook.Sheets.Count))
"valuation"
wsVal.Name = Else
wsVal.Cells.ClearEnd If
Dim iRow As Long
iRow = 1"DCF Valuation Summary"
wsVal.Cells(iRow, 1).Value = True
wsVal.Cells(iRow, 1).Font.Bold =
iRow = iRow + 2
' --- Parameters & Assumptions ---
Dim tax As Double, DEFAULT_GROWTH As Double, TERM_GROWTH As Double, DEFAULT_COST_DEBT As Double
Dim FORECAST_YEARS As Integer
' Default effective tax rate (T)
tax = 0.21 ' Annual FCFF growth rate (g)
DEFAULT_GROWTH = 0.15 ' Terminal growth rate (g_term)
TERM_GROWTH = 0.04 ' Cost of debt (r_d)
DEFAULT_COST_DEBT = 0.04 ' Forecast period (years)
FORECAST_YEARS = 5
"Assumptions:"
wsVal.Cells(iRow, 1).Value =
wsVal.Cells(iRow, 1).Font.Underline = xlUnderlineStyleSingle
iRow = iRow + 1"Effective Tax Rate (T): " & Format(tax, "0.00%")
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Default Growth Rate (g): " & Format(DEFAULT_GROWTH, "0.00%")
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Terminal Growth Rate (g_term): " & Format(TERM_GROWTH, "0.00%")
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Default Cost of Debt (r_d): " & Format(DEFAULT_COST_DEBT, "0.00%")
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Forecast Period: " & FORECAST_YEARS & " years"
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 2
' --- Extract Key Metrics ---
Dim EBIT As Double, depr As Double, capex As Double, FCFF0 As Double
"EBIT") ' Searches column B for "EBIT"; gets value from column C
EBIT = GetValue(wsFin, "Depreciation")
depr = GetValue(wsCF, "Capital Expenditure"))
capex = Abs(GetValue(wsCF,
"Extracted Metrics:"
wsVal.Cells(iRow, 1).Value =
wsVal.Cells(iRow, 1).Font.Underline = xlUnderlineStyleSingle
iRow = iRow + 1"EBIT: " & EBIT
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Depreciation: " & depr
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"CAPEX: " & capex
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1
Dim wcCurrent As Double, wcPrev As Double, deltaWC As Double
"Working Capital")
wcCurrent = GetValue(wsBal, "Working Capital", True) ' Second occurrence for previous period
wcPrev = GetValue(wsBal,
deltaWC = wcCurrent - wcPrev"Working Capital (Current): " & wcCurrent
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Working Capital (Previous): " & wcPrev
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Δ Working Capital: " & deltaWC
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 2
' --- FCFF Calculation ---
' Equation: FCFF = EBIT * (1 - T) + Depreciation - CAPEX - ΔWC
"Free Cash Flow")
FCFF0 = GetValue(wsCF, If FCFF0 = 0 Then
FCFF0 = EBIT * (1 - tax) + depr - capex - deltaWC"Calculated FCFF = EBIT*(1-T) + Depreciation - CAPEX - ΔWC: " & FCFF0
wsVal.Cells(iRow, 1).Value = Else
"Extracted FCFF: " & FCFF0
wsVal.Cells(iRow, 1).Value = End If
iRow = iRow + 2
' --- Net Debt ---
Dim netDebt As Double
"Net Cash (Debt)")
netDebt = GetValue(wsBal, If netDebt = 0 Then
Dim totalDebt As Double, cashEquiv As Double
"Total Debt")
totalDebt = GetValue(wsBal, "Cash & Equivalents")
cashEquiv = GetValue(wsBal,
netDebt = totalDebt - cashEquivEnd If
"Net Debt: " & netDebt
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 2
' --- Forecast FCFF ---
Dim forecast() As Double
ReDim forecast(1 To FORECAST_YEARS)
"Forecasted FCFF (for each year):"
wsVal.Cells(iRow, 1).Value =
wsVal.Cells(iRow, 1).Font.Underline = xlUnderlineStyleSingle
iRow = iRow + 1Dim j As Integer
For j = 1 To FORECAST_YEARS
forecast(j) = FCFF0 * (1 + DEFAULT_GROWTH) ^ j"Year " & j & ": " & forecast(j)
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1Next j
iRow = iRow + 1
' --- WACC Calculation ---
Dim rf As Double, beta As Double, mrp As Double, ce As Double, de As Double
Dim we As Double, wd As Double, WACC As Double
' Risk-free rate (e.g., TLT yield)
rf = 0.022 ' Assumed beta (adjust as needed)
beta = 1 ' Assumed market risk premium
mrp = 0.06 ' Cost of Equity
ce = rf + beta * mrp ' Cost of Debt
de = DEFAULT_COST_DEBT ' Equity weight
we = 0.8 ' Debt weight
wd = 0.2
WACC = we * ce + wd * de * (1 - tax)
"WACC Calculation:"
wsVal.Cells(iRow, 1).Value =
wsVal.Cells(iRow, 1).Font.Underline = xlUnderlineStyleSingle
iRow = iRow + 1"Risk-free Rate (r_f): " & rf
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Beta: " & beta
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Market Risk Premium (r_m - r_f): " & mrp
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Cost of Equity (r_e): " & ce
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Cost of Debt (r_d): " & de
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Equity Weight (w_e): " & we
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Debt Weight (w_d): " & wd
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"WACC: " & WACC
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 2
' --- Terminal Value and DCF Calculation ---
Dim sumDCF As Double, termVal As Double, EV As Double
sumDCF = 0For j = 1 To FORECAST_YEARS
sumDCF = sumDCF + forecast(j) / ((1 + WACC) ^ j)Next j
termVal = forecast(FORECAST_YEARS) * (1 + TERM_GROWTH) / (WACC - TERM_GROWTH)
EV = sumDCF + termVal / ((1 + WACC) ^ FORECAST_YEARS)
"Terminal Value and DCF Calculation:"
wsVal.Cells(iRow, 1).Value =
wsVal.Cells(iRow, 1).Font.Underline = xlUnderlineStyleSingle
iRow = iRow + 1"Sum of Discounted FCFF: " & sumDCF
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Terminal Value: " & termVal
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1"Enterprise Value (EV): " & EV
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 1Dim eqValue As Double
eqValue = EV - netDebt"Equity Value (EV - Net Debt): " & eqValue
wsVal.Cells(iRow, 1).Value =
iRow = iRow + 2
' --- Intrinsic Share Price ---
Dim shares As Double, intrinsicPrice As Double
' Adjust to actual shares outstanding
shares = 17000000000# If shares <> 0 Then
intrinsicPrice = eqValue / sharesElse
intrinsicPrice = 0End If
"Intrinsic Share Price: " & intrinsicPrice
wsVal.Cells(iRow, 1).Value =
"A:A").EntireColumn.AutoFit
wsVal.Columns("DCF Valuation summary has been output to the 'valuation' sheet.", vbInformation
MsgBox End Sub
This VBA module calculates the DCF valuation based on your financial statements and creates a clean, well-formatted report on a dedicated “valuation” sheet. Each section of the report shows the assumptions, equations used, and intermediate values calculated during the process. You can adjust search strings, column references, and parameters as needed to match your specific data.