1+ ''
2+ ' Install Excel-REST
3+ '
4+ ' Run: cscript install.vbs
5+ '
6+ ' (c) Tim Hall - https://github.com/timhall/Excel-REST
7+ ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
8+ Option Explicit
9+
10+ Dim Args
11+ Set Args = WScript.Arguments
12+
13+ Dim FSO
14+ Set FSO = CreateObject( "Scripting.FileSystemObject" )
15+ Dim Excel
16+ Dim ExcelWasOpen
17+ Set Excel = Nothing
18+
19+ Main
20+
21+ Sub Main()
22+ On Error Resume Next
23+
24+ Print "----------------------------------------------------------------" & vbNewLine & _
25+ "Excel-REST" & vbNewLine & vbNewLine & _
26+ "Welcome to the Excel-REST installer!" & vbNewLine & _
27+ "This will walk you through installing Excel-REST in your project" & vbNewLine & _
28+ "----------------------------------------------------------------" & vbNewLine
29+
30+ ExcelWasOpen = OpenExcel(Excel)
31+
32+ If Not Excel Is Nothing Then
33+ Install
34+ ElseIf Err.Number <> 0 Then
35+ Print "ERROR: Failed to open Excel" & vbNewLine & Err.Description
36+ End If
37+
38+ CloseExcel Excel, ExcelWasOpen
39+
40+ Input vbNewLine & "All Finished! Press Enter to exit..."
41+ End Sub
42+
43+ Sub Install
44+ Dim Path
45+ Path = Input( "In what Workbook that you would like to install Excel-REST?" & vbNewLine & "(e.g. C:\Users\Tim\DownloadStuff.xlsm)" )
46+ Path = FullPath(Path)
47+
48+ Dim Workbook
49+ Dim WorkbookWasOpen
50+ Set Workbook = Nothing
51+ WorkbookWasOpen = OpenWorkbook(Excel, Path, Workbook)
52+
53+ If Not Workbook Is Nothing Then
54+ ' TODO Install
55+ ElseIf Err.Number <> 0 Then
56+ Print "ERROR: Failed to open Workbook" & vbNewLine & Err.Description
57+ End If
58+
59+ CloseWorkbook Workbook, WorkbookWasOpen
60+ End Sub
61+
62+
63+ ''
64+ ' Excel helpers
65+ ' ------------------------------------ '
66+
67+ ''
68+ ' Open Workbook and return whether Workbook was already open
69+ '
70+ ' @param {Object} Excel
71+ ' @param {String} Path
72+ ' @param {Object} Workbook object to load Workbook into
73+ ' @return {Boolean} Workbook was already open
74+ Function OpenWorkbook(Excel, Path, ByRef Workbook)
75+ On Error Resume Next
76+
77+ Path = FullPath(Path)
78+ Set Workbook = Excel.Workbooks(GetFilename(Path))
79+
80+ If Workbook Is Nothing Or Err.Number <> 0 Then
81+ Err.Clear
82+
83+ If FileExists(Path) Then
84+ Set Workbook = Excel.Workbooks.Open(Path)
85+ Else
86+ Print "Workbook not found at " & Path
87+ ' TODO Create workbook if it doesn't exist
88+ 'Dim CreateWorkbook
89+ 'CreateWorkbook = Input("Workbook not found at " & Path & vbNewLine & "Would you like to create it, yes or no? (yes)")
90+ '
91+ 'If UCase(CreateWorkbook) = "YES" Or CreateWorkbook = "" Then
92+ ' Print "Create workbook..."
93+ 'End If
94+ End If
95+ OpenWorkbook = False
96+ Else
97+ OpenWorkbook = True
98+ End If
99+ End Function
100+
101+ ''
102+ ' Close Workbook and save changes
103+ ' (keep open without saving changes if previously open)
104+ '
105+ ' @param {Object} Workbook
106+ ' @param {Boolean} KeepWorkbookOpen
107+ Sub CloseWorkbook( ByRef Workbook, KeepWorkbookOpen)
108+ If Not KeepWorkbookOpen And Not Workbook Is Nothing Then
109+ Workbook.Close True
110+ End If
111+
112+ Set Workbook = Nothing
113+ End Sub
114+
115+ ''
116+ ' Open Excel and return whether Excel was already open
117+ '
118+ ' @param {Object} Excel object to load Excel into
119+ ' @return {Boolean} Excel was already open
120+ Function OpenExcel( ByRef Excel)
121+ On Error Resume Next
122+
123+ Set Excel = GetObject(, "Excel.Application" )
124+
125+ If Excel Is Nothing Or Err.Number <> 0 Then
126+ Err.Clear
127+
128+ Set Excel = CreateObject( "Excel.Application" )
129+ OpenExcel = False
130+ Else
131+ OpenExcel = True
132+ End If
133+ End Function
134+
135+ ''
136+ ' Close Excel (keep open if previously open)
137+ '
138+ ' @param {Object} Excel
139+ ' @param {Boolean} KeepExcelOpen
140+ Sub CloseExcel( ByRef Excel, KeepExcelOpen)
141+ If Not KeepExcelOpen And Not Excel Is Nothing Then
142+ Excel.Quit
143+ End If
144+
145+ Set Excel = Nothing
146+ End Sub
147+
148+ ''
149+ ' Filesystem helpers
150+ ' ------------------------------------ '
151+
152+ Function FullPath(Path)
153+ FullPath = FSO.GetAbsolutePathName(Path)
154+ End Function
155+
156+ Function GetFilename(Path)
157+ Dim Parts
158+ Parts = Split(Path, "\" )
159+
160+ GetFilename = Parts(UBound(Parts))
161+ End Function
162+
163+ Function RemoveExtension(Name)
164+ Dim Parts
165+ Parts = Split(Name, "." )
166+
167+ If UBound(Parts) > LBound(Parts) Then
168+ ReDim Preserve Parts(UBound(Parts) - 1 )
169+ End If
170+
171+ RemoveExtension = Join (Parts, "." )
172+ End Function
173+
174+ Function FileExists(Path)
175+ FileExists = FSO.FileExists(Path)
176+ End Function
177+
178+ ''
179+ ' General helpers
180+ ' ------------------------------------ '
181+
182+ Sub Print(Message)
183+ WScript.Echo Message
184+ End Sub
185+
186+ Function Input(Prompt)
187+ If Prompt <> "" Then
188+ WScript.StdOut.Write Prompt & " "
189+ End If
190+
191+ Input = WScript.StdIn.ReadLine
192+ End Function
0 commit comments