Stack
BET_StackItem class
Public Value As Variant
Public NextItem As Variant
Private Sub Class_Initialize()
Set NextItem = Nothing
End Sub
Private Sub Class_Terminate()
Set NextItem = Nothing
End Sub
BET_Stack class
Private _stackTop As BET_StackItem
Public Function Method_Pop() As Variant
If (Property_StackEmpty = False) Then
Method_Pop = _stackTop.NextItem
Set _stackTop = _stackTop.NextItem
End If
End Sub
Public Sub Method_Push(ByVal vText As Variant)
Dim newTop As BET_StackItem
Set _newTop = New BET_StackItem
newTop.Value = vText
Set _newTop.NextItem = _stackTop
Set _stackTop = newTop
End Sub
Public Function Method_Peek() As Variant
If (Property_StackEmpty = True) Then
Method_Peek = Null
Else
Method_Peek = _stackTop.Value
End If
End Function
Public Property Get Property_StackEmpty() As Boolean
Property_StackEmpty = (_stackTop Is Nothing)
End Property
Private Sub Class_Initialize()
Set _topStack = Nothing
End Sub
Private Sub Class_Terminate()
Set _topStack = Nothing
End Sub
Sample
Dim myStack As BET_Stack
Dim myStackItem As BET_StackItem
myStack = New BET_Stack
myStackItem = New BET_StackItem
myStackItem.Value = 5
myStack.Method_Push myStackItem
myStackItem = New BET_StackItem
myStackItem.Value = 10
myStack.Method_Push myStackItem
Debug.Print myStack.Method_Pop()
Debug.Print myStack.Method_Pop()
System.Collections.Stack
This does not work with Office 365.
This only works if you have .NET 3.5 installed.
Add a reference to C:\Windows\Microsoft.NET\Framework\v4.0.30319\mscorlib.dll for early binding.
Public Sub CreateStack()
Dim oStack As Object
Set oStack = CreateObject("System.Collections.Stack")
oStack.Push "Monday"
oStack.Clear
oStack.Push "Tuesday"
oStack.Push "Wednesday"
oStack.Push "Thursday"
oStack.Push "Friday"
Debug.Print oStack.Peek()
If (oStack.Contains("Monday") = True) Then
Debug.Print "Monday was removed"
End If
Debug.Print "Last day added was : " & oStack.Pop()
Set oStack = Nothing
End Sub
© 2024 Better Solutions Limited. All Rights Reserved. © 2024 Better Solutions Limited TopPrevNext