subroutine Drawworks_INPUTS Use CDrillingConsoleVariables Use CDataDisplayConsoleVariables Use CHoistingVariables Use CSimulationVariables Use CSlipsEnumVariables Use CKellyConnectionEnumVariables Use CElevatorConnectionEnumVariables Use COperationConditionEnumVariables Use COperationScenariosVariables Use CSwingEnumVariables Use CUnityInputs Use CTdsConnectionModesEnumVariables Use CTdsElevatorModesEnumVariables Use CTdsSwingEnumVariables Use VARIABLES Use Drawworks_VARIABLES Use TD_StringConnectionData Use TD_DrillStemComponents IMPLICIT NONE Call DWMalfunction_ClutchEngage Drawworks%TransMode = DrillingConsole%DWTransmisionLever Drawworks%Direction_Var = DrillingConsole%DWSwitch if (IsPortable) then if (Drawworks%Direction_Var==-1 .and. DataDisplayConsole%Clutch==1) then !in FWD mode Drawworks%Conv_Ratio = Drawworks%FWD_Conv_Ratio(Drawworks%ClutchMode,Drawworks%TransMode) else Drawworks%Conv_Ratio = 1.d0 end if else if (Drawworks%Direction_Var==-1) then !in FWD mode Drawworks%Conv_Ratio = Drawworks%FWD_Conv_Ratio(Drawworks%ClutchMode,Drawworks%TransMode) else if (Drawworks%Direction_Var==+1) then !in REV mode Drawworks%Conv_Ratio = 1.d0 else if (Drawworks%Direction_Var==0) then !in OFF mode Drawworks%Conv_Ratio = 1.d0 end if end if !===> Main Brake and Eddy Brake Drawworks%EddyBreak = DrillingConsole%EddyBreakLever*0.5 !0 Brake Load (Main Brake) Drawworks%BreakLoad = Hoisting%DrillingLineBreakingLoad ![Lbf] Drawworks%BreakLoad = 4.448221619*Drawworks%BreakLoad ![N] !===> F_fastline Drawworks%F_fastline = real(TD_DrawworksLoadInput) ![Lbf] Drawworks%F_fastline = 4.448221619*Drawworks%F_fastline ![N] !===> min&max Hook Height if ( Hoisting%DriveType==1 .and. Get_OperationCondition()==OPERATION_DRILL ) then if ( Get_Swing()==SWING_WELL_END .and. Get_KellyConnection()==KELLY_CONNECTION_NOTHING ) then DW_DrillModeCond = 1 Drawworks%min_Hook_Height = TD_TopJointHeight+HKL-RE ![ft] HKL=63.76=Kelly Ass. Height , RE=Release Drawworks%max_Hook_Height = 120.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_KellyConnection()==KELLY_CONNECTION_SINGLE ) then DW_DrillModeCond = 2 Drawworks%min_Hook_Height = TD_TopJointHeight+HKL+PL-RE ![ft] PL=30=Pipe Lenght Drawworks%max_Hook_Height = 120.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_KellyConnection() == KELLY_CONNECTION_STRING ) then DW_DrillModeCond = 3 Drawworks%min_Hook_Height = 21.44d0-RE ![ft] ?????????? check 21.44=(TD_KellyConst-TD_KellyElementConst) Drawworks%max_Hook_Height = 120.d0 ![ft] else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_KellyConnection()==KELLY_CONNECTION_NOTHING ) then DW_DrillModeCond = 4 Drawworks%min_Hook_Height = 66.d0-RE ![ft] Drawworks%max_Hook_Height = 120.d0 ![ft] else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_KellyConnection()==KELLY_CONNECTION_SINGLE ) then DW_DrillModeCond = 5 Drawworks%min_Hook_Height = 65.1d0-RE ![ft] Drawworks%max_Hook_Height = 120.d0 ![ft] else if ( Get_Swing()==SWING_RAT_HOLE_END ) then DW_DrillModeCond = 6 Drawworks%min_Hook_Height = 66.d0-RE ![ft] Drawworks%max_Hook_Height = 120.d0 ![ft] end if else if ( Hoisting%DriveType==1 .and. Get_OperationCondition()==OPERATION_TRIP ) then if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING ) then DW_DrillModeCond = 7 Drawworks%min_Hook_Height = 18.38d0 ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STAND ) then DW_DrillModeCond = 8 Drawworks%min_Hook_Height = TD_TopJointHeight+HL+SL-(3.d0*RE) ![ft] HL=17.81=Hook Assy , SL=90=Stand Length , 3: chon meghdari az toole loole(tool joint) dakhele elevator gharar migirad Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE ) then DW_DrillModeCond = 9 Drawworks%min_Hook_Height = TD_TopJointHeight+HL+PL-(3.d0*RE) ![ft] 3: chon meghdari az toole loole(tool joint) balaye elevator mimanad Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING ) then DW_DrillModeCond = 10 Drawworks%min_Hook_Height = 18.5d0-RE ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING ) then DW_DrillModeCond = 11 Drawworks%min_Hook_Height = 19.38d0-RE ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE ) then DW_DrillModeCond = 12 Drawworks%min_Hook_Height = 17.73d0-RE ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_RAT_HOLE_END ) then DW_DrillModeCond = 13 Drawworks%min_Hook_Height = 27.41d0-RE ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING ) then DW_DrillModeCond = 14 Drawworks%min_Hook_Height = 18.38d0 ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_LATCH_SINGLE ) then DW_DrillModeCond = 25 !warning & collision Drawworks%min_Hook_Height = 18.38d0 !????????????????? ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_ElevatorConnection() == ELEVATOR_LATCH_SINGLE ) then DW_DrillModeCond = 26 Drawworks%min_Hook_Height = 10.38d0 !????????????????? ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_LATCH_STAND ) then DW_DrillModeCond = 27 Drawworks%min_Hook_Height = 18.38d0 !????????????????? ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] end if else if ( Hoisting%DriveType==0 ) then if ( Get_TdsSwing()==TDS_SWING_TILT_END ) then if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_LATCH_SINGLE ) then DW_DrillModeCond = 15 Drawworks%min_Hook_Height = 15.0d0 ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_SINGLE ) then DW_DrillModeCond = 16 Drawworks%min_Hook_Height = 15.0d0 ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then DW_DrillModeCond = 17 Drawworks%min_Hook_Height = 15.0d0 ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] end if else if ( Get_TdsSwing()==TDS_SWING_OFF_END ) then if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_LATCH_STRING ) then DW_DrillModeCond = 18 Drawworks%min_Hook_Height = max(16.0d0,TD_TopJointHeight) ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_STRING ) then DW_DrillModeCond = 19 Drawworks%min_Hook_Height = TD_TopJointHeight ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_STRING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then DW_DrillModeCond = 20 Drawworks%min_Hook_Height = TD_TopJointHeight ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then DW_DrillModeCond = 21 Drawworks%min_Hook_Height = max(16.0d0,TD_TopJointHeight) ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_LATCH_STAND ) then DW_DrillModeCond = 22 Drawworks%min_Hook_Height = max(16.0d0,TD_TopJointHeight) ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_STAND ) then DW_DrillModeCond = 23 Drawworks%min_Hook_Height = max(16.0d0,TD_TopJointHeight) ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] else if ( Get_TdsConnectionModes()==TDS_CONNECTION_SPINE .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then DW_DrillModeCond = 24 Drawworks%min_Hook_Height = TD_TopJointHeight ![ft] Drawworks%max_Hook_Height = 140.d0 ![ft] end if end if end if !print* , 'DW_DrillModeCond=' , DW_DrillModeCond !!print* , 'Drawworks%min_Hook_Height=' , Drawworks%min_Hook_Height !!print* , 'Drawworks%max_Hook_Height=' , Drawworks%max_Hook_Height !print* , 'Drawworks%Hook_Height_final=' , Drawworks%Hook_Height_final !print*, 'TD_DrillStemComponentsNumbs2=' , TD_DrillStemComponentsNumbs !print*, 'TD_TopJointHeight2=' , TD_TopJointHeight !print*, 'TD_DrillStemTotalLength2=', TD_DrillStemTotalLength !===> SLIPS SET , No Motion if ( Hoisting%DriveType==1 .and. Get_Slips() == SLIPS_SET_END .and. Get_KellyConnection() == KELLY_CONNECTION_STRING ) then Drawworks%ManualBreak = 100.d0 Drawworks%N_ref = 0.d0 end if if ( Hoisting%DriveType==0 .and. Get_Slips() == SLIPS_SET_END .and. (Get_TdsConnectionModes()==TDS_CONNECTION_SPINE .or. Get_TdsConnectionModes()==TDS_CONNECTION_STRING) ) then Drawworks%ManualBreak = 100.d0 Drawworks%N_ref = 0.d0 end if !if ( Get_Slips() == SLIPS_SET_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and. Drawworks%motion==+1 ) then ! Drawworks%ManualBreak = 100.d0 ! Drawworks%N_ref = 0.d0 !!else if ( Get_Slips() == SLIPS_SET_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and. Drawworks%motion/=+1 ) then !! Drawworks%N_ref = 0.d0 !! !Call DWFixModeMotion !! !print*, 'ELEVATOR_CONNECTION_STRING' !end if !===> Closed BOP Rams , No Motion !if ( PipeRam1_Situation_forTD==1 .or. PipeRam2_Situation_forTD==1 .or. ShearBop_Situation_forTD==1 ) then if ( ShearBop_Situation_forTD==1 .and. (any(DW_DrillModeCond==(/3,10,19,20,24/))) ) then Drawworks%ManualBreak = 100.d0 Drawworks%N_ref = 0.d0 end if end subroutine Drawworks_INPUTS