Click here to Skip to main content
15,902,636 members
Home / Discussions / Visual Basic
   

Visual Basic

 
GeneralRe: vb.net visibility o form objects Pin
classy_dog8-Jun-15 5:06
classy_dog8-Jun-15 5:06 
GeneralRe: vb.net visibility o form objects Pin
Richard MacCutchan8-Jun-15 5:34
mveRichard MacCutchan8-Jun-15 5:34 
Questionhow to get internet time using http request Pin
Member 107622705-Jun-15 1:34
Member 107622705-Jun-15 1:34 
AnswerRe: how to get internet time using http request Pin
Richard MacCutchan5-Jun-15 2:32
mveRichard MacCutchan5-Jun-15 2:32 
AnswerRe: how to get internet time using http request Pin
Richard Deeming5-Jun-15 2:34
mveRichard Deeming5-Jun-15 2:34 
QuestionCopying data between to SQL Servers Pin
Member 117439064-Jun-15 23:26
Member 117439064-Jun-15 23:26 
AnswerRe: Copying data between to SQL Servers Pin
Eddy Vluggen5-Jun-15 0:35
professionalEddy Vluggen5-Jun-15 0:35 
QuestionExcel 2013 VBA - Secure Website Login Pin
Member 110154484-Jun-15 8:07
Member 110154484-Jun-15 8:07 
I attempted a small VBA Sub() in Excel 2013 with the intent of:
- iterating through a list of high volume ETFs on the Main worksheet,
- creating a Web Query for each ETF to access Security Holdings info for each ETF,
- pull that data into an individual worksheet for each ETF.

My issue is getting past the Fidelity secure access. The code below processes my password input correctly, but not my username. Being logged into the Fidelity website in an open browser session does not allow the web query access to the ETF data pages.

Can anyone tell me why the username portion of the code is failing? Is there an easier way for me to skin this cat?

Thanks

=====

Sub Update()
' Requires a reference to MICROSOFT INTERNET CONTROLS object
On Error GoTo ErrorOut:

Dim wbThis As Workbook: Set wbThis = ThisWorkbook
Dim wsMain As Worksheet: Set wsMain = wbThis.Worksheets("Main")
Dim objIntExp As InternetExplorer: Set objIntExp = New InternetExplorer
Dim objIntExpDoc As Object
Dim objIntExpDocElmt As Object
Dim wsData As Worksheet
Dim strUsername As Long
Dim strPassword As String
Dim lngDateLast As Long
Dim lngDateCurrent As Long
Dim strSymbol As String
Dim strQuery As String
Dim lngRow As Long
Dim lngLength As Long
Dim lngLastSymbolRow As Long
Const str_LOGIN_PAGE As String = "https://oltx.fidelity.com/ftgw/fbc/ofsummary/defaultPage"
Const str_START As String = "http://research2.fidelity.com/fidelity/screeners/etf/etfholdings.asp?symbol="
Const str_END As String = "&view=Sector"
Const lng_SYMBOL_LENGTH_MIN As Long = 3
Const lng_SYMBOL_LENGTH_MAX As Long = 5
Const lng_SYMBOL_ROW_MIN As Long = 2
Const lng_SYMBOL_ROW_MAX As Long = 21

' Check for a new date
lngDateLast = CLng(wsMain.Cells(5, 3))
lngDateCurrent = CLng(Date)
If lngDateLast >= lngDateCurrent Then
MsgBox "TRY AGAIN", vbOKOnly, "Data is already current!"
Exit Sub
End If
' Delete any existing data sheets
If wbThis.Worksheets.Count > 1 Then
Application.DisplayAlerts = False
For Each wsData In wbThis.Worksheets
If wsData.Name <> "Main" Then
wsData.Delete
End If
Next wsData
Application.DisplayAlerts = True
End If
' Get the last symbol row
lngLastSymbolRow = wsMain.Range("A100").End(xlUp).Row
If lngLastSymbolRow > lng_SYMBOL_ROW_MAX Then
lngLastSymbolRow = lng_SYMBOL_ROW_MAX
End If
If lngLastSymbolRow < lng_SYMBOL_ROW_MIN Then
MsgBox "TRY AGAIN", vbOKOnly, "No ETF Symbols detected in Column-A to process!"
Exit Sub
End If
' Set the Username and Password
strUsername = Trim(CStr(InputBox("Enter your Fidelity Username for login.", "FIDELITY USERNAME")))
strPassword = Trim(CStr(InputBox("Enter your Fidelity Password for login.", "FIDELITY PASSWORD")))
' Next line not required, but helps for debugging
objIntExp.Visible = True
' Go to Fidelity LogIn page
objIntExp.Navigate str_LOGIN_PAGE
Do While objIntExp.Busy: DoEvents: Loop
Do Until objIntExp.ReadyState = READYSTATE_COMPLETE: DoEvents: Loop
' Login with user inputs
Set objIntExpDoc = objIntExp.Document
Debug.Print "Form = " & objIntExpDoc.forms(0).Name
Set objIntExpDocElmt = objIntExpDoc.getElementByID("userId-select")
objIntExpDocElmt.Value = strUsername
Debug.Print objIntExpDocElmt.Name & " = " & objIntExpDocElmt.Value
Set objIntExpDocElmt = objIntExpDoc.getElementByID("password")
' Note - password disappears here!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
objIntExpDocElmt.Value = strPassword
Debug.Print objIntExpDocElmt.Name & " = " & objIntExpDocElmt.Value
objIntExpDoc.forms(0).submit

