|
- module PressureDisplayVARIABLESModule
-
- USE DynamicRealArray,only:DynamicRealArrayType
-
- IMPLICIT NONE
-
- TYPE PressureDisplayVARIABLESTYPE
- INTEGER :: NoGauges
- REAL , DIMENSION(6) :: PressureGauges
- INTEGER , DIMENSION(3) :: PressureTimeStepDelay
- END TYPE PressureDisplayVARIABLESTYPE
-
-
- INTEGER :: SoundSpeed ! speed of sound [ft/s]
-
- TYPE(DynamicRealArrayType) :: PumpPressureDelay
- TYPE(DynamicRealArrayType) :: CasingPressureDelay
- TYPE(DynamicRealArrayType) :: BottomHolePressureDelay
- TYPE(DynamicRealArrayType) :: ShoePressureDelay
-
-
- TYPE :: ObservationAndGaugePointsInformations ! We have some gauges and may be have many observation points like casing shoe, bottomhole , etc.
- ! This module stores information of these points to calculate pressure, density and other desired properties
- ! at these points
- ! Locations: 1: Stand Pipe , 2: Choke Manifold, 3: Botton Hole, 4: Under Bit, 5: Shoe, 6: Before BOP
- INTEGER :: ElementNo ! Element Nubmer based on mud elements
- REAL :: DistancetoRefrence ! Distance from pump or the end of fluid path [ft]
- REAL :: ElementTrueDepth ! True depth of point or gauge [ft]
- REAL :: Pressure ! Pressure [psi]
- END TYPE
-
- !TYPE(ObservationAndGaugePointsInformations) , ALLOCATABLE :: GaugePoint(:)
-
- END MODULE
|