-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathM_clsLogFilterNumeric.def
92 lines (77 loc) · 2.81 KB
/
M_clsLogFilterNumeric.def
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
'---------------------------------------------------------------------------------------
' Module : clsLogFilterNumeric
' Author : K.Gundermann
' Date : 04.02.2012
' Purpose : Matches Numeric Values
'---------------------------------------------------------------------------------------
Option Compare Database
Option Explicit
Public Enum e_EntryFilter_Numeric
IgnoreNumber
EqualTo
GreaterThan
LowerThan
Between
NotBetween
End Enum
Public Entry As String
Public Match As e_EntryFilter_Numeric
Public Value1 As Long
Public Value2 As Long
Public Function MatchesNumber(ByVal TheValue As Long) As Boolean
Select Case Me.Match
Case IgnoreNumber: MatchesNumber = True
Case EqualTo: MatchesNumber = (TheValue = Me.Value1)
Case GreaterThan: MatchesNumber = (TheValue > Me.Value1)
Case LowerThan: MatchesNumber = (TheValue < Me.Value1)
Case Between: MatchesNumber = ((TheValue >= Me.Value1) And (TheValue <= Me.Value2))
Case NotBetween: MatchesNumber = Not ((TheValue >= Me.Value1) And (TheValue <= Me.Value2))
End Select
End Function
Public Property Get Self() As clsLogFilterNumeric
Set Self = Me
End Property
Public Function ToString() As String
If Me.Match <> IgnoreNumber Then
ToString = Entry & " " & MatchToString & " " & ValueToString
End If
End Function
Public Sub FromString(ByVal TheString As String)
' TODO: Parse TheString
End Sub
Public Function MatchToString() As String
Select Case Me.Match
Case IgnoreNumber: MatchToString = ""
Case EqualTo: MatchToString = "="
Case GreaterThan: MatchToString = ">"
Case LowerThan: MatchToString = "<"
Case Between: MatchToString = "Between"
Case NotBetween: MatchToString = "Not Between"
End Select
End Function
Public Property Let MatchFromString(ByVal TheMatch As String)
Select Case Trim$(TheMatch)
Case "": Me.Match = IgnoreNumber
Case "=": Me.Match = EqualTo
Case ">": Me.Match = GreaterThan
Case "<": Me.Match = LowerThan
Case "Between": Me.Match = Between
Case "Not Between": Me.Match = NotBetween
End Select
End Property
Public Function ValueToString() As String
Select Case Me.Match
Case IgnoreString: ValueToString = ""
Case EqualTo, _
GreaterThan, _
LowerThan: ValueToString = str(Me.Value1)
Case Between, _
NotBetween: ValueToString = str(Me.Value1) & " AND" & str(Me.Value2)
End Select
End Function
Public Property Let ValueFromString(ByVal TheValue As String)
End Property