subroutine RTable_INPUTS
    
    use CDrillingConsoleVariables
    use CDataDisplayConsoleVariables
    use CSimulationVariables
    use CTdsConnectionModesEnumVariables
    use CTdsElevatorModesEnumVariables
    use CHoistingVariables
    use RTable_VARIABLES
    use TD_DrillStemComponents
    use CUnityInputs
    use CSlipsEnumVariables
    
    IMPLICIT NONE
    integer :: i
    
    
    
    !===> String Torque
    !print* , 'TD_StringTorquert=' , TD_StringTorque
    RTable%String_Torque = TD_StringTorque*12.d0              ![lb.ft]*12 ---> [lb.in]  ?????????
    !RTable%String_Torque = 20000.
    RTable%String_Torque = 0.112984829*RTable%String_Torque   ![N.m]
    !print* , 'TD_StringTorquert2=' , RTable%String_Torque
    
    
    
    
    !===> String_JCoef Calculation
    if ( DriveType==0 ) then
        if ( Get_TdsConnectionModes()==TDS_CONNECTION_NOTHING .and. Get_TdsElevatorModes()==TDS_ELEVATOR_CONNECTION_NOTHING ) then
            RT_RotaryMode = 1
            RTable%String_JCoef = 0.0
            Do i = 1,TD_StringConfigurationCount
                RTable%String_JCoef  = RTable%String_JCoef+( (TD_DrillStem(i)%TotalWeight*((TD_DrillStem(i)%Id**2)+(TD_DrillStem(i)%Od**2)))/8.0 )   ![lb.ft^2] , Jz=(1/2)*m*(r1^2+r2^2)
            End Do
            RTable%String_JCoef = RTable%String_JCoef*0.0421401   ![kg.m^2]
        else if ( Get_Slips() /= SLIPS_SET_END ) then
            RT_RotaryMode = 2
            RTable%String_JCoef  = 0.0
            RTable%String_Torque = 0.0
        else
            RT_RotaryMode = 3
            RTable%String_JCoef  = 0.0
            RTable%String_Torque = 0.0
        end if
    else if ( DriveType==1 ) then
        if ( Get_IsKellyBushingSetInTable() .or. Get_Slips() == SLIPS_SET_END ) then        !if rotary connected to string
            RT_RotaryMode = 4
            RTable%String_JCoef = 0.0
            Do i = 1,TD_StringConfigurationCount
                RTable%String_JCoef  = RTable%String_JCoef+( (TD_DrillStem(i)%TotalWeight*((TD_DrillStem(i)%Id**2)+(TD_DrillStem(i)%Od**2)))/8.0 )   ![lb.ft^2] , Jz=(1/2)*m*(r1^2+r2^2)
            End Do
            RTable%String_JCoef = RTable%String_JCoef*0.0421401   ![kg.m^2]
        else
            RT_RotaryMode = 5
            RTable%String_JCoef  = 0.0
            RTable%String_Torque = 0.0  
        end if
    end if
    !print*, 'DriveType=', DriveType , RT_RotaryMode , Get_IsKellyBushingSetInTable() , Get_Slips()
    !if ( Get_IsKellyBushingSetInTable() .or. Get_Slips() == SLIPS_SET_END ) then        !if rotary connected to string
    !    RTable%String_JCoef = 0.0
    !    Do i = 1,TD_StringConfigurationCount
    !        RTable%String_JCoef  = RTable%String_JCoef+( (TD_DrillStem(i)%TotalWeight*((TD_DrillStem(i)%Id**2)+(TD_DrillStem(i)%Od**2)))/8.0 )   ![lb.ft^2] , Jz=(1/2)*m*(r1^2+r2^2)
    !    End Do
    !    RTable%String_JCoef = RTable%String_JCoef*0.0421401   ![kg.m^2]
    !else
    !    RTable%String_JCoef  = 0.0
    !    RTable%String_Torque = 0.0  
    !end if
    !RTable%String_JCoef = RTable%String_JCoef/10.  !???????? /10: with no reason, check it
    
    
    
    
    !===> Transmission Mode
    if (RTTransmissionLever==1) then              ! in high mode
        RTable%Conv_Ratio = RTable%High_Conv_Ratio
    else if (RTTransmissionLever==-1) then        ! in low mode
        RTable%Conv_Ratio = RTable%Low_Conv_Ratio
    else if (RTTransmissionLever==0) then         ! in low mode
        RTable%Conv_Ratio = RTable%Low_Conv_Ratio
    end if
    
    
    
    
    
end subroutine RTable_INPUTS