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