Do While objIntExp.Busy: DoEvents: Loop
Do Until objIntExp.ReadyState = READYSTATE_COMPLETE: DoEvents: Loop
' Cycle through all symbols
For lngRow = lng_SYMBOL_ROW_MIN To lngLastSymbolRow Step 1
strSymbol = Trim(CStr(wsMain.Cells(lngRow, 1)))
lngLength = Len(strSymbol)
If (lngLength < lng_SYMBOL_LENGTH_MIN) Or (lngLength > lng_SYMBOL_LENGTH_MAX) Then
' Invalid symbol ... skip it
GoTo GetNextSymbol:
End If
' Build the web query URL
strQuery = str_START & strSymbol & str_END
' Add a new worksheet
wbThis.Worksheets.Add(After:=Worksheets(Worksheets.Count)).Name = strSymbol
' Get the raw ETF query data
With wsMain.QueryTables.Add(Connection:=strQuery, Destination:=Worksheets(strSymbol).Range("A1"))
.Name = strSymbol & "_Query"
.RowNumbers = False
.FillAdjacentFormulas = False
.PreserveFormatting = True
.RefreshOnFileOpen = False
.BackgroundQuery = False
.RefreshStyle = xlOverwriteCells
.SavePassword = False
.SaveData = True
.AdjustColumnWidth = True
.RefreshPeriod = 0
.WebSelectionType = xlEntirePage
.WebFormatting = xlWebFormattingNone
.WebPreFormattedTextToColumns = True
.WebConsecutiveDelimitersAsOne = True
.WebSingleBlockTextImport = False
.WebDisableDateRecognition = False
.WebDisableRedirections = False
.Refresh BackgroundQuery:=False
End With

GetNextSymbol:
Next lngRow

' Refresh the date
wsMain.Cells(5, 3) = lngDateCurrent

NormalExit:
Application.DisplayAlerts = True
GoTo Cleanup:

ErrorOut:
MsgBox "Unable to update data!", vbOKOnly, "UPDATE ERROR"

Cleanup:
Application.DisplayAlerts = True
Set objIntExpDocElmt = Nothing
Set objIntExpDoc = Nothing
Set objIntExp = Nothing
Set wsData = Nothing
Set wsMain = Nothing
Set wbThis = Nothing

End Sub
AnswerRe: Excel 2013 VBA - Secure Website Login Pin
Member 110154488-Jun-15 7:52
Member 110154488-Jun-15 7:52 
QuestionRe: Excel 2013 VBA - Secure Website Login Pin
Member 110154489-Jun-15 12:09
Member 110154489-Jun-15 12:09 
QuestionHTML Textbox Pin
Member 117418844-Jun-15 7:46
Member 117418844-Jun-15 7:46 
SuggestionRe: HTML Textbox Pin
Richard Deeming5-Jun-15 1:20
mveRichard Deeming5-Jun-15 1:20 
Questionvb.net 2010 startup form for desktop application Pin
dcof4-Jun-15 5:47
dcof4-Jun-15 5:47 
AnswerRe: vb.net 2010 startup form for desktop application Pin
Eddy Vluggen4-Jun-15 10:07
professionalEddy Vluggen4-Jun-15 10:07 
AnswerRe: vb.net 2010 startup form for desktop application Pin
Sascha Lefèvre4-Jun-15 10:32
professionalSascha Lefèvre4-Jun-15 10:32 
GeneralRe: vb.net 2010 startup form for desktop application Pin
dcof4-Jun-15 11:29
dcof4-Jun-15 11:29 
GeneralRe: vb.net 2010 startup form for desktop application Pin
Sascha Lefèvre4-Jun-15 11:52
professionalSascha Lefèvre4-Jun-15 11:52 
QuestionVB.net 2010 desktop app select file from drop down list box Pin
dcof4-Jun-15 5:11
dcof4-Jun-15 5:11 
AnswerRe: VB.net 2010 desktop app select file from drop down list box Pin
Eddy Vluggen4-Jun-15 10:10
professionalEddy Vluggen4-Jun-15 10:10 
GeneralRe: VB.net 2010 desktop app select file from drop down list box Pin
dcof4-Jun-15 11:32
dcof4-Jun-15 11:32 
GeneralRe: VB.net 2010 desktop app select file from drop down list box Pin
Eddy Vluggen4-Jun-15 22:20
professionalEddy Vluggen4-Jun-15 22:20 
QuestionOpen a form when the name is known only on runtime Pin
satc3-Jun-15 9:35
satc3-Jun-15 9:35 
AnswerRe: Open a form when the name is known only on runtime Pin
Sascha Lefèvre3-Jun-15 10:26
professionalSascha Lefèvre3-Jun-15 10:26 
GeneralRe: Open a form when the name is known only on runtime Pin
satc3-Jun-15 16:29
satc3-Jun-15 16:29 
GeneralRe: Open a form when the name is known only on runtime Pin
Sascha Lefèvre3-Jun-15 22:00
professionalSascha Lefèvre3-Jun-15 22:00 

General General    News News    Suggestion Suggestion    Question Question    Bug Bug    Answer Answer    Joke Joke    Praise Praise    Rant Rant    Admin Admin   

Use Ctrl+Left/Right to switch messages, Ctrl+Up/Down to switch threads, Ctrl+Shift+Left/Right to switch pages.