Skip to content

Commit

Permalink
Update examples
Browse files Browse the repository at this point in the history
  • Loading branch information
timhall committed Apr 2, 2014
1 parent 8b879e0 commit e129301
Show file tree
Hide file tree
Showing 3 changed files with 60 additions and 17 deletions.
23 changes: 18 additions & 5 deletions examples/analytics/Analytics.bas
Original file line number Diff line number Diff line change
Expand Up @@ -7,14 +7,22 @@ Private pGAClientSecret As String

Private Property Get GAClientId() As String
If pGAClientId = "" Then
pGAClientId = InputBox("Please Enter Google API Client Id")
If Credentials.Loaded Then
pGAClientId = Credentials.Values("Google")("id")
Else
pGAClientId = InputBox("Please Enter Google API Client Id")
End If
End If

GAClientId = pGAClientId
End Property
Private Property Get GAClientSecret() As String
If pGAClientSecret = "" Then
pGAClientSecret = InputBox("Please Enter Google API Client Secret")
If Credentials.Loaded Then
pGAClientSecret = Credentials.Values("Google")("secret")
Else
pGAClientSecret = InputBox("Please Enter Google API Client Secret")
End If
End If

GAClientSecret = pGAClientSecret
Expand All @@ -26,17 +34,22 @@ Public Property Get GAClient() As RestClient
pGAClient.BaseUrl = "https://www.googleapis.com/analytics/v3"

Dim Auth As New GoogleAuthenticator
Set pGAClient.Authenticator = Auth
Call Auth.Setup(GAClientId, GAClientSecret)
Auth.Scope = Array("https://www.googleapis.com/auth/analytics.readonly")
Auth.Setup GAClientId, GAClientSecret
Auth.AddScope "analytics.readonly"
Call Auth.Login

Set pGAClient.Authenticator = Auth
End If

Set GAClient = pGAClient
End Property

Public Function AnalyticsRequest(ProfileId As String, StartDate As Date, EndDate As Date) As RestRequest

If ProfileId = "" And Credentials.Loaded Then
ProfileId = Credentials.Values("Google")("profile")
End If

Set AnalyticsRequest = New RestRequest
AnalyticsRequest.Resource = "data/ga"
AnalyticsRequest.Method = httpGET
Expand Down
30 changes: 26 additions & 4 deletions examples/salesforce/SalesforceSheet.cls
Original file line number Diff line number Diff line change
Expand Up @@ -11,12 +11,30 @@ Private pConsumerSecret As String
Private pPassword As String
Private pSecurityToken As String

Public Property Get ConsumerKeyValue() As String
If Me.[ConsumerKey].Value = "" And Credentials.Loaded Then
ConsumerKeyValue = Credentials.Values("Salesforce")("key")
Else
ConsumerKeyValue = Me.[ConsumerKey].Value
End If
End Property
Public Property Get ConsumerSecret() As String
If pConsumerSecret = "" Then
pConsumerSecret = InputBox("Please enter Salesforce consumer secret")
If Credentials.Loaded Then
pConsumerSecret = Credentials.Values("Salesforce")("secret")
Else
pConsumerSecret = InputBox("Please enter Salesforce consumer secret")
End If
End If
ConsumerSecret = pConsumerSecret
End Property
Public Property Get UsernameValue() As String
If Me.[Username].Value = "" And Credentials.Loaded Then
UsernameValue = Credentials.Values("Salesforce")("username")
Else
UsernameValue = Me.[Username].Value
End If
End Property
Public Property Get Password() As String
If pPassword = "" Then
pPassword = InputBox("Please enter Salesforce password")
Expand All @@ -25,7 +43,11 @@ Public Property Get Password() As String
End Property
Public Property Get SecurityToken() As String
If pSecurityToken = "" Then
pSecurityToken = InputBox("Please enter Salesforce security token")
If Credentials.Loaded Then
pSecurityToken = Credentials.Values("Salesforce")("token")
Else
pSecurityToken = InputBox("Please enter Salesforce security token")
End If
End If
SecurityToken = pSecurityToken
End Property
Expand Down Expand Up @@ -72,9 +94,9 @@ Private Sub OutputError(Code As Long, Message As String)
End Sub

Private Sub Login()
Salesforce.ConsumerKey = Me.[ConsumerKey].Value
Salesforce.ConsumerKey = ConsumerKeyValue
Salesforce.ConsumerSecret = ConsumerSecret
Salesforce.Username = Me.[Username].Value
Salesforce.Username = UsernameValue
Salesforce.Password = Password
Salesforce.SecurityToken = SecurityToken
End Sub
24 changes: 16 additions & 8 deletions examples/twitter/Twitter.bas
Original file line number Diff line number Diff line change
Expand Up @@ -7,14 +7,22 @@ Private pTwitterSecret As String

Private Property Get TwitterKey() As String
If pTwitterKey = "" Then
pTwitterKey = InputBox("Please Enter Twitter Consumer Key")
If Credentials.Loaded Then
pTwitterKey = Credentials.Values("Twitter")("key")
Else
pTwitterKey = InputBox("Please Enter Twitter Consumer Key")
End If
End If

TwitterKey = pTwitterKey
End Property
Private Property Get TwitterSecret() As String
If pTwitterSecret = "" Then
pTwitterSecret = InputBox("Please Enter Twitter Consumer Secret")
If Credentials.Loaded Then
pTwitterSecret = Credentials.Values("Twitter")("secret")
Else
pTwitterSecret = InputBox("Please Enter Twitter Consumer Secret")
End If
End If

TwitterSecret = pTwitterSecret
Expand All @@ -38,22 +46,22 @@ End Property



Private Function SearchTweetsRequest(Query As String) As RestRequest
Private Function SearchTweetsRequest(query As String) As RestRequest
Set SearchTweetsRequest = New RestRequest
SearchTweetsRequest.Resource = "search/tweets.{format}"

SearchTweetsRequest.Format = json
SearchTweetsRequest.AddParameter "q", Query
SearchTweetsRequest.AddParameter "q", query
SearchTweetsRequest.AddParameter "lang", "en"
SearchTweetsRequest.AddParameter "count", 20
SearchTweetsRequest.Method = httpGET
End Function

Public Function SearchTwitter(Query As String) As RestResponse
Set SearchTwitter = TwitterClient.Execute(SearchTweetsRequest(Query))
Public Function SearchTwitter(query As String) As RestResponse
Set SearchTwitter = TwitterClient.Execute(SearchTweetsRequest(query))
End Function

Public Sub SearchTwitterAsync(Query As String, Callback As String)
TwitterClient.ExecuteAsync SearchTweetsRequest(Query), Callback
Public Sub SearchTwitterAsync(query As String, Callback As String)
TwitterClient.ExecuteAsync SearchTweetsRequest(query), Callback
End Sub

0 comments on commit e129301

Please sign in to comment.