Getting Data from Quandle
Here we show how to get data from the online marketplace for financial, economic, and alternative data, Quandl.
We do this for two types of data, FX Rates, and OPEC Oil Prices.
Screenshots
VBA Module Code - FX Rates
VBA
Sub Get_FXRates()
Application.DisplayAlerts = False
'Define Variables
Dim lastRow As Integer
Dim Code, qurl As String
Dim edate, sdate As Date
Code = Range("Code").Value
edate = Range("End_Date").Value
sdate = Range("Start_Date").Value
'Define Source
qurl = "https://www.quandl.com/api/v3/datasets/BOE/" & Code & ".csv?" & "start_date=" & Year(sdate) & "-" & Month(sdate) & "-" & Day(sdate) & "&end_date=" & Year(edate) & "-" & Month(edate) & "-" & Day(edate) & "&api_key=nB7pRLb2Rtj-TB6eigCb"
'Clear Prior
lastRow = Sheets("FX Rates").Cells(Rows.Count, "A").End(xlUp).Row
Sheets("FX Rates").Range(Cells(1, 1), Cells(lastRow, 2)).Clear
'Query Table
ActiveWorkbook.Worksheets("FX Rates").Activate
With ActiveSheet.QueryTables.Add(Connection:="TEXT;" & qurl & "", Destination:=Range("$A$2"))
.Name = "Test"
.FieldNames = True
.RowNumbers = False
.FillAdjacentFormulas = False
.PreserveFormatting = False
.RefreshOnFileOpen = False
.RefreshStyle = xlInsertDeleteCells
.SavePassword = False
.SaveData = True
.AdjustColumnWidth = False
.RefreshPeriod = 0
.TextFilePromptOnRefresh = False
.TextFilePlatform = 65001
.TextFileStartRow = 1
.TextFileParseType = xlDelimited
.TextFileTextQualifier = xlTextQualifierDoubleQuote
.TextFileConsecutiveDelimiter = False
.TextFileTabDelimiter = True
.TextFileSemicolonDelimiter = False
.TextFileCommaDelimiter = True
.TextFileSpaceDelimiter = False
.TextFileColumnDataTypes = Array(1, 1, 9, 9)
.TextFileTrailingMinusNumbers = True
.Refresh BackgroundQuery:=False
End With
'Format Data
Range("A2:B2").Select
Selection.Font.Bold = True
Columns("A:A").Select
Selection.NumberFormat = "dd/mm/yyyy;@"
lastRow = Sheets("FX Rates").Cells(Rows.Count, "A").End(xlUp).Row
Range("A2:B" & lastRow).Select
Application.CutCopyMode = False
'Remove Data connections and Query Tables
Dim Cn As Variant
For Each Cn In ThisWorkbook.Connections
Cn.Delete
Next Cn
For Each Cn In ActiveSheet.QueryTables
Cn.Delete
Next Cn
'Table Formatting
ActiveSheet.ListObjects.Add(xlSrcRange, Range("$A$2:$B$" & lastRow), , xlYes).Name = _
"FX_Rates"
ActiveSheet.ListObjects("FX_Rates").TableStyle = "TableStyleMedium2"
Range("A1").Select
End Sub
VBA Module Code - OPEC Prices
VBA
Sub Get_OpecPrices()
Application.DisplayAlerts = False
'Define Variables
Dim lastRow As Integer
Dim qurl As String
Dim edate, sdate As Date
edate = Range("End_Date2").Value
sdate = Range("Start_Date2").Value
'Define Source
qurl = "https://www.quandl.com/api/v3/datasets/OPEC/ORB.csv?" & "start_date=" & Year(sdate) & "-" & Month(sdate) & "-" & Day(sdate) & "&end_date=" & Year(edate) & "-" & Month(edate) & "-" & Day(edate) & "&api_key=nB7pRLb2Rtj-TB6eigCb"
'Clear Prior
lastRow = Sheets("OPEC Prices").Cells(Rows.Count, "A").End(xlUp).Row
Sheets("OPEC Prices").Range(Cells(1, 1), Cells(lastRow, 2)).Clear
'Query Table
ActiveWorkbook.Worksheets("OPEC Prices").Activate
With ActiveSheet.QueryTables.Add(Connection:="TEXT;" & qurl & "", Destination:=Range("$A$2"))
.Name = "Test"
.FieldNames = True
.RowNumbers = False
.FillAdjacentFormulas = False
.PreserveFormatting = False
.RefreshOnFileOpen = False
.RefreshStyle = xlInsertDeleteCells
.SavePassword = False
.SaveData = True
.AdjustColumnWidth = False
.RefreshPeriod = 0
.TextFilePromptOnRefresh = False
.TextFilePlatform = 65001
.TextFileStartRow = 1
.TextFileParseType = xlDelimited
.TextFileTextQualifier = xlTextQualifierDoubleQuote
.TextFileConsecutiveDelimiter = False
.TextFileTabDelimiter = True
.TextFileSemicolonDelimiter = False
.TextFileCommaDelimiter = True
.TextFileSpaceDelimiter = False
.TextFileColumnDataTypes = Array(1, 1, 9, 9)
.TextFileTrailingMinusNumbers = True
.Refresh BackgroundQuery:=False
End With
'Format Data
Range("A2:B2").Select
Selection.Font.Bold = True
Columns("A:A").Select
Selection.NumberFormat = "dd/mm/yyyy;@"
Range("B2").Select
ActiveCell.FormulaR1C1 = "Value ($/bbl)"
Range("B3").Select
Columns("B:B").EntireColumn.AutoFit
lastRow = Sheets("OPEC Prices").Cells(Rows.Count, "A").End(xlUp).Row
Range("A2:B" & lastRow).Select
Application.CutCopyMode = False
'Remove Data connections and Query Tables
Dim Cn As Variant
For Each Cn In ThisWorkbook.Connections
Cn.Delete
Next Cn
For Each Cn In ActiveSheet.QueryTables
Cn.Delete
Next Cn
'Table Formatting
ActiveSheet.ListObjects.Add(xlSrcRange, Range("$A$2:$B$" & lastRow), , xlYes).Name = _
"Opec_Prices"
ActiveSheet.ListObjects("Opec_Prices").TableStyle = "TableStyleMedium6"
Range("A1").Select
End Sub
Check API Key
Note:
You may have to change the API key used in both samples above.
Download
The full file can be downloaded here:
Feedback
Submit and view feedback