Skip to content
Mathieu Guindon edited this page Oct 27, 2020 · 2 revisions

MVVM?

Model-View-ViewModel (MVVM) is a UI design pattern used in modern software development, both in Win32/desktop (WPF/XAML) and web front-ends (Javascript). What sets this pattern apart from, say, Model-View-Presenter, is property and command bindings: we don't handle control events anymore, so the form's code-behind is focused on the only concern that remains - presentation.

In MVVM, we're going to be referring to a UserForm as a View to broadly generalize the abstraction, but keep in mind that a View could just as well be a MSForms.Tab control in a MSForms.TabStrip container, itself a child of a UserForm. The "Model-View-ViewModel" triad is about abstractions, so think of the View as whichever component is responsible for directly interacting with the user.

This is a significant departure from how VBA traditionally makes you reason about programming. The Visual Basic Editor (VBE) has made a lot of us believe having lots of small, specialized modules was combersome and counter-productive. We are rightfully reluctant to code against interfaces, when there's no IDE support to navigate to their implementations. What if we just ran with it though, and embraced the full breadth of what Rubberduck and VBA as a language have to offer? This project is what happens then.

We can still drag-and-drop design our forms - but a View will only initialize property and command bindings, and MVVM does everything else. Or we can use an API to create the entire UI at run-time and bind the controls to ViewModel properties; either way, with MVVM the only code that's needed in a form's code-behind module, is code that configures all the property bindings, and boilerplate IView interface implementation.

The ViewModel is an object that exposes all the properties needed by the View, and implements the INotifyPropertyChanged interface to notify listeners (property bindings) when a value needs to be synchronized.

The Model is an abstraction representing the object(s) responsible for retrieving and persisting the ViewModel data, as applicable. It's arguably also the commands you implement that read ViewModel properties and pass them to some stored procedure on SQL Server.


Getting Started

  1. Get Rubberduck. Seriously, you'll need it.
  2. Download MVVM.xlsm from this repository and open it in Microsoft Excel, then press Alt+F11 to bring up the VBE.
  3. Add a new user form (UserForm1) and paste this code in:
Option Explicit
Implements IView
Implements ICancellable

Private Type TState
    Context As MVVM.IAppContext
    ViewModel As Class1
    IsCancelled As Boolean
End Type

Private This As TState

'@Description "Creates a new instance of this form."
Public Function Create(ByVal Context As MVVM.IAppContext, ByVal ViewModel As Class1) As IView
    Dim Result As UserForm1
    Set Result = New UserForm1
    Set Result.Context = Context
    Set Result.ViewModel = ViewModel
    Set Create = Result
End Function

Public Property Get Context() As MVVM.IAppContext
    Set Context = This.Context
End Property

Public Property Set Context(ByVal RHS As MVVM.IAppContext)
    Set This.Context = RHS
End Property

Public Property Get ViewModel() As Object
    Set ViewModel = This.ViewModel
End Property

Public Property Set ViewModel(ByVal RHS As Object)
    Set This.ViewModel = RHS
End Property

Private Sub OnCancel()
    This.IsCancelled = True
    Me.Hide
End Sub

Private Sub InitializeView()
    With This.Context.Bindings
        'TODO configure property bindings
    End With
    With This.Context.Commands
        'TODO configure command bindings
    End With
    This.Context.Bindings.Apply This.ViewModel
End Sub

Private Property Get ICancellable_IsCancelled() As Boolean
    ICancellable_IsCancelled = This.IsCancelled
End Property

Private Sub ICancellable_OnCancel()
    OnCancel
End Sub

Private Sub IView_Hide()
    Me.Hide
End Sub

Private Sub IView_Show()
    InitializeView
    Me.Show vbModal
End Sub

Private Function IView_ShowDialog() As Boolean
    InitializeView
    Me.Show vbModal
    IView_ShowDialog = Not This.IsCancelled
End Function

Private Property Get IView_ViewModel() As Object
    Set IView_ViewModel = This.ViewModel
End Property

Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
    If CloseMode = VbQueryClose.vbFormControlMenu Then
        Cancel = True
        OnCancel
    End If
End Sub
  1. Add a new standard module (Module1) and a new class module (Class1) to the project, then add a new parameterless Sub procedure (say, DoSomething) to Module1. Inside that procedure scope:

    • Declare a Context As IAppContext object reference, and assign it to the output of the AppContext.Create factory method.
    • Declare a ViewModel As Class1 object reference, and then Set ViewModel = New Class1.
    • Declare a View As IView object reference, and then Set View = UserForm1.Create(Context, ViewModel).
  2. Add the properties you need in Class1; make the class implement the INotifyPropertyChanged to support 2-way bindings. Use .BindPropertyPath in the With This.Context.Bindings block of the InitializeView method to configure property bindings and associate a ViewModel property with a property of a control on the form.

  3. Add a new class (Class2) and make it implement the ICommand interface; the Context parameter in both CanExecute and Execute methods holds a reference to the ViewModel. Use .BindCommand in the With This.Context.Commands block of the InitializeView method to configure command bindings and associate a command object with a CommandButton control on the form.

Clone this wiki locally