|
- module CVoidEventHandler
- use CIActionReference
- implicit none
- public
-
- type :: VoidEventHandler
- procedure(ActionVoid), pointer, nopass :: Delegate => null()
- contains
- procedure :: AssignTo => AssignTo
- procedure :: MakeNull => MakeNull
- procedure :: IsNull => IsNull
- procedure :: Run => Run
- end type VoidEventHandler
-
- contains
-
- subroutine AssignTo(this, proc)
- implicit none
- class(VoidEventHandler), intent(inout) :: this
- procedure (ActionVoid), pointer, intent(in) :: proc
- this%Delegate => proc
- end subroutine
-
- subroutine MakeNull(this)
- implicit none
- class(VoidEventHandler), intent(inout) :: this
- this%Delegate => null()
- end subroutine
-
- logical function IsNull(this)
- implicit none
- class(VoidEventHandler), intent(in) :: this
- IsNull = .not.associated(this%Delegate)
- end function
-
- subroutine Run(this)
- implicit none
- class(VoidEventHandler), intent(inout) :: this
- !if(.not.this%IsNull()) then
- call this%Delegate()
- !endif
- end subroutine
-
- end module CVoidEventHandler
|