module NotificationVariables use CVoidEventHandlerCollection implicit none type::NotificationType logical :: CloseKellyCockLed = .false. type(VoidEventHandlerCollection) :: OnCloseKellyCockLedChange logical :: CloseSafetyValveLed = .false. integer :: operation_CloseSafetyValveLed = 0 type(VoidEventHandlerCollection) :: OnCloseSafetyValveLedChange logical :: FillMouseHoleLed = .false. type(VoidEventHandlerCollection) :: OnFillMouseHoleLedChange logical :: IrIBopLed = .false. type(VoidEventHandlerCollection) :: OnIrIBopLedChange logical :: IrSafetyValveLed = .false. integer :: operation_IrSafetyValveLed = 0 type(VoidEventHandlerCollection) :: OnIrSafetyValveLedChange logical :: LatchLed = .false. type(VoidEventHandlerCollection) :: OnLatchLedChange logical :: OpenKellyCockLed = .false. type(VoidEventHandlerCollection) :: OnOpenKellyCockLedChange logical :: OpenSafetyValveLed = .false. integer :: operation_OpenSafetyValveLed = 0 type(VoidEventHandlerCollection) :: OnOpenSafetyValveLedChange logical :: SlipsNotification = .false. ! procedure (ActionBool), pointer :: SlipsNotificationPtr type(VoidEventHandlerCollection) :: OnSlipsNotificationChange logical :: SwingLed = .false. type(VoidEventHandlerCollection) :: OnSwingLedChange logical :: IbopLed = .false. type(VoidEventHandlerCollection) :: OnIbopLedChange logical :: PowerLed = .false. type(VoidEventHandlerCollection) :: OnPowerLedChange integer :: TorqueWrenchLed = 0 type(VoidEventHandlerCollection) :: OnTorqueWrenchLedChange logical :: TongNotification = .false. ! procedure (ActionBool), pointer :: TongNotificationPtr type(VoidEventHandlerCollection) :: OnTongNotificationChange logical :: UnlatchLed = .false. type(VoidEventHandlerCollection) :: OnUnlatchLedChange end type NotificationType type(NotificationType)::notifications contains subroutine Set_UnlatchLed(v) use CDrillingConsoleVariables!, only: DrillingConsole%UnlatchPipeLED !use CLatchLedNotification implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%UnlatchLed == v) return #endif notifications%UnlatchLed = v if(notifications%UnlatchLed) then DrillingConsole%UnlatchPipeLED = 1 !call Set_LatchLed(.false.) else DrillingConsole%UnlatchPipeLED = 0 endif call notifications%OnUnlatchLedChange%RunAll() end subroutine logical function Get_UnlatchLed() implicit none Get_UnlatchLed = notifications%UnlatchLed end function subroutine Set_TongNotification(v) implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%TongNotification == v) return #endif notifications%TongNotification = v ! if(associated(notifications%TongNotificationPtr)) call notifications%TongNotificationPtr(notifications%TongNotification) #ifdef deb print*, 'notifications%TongNotification=', notifications%TongNotification #endif call notifications%OnTongNotificationChange%RunAll() end subroutine logical function Get_TongNotification() implicit none Get_TongNotification = notifications%TongNotification end function subroutine Set_TorqueWrenchLed(v) use CTopDrivePanelVariables!, only: TopDrivePanel%TopDriveTorqueWrenchLed implicit none integer , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%TorqueWrenchLed == v) return #endif notifications%TorqueWrenchLed = v TopDrivePanel%TopDriveTorqueWrenchLed = v call notifications%OnTorqueWrenchLedChange%RunAll() end subroutine logical function Get_TorqueWrenchLed() implicit none Get_TorqueWrenchLed = notifications%TorqueWrenchLed end function subroutine Set_PowerLed(v) use CTopDrivePanelVariables!, only: TopDrivePanel%TopDriveTdsPowerLed !use CLatchLedNotification implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%PowerLed == v) return #endif notifications%PowerLed = v if(notifications%PowerLed) then TopDrivePanel%TopDriveTdsPowerLed = 1 !call Set_LatchLed(.false.) else TopDrivePanel%TopDriveTdsPowerLed = 0 endif call notifications%OnPowerLedChange%RunAll() end subroutine logical function Get_PowerLed() implicit none Get_PowerLed = notifications%PowerLed end function subroutine Set_IbopLed(v) use CTopDrivePanelVariables!, only: TopDrivePanel%TopDriveIbopLed use CManifolds, Only: OpenTopDriveIBop, CloseTopDriveIBop !use CLatchLedNotification implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%IbopLed == v) return #endif notifications%IbopLed = v if(notifications%IbopLed) then TopDrivePanel%TopDriveIbopLed = 1 call CloseTopDriveIBop() else TopDrivePanel%TopDriveIbopLed = 0 call OpenTopDriveIBop() endif call notifications%OnIbopLedChange%RunAll() end subroutine logical function Get_IbopLed() implicit none Get_IbopLed = notifications%IbopLed end function subroutine Set_SwingLed(v) use CDrillingConsoleVariables!, only: SwingLedHw => SwingLed implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%SwingLed == v) return #endif notifications%SwingLed = v if(notifications%SwingLed) then DrillingConsole%SwingLed = 1 else DrillingConsole%SwingLed = 0 endif call notifications%OnSwingLedChange%RunAll() end subroutine logical function Get_SwingLed() implicit none Get_SwingLed = notifications%SwingLed end function subroutine Set_SlipsNotification(v) implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%SlipsNotification == v) return #endif notifications%SlipsNotification = v ! if(associated(notifications%SlipsNotificationPtr)) call notifications%SlipsNotificationPtr(notifications%SlipsNotification) #ifdef deb print*, 'notifications%SlipsNotification=', notifications%SlipsNotification #endif call notifications%OnSlipsNotificationChange%RunAll() end subroutine logical function Get_SlipsNotification() implicit none Get_SlipsNotification = notifications%SlipsNotification end function subroutine Set_OpenSafetyValveLed(v) use CDrillingConsoleVariables!, only: OpenSafetyValveLedHw => OpenSafetyValveLed use CManifolds, only: OpenSafetyValve_TopDrive, OpenSafetyValve_KellyMode, OpenSafetyValve_TripMode use CHoistingVariables!, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%OpenSafetyValveLed == v) return #endif notifications%OpenSafetyValveLed = v if(notifications%OpenSafetyValveLed) then !!call OpenSafetyValve() if(Hoisting%DriveType == TopDrive_DriveType) call OpenSafetyValve_TopDrive() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_OpenSafetyValveLed == 0) call OpenSafetyValve_KellyMode() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_OpenSafetyValveLed == 1) call OpenSafetyValve_TripMode() endif call notifications%OnOpenSafetyValveLedChange%RunAll() end subroutine logical function Get_OpenSafetyValveLed() implicit none Get_OpenSafetyValveLed = notifications%OpenSafetyValveLed end function subroutine Set_OpenKellyCockLed(v) ! use CDrillingConsoleVariables!, only: OpenKellyCockLedHw => OpenKellyCockLed use CManifolds, only: OpenKellyCock implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%OpenKellyCockLed == v) return #endif notifications%OpenKellyCockLed = v if(notifications%OpenKellyCockLed) then call OpenKellyCock() endif ! HAS BEEN IMPLEMENTED IN CMANIFOLD !if(OpenKellyCockLed) then ! OpenKellyCockLedHw = 1 !else ! OpenKellyCockLedHw = 0 !endif call notifications%OnOpenKellyCockLedChange%RunAll() end subroutine logical function Get_OpenKellyCockLed() implicit none Get_OpenKellyCockLed = notifications%OpenKellyCockLed end function subroutine Set_LatchLed(v) use CDrillingConsoleVariables!, only: DrillingConsole%LatchPipeLED !use CUnlatchLedNotification implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%LatchLed == v) return #endif notifications%LatchLed = v if(notifications%LatchLed) then DrillingConsole%LatchPipeLED = 1 !call Set_UnlatchLed(.false.) else DrillingConsole%LatchPipeLED = 0 endif call notifications%OnLatchLedChange%RunAll() end subroutine logical function Get_LatchLed() implicit none Get_LatchLed = notifications%LatchLed end function subroutine Set_IrSafetyValveLed(v) use CDrillingConsoleVariables!, only: DrillingConsole%CloseKellyCockLed => IRSafetyValveLed use CManifolds, only: & InstallSafetyValve_TopDrive, & InstallSafetyValve_KellyMode, & InstallSafetyValve_TripMode, & RemoveSafetyValve_TopDrive, & RemoveSafetyValve_KellyMode, & RemoveSafetyValve_TripMode use UnitySignalVariables, only: Set_SafetyValve_Install, Set_SafetyValve_Remove use CHoistingVariables!, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%IrSafetyValveLed == v) return #endif notifications%IrSafetyValveLed = v if(notifications%IrSafetyValveLed) then DrillingConsole%IRSafetyValveLed = 1 if(Hoisting%DriveType == TopDrive_DriveType) call InstallSafetyValve_TopDrive() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_IrSafetyValveLed == 0) call InstallSafetyValve_KellyMode() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_IrSafetyValveLed == 1) call InstallSafetyValve_TripMode() call Set_SafetyValve_Install() else DrillingConsole%IRSafetyValveLed = 0 if(Hoisting%DriveType == TopDrive_DriveType) call RemoveSafetyValve_TopDrive() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_IrSafetyValveLed == 0) call RemoveSafetyValve_KellyMode() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_IrSafetyValveLed == 1) call RemoveSafetyValve_TripMode() call Set_SafetyValve_Remove() endif call notifications%OnIrSafetyValveLedChange%RunAll() end subroutine logical function Get_IrSafetyValveLed() implicit none Get_IrSafetyValveLed = notifications%IrSafetyValveLed end function subroutine Set_IrIBopLed(v) use CDrillingConsoleVariables!, only: IRIBopLedHw => IRIBopLed use CManifolds, only: InstallIBop, RemoveIBop use UnitySignalVariables, only: Set_Ibop_Install, Set_Ibop_Remove implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%IrIBopLed == v) return #endif notifications%IrIBopLed = v if(notifications%IrIBopLed) then DrillingConsole%IRIBopLed = 1 call InstallIBop() call Set_Ibop_Install() else DrillingConsole%IRIBopLed = 0 call RemoveIBop() call Set_Ibop_Remove() endif call notifications%OnIrIBopLedChange%RunAll() end subroutine logical function Get_IrIBopLed() implicit none Get_IrIBopLed = notifications%IrIBopLed end function subroutine Set_FillMouseHoleLed(v) use CDrillingConsoleVariables!, only: FillMouseHoleLedHw => FillMouseHoleLed ! use CMouseHoleEnumVariables use UnitySignalVariables implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%FillMouseHoleLed == v) return #endif notifications%FillMouseHoleLed = v if(notifications%FillMouseHoleLed) then DrillingConsole%FillMouseHoleLed = 1 !call Set_MouseHole(MOUSE_HOLE_FILL) else DrillingConsole%FillMouseHoleLed = 0 !call Set_MouseHole(MOUSE_HOLE_EMPTY) endif call notifications%OnFillMouseHoleLedChange%RunAll() end subroutine logical function Get_FillMouseHoleLed() implicit none Get_FillMouseHoleLed = notifications%FillMouseHoleLed end function subroutine Set_CloseKellyCockLed(v) use CDrillingConsoleVariables!, only: CloseKellyCockLedHw => CloseKellyCockLed use CManifolds, only: CloseKellyCock implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%CloseKellyCockLed == v) return #endif notifications%CloseKellyCockLed = v if(notifications%CloseKellyCockLed) then call CloseKellyCock() endif call notifications%OnCloseKellyCockLedChange%RunAll() end subroutine logical function Get_CloseKellyCockLed() implicit none Get_CloseKellyCockLed = notifications%CloseKellyCockLed end function subroutine Set_CloseSafetyValveLed(v) ! use CDrillingConsoleVariables, only: CloseSafetyValveLedHw => CloseSafetyValveLed use CManifolds, only: CloseSafetyValve_TopDrive, CloseSafetyValve_KellyMode, CloseSafetyValve_TripMode use CHoistingVariables!, only: Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType implicit none logical , intent(in) :: v #ifdef ExcludeExtraChanges if(notifications%CloseSafetyValveLed == v) return #endif notifications%CloseSafetyValveLed = v if(notifications%CloseSafetyValveLed) then !!call CloseSafetyValve() if(Hoisting%DriveType == TopDrive_DriveType) call CloseSafetyValve_TopDrive() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_CloseSafetyValveLed == 0) call CloseSafetyValve_KellyMode() if(Hoisting%DriveType == Kelly_DriveType .and. notifications%operation_CloseSafetyValveLed == 1) call CloseSafetyValve_TripMode() endif call notifications%OnCloseSafetyValveLedChange%RunAll() end subroutine logical function Get_CloseSafetyValveLed() implicit none Get_CloseSafetyValveLed = notifications%CloseSafetyValveLed end function end module NotificationVariables