|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111 |
- SUBROUTINE Utube
-
- !! This subroutine calculates flow rate when pump is off, pump is disconnected from drill pipe
- !! and both annulus and drill pipe are exposed to atmosphere pressure and thus a U-tube situation is occurs
-
- !! Record of revisions
- !! Date Programmer Discription of change
- !! ------ ------------ -----------------------
- !! 1396/07/29 Sheikh Original code
- !! 1396/08/09 Sheikh Two-side U-tube
- !!
-
- USE FricPressDropVarsModule
- USE MudSystemVARIABLES
- use SimulationVariables !@@@
- use UTUBEVARSModule
- USE Fluid_Flow_Startup_Vars
-
- IMPLICIT NONE
-
-
-
- INTEGER :: i ,j, ibit , ij , ijk
- REAL :: AreaBeforeBit !!! Area of element before bit in U-Tube condition [in^2]
-
- UTUBEVARS%QUTubeInput = 1.0
- UTUBEVARS%QUTubeOutput = 1.0
- data%State%FricPressDrop%TotFricPressLoss = 0
- BitPressLoss = 0
- UTUBEVARS%PressureDp = 0
- UTUBEVARS%PressureAnn = 0
- !!!!!!!!!!!!!!!!!!!!!! Bit
- !!!!!!!!!!!! Calculating Pressure at the bottom of drill string from mud columns in drill pipes and annulus space
-
- UTUBEVARS%PressureDp = SUM(FlowEl(data%State%FricPressDrop%StringFirstEl : data%State%FricPressDrop%StringLastEl)%StaticPressDiff)
-
- UTUBEVARS%PressureAnn = SUM(FlowEl(data%State%FricPressDrop%AnnulusFirstEl : data%State%FricPressDrop%AnnulusLastEl)%StaticPressDiff)
- !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
- !!!!!!!!!!!! U tube:: flow from string to annulus
- IF ((UTUBEVARS%PressureDp - UTUBEVARS%PressureAnn) > UTubePressTolerance) THEN
- DO ijk = 1 , 10
- FlowEl(data%State%FricPressDrop%StringFirstEl : data%State%FricPressDrop%AnnulusLastEl)%Flowrate = UTUBEVARS%QUTubeInput
- !WRITE (*,*) 'QUTubeInput', FlowEl(AnnulusLastEl)%Flowrate
- DO ij = data%State%FricPressDrop%StringFirstEl , data%State%FricPressDrop%AnnulusLastEl !!!!! Updating values of flowrates
- CALL FricPressDrop(ij)
- CALL PartialDerivativeFricToFlowRate(ij)
- !WRITE (*,*) 'FricPressDrop, PartialDerivative', FlowEl(ij)%FricPressLoss, FlowEl(ij)%FricToQPartialDiff, FlowEl(ij)%Length
- END DO
-
- !!!!!!!!!!!!!! Bit pressure drop calculation
- IF (BitTrue) THEN
- i = data%State%FricPressDrop%NoHorizontalEl + data%State%FricPressDrop%NoStringEl
- AreaBeforeBit = FlowEl(i)%Area * Convfttoinch**2
- BitPressLoss = FlowEl(i)%density * Convft3toUSgal * (FlowEl(i)%vel**2 * ((AreaBeforeBit/BitTotNozzArea)**2 - 1.)) / 2. / Convlbftolbm / Convfttoinch**2
- END IF
-
- !!!!!!!!!!!!!!!!!!!!!!!!!!!
- i = data%State%FricPressDrop%NoHorizontalEl + 1
- j = data%State%FricPressDrop%NoHorizontalEl + data%State%FricPressDrop%NoStringEl + data%State%FricPressDrop%NoAnnulusEl
-
- data%State%FricPressDrop%TotFricPressLoss = SUM(FlowEl(i : j)%FricPressLoss) + BitPressLoss
- IF (ABS((UTUBEVARS%PressureDp - UTUBEVARS%PressureAnn) - data%State%FricPressDrop%TotFricPressLoss) <= UTubePressTolerance .OR. UTUBEVARS%QUTubeInput < 1.0) EXIT ! tolerance set to 1.0 psi
- IF ((UTUBEVARS%PressureDp - UTUBEVARS%PressureAnn) > data%State%FricPressDrop%TotFricPressLoss) THEN
- UTUBEVARS%QUTubeInput = UTUBEVARS%QUTubeInput + ((UTUBEVARS%PressureDp - UTUBEVARS%PressureAnn) - data%State%FricPressDrop%TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff)
- ELSE IF ((UTUBEVARS%PressureDp - UTUBEVARS%PressureAnn) < data%State%FricPressDrop%TotFricPressLoss) THEN
- UTUBEVARS%QUTubeInput = UTUBEVARS%QUTubeInput + ((UTUBEVARS%PressureDp - UTUBEVARS%PressureAnn) - data%State%FricPressDrop%TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff)
- END IF
- !WRITE (*,*) 'QUTubeInput, TotFricPressLoss', QUTubeInput, TotFricPressLoss
- !WRITE (*,*) '1) PressureDp, PressureAnn', PressureDp, PressureAnn, TotFricPressLoss, QUTubeInput
-
- END DO
- UTUBEVARS%QUTubeOutput = 0.0
- !!!!!!!!!!!!!!!!!!!!!!!!
- !!!!!!!!!!!! U tube:: flow from annulus to string
- ELSE IF ((UTUBEVARS%PressureAnn - UTUBEVARS%PressureDp) > UTubePressTolerance) THEN
- DO ijk = 1 , 10
- DO ij = data%State%FricPressDrop%NoHorizontalEl + 1 , data%State%FricPressDrop%NoHorizontalEl + data%State%FricPressDrop%NoStringEl + data%State%FricPressDrop%NoAnnulusEl !!!!! Updating values of flowrates
- FlowEl(ij)%Flowrate = UTUBEVARS%QUTubeOutput
- CALL FricPressDrop(ij)
- CALL PartialDerivativeFricToFlowRate(ij)
- END DO
-
- !!!!!!!!!!!!!! Bit pressure drop calculation
- IF (BitTrue) THEN
- i = data%State%FricPressDrop%NoHorizontalEl + data%State%FricPressDrop%NoStringEl + 1
- AreaBeforeBit = FlowEl(i)%Area * Convfttoinch**2
- BitPressLoss = FlowEl(i)%density * Convft3toUSgal * (FlowEl(i)%vel**2 * ((AreaBeforeBit/BitTotNozzArea)**2 - 1.)) / 2. / Convlbftolbm / Convfttoinch**2
- END IF
- !!!!!!!!!!!!!!!!!!!!!!!!!!!
- i = data%State%FricPressDrop%NoHorizontalEl + 1
- j = data%State%FricPressDrop%NoHorizontalEl + data%State%FricPressDrop%NoStringEl + data%State%FricPressDrop%NoAnnulusEl
- data%State%FricPressDrop%TotFricPressLoss = SUM(FlowEl(i : j)%FricPressLoss) + BitPressLoss
-
- IF (ABS((UTUBEVARS%PressureDp - UTUBEVARS%PressureAnn) - data%State%FricPressDrop%TotFricPressLoss) <= UTubePressTolerance) EXIT ! tolerance set to 1.0 psi
- IF ((UTUBEVARS%PressureAnn - UTUBEVARS%PressureDp) > data%State%FricPressDrop%TotFricPressLoss) THEN
- UTUBEVARS%QUTubeOutput = UTUBEVARS%QUTubeOutput - (((UTUBEVARS%PressureAnn - UTUBEVARS%PressureDp) - data%State%FricPressDrop%TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff))
- ELSE IF ((UTUBEVARS%PressureAnn - UTUBEVARS%PressureDp) < data%State%FricPressDrop%TotFricPressLoss) THEN
- UTUBEVARS%QUTubeOutput = UTUBEVARS%QUTubeOutput + (((UTUBEVARS%PressureAnn - UTUBEVARS%PressureDp) - data%State%FricPressDrop%TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff))
- END IF
- !WRITE (*,*) 'QUTubeOutput, TotFricPressLoss', QUTubeOutput, TotFricPressLoss
-
- WRITE (*,*) '2) PressureDp, PressureAnn', UTUBEVARS%PressureDp, UTUBEVARS%PressureAnn, data%State%FricPressDrop%TotFricPressLoss
- END DO
- UTUBEVARS%QUTubeInput = 0.0
- !!!!!!!!!!!! No U-Tube
- ELSE
- UTUBEVARS%QUTubeInput = 0.0
- UTUBEVARS%QUTubeOutput = 0.0
- END IF
-
- END SUBROUTINE
|