Simulation Core
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 
 
 

47 lines
1.9 KiB

  1. SUBROUTINE AnnulusPropertyCalculator (md, den, pre, tem)
  2. !!! 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.
  3. use PressureDisplayVARIABLESModule
  4. USE Fluid_Flow_Startup_Vars
  5. USE MudSystemVARIABLES
  6. use SimulationVariables !@@@
  7. USE FricPressDropVarsModule
  8. ! use ConfigurationVariables !@
  9. use SimulationVariables
  10. IMPLICIT NONE
  11. INTEGER, intent(in) :: md ! input
  12. REAL(8) :: TVD
  13. real(8), intent(inout) :: den ! output
  14. real(8), intent(inout) :: pre ! output
  15. real(8), intent(inout) :: tem ! output
  16. INTEGER :: ilocal
  17. CALL TVD_Calculator(md * 1.d0 , TVD)
  18. IF (md <= INT(FinalFlowEl(data%State%FricPressDrop%AnnulusFirstEl)%StartX)) THEN !! mouse pointer is in the annulus space
  19. DO ilocal = data%State%FricPressDrop%AnnulusFirstEl , data%State%FricPressDrop%AnnulusLastEl
  20. IF (INT(FinalFlowEl(ilocal)%EndX) <= md) EXIT
  21. END DO
  22. ELSE IF (md > INT(FinalFlowEl(data%State%FricPressDrop%NumbEl)%EndX)) THEN ! mouse pointer is in the open hole space
  23. DO ilocal = data%State%FricPressDrop%OpenholeFirstEl , data%State%FricPressDrop%NumbEl
  24. IF (INT(FinalFlowEl(ilocal)%EndX) <= md) EXIT
  25. END DO
  26. ELSE
  27. WRITE (*,*) ' Error in calculating annulus observation point '
  28. END IF
  29. pre = FinalFlowEl(ilocal)%StartPress - (FinalFlowEl(ilocal)%StartX - md) * FinalFlowEl(ilocal)%dPdLfric &
  30. - (FinalFlowEl(ilocal)%StartTVD - TVD) * FinalFlowEl(ilocal)%dPdLGrav
  31. !write(*,*) ' md, ilocal', md, ilocal
  32. !WRITE (*,*) ' FlowEl dPdLfric , dPdLGrav', FlowEl(ilocal)%dPdLfric , FlowEl(ilocal)%dPdLGrav
  33. den = FinalFlowEl(ilocal)%Density
  34. !tem = 500
  35. END SUBROUTINE