|
- subroutine RTable_INPUTS
-
- use CDrillingConsoleVariables
- ! use CSimulationVariables
- use CTdsConnectionModesEnumVariables
- use CTdsElevatorModesEnumVariables
- use CHoistingVariables
- use RTable_VARIABLES
- use TD_DrillStemComponents
- use CUnityInputs
- use CWarningsVariables
- use UnitySignalVariables
-
- IMPLICIT NONE
- integer :: i
-
-
-
- RTable%AssignmentSwitch = DrillingConsole%AssignmentSwitch
- RTable%Switch = DrillingConsole%RTSwitch
- !RTable%GearsAbuse = RotaryGearsAbuse
- RTable%Throttle = DrillingConsole%RTThrottle ![RPM]
- RTable%String_Torque = TD_String%StringTorque*12.d0 ![lb.ft]*12 ---> [lb.in] ?????????
- !RTable%RpmGaugeMalf !:dar module haye C meghdardehi mishe
-
-
-
-
- RTable%N_new = RTable%Throttle
- if ( RTable%MotorFaileMalf==1 ) then
- RTable%N_new = 0.d0
- end if
- RTable%String_Torque = 0.112984d0*RTable%String_Torque ![N.m]
-
-
-
- !===> String_JCoef Calculation
- if ( Hoisting%DriveType==0 ) then
- if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then
- RTable%RotaryMode = 1
- RTable%String_JCoef = 0.d0
- Do i = 1,TD_String%StringConfigurationCount
- RTable%String_JCoef = RTable%String_JCoef+( (TD_DrillStem(i)%TotalWeight*((TD_DrillStem(i)%Id**2.d0)+(TD_DrillStem(i)%Od**2.d0)))/8.d0 ) ![lb.ft^2] , Jz=(1/2)*m*(r1^2+r2^2)
- End Do
- RTable%String_JCoef = RTable%String_JCoef*0.0421401d0 ![kg.m^2]
- else if ( Get_Slips() /= SLIPS_SET_END ) then
- RTable%RotaryMode = 2
- RTable%String_JCoef = 0.d0
- RTable%String_Torque = 0.d0
- else
- RTable%RotaryMode = 3
- RTable%String_JCoef = 0.d0
- RTable%String_Torque = 0.d0
- end if
- else if ( Hoisting%DriveType==1 ) then
- if ( Get_IsKellyBushingSetInTable() .or. Get_Slips() == SLIPS_SET_END ) then !if rotary connected to string
- RTable%RotaryMode = 4
- RTable%String_JCoef = 0.d0
- Do i = 1,TD_String%StringConfigurationCount
- RTable%String_JCoef = RTable%String_JCoef+( (TD_DrillStem(i)%TotalWeight*((TD_DrillStem(i)%Id**2.d0)+(TD_DrillStem(i)%Od**2.d0)))/8.d0 ) ![lb.ft^2] , Jz=(1/2)*m*(r1^2+r2^2)
- End Do
- RTable%String_JCoef = RTable%String_JCoef*0.0421401e0 ![kg.m^2]
- else
- RTable%RotaryMode = 5
- RTable%String_JCoef = 0.d0
- RTable%String_Torque = 0.d0
- end if
- end if
-
-
- !===> Transmission Mode
- RTable%Conv_Ratio = RTable%High_Conv_Ratio
-
-
-
- end subroutine RTable_INPUTS
|