module OperationScenariosModule !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !! Paseted From ....Variables.f90 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! use SimulationVariables use PermissionsModule use UnityModule use UnitySignalVariables use UnitySignalsModule use PermissionsModule use CHoistingVariables use CTopDrivePanelVariables use NotificationModule use SoftwareInputsModule contains subroutine OperationScenariosToJson(parent) type(json_value),pointer :: parent type(json_core) :: json type(json_value),pointer :: p ! 1. create new node call json%create_object(p,'OperationScenarios') ! 2. add member of data type to new node call json%add(p,"ElevatorConnection",data%State%OperationScenario%ElevatorConnection) call json%add(p,"StringUpdate",data%State%OperationScenario%StringUpdate) call json%add(p,"KellyConnection",data%State%OperationScenario%KellyConnection) ! 3. add new node to parent call json%add(parent,p) end subroutine ! moved from kellyConnectionEnum subroutine Set_KellyConnection(v) use CManifolds, Only: KellyConnected, KellyDisconnected implicit none integer , intent(in) :: v #ifdef ExcludeExtraChanges if(data%State%OperationScenario%KellyConnection == v) return #endif data%State%OperationScenario%KellyConnection = v if(data%State%OperationScenario%KellyConnection /= KELLY_CONNECTION_STRING) then call KellyDisconnected() else call KellyConnected() endif #ifdef deb if(print_log) print*, 'data%State%OperationScenario%KellyConnection=', data%State%OperationScenario%KellyConnection #endif !**call data%State%OperationScenario%OnKellyConnectionChange%RunAll() end subroutine integer function Get_KellyConnection() implicit none Get_KellyConnection = data%State%OperationScenario%KellyConnection end function subroutine Evaluate_KellyConnection() implicit none if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then #ifdef OST if(print_log) print*, 'Evaluate_KellyConnection=TopDrive' #endif endif if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then #ifdef OST if(print_log) print*, 'Evaluate_KellyConnection=Kelly' #endif !OPERATION-CODE=1 if (Get_OperationCondition() == OPERATION_DRILL .and.& !Get_JointConnectionPossible() .and.& Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.& Get_Swing() == SWING_WELL_END .and.& !Get_TongNotification() .and.& Get_Tong() == TONG_MAKEUP_END) then !call Log_4('KELLY_CONNECTION_STRING') call Set_Tong(TONG_NEUTRAL) call Set_KellyConnection(KELLY_CONNECTION_STRING) return end if !OPERATION-CODE=2 if (Get_OperationCondition() == OPERATION_DRILL .and.& Get_StringPressure() == 0 .and.& Get_HookHeight() <= (data%State%OperationScenario%HKL + Get_NearFloorConnection()) .and.& Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& Get_Swing() == SWING_WELL_END .and.& !Get_TongNotification() .and.& Get_Tong() == TONG_BREAKOUT_END) then call Set_Tong(TONG_NEUTRAL) call Set_KellyConnection(KELLY_CONNECTION_NOTHING) call Set_SwingLed(.true.) return end if !OPERATION-CODE=3 if (Get_OperationCondition() == OPERATION_DRILL .and.& !Get_JointConnectionPossible() .and.& Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and.& Get_Swing() == SWING_MOUSE_HOLE_END .and.& !Get_TongNotification() .and.& Get_FillMouseHoleLed() .and.& Get_Tong() == TONG_MAKEUP_END) then call Set_Tong(TONG_NEUTRAL) call Set_KellyConnection(KELLY_CONNECTION_SINGLE) call Set_SwingLed(.false.) call Set_FillMouseHoleLed(.false.) call Set_MouseHole(MOUSE_HOLE_NEUTRAL) return end if !OPERATION-CODE=4 if (Get_OperationCondition() == OPERATION_DRILL .and.& Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& Get_Swing() == SWING_MOUSE_HOLE_END .and.& !Get_TongNotification() .and.& Get_FillMouseHoleLed() == .false. .and.& Get_Tong() == TONG_BREAKOUT_END) then call Set_Tong(TONG_NEUTRAL) call Set_KellyConnection(KELLY_CONNECTION_NOTHING) call Set_FillMouseHoleLed(.true.) call Set_MouseHole(MOUSE_HOLE_NEUTRAL) return end if !OPERATION-CODE=5 if (Get_OperationCondition() == OPERATION_DRILL .and.& !Get_JointConnectionPossible() .and.& Get_KellyConnection() == KELLY_CONNECTION_SINGLE .and.& Get_Swing() == SWING_WELL_END .and.& !Get_TongNotification() .and.& Get_Tong() == TONG_MAKEUP_END) then call Set_Tong(TONG_NEUTRAL) call Set_KellyConnection(KELLY_CONNECTION_STRING) call Set_StringUpdate(STRING_UPDATE_ADD_SINGLE) call Set_SwingLed(.false.) return end if !OPERATION-CODE=6 if (Get_OperationCondition() == OPERATION_DRILL .and.& Get_StringPressure() == 0 .and.& Get_HookHeight() > 70.0 .and.& Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& !Get_TongNotification() .and.& Get_Swing() == SWING_WELL_END .and.& Get_Tong() == TONG_BREAKOUT_END) then call Set_Tong(TONG_NEUTRAL) call Set_KellyConnection(KELLY_CONNECTION_SINGLE) call Set_StringUpdate(STRING_UPDATE_REMOVE_SINGLE) return end if endif end subroutine ! subroutine Subscribe_KellyConnection() ! use CDrillingConsoleVariables ! use ConfigurationVariables ! use ConfigurationVariables ! implicit none ! call OnBreakoutLeverPress%Add(ButtonPress_Breakout) ! call OnMakeupLeverPress%Add(ButtonPress_Makeup) ! end subroutine subroutine ButtonPress_Breakout() implicit none #ifdef deb if(print_log) print*, 'ButtonPress_Breakout on ======> CKellyConnectionEnum' #endif end subroutine subroutine ButtonPress_Makeup() implicit none #ifdef deb if(print_log) print*, 'ButtonPress_Makeup on ======> CKellyConnectionEnum' #endif end subroutine subroutine Set_StringUpdate(v) implicit none integer , intent(in) :: v #ifdef ExcludeExtraChanges if(data%State%OperationScenario%StringUpdate == v) return #endif data%State%OperationScenario%StringUpdate = v !**call data%State%OperationScenario%OnStringUpdateChange%RunAll(v) end subroutine integer function Get_StringUpdate() implicit none Get_StringUpdate = data%State%OperationScenario%StringUpdate end function real(8) function TJH() use TD_DrillStemComponents implicit none TJH = data%State%TD_String%TopJointHeight end function real function TL() implicit none TL = 26.97 end function real function NFC() implicit none NFC = Get_NearFloorConnection() end function subroutine Set_ElevatorConnection(v) implicit none integer , intent(in) :: v #ifdef ExcludeExtraChanges if(data%State%OperationScenario%ElevatorConnection == v) return #endif data%State%OperationScenario%ElevatorConnection = v #ifdef deb if(print_log) print*, 'data%State%OperationScenario%ElevatorConnection=', data%State%OperationScenario%ElevatorConnection #endif !**call data%State%OperationScenario%OnElevatorConnectionChange%RunAll() end subroutine integer function Get_ElevatorConnection() implicit none Get_ElevatorConnection = data%State%OperationScenario%ElevatorConnection end function !//SLIPS: everythings start here subroutine ButtonPress_Slips() bind(C,name="ButtonPress_Slips") ! use NotificationModule use CUnityOutputs ! use UnitySignalsModule implicit none if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then if(print_log) print*, 'ButtonPress_Slips=TopDrive' !TOPDRIVE-CODE=30 if (Get_Slips() == SLIPS_UNSET_END .and.& Get_SlipsNotification()) then call Set_Slips(SLIPS_SET_BEGIN) return end if !TOPDRIVE-CODE=31 if (Get_TdsConnectionModes() == TDS_CONNECTION_STRING .and.& Get_Slips() == SLIPS_SET_END .and.& Get_SlipsNotification()) then call Set_Slips(SLIPS_UNSET_BEGIN) return end if !TOPDRIVE-CODE=32 if (Get_TdsElevatorModes() == TDS_ELEVATOR_CONNECTION_STRING .and.& Get_Slips() == SLIPS_SET_END .and.& Get_SlipsNotification()) then call Set_Slips(SLIPS_UNSET_BEGIN) return end if endif if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then if(print_log) print*, 'ButtonPress_Slips=Kelly' !OPERATION-CODE=19 if (Get_Slips() == SLIPS_UNSET_END .and.& Get_SlipsNotification()) then call Set_Slips(SLIPS_SET_BEGIN) return end if !OPERATION-CODE=20 if (Get_OperationCondition() == OPERATION_DRILL .and.& Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& GetRotaryRpm() == 0.0d0 .and.& Get_SlipsNotification() .and.& Get_Slips() == SLIPS_SET_END) then call Set_Slips(SLIPS_UNSET_BEGIN) return end if !OPERATION-CODE=21 if (Get_OperationCondition() == OPERATION_TRIP .and.& Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and.& GetRotaryRpm() == 0.0d0 .and.& Get_SlipsNotification() .and.& Get_Slips() == SLIPS_SET_END) then call Set_Slips(SLIPS_UNSET_BEGIN) return end if endif end subroutine end module OperationScenariosModule