|
- MODULE TD_DrillStemComponents
-
- Use CDownHoleVariables
-
- IMPLICIT NONE
- PUBLIC
-
-
- !************************************************************************************************************************************
- TYPE, PUBLIC :: TD_StringInfo
- INTEGER :: StringConfigurationCount , DrillStemComponentsNumbs , DrillStemForceType
- INTEGER :: NoHorizontalMudElements , NoStringMudElements , NoCasingMudElements
- REAL(8) :: DrillStemTotalLength , DrillStemTotalLengthIni , OutOfWellLength , DrillStemTotalWeight , DrillStemBottom
- REAL(8) :: DrillStemAxialVelocity , DrillStemRotVelocity , TopJointHeight
- REAL(8) :: WeightOnBit , BitTorque , TotalTorque , StaticHookLoad , DlMax , DlTotal , DlTouch
- REAL(8) :: HookLoad , StringTorque
- REAL(8) :: ToolJointRange
- real(8) , allocatable :: FluidMudDensity(:) , FluidMudEndX(:) , FluidMudStartX(:)
- !====================================================
- ! Separated Parts of the Drill Stem
- INTEGER :: NearFloorConnectionNo
- REAL(8) :: NearFloorConnectionHeight
- !====================================================
- END TYPE TD_StringInfo
- !************************************************************************************************************************************
-
-
-
- !************************************************************************************************************************************
- !====================================================
- ! Drill Stem Components Info
- !====================================================
- TYPE, PUBLIC :: TD_DrillStemInfo
- INTEGER :: Numbs , ComponentType
- REAL(8) :: Length , TopDepth , DownDepth , Od , Id , WeightperLength , TotalLength , TotalWeight
- END TYPE TD_DrillStemInfo
- !************************************************************************************************************************************
-
-
-
- !************************************************************************************************************************************
- !====================================================
- ! Separated Parts of the Drill Stem
- !====================================================
- TYPE , PUBLIC :: TD_SeparatedDrillStemInfo
- !=========> Elements Geometry
- INTEGER :: HoleType , ComponentType
- REAL(8) :: Length , TopDepth , DownDepth , Od , Id , Area , Weight , WeightperLength , StartAngle , EndAngle
- REAL(8) :: RCurvature , RtoolJoint , HoleDiameter , ToolJointRange
- !=========> Elements initial Geometry
- REAL(8) :: LengthIni , TopDepthIni , DownDepthIni , StartAngleIni , EndAngleIni
- !=========> Elements initial Geometry (graphic)
- REAL(8) :: TopDepthIniG , DownDepthIniG
- !=========> Pipes Properties
- REAL(8) :: Density , ElasticModule
- !=========> Forces Info
- REAL(8) :: Force1 , Force2 , Torque , Drag , CombVelRatio
- !=========> Mud Properties
- REAL(8) :: MudDensityIn , MudDensityOut , MudViscosity , MudVisCorrectCoef , BouyancyFactor , MudWeight , MudPlasticVis , MudYieldPoint
- !=========> Viscous Drag Force
- REAL(8) :: FricFactor , DiamRatio , MudClingingConst , PipeVelocity , AveEffVelocity , ReNumber , Dp_Dl
- !=========> Hook Load
- REAL(8) :: StaticHookLoad , TotalSHookLoad , Dl , DlTotal
- END TYPE TD_SeparatedDrillStemInfo
- !************************************************************************************************************************************
-
-
-
- !************************************************************************************************************************************
- !====================================================
- ! Add&Remove DrillStem Components
- !====================================================
- TYPE , PUBLIC :: TD_AddRemoveInfo
- INTEGER :: IBOPNewAdd , IBOPOldAdd , SafetyValveNewAdd , SafetyValveOldAdd , KellyNewAdd , KellyOldAdd
- INTEGER :: IBOPNewRemove , IBOPOldRemove , SafetyValveNewRemove , SafetyValveOldRemove , KellyNewRemove , KellyOldRemove
- INTEGER , Dimension(19) :: KellyOldStatus , KellyNewStatus
- !integer :: TD_KellyOldStatus1 , TD_KellyNewStatus1 , TD_KellyOldStatus2 , TD_KellyNewStatus2 , TD_KellyOldStatus3 , TD_KellyNewStatus3
- !integer :: TD_KellyOldStatus4 , TD_KellyNewStatus4 , TD_KellyOldStatus5 , TD_KellyNewStatus5 , TD_KellyOldStatus6 , TD_KellyNewStatus6
- !integer :: TD_KellyOldStatus7 , TD_KellyNewStatus7 , TD_KellyOldStatus8 , TD_KellyNewStatus8
- !integer :: TD_KellyOldStatus9 , TD_KellyNewStatus9 , TD_KellyOldStatus10 , TD_KellyNewStatus10
- !integer :: TD_KellyOldStatus11 , TD_KellyNewStatus11 , TD_KellyOldStatus12 , TD_KellyNewStatus12
- !integer :: TD_KellyOldStatus13 , TD_KellyNewStatus13 , TD_KellyOldStatus14 , TD_KellyNewStatus14
- !integer :: TD_KellyOldStatus15 , TD_KellyNewStatus15 , TD_KellyOldStatus16 , TD_KellyNewStatus16 , TD_KellyOldStatus17 , TD_KellyNewStatus17
- !integer :: TD_KellyOldStatus18 , TD_KellyNewStatus18 , TD_KellyOldStatus19 , TD_KellyNewStatus19
- END TYPE TD_AddRemoveInfo
- !************************************************************************************************************************************
-
-
-
- !************************************************************************************************************************************
- !====================================================
- ! Graphic Output Info
- !====================================================
- !TYPE, PUBLIC :: CStringComponent
- ! Integer :: ComponentType
- ! REAL(8) :: Length , TopDepth , DownDepth , Od , Id
- !END TYPE CStringComponent
- !************************************************************************************************************************************
-
-
-
- !************************************************************************************************************************************
- !====================================================
- ! Removed-Volume Variables
- !====================================================
- TYPE , PUBLIC :: TD_RemovedVolumeInfo
- Integer :: PreCount
- REAL(8) :: RemoveVolume , PreElementVolume , PreElementLength
- END TYPE TD_RemovedVolumeInfo
- !************************************************************************************************************************************
- END MODULE TD_DrillStemComponents
|