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