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 FricPressDropVars USE MudSystemVARIABLES USE UTUBEVARS 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] QUTubeInput = 1.0 QUTubeOutput = 1.0 TotFricPressLoss = 0 BitPressLoss = 0 PressureDp = 0 PressureAnn = 0 !!!!!!!!!!!!!!!!!!!!!! Bit !!!!!!!!!!!! Calculating Pressure at the bottom of drill string from mud columns in drill pipes and annulus space PressureDp = SUM(FlowEl(StringFirstEl : StringLastEl)%StaticPressDiff) PressureAnn = SUM(FlowEl(AnnulusFirstEl : AnnulusLastEl)%StaticPressDiff) !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!! U tube:: flow from string to annulus IF ((PressureDp - PressureAnn) > UTubePressTolerance) THEN DO ijk = 1 , 10 FlowEl(StringFirstEl : AnnulusLastEl)%Flowrate = QUTubeInput !WRITE (*,*) 'QUTubeInput', FlowEl(AnnulusLastEl)%Flowrate DO ij = StringFirstEl , 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 = NoHorizontalEl + 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 = NoHorizontalEl + 1 j = NoHorizontalEl + NoStringEl + NoAnnulusEl !IF (ALLOCATED(FlowEl)) THEN ! WRITE (*,*) ' H, S, A, Ch, O', NoHorizontalEl , NoStringEl , NoAnnulusEl , NoWellToChokeEl , NoOpenHoleEl !END IF TotFricPressLoss = SUM(FlowEl(i : j)%FricPressLoss) + BitPressLoss IF (ABS((PressureDp - PressureAnn) - TotFricPressLoss) <= UTubePressTolerance .OR. QUTubeInput < 1.0) EXIT ! tolerance set to 1.0 psi IF ((PressureDp - PressureAnn) > TotFricPressLoss) THEN QUTubeInput = QUTubeInput + ((PressureDp - PressureAnn) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff) ELSE IF ((PressureDp - PressureAnn) < TotFricPressLoss) THEN QUTubeInput = QUTubeInput + ((PressureDp - PressureAnn) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff) END IF !WRITE (*,*) 'QUTubeInput, TotFricPressLoss', QUTubeInput, TotFricPressLoss !WRITE (*,*) '1) PressureDp, PressureAnn', PressureDp, PressureAnn, TotFricPressLoss, QUTubeInput END DO QUTubeOutput = 0.0 !!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!! U tube:: flow from annulus to string ELSE IF ((PressureAnn - PressureDp) > UTubePressTolerance) THEN DO ijk = 1 , 10 DO ij = NoHorizontalEl + 1 , NoHorizontalEl + NoStringEl + NoAnnulusEl !!!!! Updating values of flowrates FlowEl(ij)%Flowrate = QUTubeOutput CALL FricPressDrop(ij) CALL PartialDerivativeFricToFlowRate(ij) END DO !!!!!!!!!!!!!! Bit pressure drop calculation IF (BitTrue) THEN !DO i = NumbEl , 1 , -1 !! This loop starts from the first elements of string and check the elements to reach the bit at the bottom of string ! IF (FlowEl(i)%Id==0) CYCLE i = NoHorizontalEl + 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 !IF (FlowEl(i)%Id>0) EXIT !END DO END IF !!!!!!!!!!!!!!!!!!!!!!!!!!! i = NoHorizontalEl + 1 j = NoHorizontalEl + NoStringEl + NoAnnulusEl TotFricPressLoss = SUM(FlowEl(i : j)%FricPressLoss) + BitPressLoss IF (ABS((PressureDp - PressureAnn) - TotFricPressLoss) <= UTubePressTolerance) EXIT ! tolerance set to 1.0 psi IF ((PressureAnn - PressureDp) > TotFricPressLoss) THEN QUTubeOutput = QUTubeOutput - (((PressureAnn - PressureDp) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff)) ELSE IF ((PressureAnn - PressureDp) < TotFricPressLoss) THEN QUTubeOutput = QUTubeOutput + (((PressureAnn - PressureDp) - TotFricPressLoss) / SUM(FlowEl(i : j)%FricToQPartialDiff)) END IF !WRITE (*,*) 'QUTubeOutput, TotFricPressLoss', QUTubeOutput, TotFricPressLoss WRITE (*,*) '2) PressureDp, PressureAnn', PressureDp, PressureAnn, TotFricPressLoss END DO QUTubeInput = 0.0 !!!!!!!!!!!! No U-Tube ELSE QUTubeInput = 0.0 QUTubeOutput = 0.0 END IF END SUBROUTINE