|
- SUBROUTINE AnnulusPropertyCalculator (md, den, pre, tem)
-
- !!! This subroutine gets location of a guage or an observation point and determines information of that point such as pressure, density, velocity and temperature later.
- USE PressureDisplayVARIABLES
- USE Fluid_Flow_Startup_Vars
- USE MudSystemVARIABLES
- USE FricPressDropVars
- USE CDrillWatchVariables
-
- IMPLICIT NONE
- INTEGER, intent(in) :: md ! input
- REAL(8) :: TVD
- real(8), intent(inout) :: den ! output
- real(8), intent(inout) :: pre ! output
- real(8), intent(inout) :: tem ! output
-
-
- INTEGER :: ilocal
-
- CALL TVD_Calculator(md * 1.d0 , TVD)
-
- IF (md <= INT(FinalFlowEl(AnnulusFirstEl)%StartX)) THEN !! mouse pointer is in the annulus space
- DO ilocal = AnnulusFirstEl , AnnulusLastEl
- IF (INT(FinalFlowEl(ilocal)%EndX) <= md) EXIT
- END DO
-
- ELSE IF (md > INT(FinalFlowEl(NumbEl)%EndX)) THEN ! mouse pointer is in the open hole space
- DO ilocal = OpenholeFirstEl , NumbEl
- IF (INT(FinalFlowEl(ilocal)%EndX) <= md) EXIT
- END DO
-
- ELSE
- WRITE (*,*) ' Error in calculating annulus observation point '
- END IF
- pre = FinalFlowEl(ilocal)%StartPress - (FinalFlowEl(ilocal)%StartX - md) * FinalFlowEl(ilocal)%dPdLfric &
- - (FinalFlowEl(ilocal)%StartTVD - TVD) * FinalFlowEl(ilocal)%dPdLGrav
- !write(*,*) ' md, ilocal', md, ilocal
- !WRITE (*,*) ' FlowEl dPdLfric , dPdLGrav', FlowEl(ilocal)%dPdLfric , FlowEl(ilocal)%dPdLGrav
-
- den = FinalFlowEl(ilocal)%Density
-
- !tem = 500
-
-
- END SUBROUTINE
|