Skip to content

Commit 923268a

Browse files
authored
Merge pull request #2 from ws-garcia/VBA-Expressions-v2.0.0
Vba expressions v2.0.0
2 parents 72cf98f + 90c23c5 commit 923268a

File tree

6 files changed

+2259
-269
lines changed

6 files changed

+2259
-269
lines changed

README.md

Lines changed: 16 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -2,15 +2,17 @@
22
[![GitHub](https://img.shields.io/github/license/ws-garcia/VBA-Expressions?style=plastic)](https://github.com/ws-garcia/VBA-Expressions/blob/master/LICENSE) [![GitHub release (latest by date)](https://img.shields.io/github/v/release/ws-garcia/VBA-Expressions?style=plastic)](https://github.com/ws-garcia/VBA-Expressions/releases/latest)
33

44
## Introductory words
5-
VBA Expressions is a powerful string expressions evaluator for VBA, focused on mathematical ones. The `VBAexpressions.cls` class serves as an intermediary between user interfaces and the main VBA/custom functions exposed through it. The main development goal of the class is to integrate it with [CSV Interface](https://github.com/ws-garcia/VBA-CSV-interface), with as minimal programming effort as possible, and to allow users to perform complex queries from CSV files using built-in and custom functions.
5+
VBA Expressions is a powerful string expression evaluator for VBA, which puts more than 60 mathematical, financial, date-time, logic and text manipulation functions at the user's fingertips. The `VBAexpressions.cls` class mediates almost all VBA functions as well as custom functions exposed through it.
6+
7+
Although the main development goal of the class was the integration with [CSV Interface](https://github.com/ws-garcia/VBA-CSV-interface), VBA Expressions has evolved to become a support tool for students and teachers of science, accounting and engineering; this due to the added capability to solve systems of equations and non-linear equations in one variable.
68

79
## Advantages
810
* __Easy to use and integrate__.
911
* __Basic math operators__: `+` `-` `*` `/` `\` `^` `!`
1012
* __Logical expressions__: `&` (AND), `|` (OR), `||` (XOR)
1113
* __Binary relations__: `<`, `<=`, `<>`, `>=`, `=`, `>`, `$` (LIKE)
12-
* __More than 20 built-in functions__: `Max`, `Min`, `Avg`, `Sin`, `Ceil`, `Floor`...
13-
* __Very flexible__: variables, constants and user-defined functions (UDFs) support.
14+
* __More than 60 built-in functions__: `Max`, `Sin`, `IRR`, `Switch`, `Iff`, `DateDiff`, `Solve`, `fZero`, `Format`...
15+
* __Very flexible and powerful__: variables, constants and user-defined functions (UDFs) support.
1416
* __Implied multiplication for variables, constants and functions__: `5avg(2;abs(-3-7tan(5));9)` is valid expression; `5(2)` is not.
1517
* __Evaluation of arrays of expressions given as text strings, as in Java__: curly brackets must be used to define arrays`{{...};{...}}`
1618
* __Floating point notation input support__: `-5E-5`, `(1.434E3+1000)*2/3.235E-5` are valid inputs.
@@ -92,19 +94,11 @@ Sub AddingNewFunctions()
9294
End Sub
9395
```
9496
## Working with arrays
95-
VBA expressions can evaluate matrix functions whose arguments are given as arrays/vectors, using a syntax like [Java](https://www.w3schools.com/java/java_arrays_multi.asp). The following expression will calculate the determinant (`DET`) of a matrix composed of 3 vectors with 3 elements each:
96-
97-
`DET({{(sin(atn(1)*2)); 0; 0}; {0; 2; 0}; {0; 0; 3}})`
98-
99-
If the user needs to evaluate a function that accepts more than one argument, including more than one array, all arrays arguments must be passed surrounded by parentheses "({...})". For example, a function call that emulates the SQL IN statement using an array argument and a reference value can be written as follows.
100-
101-
`IN_(({{(sin(atn(1)*2)); 2; 3; 4; 5}});1)`
102-
103-
The above will pass this array of strings to the `IN_` function:
97+
VBA expressions can evaluate matrix functions whose arguments are given as arrays/vectors, using a syntax like [Java](https://www.w3schools.com/java/java_arrays.asp). The following expression will calculate, and format to percentage, the internal rate of return (`IRR`) of a cash flow described using a one dimensional array with 5 entries:
10498

105-
`[{{1;2;3;4;5}}] [1]`
99+
`FORMAT(IRR({{-70000;12000;15000;18000;21000}});'Percent')`
106100

107-
However, matrix functions need to take care of creating arrays from a string, the ArrayFromString method can be used for this purpose.
101+
However, user-defined array functions need to take care of creating arrays from a string, the `ArrayFromString` method can be used for this purpose.
108102

109103
As an illustration, the `UDFunctions.cls` module has an implementation of the `DET` function with an example of using the array handle function. In addition, the `GCD` function is implemented as a demo.
110104

@@ -143,8 +137,8 @@ Sub EarlyVariableAssignment()
143137
If .ReadyToEval Then
144138
Debug.Print "Variables: "; .CurrentVariables
145139
.VarValue("Pi.e") = 1
146-
.VarValue("Pie.1") = 2
147-
.VarValue("Pie") = 3
140+
.ImplicitVarValue("Pie.1") = "2*Pi.e"
141+
.ImplicitVarValue("Pie") = "Pie.1/3"
148142
.Eval
149143
Debug.Print .Expression; " = "; .Result; _
150144
"; for: "; .CurrentVarValues
@@ -162,22 +156,22 @@ Sub TrigFunctions()
162156
End If
163157
End With
164158
End Sub
165-
Sub StringComp()
159+
Sub StringFunctions()
166160
Dim Evaluator As VBAexpressions
167161
Set Evaluator = New VBAexpressions
168162
169163
With Evaluator
170-
.Create "Region = 'Central America'" 'Create a expression with `Region` as variable
171-
.Eval ("Region = 'Asia'") 'Assign value to variable and then evaluate
164+
.Create "CONCAT(CHOOSE(1;x;'2nd';'3th';'4th';'5th');'Element';'selected';'/')"
165+
.Eval ("x='1st'")
172166
End With
173167
End Sub
174-
Sub CompareUsingLikeOperator()
168+
Sub LogicalFunctions()
175169
Dim Evaluator As VBAexpressions
176170
Set Evaluator = New VBAexpressions
177171
178172
With Evaluator
179-
.Create "Region $ 'C?????? *a'" 'Create using the LIKE operator ($) and with `Region` as variable
180-
.Eval("Region = 'Central America'") 'This will be evaluated to TRUE
173+
.Create "IFF(x > y & x > 0; x; y)"
174+
.Eval("x=70;y=15") 'This will be evaluated to 70
181175
End With
182176
End Sub
183177
```

src/Tests/TestRunner.bas

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ Private Function GetResult(Expression As String _
4646
End With
4747
End Function
4848

49-
'@TestMethod("VBA Expressions")
49+
'@TestMethod("General")
5050
Private Sub Parentheses()
5151
On Error GoTo TestFail
5252

@@ -62,7 +62,7 @@ TestFail:
6262
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
6363
Resume TestExit
6464
End Sub
65-
'@TestMethod("VBA Expressions")
65+
'@TestMethod("General")
6666
Private Sub ParenthesesAndSingleFunction()
6767
On Error GoTo TestFail
6868

@@ -78,7 +78,7 @@ TestFail:
7878
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
7979
Resume TestExit
8080
End Sub
81-
'@TestMethod("VBA Expressions")
81+
'@TestMethod("General")
8282
Private Sub FunctionsWithMoreThanOneArgument()
8383
On Error GoTo TestFail
8484

@@ -94,7 +94,7 @@ TestFail:
9494
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
9595
Resume TestExit
9696
End Sub
97-
'@TestMethod("VBA Expressions")
97+
'@TestMethod("General")
9898
Private Sub NestedFunctions()
9999
On Error GoTo TestFail
100100

@@ -111,7 +111,7 @@ TestFail:
111111
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
112112
Resume TestExit
113113
End Sub
114-
'@TestMethod("VBA Expressions")
114+
'@TestMethod("General")
115115
Private Sub FloatingPointArithmetic()
116116
On Error GoTo TestFail
117117

@@ -127,7 +127,7 @@ TestFail:
127127
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
128128
Resume TestExit
129129
End Sub
130-
'@TestMethod("VBA Expressions")
130+
'@TestMethod("General")
131131
Private Sub ExponentiationPrecedence()
132132
On Error GoTo TestFail
133133

@@ -143,7 +143,7 @@ TestFail:
143143
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
144144
Resume TestExit
145145
End Sub
146-
'@TestMethod("VBA Expressions")
146+
'@TestMethod("General")
147147
Private Sub Factorials()
148148
On Error GoTo TestFail
149149

@@ -159,7 +159,7 @@ TestFail:
159159
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
160160
Resume TestExit
161161
End Sub
162-
'@TestMethod("VBA Expressions")
162+
'@TestMethod("General")
163163
Private Sub Precedence()
164164
On Error GoTo TestFail
165165

@@ -175,7 +175,7 @@ TestFail:
175175
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
176176
Resume TestExit
177177
End Sub
178-
'@TestMethod("VBA Expressions")
178+
'@TestMethod("General")
179179
Private Sub Variables()
180180
On Error GoTo TestFail
181181

@@ -192,7 +192,7 @@ TestFail:
192192
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
193193
Resume TestExit
194194
End Sub
195-
'@TestMethod("VBA Expressions")
195+
'@TestMethod("General")
196196
Private Sub UDFsAndArrays()
197197
On Error GoTo TestFail
198198
'///////////////////////////////////////////////////////////////////////////////////
@@ -218,7 +218,7 @@ TestFail:
218218
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
219219
Resume TestExit
220220
End Sub
221-
'@TestMethod("VBA Expressions")
221+
'@TestMethod("General")
222222
Private Sub LogicalOperatorsNumericOutput()
223223
On Error GoTo TestFail
224224

@@ -235,7 +235,7 @@ TestFail:
235235
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
236236
Resume TestExit
237237
End Sub
238-
'@TestMethod("VBA Expressions")
238+
'@TestMethod("General")
239239
Private Sub TestLogicalOperatorsBooleanOutput()
240240
On Error GoTo TestFail
241241

@@ -252,7 +252,7 @@ TestFail:
252252
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
253253
Resume TestExit
254254
End Sub
255-
'@TestMethod("VBA Expressions")
255+
'@TestMethod("General")
256256
Private Sub TestTrigFunctions()
257257
On Error GoTo TestFail
258258

@@ -268,7 +268,7 @@ TestFail:
268268
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
269269
Resume TestExit
270270
End Sub
271-
'@TestMethod("VBA Expressions")
271+
'@TestMethod("General")
272272
Private Sub TestModFunction()
273273
On Error GoTo TestFail
274274

@@ -284,7 +284,7 @@ TestFail:
284284
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
285285
Resume TestExit
286286
End Sub
287-
'@TestMethod("VBA Expressions")
287+
'@TestMethod("General")
288288
Private Sub testStringComp()
289289
On Error GoTo TestFail
290290

src/UDFunctions.cls

Lines changed: 13 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ Attribute VB_Name = "UDFunctions"
66
Attribute VB_GlobalNameSpace = False
77
Attribute VB_Creatable = False
88
Attribute VB_PredeclaredId = False
9-
Attribute VB_Exposed = False
9+
Attribute VB_Exposed = True
1010
Option Explicit
1111
'#
1212
'////////////////////////////////////////////////////////////////////////////////////////////
@@ -17,13 +17,12 @@ Option Explicit
1717
'#
1818
' GENERAL INFO:
1919
' Class module developed to provide samples of user defined functions (UDF).
20-
2120
Private Const Apostrophe As String = "'"
21+
2222
Public Function GCD(ByRef aValues As Variant) As Long 'Expected an array
2323
Dim t As Long
2424
Dim u As Long
2525
Dim v As Long
26-
Dim args(0 To 1) As Variant
2726
Static RecursionLevel As Long
2827

2928
RecursionLevel = RecursionLevel + 1
@@ -62,11 +61,13 @@ Private Function minor(a() As Double, x As Integer, y As Integer) As Double()
6261
End Function
6362

6463
'Adapted from: https://rosettacode.org/wiki/Determinant_and_permanent#VBA
65-
Public Function DET(StrArray As Variant) As Double 'Expected an one element string array
64+
Public Function DET(strArray As Variant) As Double 'Expected an one element string array
6665
Dim a() As Double
6766
Dim ArrayHelper As New VBAexpressions
6867

69-
a() = StringTodblArray(ArrayHelper.ArrayFromString(CStr(StrArray(LBound(StrArray)))))
68+
With ArrayHelper
69+
a() = .StringTodblArray(.ArrayFromString(CStr(strArray(LBound(strArray)))))
70+
End With
7071
DET = DET_(a)
7172
End Function
7273

@@ -88,24 +89,7 @@ Private Function DET_(a() As Double) As Double
8889
err:
8990
DET_ = a(1)
9091
End Function
91-
'Gets an array from a string like "{{1;2;3};{4;5;6};{7;8;9}}"
92-
Private Function StringTodblArray(ByRef StringArray() As String) As Double()
93-
Dim i As Long, LB As Long, UB As Long
94-
Dim j As Long, LB2 As Long, UB2 As Long
95-
Dim tmpResult() As Double
96-
97-
LB = LBound(StringArray)
98-
UB = UBound(StringArray)
99-
LB2 = LBound(StringArray, 2)
100-
UB2 = UBound(StringArray, 2)
101-
ReDim tmpResult(LB To UB, LB2 To UB2)
102-
For i = LB To UB
103-
For j = LB2 To UB2
104-
tmpResult(i, j) = CDbl(StringArray(i, j))
105-
Next j
106-
Next i
107-
StringTodblArray = tmpResult
108-
End Function
92+
10993
''' <summary>
11094
''' List is expected to be an array. The last element will be used as
11195
''' the concatenation string.
@@ -122,9 +106,15 @@ Public Function Concat(List As Variant) As String
122106
joinString = MidB$(List(endIdx), 3, LenB(List(endIdx)) - 4)
123107
tmpResult = MidB$(List(startIdx), 3, LenB(List(startIdx)) - 4)
124108
For i = startIdx + 1 To endIdx - 1
109+
If AscW(List(i)) = 39 Then ' [']
125110
tmpResult = tmpResult & _
126111
joinString & _
127112
MidB$(List(i), 3, LenB(List(i)) - 4)
113+
Else
114+
tmpResult = tmpResult & _
115+
joinString & _
116+
List(i)
117+
End If
128118
Next i
129119
Concat = Apostrophe & tmpResult & Apostrophe
130120
End Function

src/VBAcallBack.cls

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ Attribute VB_Name = "VBAcallBack"
66
Attribute VB_GlobalNameSpace = False
77
Attribute VB_Creatable = False
88
Attribute VB_PredeclaredId = False
9-
Attribute VB_Exposed = False
9+
Attribute VB_Exposed = True
1010
Option Explicit
1111
'#
1212
'////////////////////////////////////////////////////////////////////////////////////////////

0 commit comments

Comments
 (0)