module CIbopHeight
    use CVoidEventHandlerCollection
    implicit none
    real :: IbopHeight = 0
    
    public
    
    type(VoidEventHandlerCollection) :: OnIbopHeightChange
    
    private :: IbopHeight
    
    contains
    
    
    subroutine Set_IbopHeight(v)
        implicit none
        real , intent(in) :: v
#ifdef ExcludeExtraChanges
        if(IbopHeight == v) return
#endif
        IbopHeight = v
#ifdef deb
        print*, 'IbopHeight=', IbopHeight
#endif
        call OnIbopHeightChange%RunAll()
    end subroutine
    
    real function Get_IbopHeight()
        implicit none
        Get_IbopHeight = IbopHeight
        !Get_IbopHeight = 23.0
    end function
    
    
    
    
    subroutine Set_IbopHeight_WN(v)
    !DEC$ ATTRIBUTES DLLEXPORT :: Set_IbopHeight_WN
    !DEC$ ATTRIBUTES ALIAS: 'Set_IbopHeight_WN' :: Set_IbopHeight_WN
        implicit none
        real , intent(in) :: v
        call Set_IbopHeight(v)
    end subroutine
    real function Get_IbopHeight_WN()
    !DEC$ ATTRIBUTES DLLEXPORT :: Get_IbopHeight_WN
    !DEC$ ATTRIBUTES ALIAS: 'Get_IbopHeight_WN' :: Get_IbopHeight_WN
        implicit none
        Get_IbopHeight_WN = IbopHeight
        !Get_IbopHeight_WN = 23.0
    end function
    
    
    subroutine Subscribe_IbopHeight()
        implicit none
    end subroutine
    
    
end module CIbopHeight