|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128 |
- MODULE TD_DrillStemComponents
-
- Use CDownHoleVariables
-
- IMPLICIT NONE
- PUBLIC
-
- INTEGER :: TD_StringConfigurationCount , TD_DrillStemComponentsNumbs , TD_DrillStemForceType
- REAL(8) :: TD_DrillStemTotalLength , TD_DrillStemTotalLengthIni , TD_OutOfWellLength , TD_DrillStemTotalWeight , TD_DrillStemBottom
- REAL(8) :: TD_DrillStemAxialVelocity , TD_DrillStemRotVelocity , TD_TopJointHeight
- REAL(8) :: TD_WeightOnBit , TD_BitTorque , TD_TotalTorque , TD_StaticHookLoad , TD_DlMax , TD_DlTotal , TD_DlTouch
- REAL(8) :: TD_HookLoad , TD_StringTorque
- REAL(8) :: TD_ToolJointRange
- real(8) , allocatable :: TD_FluidMudDensity(:) , TD_FluidMudEndX(:) , TD_FluidMudStartX(:)
- INTEGER :: TD_NoHorizontalMudElements , TD_NoStringMudElements , TD_NoCasingMudElements
-
-
-
-
-
- !====================================================
- ! 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
-
- TYPE(TD_DrillStemInfo), ALLOCATABLE, DIMENSION(:) :: TD_DrillStem
-
-
-
-
-
-
-
- !====================================================
- ! 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
-
- TYPE(TD_SeparatedDrillStemInfo), ALLOCATABLE, DIMENSION(:) :: TD_DrillStems
-
-
-
-
-
-
-
- !====================================================
- ! Separated Parts of the Drill Stem
- !====================================================
-
- INTEGER :: TD_NearFloorConnectionNo
- REAL(8) :: TD_NearFloorConnectionHeight
-
-
-
-
-
-
- !====================================================
- ! Add&Remove DrillStem Components
- !====================================================
- integer :: TD_IBOPNewAdd , TD_IBOPOldAdd , TD_SafetyValveNewAdd , TD_SafetyValveOldAdd , TD_KellyNewAdd , TD_KellyOldAdd
- integer :: TD_IBOPNewRemove , TD_IBOPOldRemove , TD_SafetyValveNewRemove , TD_SafetyValveOldRemove , TD_KellyNewRemove , TD_KellyOldRemove
- 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
-
-
-
-
-
- !====================================================
- ! Graphic Output Info
- !====================================================
-
- !TYPE, PUBLIC :: CStringComponent
- ! Integer :: ComponentType
- ! REAL(8) :: Length , TopDepth , DownDepth , Od , Id
- !END TYPE CStringComponent
-
- TYPE(CStringComponents), ALLOCATABLE, DIMENSION(:) :: G_StringElement
-
-
-
-
-
-
- !====================================================
- ! Removed-Volume Variables
- !====================================================
- Integer :: TD_PreCount
- REAL(8) :: TD_RemoveVolume , TD_PreElementVolume , TD_PreElementLength
-
-
-
-
-
-
- END MODULE TD_DrillStemComponents
|