-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathCustom Collection Class
216 lines (196 loc) · 7.52 KB
/
Custom Collection Class
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
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'README
'Use this as a Template, and search-replace Person / People. I wish it were as easy as dropping the
'code into a new Class module, but you’ll need to do this little workaround instead. You see, we
'need a few Attribute modifiers to alter the behaviour of two important properties, and it’s not
'possible to edit Attribute modifiers from VBA’s User Interface. If you didn’t attach the Attribute
'modifiers, the Item property would not be the default property, and you would lose the ability to
'For Each / Next on the Collection. So, using Notepad, save the following code as clsPeople.cls, then
'from VBA > File > Import File, and import clsPeople.cls.
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
VERSION 1.0 CLASS
BEGIN
MultiUse = -1 'True
End
Attribute VB_Name = "clsPeople"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Compare Database
Option Explicit
'**************************************************************************************************
'DATE
'
'
'PURPOSE
'
'
'TICKETS
'Date Ticket Description
'
'**************************************************************************************************
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Public Properties
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Private Properties
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
Private colPeople As Collection
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Public Constants
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Private Constants
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Public Enumerations
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Private Enumerations
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Events
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Property Getters/Setters
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Initialization/Termination Event Handlers
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
Private Sub Class_Initialize()
Set colPeople = New Collection
End Sub
Private Sub Class_Terminate()
Set colPeople = Nothing
End Sub
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Custom Event Handlers
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Custom collection methods
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
Public Property Get NewEnum() As IUnknown
Attribute NewEnum.VB_UserMemId = -4
Attribute NewEnum.VB_MemberFlags = "40"
Set NewEnum = colPeople.[_NewEnum]
End Property
Public Sub Add(obj As clsPerson)
'**************************************************************************************************
'DATE
'
'
'PURPOSE
'Adds a new clsPerson object to the collection
'
'PARAMETERS
' obj clsPerson object to add to the collection
'
'RETURNS
' None
'
'TICKETS
'Date Ticket Description
'
'**************************************************************************************************
colPeople.Add obj
End Sub
Public Sub Remove(Index As Variant)
'**************************************************************************************************
'DATE
'
'
'PURPOSE
'Removes the given object at the given index from the collection
'
'PARAMETERS
' Index Index of the object to remove from the collection
'
'RETURNS
' None
'
'TICKETS
'Date Ticket Description
'
'**************************************************************************************************
colPeople.Remove Index
End Sub
Public Property Get Item(Index As Variant) As clsPerson
Attribute Item.VB_UserMemId = 0
Set Item = colPeople.Item(Index)
End Property
Public Property Get Count() As Long
Count = colPeople.Count
End Property
Public Sub Clear()
'**************************************************************************************************
'DATE
'
'
'PURPOSE
'Clears the entire collection with a new collection
'
'PARAMETERS
' None
'
'RETURNS
' None
'
'TICKETS
'Date Ticket Description
'
'**************************************************************************************************
Set colPeople = New Collection
End Sub
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Public Methods
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'<model>'Public Sub TestPublicMethod( _
'<model>' <VariableName1> As <VariableDataType1>, _
'<model>' <VariableNameN> As <VariableDataTypeN> _
'<model>')
'<model>''**************************************************************************************************
'<model>''DATE
'<model>''<Date>
'<model>''
'<model>''PURPOSE
'<model>''<Purpose>
'<model>''
'<model>''PARAMETERS
'<model>'' <ParameterName1> <ParameterDescription1>
'<model>''
'<model>''RETURNS
'<model>'' <Returns>
'<model>''
'<model>''TICKETS
'<model>''Date Ticket Description
'<model>''<Date>
'<model>''**************************************************************************************************
'<model>'
'<model>'End Sub
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'Private Methods
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'<model>'Private Sub TestPrivateMethod( _
'<model>' <VariableName1> As <VariableDataType1>, _
'<model>' <VariableNameN> As <VariableDataTypeN> _
'<model>')
'<model>''**************************************************************************************************
'<model>''DATE
'<model>''<Date>
'<model>''
'<model>''PURPOSE
'<model>''<Purpose>
'<model>''
'<model>''PARAMETERS
'<model>'' <ParameterName1> <ParameterDescription1>
'<model>'
'<model>''RETURNS
'<model>'' <Returns>
'<model>''
'<model>''TICKETS
'<model>''Date Ticket Description
'<model>''<Date>
'<model>''**************************************************************************************************
'<model>'
'<model>'End Sub