Skip to content

Commit

Permalink
Merge pull request #2 from ws-garcia/VBA-Expressions-v2.0.0
Browse files Browse the repository at this point in the history
Vba expressions v2.0.0
  • Loading branch information
ws-garcia authored Oct 9, 2022
2 parents 72cf98f + 90c23c5 commit 923268a
Show file tree
Hide file tree
Showing 6 changed files with 2,259 additions and 269 deletions.
38 changes: 16 additions & 22 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,15 +2,17 @@
[![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)

## Introductory words
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.
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.

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.

## Advantages
* __Easy to use and integrate__.
* __Basic math operators__: `+` `-` `*` `/` `\` `^` `!`
* __Logical expressions__: `&` (AND), `|` (OR), `||` (XOR)
* __Binary relations__: `<`, `<=`, `<>`, `>=`, `=`, `>`, `$` (LIKE)
* __More than 20 built-in functions__: `Max`, `Min`, `Avg`, `Sin`, `Ceil`, `Floor`...
* __Very flexible__: variables, constants and user-defined functions (UDFs) support.
* __More than 60 built-in functions__: `Max`, `Sin`, `IRR`, `Switch`, `Iff`, `DateDiff`, `Solve`, `fZero`, `Format`...
* __Very flexible and powerful__: variables, constants and user-defined functions (UDFs) support.
* __Implied multiplication for variables, constants and functions__: `5avg(2;abs(-3-7tan(5));9)` is valid expression; `5(2)` is not.
* __Evaluation of arrays of expressions given as text strings, as in Java__: curly brackets must be used to define arrays`{{...};{...}}`
* __Floating point notation input support__: `-5E-5`, `(1.434E3+1000)*2/3.235E-5` are valid inputs.
Expand Down Expand Up @@ -92,19 +94,11 @@ Sub AddingNewFunctions()
End Sub
```
## Working with arrays
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:

`DET({{(sin(atn(1)*2)); 0; 0}; {0; 2; 0}; {0; 0; 3}})`

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.

`IN_(({{(sin(atn(1)*2)); 2; 3; 4; 5}});1)`

The above will pass this array of strings to the `IN_` function:
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:

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

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

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.

Expand Down Expand Up @@ -143,8 +137,8 @@ Sub EarlyVariableAssignment()
If .ReadyToEval Then
Debug.Print "Variables: "; .CurrentVariables
.VarValue("Pi.e") = 1
.VarValue("Pie.1") = 2
.VarValue("Pie") = 3
.ImplicitVarValue("Pie.1") = "2*Pi.e"
.ImplicitVarValue("Pie") = "Pie.1/3"
.Eval
Debug.Print .Expression; " = "; .Result; _
"; for: "; .CurrentVarValues
Expand All @@ -162,22 +156,22 @@ Sub TrigFunctions()
End If
End With
End Sub
Sub StringComp()
Sub StringFunctions()
Dim Evaluator As VBAexpressions
Set Evaluator = New VBAexpressions
With Evaluator
.Create "Region = 'Central America'" 'Create a expression with `Region` as variable
.Eval ("Region = 'Asia'") 'Assign value to variable and then evaluate
.Create "CONCAT(CHOOSE(1;x;'2nd';'3th';'4th';'5th');'Element';'selected';'/')"
.Eval ("x='1st'")
End With
End Sub
Sub CompareUsingLikeOperator()
Sub LogicalFunctions()
Dim Evaluator As VBAexpressions
Set Evaluator = New VBAexpressions
With Evaluator
.Create "Region $ 'C?????? *a'" 'Create using the LIKE operator ($) and with `Region` as variable
.Eval("Region = 'Central America'") 'This will be evaluated to TRUE
.Create "IFF(x > y & x > 0; x; y)"
.Eval("x=70;y=15") 'This will be evaluated to 70
End With
End Sub
```
Expand Down
30 changes: 15 additions & 15 deletions src/Tests/TestRunner.bas
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ Private Function GetResult(Expression As String _
End With
End Function

'@TestMethod("VBA Expressions")
'@TestMethod("General")
Private Sub Parentheses()
On Error GoTo TestFail

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

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

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

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

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

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

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

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

Expand All @@ -192,7 +192,7 @@ TestFail:
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
Resume TestExit
End Sub
'@TestMethod("VBA Expressions")
'@TestMethod("General")
Private Sub UDFsAndArrays()
On Error GoTo TestFail
'///////////////////////////////////////////////////////////////////////////////////
Expand All @@ -218,7 +218,7 @@ TestFail:
Assert.Fail "Test raised an error: #" & err.Number & " - " & err.Description
Resume TestExit
End Sub
'@TestMethod("VBA Expressions")
'@TestMethod("General")
Private Sub LogicalOperatorsNumericOutput()
On Error GoTo TestFail

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

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

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

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

Expand Down
36 changes: 13 additions & 23 deletions src/UDFunctions.cls
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ Attribute VB_Name = "UDFunctions"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Attribute VB_Exposed = True
Option Explicit
'#
'////////////////////////////////////////////////////////////////////////////////////////////
Expand All @@ -17,13 +17,12 @@ Option Explicit
'#
' GENERAL INFO:
' Class module developed to provide samples of user defined functions (UDF).

Private Const Apostrophe As String = "'"

Public Function GCD(ByRef aValues As Variant) As Long 'Expected an array
Dim t As Long
Dim u As Long
Dim v As Long
Dim args(0 To 1) As Variant
Static RecursionLevel As Long

RecursionLevel = RecursionLevel + 1
Expand Down Expand Up @@ -62,11 +61,13 @@ Private Function minor(a() As Double, x As Integer, y As Integer) As Double()
End Function

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

a() = StringTodblArray(ArrayHelper.ArrayFromString(CStr(StrArray(LBound(StrArray)))))
With ArrayHelper
a() = .StringTodblArray(.ArrayFromString(CStr(strArray(LBound(strArray)))))
End With
DET = DET_(a)
End Function

Expand All @@ -88,24 +89,7 @@ Private Function DET_(a() As Double) As Double
err:
DET_ = a(1)
End Function
'Gets an array from a string like "{{1;2;3};{4;5;6};{7;8;9}}"
Private Function StringTodblArray(ByRef StringArray() As String) As Double()
Dim i As Long, LB As Long, UB As Long
Dim j As Long, LB2 As Long, UB2 As Long
Dim tmpResult() As Double

LB = LBound(StringArray)
UB = UBound(StringArray)
LB2 = LBound(StringArray, 2)
UB2 = UBound(StringArray, 2)
ReDim tmpResult(LB To UB, LB2 To UB2)
For i = LB To UB
For j = LB2 To UB2
tmpResult(i, j) = CDbl(StringArray(i, j))
Next j
Next i
StringTodblArray = tmpResult
End Function

''' <summary>
''' List is expected to be an array. The last element will be used as
''' the concatenation string.
Expand All @@ -122,9 +106,15 @@ Public Function Concat(List As Variant) As String
joinString = MidB$(List(endIdx), 3, LenB(List(endIdx)) - 4)
tmpResult = MidB$(List(startIdx), 3, LenB(List(startIdx)) - 4)
For i = startIdx + 1 To endIdx - 1
If AscW(List(i)) = 39 Then ' [']
tmpResult = tmpResult & _
joinString & _
MidB$(List(i), 3, LenB(List(i)) - 4)
Else
tmpResult = tmpResult & _
joinString & _
List(i)
End If
Next i
Concat = Apostrophe & tmpResult & Apostrophe
End Function
2 changes: 1 addition & 1 deletion src/VBAcallBack.cls
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ Attribute VB_Name = "VBAcallBack"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Attribute VB_Exposed = True
Option Explicit
'#
'////////////////////////////////////////////////////////////////////////////////////////////
Expand Down
Loading

0 comments on commit 923268a

Please sign in to comment.