Skip to content

Commit 91a7362

Browse files
committed
Update install script
1 parent 9e15a52 commit 91a7362

File tree

2 files changed

+89
-58
lines changed

2 files changed

+89
-58
lines changed

build/dev.vbs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ Sub Development
9999
"- release"
100100

101101
Dim Action
102-
Action = Input(vbNewLine & "What would you like to do? >")
102+
Action = Input(vbNewLine & "What would you like to do? <")
103103

104104
If Action = "" Then
105105
Exit Sub
@@ -140,7 +140,7 @@ Sub Development
140140
End If
141141
End If
142142

143-
If UCase(Left(Input(vbNewLine & "Would you like to do anything else? [yes/no] >"), 1)) = "Y" Then
143+
If UCase(Left(Input(vbNewLine & "Would you like to do anything else? [yes/no] <"), 1)) = "Y" Then
144144
Development
145145
End If
146146
End Sub
@@ -291,7 +291,7 @@ Function OpenWorkbook(Excel, Path, ByRef Workbook)
291291
Else
292292
Path = Input(vbNewLine & _
293293
"Workbook not found at " & Path & vbNewLine & _
294-
"Would you like to try another location? [path.../cancel]")
294+
"Would you like to try another location? [path.../cancel] <")
295295

296296
If UCase(Path) <> "CANCEL" And Path <> "" Then
297297
OpenWorkbook = OpenWorkbook(Excel, Path, Workbook)
@@ -496,7 +496,7 @@ End Sub
496496

497497
Function Input(Prompt)
498498
If Prompt <> "" Then
499-
WScript.StdOut.Write Prompt & " "
499+
Print Prompt & " "
500500
End If
501501

502502
Input = WScript.StdIn.ReadLine

build/install.vbs

Lines changed: 85 additions & 54 deletions
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ Main
5555
Sub Main()
5656
On Error Resume Next
5757

58-
Print "Welcome to Excel-REST v3.1.0, let's get started!"
58+
PrintLn "Welcome to Excel-REST v3.1.0, let's get started!"
5959

6060
ExcelWasOpen = OpenExcel(Excel)
6161

@@ -64,60 +64,86 @@ Sub Main()
6464

6565
CloseExcel Excel, ExcelWasOpen
6666
ElseIf Err.Number <> 0 Then
67-
Print vbNewLine & "ERROR: Failed to open Excel" & vbNewLine & Err.Description
67+
PrintLn vbNewLine & "ERROR: Failed to open Excel" & vbNewLine & Err.Description
6868
End If
6969

7070
Input vbNewLine & "All finished, thanks for using Excel-REST! Press any key to exit..."
7171
End Sub
7272

7373
Sub Install
74-
Dim Success
7574
Path = Input(vbNewLine & _
76-
"In what Workbook would you like to install or update Excel-REST?" & vbNewLine & _
77-
"(e.g. C:\Users\Tim\DownloadStuff.xlsm)")
75+
"In what Workbook would you like to install Excel-REST?" & vbNewLine & _
76+
"(e.g. C:\Users\...\DownloadStuff.xlsm) <")
7877
Path = FullPath(Path)
7978

8079
WorkbookWasOpen = OpenWorkbook(Excel, Path, Workbook)
8180

8281
If Not Workbook Is Nothing Then
8382
If Not VBAIsTrusted(Workbook) Then
84-
Print vbNewLine & _
83+
PrintLn vbNewLine & _
8584
"ERROR: In order to install Excel-REST," & vbNewLine & _
8685
"access to the VBA project object model needs to be trusted in Excel." & vbNewLine & vbNewLine & _
8786
"To enable:" & vbNewLine & _
8887
"Options > Trust Center > Trust Center Settings > Macro Settings > " & vbnewLine & _
8988
"Trust access to the VBA project object model"
9089
Else
91-
If Not AlreadyInstalled(Workbook) Then
92-
Success = InstallModules
93-
Else
94-
Dim ShouldUpgrade
95-
ShouldUpgrade = Input(vbNewLine & "Excel-REST appears to already be installed." & vbNewLine & vbNewLine & _
96-
"Warning: The currently installed Excel-REST files will be removed" & vbNewLine & _
97-
"and any previously made changes to those files will be lost" & vbNewLine & vbNewLine & _
98-
"Would you like to upgrade to v3.1.0? [yes/no]")
99-
100-
If UCase(ShouldUpgrade) = "YES" Then
101-
Success = InstallModules
102-
Else
103-
Success = True
104-
End If
105-
End If
106-
End If
107-
108-
If Success Then
109-
If UCase(Input(vbNewLine & "Would you like to install an authenticator (e.g. OAuth2)? [yes/no]")) = "YES" Then
110-
InstallAuthenticator
111-
End If
90+
Execute
11291
End If
11392

