subroutine Drawworks_Solver Use CUnityInputs Use UnitySignalVariables Use Drawworks_VARIABLES Use CKellyConnectionEnumVariables Use CElevatorConnectionEnumVariables Use CTdsConnectionModesEnumVariables Use CTdsElevatorModesEnumVariables Use COperationScenariosVariables IMPLICIT NONE Integer :: j Integer :: CrownCollision_Status , FloorCollision_Status , CrownWarning_Status , FloorWarning_Status !>>>>>>>>>>>>>>>>>>>> Speed <<<<<<<<<<<<<<<<<<<<<<<< Drawworks%N_Throtle = Drawworks%Throttle ![rpm] !Drawworks%N_Accelarator = (Drawworks%Acceleretor/100.d0)*965.d0 ![rpm] !IF (Drawworks%N_Throtle>Drawworks%N_Accelarator) THEN Drawworks%N_new = Drawworks%N_Throtle !ELSE ! Drawworks%N_new = Drawworks%N_Accelarator !END IF !========================== Drawworks Rate limit ========================== if (((Drawworks%N_new-Drawworks%N_old)/Drawworks%time_step)>Drawworks%RateChange) then Drawworks%Speed =(Drawworks%RateChange*Drawworks%time_step)+Drawworks%N_old ![rpm] else if (((Drawworks%N_old-Drawworks%N_new)/Drawworks%time_step)>Drawworks%RateChange) then Drawworks%Speed = (-Drawworks%RateChange*Drawworks%time_step)+Drawworks%N_old else Drawworks%Speed = Drawworks%N_new end if !======================================================================= !========================== Speed Correction ========================== !===> SLIPS SET , No Motion if ( Drawworks%DriveType==1 .and. Get_Slips() == SLIPS_SET_END .and. Get_KellyConnection() == KELLY_CONNECTION_STRING ) then Drawworks%Speed = 0.d0 end if if ( Drawworks%DriveType==0 .and. Get_Slips() == SLIPS_SET_END .and. (Get_TdsConnectionModes()==TDS_CONNECTION_SPINE .or. Get_TdsConnectionModes()==TDS_CONNECTION_STRING) ) then Drawworks%Speed = 0.d0 end if !===> Closed BOP Rams , No Motion if ( Drawworks%ShearBopSituation==1 .and. (any(Drawworks%DrillModeCond==(/3,10,19,20,24/))) ) then Drawworks%Speed = 0.d0 end if !======================================================================= Call Drawworks_Direction !==================================================== ! Collision & Warning !==================================================== if ( Drawworks%CrownCollision == .false. ) then CrownCollision_Status = 0 end if if ( Drawworks%FloorCollision == .false. ) then FloorCollision_Status = 0 end if !==================================================== ! Crown Collision (Max_Hook_Height) !==================================================== if ( ((3.280839895d0*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then if ( CrownCollision_Status==0 .and. Drawworks%motion==1 ) then CrownCollision_Status = 1 Drawworks%CrownCollision = .true. Drawworks%SoundCrownCollision = .true. else Drawworks%SoundCrownCollision = .false. end if if ( Drawworks%motion==-1 .and. Drawworks%CrownCollision==.false. ) then Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft] else Call DWFixModeMotion end if return end if !==================================================== ! Floor Collision (Min_Hook_Height) !==================================================== if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then if ( FloorCollision_Status==0 .and. Drawworks%motion==-1 ) then FloorCollision_Status = 1 Drawworks%FloorCollision = .true. Drawworks%SoundFloorCollision = .true. else Drawworks%SoundFloorCollision = .false. end if if ( Drawworks%motion==1 .and. Drawworks%FloorCollision==.false. ) then Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft] else Call DWFixModeMotion end if return end if !==================================================== ! Crown Warning !==================================================== if ( ((3.280839895*Drawworks%Hook_Height)>=Drawworks%max_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then if ( Drawworks%motion==-1 ) then Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft] else Call DWFixModeMotion end if return end if !==================================================== ! Floor Warning !==================================================== if ( ((3.280839895*Drawworks%Hook_Height)<=Drawworks%min_Hook_Height) .and. (any(Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then if ( Drawworks%motion==1 ) then Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft] else Call DWFixModeMotion end if return end if !==================================================== ! ELEVATOR CONNECTION STRING (SLIPS SET , No Motion) !==================================================== if ( Drawworks%DriveType==1 .and. Get_Slips() == SLIPS_SET_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_STRING .and. Drawworks%motion/=-1 ) then Call DWFixModeMotion return end if if ( Drawworks%DriveType==0 .and. Get_Slips() == SLIPS_SET_END .and. (Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_STRING) .and. Drawworks%motion/=-1 ) then Call DWFixModeMotion return end if !==================================================== ! RAM & ToolJoint Collision (Top of RAM) !==================================================== Do j = 2,4 !startup problem ??????? if ( Drawworks%TDBOPElementNo(j)/=0 ) then if ( ((Drawworks%TDBOPHeight(j)-Drawworks%TDBOPThickness)<=(Drawworks%TDDrillStemsTopDepth(Drawworks%TDBOPElementNo(j))+Drawworks%TDDrillStemsToolJointRange(Drawworks%TDBOPElementNo(j)))) .and. ((Drawworks%TDBOPHeight(j)-Drawworks%TDBOPThickness)>Drawworks%TDDrillStemsTopDepth(Drawworks%TDBOPElementNo(j))) .and. (Drawworks%TDBOPRamDiam(j)<(2.d0*12.d0*Drawworks%TDDrillStemsRtoolJoint(Drawworks%TDBOPElementNo(j)))) ) then if ( Drawworks%motion==1 ) then Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft] else Call DWFixModeMotion end if return end if end if End Do !==================================================== ! RAM & ToolJoint Collision (Bottom of RAM) !==================================================== Do j = 2,4 if ( Drawworks%TDBOPElementNo(j)/=0 ) then if ( ((Drawworks%TDBOPHeight(j)+Drawworks%TDBOPThickness)>=(Drawworks%TDDrillStemsDownDepth(Drawworks%TDBOPElementNo(j))-Drawworks%TDDrillStemsToolJointRange(Drawworks%TDBOPElementNo(j)))) .and. ((Drawworks%TDBOPHeight(j)+Drawworks%TDBOPThickness) BottomHole ROP Condition if ( (int(Drawworks%TDDrillStemBottom*10000.d0)>=(int((Drawworks%TDWellTotalLength+Drawworks%TDDlMax)*10000.d0))) .and. (Drawworks%motion==-1 .or. Drawworks%motion==0) ) then if ( Drawworks%StringIsBottomOfWell==0 ) then Drawworks%Hook_Height_final = Drawworks%Hook_Height_final+(Drawworks%TDDrillStemBottom-(Drawworks%TDWellTotalLength+Drawworks%TDDlMax)) Drawworks%StringIsBottomOfWell = 1 end if Call DWFixModeMotion return else Drawworks%StringIsBottomOfWell = 0 end if Drawworks%Hook_Height_final = 3.280839895d0*Drawworks%Hook_Height ![ft] Drawworks%HookHeight_graph_output = 0.1189d0*((3.280839895d0*Drawworks%Hook_Height)-28.d0)-2.6d0 ![ft] end subroutine Drawworks_Solver