|
- subroutine Drawworks_Inputs
-
- Use CDrillingConsoleVariables
- ! Use CSimulationVariables
- Use COperationScenariosVariables
- Use CWarningsVariables
- Use VARIABLES
- Use Drawworks_VARIABLES
- Use TD_StringConnectionData
- Use TD_DrillStemComponents
- Use TD_GeneralData
- Use TD_WellGeometry
-
- IMPLICIT NONE
-
-
-
- Drawworks%AssignmentSwitch = DrillingConsole%AssignmentSwitch
- Drawworks%Switch = DrillingConsole%DWSwitch
- Drawworks%Throttle = DrillingConsole%DWThrottle ![RPM]
- Drawworks%DriveType = Hoisting%DriveType
- Drawworks%ShearBopSituation = RamLine%ShearBop_Situation_forTD
- !Drawworks%MotorFaileMalf = ?????? motaghayere voroudi !dar CHoistingProblemsVariables meghdardehi mishavad
-
-
-
- !>>> RAM & ToolJoint Collision
- Drawworks%TDBOPElementNo = TD_BOP%BOPElementNo
- Drawworks%TDBOPHeight = TD_BOP%BOPHeight
- Drawworks%TDBOPRamDiam = TD_BOP%BOPRamDiam
- Drawworks%TDBOPThickness = TD_BOP%BOPThickness
- Drawworks%TDDrillStemBottom = TD_String%DrillStemBottom
- Drawworks%TDWellTotalLength = TD_WellGeneral%WellTotalLength
- Drawworks%TDDlMax = TD_String%DlMax
- Drawworks%TDDrillStemComponentsNumbs = TD_String%DrillStemComponentsNumbs
- if (Allocated(Drawworks%TDDrillStemsDownDepth)) deAllocate (Drawworks%TDDrillStemsDownDepth) ! inja gozashtameshun cho momkene tuye startup tedade elemanha dir berese va error bede
- Allocate (Drawworks%TDDrillStemsDownDepth(Drawworks%TDDrillStemComponentsNumbs+400)) ! +400: because of: Add or Remove DrillStem Components
- Drawworks%TDDrillStemsDownDepth = TD_DrillStems%DownDepth
- if (Allocated(Drawworks%TDDrillStemsToolJointRange)) deAllocate (Drawworks%TDDrillStemsToolJointRange)
- Allocate (Drawworks%TDDrillStemsToolJointRange(Drawworks%TDDrillStemComponentsNumbs+400)) ! +400: because of: Add or Remove DrillStem Components
- Drawworks%TDDrillStemsToolJointRange = TD_DrillStems%ToolJointRange
- if (Allocated(Drawworks%TDDrillStemsTopDepth)) deAllocate (Drawworks%TDDrillStemsTopDepth)
- Allocate (Drawworks%TDDrillStemsTopDepth(Drawworks%TDDrillStemComponentsNumbs+400)) ! +400: because of: Add or Remove DrillStem Components
- Drawworks%TDDrillStemsTopDepth = TD_DrillStems%TopDepth
- if (Allocated(Drawworks%TDDrillStemsRtoolJoint)) deAllocate (Drawworks%TDDrillStemsRtoolJoint)
- Allocate (Drawworks%TDDrillStemsRtoolJoint(Drawworks%TDDrillStemComponentsNumbs+400)) ! +400: because of: Add or Remove DrillStem Components
- Drawworks%TDDrillStemsRtoolJoint = TD_DrillStems%RtoolJoint
-
-
-
- !>>> Warnings
- Drawworks%CrownCollision = Warmings%CrownCollision
- Drawworks%FloorCollision = Warmings%FloorCollision
-
-
-
- Drawworks%Conv_Ratio = 1.0d0/.380d0 !che meghdari bashad?????????????????? !Drawworks%FWD_Conv_Ratio(Drawworks%ClutchMode,Drawworks%TransMode)
-
-
-
- DrillingConsole%ParkingBrakeLed = 0
-
-
-
- !===> min&max Hook Height
- if ( Drawworks%DriveType==1 .and. Get_OperationCondition()==OPERATION_DRILL ) then
- if ( Get_Swing()==SWING_WELL_END .and. Get_KellyConnection()==KELLY_CONNECTION_NOTHING ) then
- Drawworks%DrillModeCond = 1
- Drawworks%min_Hook_Height = TD_String%TopJointHeight+OperationScenario%HKL-OperationScenario%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
- Drawworks%DrillModeCond = 2
- Drawworks%min_Hook_Height = TD_String%TopJointHeight+OperationScenario%HKL+OperationScenario%PL-OperationScenario%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
- Drawworks%DrillModeCond = 3
- Drawworks%min_Hook_Height = 21.44d0-OperationScenario%RE ![ft] ?????????? check 21.44=(TD_StConn%KellyConst-TD_StConn%KellyElementConst)
- Drawworks%max_Hook_Height = 120.d0 ![ft]
- else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_KellyConnection()==KELLY_CONNECTION_NOTHING ) then
- Drawworks%DrillModeCond = 4
- Drawworks%min_Hook_Height = 66.d0-OperationScenario%RE ![ft]
- Drawworks%max_Hook_Height = 120.d0 ![ft]
- else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_KellyConnection()==KELLY_CONNECTION_SINGLE ) then
- Drawworks%DrillModeCond = 5
- Drawworks%min_Hook_Height = 65.1d0-OperationScenario%RE ![ft]
- Drawworks%max_Hook_Height = 120.d0 ![ft]
- else if ( Get_Swing()==SWING_RAT_HOLE_END ) then
- Drawworks%DrillModeCond = 6
- Drawworks%min_Hook_Height = 66.d0-OperationScenario%RE ![ft]
- Drawworks%max_Hook_Height = 120.d0 ![ft]
- end if
- else if ( Drawworks%DriveType==1 .and. Get_OperationCondition()==OPERATION_TRIP ) then
- if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING ) then
- Drawworks%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
- Drawworks%DrillModeCond = 8
- Drawworks%min_Hook_Height = TD_String%TopJointHeight+OperationScenario%HL+OperationScenario%SL-(3.d0*OperationScenario%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
- Drawworks%DrillModeCond = 9
- Drawworks%min_Hook_Height = TD_String%TopJointHeight+OperationScenario%HL+OperationScenario%PL-(3.d0*OperationScenario%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
- Drawworks%DrillModeCond = 10
- Drawworks%min_Hook_Height = 18.5d0-OperationScenario%RE ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_NOTHING ) then
- Drawworks%DrillModeCond = 11
- Drawworks%min_Hook_Height = 19.38d0-OperationScenario%RE ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_Swing()==SWING_MOUSE_HOLE_END .and. Get_ElevatorConnection() == ELEVATOR_CONNECTION_SINGLE ) then
- Drawworks%DrillModeCond = 12
- Drawworks%min_Hook_Height = 17.73d0-OperationScenario%RE ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_Swing()==SWING_RAT_HOLE_END ) then
- Drawworks%DrillModeCond = 13
- Drawworks%min_Hook_Height = 27.41d0-OperationScenario%RE ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_Swing()==SWING_WELL_END .and. Get_ElevatorConnection() == ELEVATOR_LATCH_STRING ) then
- Drawworks%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
- Drawworks%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
- Drawworks%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
- Drawworks%DrillModeCond = 27
- Drawworks%min_Hook_Height = 18.38d0 !????????????????? ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- end if
- else if ( Drawworks%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
- Drawworks%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
- Drawworks%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
- Drawworks%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
- Drawworks%DrillModeCond = 18
- Drawworks%min_Hook_Height = max(16.0d0,TD_String%TopJointHeight) ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_STRING ) then
- Drawworks%DrillModeCond = 19
- Drawworks%min_Hook_Height = TD_String%TopJointHeight ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_TdsConnectionModes()==TDS_CONNECTION_STRING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then
- Drawworks%DrillModeCond = 20
- Drawworks%min_Hook_Height = TD_String%TopJointHeight ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then
- Drawworks%DrillModeCond = 21
- Drawworks%min_Hook_Height = max(16.0d0,TD_String%TopJointHeight) ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_LATCH_STAND ) then
- Drawworks%DrillModeCond = 22
- Drawworks%min_Hook_Height = max(16.0d0,TD_String%TopJointHeight) ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_STAND ) then
- Drawworks%DrillModeCond = 23
- Drawworks%min_Hook_Height = max(16.0d0,TD_String%TopJointHeight) ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- else if ( Get_TdsConnectionModes()==TDS_CONNECTION_SPINE .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then
- Drawworks%DrillModeCond = 24
- Drawworks%min_Hook_Height = TD_String%TopJointHeight ![ft]
- Drawworks%max_Hook_Height = 140.d0 ![ft]
- end if
- end if
- end if
-
-
-
- !===> 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
-
-
-
-
- end subroutine Drawworks_Inputs
|