11493
CloseWorkbook Workbook, WorkbookWasOpen
11594

116-
If UCase(Input(vbNewLine & "Would you like to install Excel-REST in another Workbook? [yes/no]")) = "YES" Then
95+
If UCase(Input(vbNewLine & "Would you like to install Excel-REST in another Workbook? [yes/no] <")) = "YES" Then
11796
Install
11897
End If
11998
ElseIf Err.Number <> 0 Then
120-
Print vbNewLine & "ERROR: Failed to open Workbook" & vbNewLine & Err.Description
99+
PrintLn vbNewLine & "ERROR: Failed to open Workbook" & vbNewLine & Err.Description
100+
End If
101+
End Sub
102+
103+
Sub Execute()
104+
Dim Message
105+
Message = "Options:" & vbNewLine
106+
107+
Dim InstallMessage
108+
If AlreadyInstalled(Workbook) Then
109+
Message = Message & "(It appears Excel-REST is already installed)" & vbNewLine
110+
Message = Message & "- upgrade - Upgrade to Excel-REST v3.1.0" & vbNewLine
111+
Else
112+
Message = Message & "- install - Install Excel-REST v3.1.0" & vbNewLine
113+
End If
114+
115+
Message = Message & "- auth - Install authenticator"
116+
PrintLn Message
117+
118+
Dim Action
119+
Action = Input(vbNewLine & "What would you like to do? <")
120+
121+
' Ensure upgrade is used if already installed
122+
If UCase(Action) = "INSTALL" And AlreadyInstalled(Workbook) Then
123+
Action = "upgrade"
124+
End If
125+
126+
Select Case UCase(Action)
127+
Case "INSTALL"
128+
InstallModules
129+
Case "UPGRADE"
130+
Dim ShouldUpgrade
131+
ShouldUpgrade = Input(vbNewLine & _
132+
"Warning: The currently installed Excel-REST files will be removed" & vbNewLine & _
133+
"and any previously made changes to those files will be lost" & vbNewLine & vbNewLine & _
134+
"Would you like to upgrade to v3.1.0? [yes/no] <")
135+
136+
If Left(UCase(ShouldUpgrade), 1) = "Y" Then
137+
InstallModules
138+
End If
139+
CASE "AUTH"
140+
InstallAuthenticator
141+
Case Else
142+
Exit Sub
143+
End Select
144+
145+
If UCase(Left(Input(vbNewLine & "Would you like to do anything else? [yes/no] <"), 1)) = "Y" Then
146+
Execute
121147
End If
122148
End Sub
123149

@@ -129,24 +155,25 @@ Function InstallModules
129155
Dim Backups
130156
ReDim Backups(UBound(Modules))
131157

132-
WScript.StdOut.Write vbNewLine & "Installing Excel-REST..."
158+
Print vbNewLine & "Installing Excel-REST"
133159

134160
For i = LBound(Modules) To UBound(Modules)
135161
' Check for existing module and create backup if found
136162
Set Backups(i) = BackupModule(Workbook, RemoveExtension(Modules(i)), "backup__")
137163

138164
If Err.Number <> 0 Then
139-
WScript.StdOut.Write "ERROR" & vbNewLine
140-
Print "Failed to backup previous version of Excel-REST" & vbNewLine & _
165+
Print "ERROR" & vbNewLine
166+
PrintLn "Failed to backup previous version of Excel-REST" & vbNewLine & _
141167
"Please manually remove any existing Excel-REST files and try again"
142168
Exit For
143169
Else
144170
' Import module
145171
ImportModule Workbook, ModulesFolder, Modules(i)
172+
Print "."
146173

147174
If Err.Number <> 0 Then
148-
WScript.StdOut.Write "ERROR" & vbNewLine
149-
Print "Failed to install new version of Excel-REST" & vbNewLine & _
175+
Print "ERROR" & vbNewLine
176+
PrintLn "Failed to install new version of Excel-REST" & vbNewLine & _
150177
"Any existing Excel-REST files will be now be attempted to be restored."
151178
Exit For
152179
End If
@@ -169,17 +196,17 @@ Function InstallModules
169196
Next
170197

171198
If Err.Number <> 0 Then
172-
WScript.StdOut.Write "ERROR" & vbNewLine
173-
Print "Excel-REST installed correctly," & vbNewLine & _
199+
Print "ERROR" & vbNewLine
200+
PrintLn "Excel-REST installed correctly," & vbNewLine & _
174201
"but failed to remove backups of the previous version" & vbNewLine & vbNewLine & _
175202
"It is safe to remove these files manually (backup__...)"
176203
End If
177204
End If
178205

