Skip to content

Commit 13edda5

Browse files
committed
Merge pull request #8 from timhall/refactor
Refactor
2 parents 0460f88 + 0f30e2e commit 13edda5

16 files changed

+1187
-540
lines changed

Excel-REST - Blank.xlsm

12.8 KB
Binary file not shown.

build/export-specs.vbs

Lines changed: 180 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,180 @@
1+
Option Explicit
2+
3+
Dim Args
4+
Dim WBPath
5+
Dim OutputPath
6+
Dim Excel
7+
Dim Workbook
8+
Dim Modules
9+
Dim ExcelWasOpen
10+
Dim WorkbookWasOpen
11+
12+
Set Args = Wscript.Arguments
13+
If Args.Length > 0 Then
14+
WBPath = Args(0)
15+
OutputPath = Args(1)
16+
End If
17+
18+
' Setup modules to export
19+
Modules = Array(_
20+
"RestClientSpecs.bas", _
21+
"RestClientAsyncSpecs.bas", _
22+
"RestRequestSpecs.bas", _
23+
"RestHelpersSpecs.bas", _
24+
"RestClientBaseSpecs.bas" _
25+
)
26+
27+
If WBPath <> "" And OutputPath <> "" Then
28+
WScript.Echo "Exporting Excel-REST specs from " & WBPath & " to " & OutputPath
29+
30+
ExcelWasOpen = OpenExcel(Excel)
31+
Excel.Visible = True
32+
Excel.DisplayAlerts = False
33+
34+
' Get workbook path relative to root Excel-REST project
35+
WBPath = FullPath(WBPath)
36+
OutputPath = FullPath(OutputPath)
37+
38+
If Right(OutputPath, 1) <> "\" Then
39+
OutputPath = OutputPath & "\"
40+
End If
41+
42+
' Open workbook
43+
WorkbookWasOpen = OpenWorkbook(Excel, WBPath, Workbook)
44+
45+
Dim i
46+
Dim Module
47+
For i = LBound(Modules) To UBound(Modules)
48+
Set Module = GetModule(Workbook, RemoveExtension(Modules(i)))
49+
50+
If Not Module Is Nothing Then
51+
Module.Export OutputPath & Modules(i)
52+
End If
53+
Next
54+
55+
CloseWorkbook Workbook, WorkbookWasOpen
56+
CloseExcel Excel, ExcelWasOpen
57+
58+
Set Workbook = Nothing
59+
Set Excel = Nothing
60+
End If
61+
62+
63+
''
64+
' Module helpers
65+
' ------------------------------------ '
66+
67+
Function RemoveModule(Workbook, Name)
68+
Dim Module
69+
Set Module = GetModule(Workbook, Name)
70+
71+
If Not Module Is Nothing Then
72+
Workbook.VBProject.VBComponents.Remove Module
73+
End If
74+
End Function
75+
76+
Function GetModule(Workbook, Name)
77+
Dim Module
78+
Set GetModule = Nothing
79+
80+
For Each Module In Workbook.VBProject.VBComponents
81+
If Module.Name = Name Then
82+
Set GetModule = Module
83+
Exit Function
84+
End If
85+
Next
86+
End Function
87+
88+
Sub ImportModule(Workbook, Folder, Filename)
89+
If VarType(Workbook) = vbObject Then
90+
RemoveModule Workbook, RemoveExtension(Filename)
91+
Workbook.VBProject.VBComponents.Import FullPath(Folder & Filename)
92+
End If
93+
End Sub
94+
95+
Sub ImportModules(Workbook, Folder, Filenames)
96+
Dim i
97+
For i = LBound(Filenames) To UBound(Filenames)
98+
ImportModule Workbook, Folder, Filenames(i)
99+
Next
100+
End Sub
101+
102+
103+
''
104+
' Excel helpers
105+
' ------------------------------------ '
106+
107+
Function OpenWorkbook(Excel, Path, ByRef Workbook)
108+
On Error Resume Next
109+
110+
Set Workbook = Excel.Workbooks(GetFilename(Path))
111+
112+
If Workbook Is Nothing Or Err.Number <> 0 Then
113+
Set Workbook = Excel.Workbooks.Open(Path)
114+
OpenWorkbook = False
115+
Else
116+
OpenWorkbook = True
117+
End If
118+
119+
Err.Clear
120+
End Function
121+
122+
Function OpenExcel(Excel)
123+
On Error Resume Next
124+
125+
Set Excel = GetObject(, "Excel.Application")
126+
127+
If Excel Is Nothing Or Err.Number <> 0 Then
128+
Set Excel = CreateObject("Excel.Application")
129+
OpenExcel = False
130+
Else
131+
OpenExcel = True
132+
End If
133+
134+
Err.Clear
135+
End Function
136+
137+
Sub CloseWorkbook(ByRef Workbook, KeepWorkbookOpen)
138+
If Not KeepWorkbookOpen And VarType(Workbook) = vbObject Then
139+
Workbook.Close True
140+
End If
141+
142+
Set Workbook = Nothing
143+
End Sub
144+
145+
Sub CloseExcel(ByRef Excel, KeepExcelOpen)
146+
If Not KeepExcelOpen Then
147+
Excel.Quit
148+
End If
149+
150+
Set Excel = Nothing
151+
End Sub
152+
153+
154+
''
155+
' Filesystem helpers
156+
' ------------------------------------ '
157+
158+
Function FullPath(Path)
159+
Dim FSO
160+
Set FSO = CreateObject("Scripting.FileSystemObject")
161+
FullPath = FSO.GetAbsolutePathName(Path)
162+
End Function
163+
164+
Function GetFilename(Path)
165+
Dim Parts
166+
Parts = Split(Path, "\")
167+
168+
GetFilename = Parts(UBound(Parts))
169+
End Function
170+
171+
Function RemoveExtension(Name)
172+
Dim Parts
173+
Parts = Split(Name, ".")
174+
175+
If UBound(Parts) > LBound(Parts) Then
176+
ReDim Preserve Parts(UBound(Parts) - 1)
177+
End If
178+
179+
RemoveExtension = Join(Parts, ".")
180+
End Function

build/export.vbs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,8 @@ Modules = Array(_
2121
"IAuthenticator.cls", _
2222
"RestClient.cls", _
2323
"RestRequest.cls", _
24-
"RestResponse.cls" _
24+
"RestResponse.cls", _
25+
"RestClientBase.bas" _
2526
)
2627

2728
If WBPath <> "" And OutputPath <> "" Then

examples/Excel-REST - Example.xlsm

-339 Bytes
Binary file not shown.

0 commit comments

Comments
 (0)