179206
If Err.Number = 0 Then
180-
WScript.StdOut.Write "Done!" & vbNewLine
207+
Print "Done!" & vbNewLine
181208

182-
Print "To complete installation of Excel-REST," & vbNewLine & _
209+
PrintLn "To complete installation of Excel-REST," & vbNewLine & _
183210
"a reference to Microsoft Scripting Runtime needs to added:" & vbNewLine & vbNewLine & _
184211
"From VBA, Tools > References > Select 'Microsoft Scripting Runtime'"
185212

@@ -200,26 +227,26 @@ Sub InstallAuthenticator
200227
Message = Message & vbNewLine & "- " & Replace(RemoveExtension(Authenticators(i)), "Authenticator", "")
201228
Next
202229

203-
Install = Input(Message & vbNewLine & "[authenticator.../cancel]")
230+
Install = Input(Message & vbNewLine & "[authenticator.../cancel] <")
204231
If Install <> "" And UCase(Install) <> "CANCEL" Then
205232
For i = LBound(Authenticators) To UBound(Authenticators)
206233
If UCase(Install) = UCase(Replace(RemoveExtension(Authenticators(i)), "Authenticator", "")) Then
207-
WScript.StdOut.Write vbNewLine & "Installing " & Authenticators(i) & "..."
234+
Print vbNewLine & "Installing " & Authenticators(i) & "..."
208235

209236
Set Backup = BackupModule(Workbook, Authenticators(i), "backup__")
210237

211238
If Err.Number <> 0 Then
212239
Err.Clear
213-
WScript.StdOut.Write "ERROR" & vbNewLine
214-
Print "Failed to backup previous version of " & Authenticators(i) & vbNewLine & _
240+
Print "ERROR" & vbNewLine
241+
PrintLn "Failed to backup previous version of " & Authenticators(i) & vbNewLine & _
215242
"Please manually remove it and try again"
216243
Else
217244
ImportModule Workbook, AuthenticatorsFolder, Authenticators(i)
218245

219246
If Err.Number <> 0 Then
220247
Err.Clear
221-
WScript.StdOut.Write "ERROR" & vbNewLine
222-
Print "Failed to install new version of " & Authenticators(i) & vbNewLine & Err.Description
248+
Print "ERROR" & vbNewLine
249+
PrintLn "Failed to install new version of " & Authenticators(i) & vbNewLine & Err.Description
223250

224251
RestoreModule Workbook, Authenticators(i), "backup__"
225252
Else
@@ -228,16 +255,16 @@ Sub InstallAuthenticator
228255
End If
229256

230257
If Err.Number <> 0 Then
231-
WScript.StdOut.Write "ERROR" & vbNewLine
232-
Print "Authenticator installed correctly," & vbNewLine & _
258+
Print "ERROR" & vbNewLine
259+
PrintLn "Authenticator installed correctly," & vbNewLine & _
233260
"but failed to remove the backup of the previous version" & vbNewLine & vbNewLine & _
234261
"It is safe to remove this file manually (backup__...)"
235262
Else
236-
WScript.StdOut.Write "Done!" & vbNewLine
237-
Another = Input(vbNewLine & "Would you like to install another authenticator? [yes/no]")
238-
If UCase(Another) = "YES" Then
239-
InstallAuthenticator
240-
End If
263+
Print "Done!" & vbNewLine
264+
' Another = Input(vbNewLine & "Would you like to install another authenticator? [yes/no] <")
265+
' If UCase(Another) = "YES" Then
266+
' InstallAuthenticator
267+
' End If
241268
End If
242269
End If
243270
End If
@@ -283,7 +310,7 @@ Function OpenWorkbook(Excel, Path, ByRef Workbook)
283310
Else
284311
Path = Input(vbNewLine & _
285312
"Workbook not found at " & Path & vbNewLine & _
286-
"Would you like to try another location? [path.../cancel]")
313+
"Would you like to try another location? [path.../cancel] <")
287314

288315
If UCase(Path) <> "CANCEL" And Path <> "" Then
289316
OpenWorkbook = OpenWorkbook(Excel, Path, Workbook)
@@ -479,12 +506,16 @@ End Function
479506
' ------------------------------------ '
480507

481508
Sub Print(Message)
482-
WScript.Echo Message
509+
WScript.StdOut.Write Message
510+
End Sub
511+
512+
Sub PrintLn(Message)
513+
WScript.Echo Message
483514
End Sub
484515

485516
Function Input(Prompt)
486517
If Prompt <> "" Then
487-
WScript.StdOut.Write Prompt & " "
518+
Print Prompt & " "
488519
End If
489520

490521
Input = WScript.StdIn.ReadLine

0 commit comments

Comments
 (0)