subroutine Pump_and_TripIn ! is called in subroutine CirculationCodeSelect Use GeoElements_FluidModule USE CMudPropertiesVariables USE MudSystemVARIABLES USE Pumps_VARIABLES !USE CHOKEVARIABLES !USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure !use CManifolds use CDrillWatchVariables !use CHOKEVARIABLES !use CChokeManifoldVariables !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity USE sROP_Other_Variables USE sROP_Variables Use KickVariables Use CShoeVariables use CError implicit none integer i,ii,AddLocation !===========================================================WELL============================================================ !===========================================================WELL============================================================ MudSystem%StringFlowRate= MUD(2)%Q MudSystem%AnnulusFlowRate= MUD(2)%Q !write(*,*) 'Trip In' !========================Horizontal PIPE ENTRANCE================= if (ABS(MudSystem%SuctionDensity_Old - MudSystem%Suction_Density_MudSystem) >= MudSystem%DensityMixTol) then ! new mud is pumped call MudSystem%Hz_Density%AddToFirst (MudSystem%Suction_Density_MudSystem) call MudSystem%Hz_MudDischarged_Volume%AddToFirst (0.0d0) call MudSystem%Hz_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(1)) call MudSystem%Hz_Mud_Forehead_section%AddToFirst (1) call MudSystem%Hz_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(1)) call MudSystem%Hz_Mud_Backhead_section%AddToFirst (1) call MudSystem%Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%Hz_MudOrKick%AddToFirst (0) MudSystem%SuctionDensity_Old= MudSystem%Suction_Density_MudSystem endif !========================Horizontal PIPE STRING================= MudSystem%Hz_MudDischarged_Volume%Array(1)= MudSystem%Hz_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) MudSystem%total_add = MudSystem%total_add + ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then MudSystem%total_add= 0. endif !write(*,*) ' total decrease(add to HZ)=' , total_add !write(*,*) ' add to HZ=' , ((MudSystem%StringFlowRate/60.0d0)*DeltaT_Mudline) imud=0 do while (imud < MudSystem%Hz_Mud_Forehead_X%Length()) imud = imud + 1 if (imud> 1) then MudSystem%Hz_Mud_Backhead_X%Array(imud)= MudSystem%Hz_Mud_Forehead_X%Array(imud-1) MudSystem%Hz_Mud_Backhead_section%Array(imud)= MudSystem%Hz_Mud_Forehead_section%Array(imud-1) endif MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))) & / ABS(MudSystem%Xend_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))) ! +1 for string , -1 for annulus MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))- MudSystem%Hz_Mud_Backhead_X%Array(imud))* & MudSystem%Area_PipeSectionFt(MudSystem%Hz_Mud_Backhead_section%Array(imud)) !(ft^3) MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal if ( MudSystem%Hz_MudDischarged_Volume%Array(imud) <= MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)) then MudSystem%Hz_Mud_Forehead_section%Array(imud)= MudSystem%Hz_Mud_Backhead_section%Array(imud) MudSystem%Hz_Mud_Forehead_X%Array(imud)= MudSystem%Hz_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%Hz_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%Hz_Mud_Backhead_section%Array(imud)) else MudSystem%isection= MudSystem%Hz_Mud_Backhead_section%Array(imud)+1 MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Hz_MudDischarged_Volume%Array(imud)- MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud) do if (MudSystem%isection > 1) then ! (horizontal pipe exit) MudSystem%Hz_MudDischarged_Volume%Array(imud)= MudSystem%Hz_MudDischarged_Volume%Array(imud)- MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud) MudSystem%Hz_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(1) MudSystem%Hz_Mud_Forehead_section%Array(imud)= 1 if (MudSystem%Hz_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string call RemoveHzMudArrays(imud) endif exit endif MudSystem%xx= MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal) if (MudSystem%xx<= 1.0) then MudSystem%Hz_Mud_Forehead_section%Array(imud)= MudSystem%isection MudSystem%Hz_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection) exit else MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) MudSystem%isection= MudSystem%isection+ 1 endif enddo endif enddo !========================Horizontal PIPE END================= !========================Utube1 Air Element Removing================= !if (UtubeMode1Activated== .true.) then ! StringUpdate == .true. ! ! ! !StringDensity_Old=MudSystem%St_Density%Array(2) ! ! write(*,*) 'StringDensity_Old=' , StringDensity_Old ! ! UtubeMode1Activated= .false. !endif !========================Utube1 Air Element Removing End================= !!========================Utube2 Removing from Annulus================= not needed 97.04.26 ! ! if (UtubeMode2Activated== .true.) then ! StringUpdate == .true. ! ! if (Ann_MudOrKick%Last() == 104) then !movaghati. albate age merge anjam shode bashe moshkeli nist ! call RemoveAnnulusMudArrays(Ann_MudOrKick%Length()) ! endif ! ! UtubeMode2Activated= .false. ! endif ! ! !!========================Utube2 Removing from Annulus End================= !========================New Pipe Filling================= !if (F_StringIntervalCounts > F_StringIntervalCountsOld) then ! StringUpdate == .true. if (MudSystem%AddedElementsToString > 0) then ! StringUpdate == .true. !NoPipeAdded= F_Counts%StringIntervalCounts - F_StringIntervalCountsOld MudSystem%NewPipeFilling=0 IF (MudSystem%St_MudOrKick%First() == 104) then MudSystem%St_MudDischarged_Volume%Array(1) = MudSystem%St_MudDischarged_Volume%Array(1) + sum(MudSystem%PipeSection_VolumeCapacity(2:1+MudSystem%AddedElementsToString)) ! new pipe is filled by air else call MudSystem%St_Density%AddToFirst (0.d0) call MudSystem%St_MudDischarged_Volume%AddToFirst (sum(MudSystem%PipeSection_VolumeCapacity(2:1+MudSystem%AddedElementsToString))) call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(2)) call MudSystem%St_Mud_Forehead_section%AddToFirst (2) call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2)) call MudSystem%St_Mud_Backhead_section%AddToFirst (2) call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.d0) call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.d0) call MudSystem%St_MudOrKick%AddToFirst (104) endif endif !F_StringIntervalCountsOld= F_StringIntervalCounts if (MudSystem%NewPipeFilling == 0) then ! 2= is the first element of string (1= is for Hz pipe) MudSystem%LackageMudVolume= MudSystem%St_MudDischarged_Volume%Array(1) ! = Air element write(*,*) 'LackageMudVolume=' , MudSystem%LackageMudVolume if (ABS(MudSystem%St_Density%Array(2) - MudSystem%Hz_Density%Last()) >= MudSystem%DensityMixTol) then ! new mud is pumped call MudSystem%St_Density%AddTo (2,MudSystem%Hz_Density%Last()) call MudSystem%St_MudDischarged_Volume%AddTo (2, 0.d0) call MudSystem%St_Mud_Forehead_X%AddTo (2,MudSystem%Xstart_PipeSection(2)) call MudSystem%St_Mud_Forehead_section%AddTo (2 , 2) call MudSystem%St_Mud_Backhead_X%AddTo (2,MudSystem%Xstart_PipeSection(2)) call MudSystem%St_Mud_Backhead_section%AddTo (2 ,2) call MudSystem%St_RemainedVolume_in_LastSection%AddTo (2,0.d0) call MudSystem%St_EmptyVolume_inBackheadLocation%AddTo (2,0.d0) call MudSystem%St_MudOrKick%AddTo (2,0) !StringDensity_Old= Hz_Density%Last() endif MudSystem%St_MudDischarged_Volume%Array(2)= MudSystem%St_MudDischarged_Volume%Array(2)+ min( ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline), MudSystem%LackageMudVolume) !(gal) MudSystem%St_MudDischarged_Volume%Array(1)= MudSystem%St_MudDischarged_Volume%Array(1)- min( ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline), MudSystem%LackageMudVolume) ! air(gal) !LackageMudVolumeAfterFilling= sum(PipeSection_VolumeCapacity(2:F_StringIntervalCounts)) - sum(St_MudDischarged_Volume%Array(:)) MudSystem%LackageMudVolumeAfterFilling= MudSystem%St_MudDischarged_Volume%Array(1) ! last time it should be zero if (MudSystem%LackageMudVolumeAfterFilling == 0.) then MudSystem%NewPipeFilling= 1 call RemoveStringMudArrays(1) MudSystem%St_Mud_Backhead_X%Array(1) = MudSystem%Xstart_PipeSection(2) MudSystem%St_Mud_Backhead_section%Array(1) = 2 endif endif !========================New Pipe Filling End================= if (MudSystem%NewPipeFilling == 0) then MudSystem%StringFlowRate= 0. MudSystem%AnnulusFlowRate= 0. endif MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate !========================STRING ENTRANCE================= if (MudSystem%StringFlowRateFinal > 0.0 .and. ABS(MudSystem%St_Density%First() - MudSystem%Hz_Density%Last()) >= MudSystem%DensityMixTol) then ! new mud is pumped call MudSystem%St_Density%AddToFirst (MudSystem%Hz_Density%Last()) call MudSystem%St_MudDischarged_Volume%AddToFirst (0.0d0) call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(2)) call MudSystem%St_Mud_Forehead_section%AddToFirst (2) call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2)) call MudSystem%St_Mud_Backhead_section%AddToFirst (2) call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%St_MudOrKick%AddToFirst (0) !StringDensity_Old= Hz_Density%Last() endif MudSystem%St_MudDischarged_Volume%Array(1)= MudSystem%St_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) !=============== save String Mud data=========== MudSystem%StMudVolumeSum= 0.d0 !St_MudSaved_Density= 0.d0 MudSystem%St_Saved_MudDischarged_Volume= 0.d0 !Saved_St_MudOrKick= 0 !Ann_to_Choke_2mud= .false. do imud=1, MudSystem%St_MudDischarged_Volume%Length() MudSystem%StMudVolumeSum = MudSystem%StMudVolumeSum + MudSystem%St_MudDischarged_Volume%Array(imud) if ( MudSystem%StMudVolumeSum > sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts)) ) then !IF (St_MudOrKick%Array(imud) == 0) THEN MudSystem%St_MudSaved_Density =MudSystem%St_Density%Array(imud) MudSystem%St_Saved_MudDischarged_Volume = MudSystem%StMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts)) !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR ! St_Kick_Saved_Volume = StMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) ! Saved_St_MudOrKick= St_MudOrKick%Array (imud) ! St_KickSaved_Density=MudSystem%St_Density%Array(imud) !END IF do ii= imud + 1, MudSystem%St_MudDischarged_Volume%Length() !IF (St_MudOrKick%Array(ii) == 0) THEN MudSystem%St_MudSaved_Density = ((MudSystem%St_MudSaved_Density * MudSystem%St_Saved_MudDischarged_Volume) + (MudSystem%St_Density%Array(ii) * MudSystem%St_MudDischarged_Volume%Array(ii))) / (MudSystem%St_Saved_MudDischarged_Volume + MudSystem%St_MudDischarged_Volume%Array(ii)) MudSystem%St_Saved_MudDischarged_Volume = MudSystem%St_Saved_MudDischarged_Volume + MudSystem%St_MudDischarged_Volume%Array(ii) !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR ! St_Kick_Saved_Volume = St_Kick_Saved_Volume + St_MudDischarged_Volume%Array(ii) ! Saved_St_MudOrKick= St_MudOrKick%Array (ii) ! St_KickSaved_Density=MudSystem%St_Density%Array(ii) !END IF enddo !WRITE (*,*) 'St_Saved_Mud_Volume, St_Kick_Saved_Volume', St_Saved_MudDischarged_Volume, St_Kick_Saved_Volume exit ! exits do endif enddo MudSystem%St_Saved_MudDischarged_Volume_Final = MudSystem%St_Saved_MudDischarged_Volume IF (MudSystem%WellHeadIsOpen) MudSystem%MudVolume_InjectedToBH = MudSystem%St_Saved_MudDischarged_Volume_Final !====================================================================== !========================STRING================= imud=0 do while (imud < MudSystem%St_Mud_Forehead_X%Length()) imud = imud + 1 if (imud> 1) then MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%St_Mud_Forehead_X%Array(imud-1) MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%St_Mud_Forehead_section%Array(imud-1) endif MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))) & / ABS(MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))) ! +1 for string , -1 for annulus MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))- MudSystem%St_Mud_Backhead_X%Array(imud))* & MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) !(ft^3) MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal !write(*,*) 'St_Mud_Backhead_section%Array(1)=' , St_Mud_Backhead_section%Array(1) !write(*,*) 'Xend_PipeSection(St_Mud_Backhead_section%Array(1))=' , Xend_PipeSection(St_Mud_Backhead_section%Array(1)) ! !write(*,*) 'St_EmptyVolume_inBackheadLocation%Array(1)=' , St_EmptyVolume_inBackheadLocation%Array(1) !write(*,*) 'St_Mud_Backhead_X%Array(1)=' , St_Mud_Backhead_X%Array(1) if ( MudSystem%St_MudDischarged_Volume%Array(imud) <= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)) then MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%St_Mud_Backhead_section%Array(imud) MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%St_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%St_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) ! 7.48 is for gal to ft^3 else MudSystem%isection= MudSystem%St_Mud_Backhead_section%Array(imud)+1 MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud) do if (MudSystem%isection > F_Counts%StringIntervalCounts) then ! last pipe section(string exit) F_Counts%StringIntervalCounts includes Horizontal line MudSystem%St_MudDischarged_Volume%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_RemainedVolume_in_LastSection%Array(imud) MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts) MudSystem%St_Mud_Forehead_section%Array(imud)= F_Counts%StringIntervalCounts if (MudSystem%St_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string call RemoveStringMudArrays(imud) endif exit endif MudSystem%xx= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal) if (MudSystem%xx<= 1.0) then MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%isection MudSystem%St_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection) exit else MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) MudSystem%isection= MudSystem%isection+ 1 endif enddo endif enddo !write(*,*) ' a before==' ! ! do imud=1, Op_MudDischarged_Volume%Length() ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud) ! enddo ! ! do imud=1, Ann_MudDischarged_Volume%Length() ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud) ! enddo ! !write(*,*) '==== a before' !write(*,*) ' iloc (a): ' , iloc !========================STRING END================= IF (MudSystem%Op_MudOrKick%Last() /= 0 .and. MudSystem%Op_MudOrKick%Last()==MudSystem%Ann_MudOrKick%First()) MudSystem%iLoc=2 ! it may be 1,2,3 or more, all of them are kick !write(*,*) ' iloc (b): ' , iloc !=============================Add PumpFlowRate to Bottom Hole ============================== !if ( MudSystem%AnnulusFlowRate>0.0 ) then if ( MudSystem%MudVolume_InjectedToBH > 0.0 ) then if (KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the AddLocation= MudSystem%Op_Density%Length()-MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick else AddLocation= MudSystem%Op_Density%Length()+1 endif !write(*,*) 'AddLocation====' , AddLocation if ( AddLocation== 0) CALL ErrorStop ('AddLocation=0') if ( ABS(MudSystem%St_Density%Last() - MudSystem%Op_Density%Array(AddLocation-1)) >= MudSystem%DensityMixTol ) then !write(*,*) 'new pocket**' !write(*,*) MudSystem%St_Density%Last()=' ,MudSystem%St_Density%Last() !write(*,*) 'Op_Density%Array(AddLocation-1)=' , Op_Density%Array(AddLocation-1) call MudSystem%Op_Density% AddTo (AddLocation,MudSystem%St_Density%Last()) !call Op_MudDischarged_Volume%AddTo (AddLocation,((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline)) call MudSystem%Op_MudDischarged_Volume%AddTo (AddLocation,MudSystem%MudVolume_InjectedToBH) call MudSystem%Op_Mud_Forehead_X%AddTo (AddLocation,MudSystem%Xstart_OpSection(1)) call MudSystem%Op_Mud_Forehead_section%AddTo (AddLocation,1) call MudSystem%Op_Mud_Backhead_X%AddTo (AddLocation,MudSystem%Xstart_OpSection(1)) call MudSystem%Op_Mud_Backhead_section%AddTo (AddLocation,1) call MudSystem%Op_RemainedVolume_in_LastSection%AddTo (AddLocation,0.0d0) call MudSystem%Op_EmptyVolume_inBackheadLocation%AddTo (AddLocation,0.0d0) call MudSystem%Op_MudOrKick%AddTo (AddLocation,0) else !write(*,*) 'merge**' !write(*,*) 'density before=' , Op_Density%Array(AddLocation-1) !write(*,*) MudSystem%St_Density%Last() for mix=' ,MudSystem%St_Density%Last() !Op_Density%Array(AddLocation-1)= (Op_Density%Array(AddLocation-1)*Op_MudDischarged_Volume%Array(AddLocation-1)MudSystem%St_Density%Last()*((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline))/(Op_MudDischarged_Volume%Array(AddLocation-1)+((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline)) !Op_MudDischarged_Volume%Array(AddLocation-1)= Op_MudDischarged_Volume%Array(AddLocation-1) + ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline) MudSystem%Op_Density%Array(AddLocation-1)= (MudSystem%Op_Density%Array(AddLocation-1)*MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)+MudSystem%St_Density%Last()*MudSystem%MudVolume_InjectedToBH)/(MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)+MudSystem%MudVolume_InjectedToBH) MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)= MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1) + MudSystem%MudVolume_InjectedToBH !write(*,*) 'density after=' , Op_Density%Array(AddLocation-1) endif endif !=======================Add PumpFlowRate to Bottom Hole- End ============================== !=============== save OP Mud data to transfer to the annulus enterance due to tripin or kick MudSystem%OpMudVolumeSum= 0.d0 !Op_MudSaved_Density= 0.d0 !Op_KickSaved_Density= 0.d0 MudSystem%Op_Saved_MudDischarged_Volume= 0.d0 MudSystem%Op_Kick_Saved_Volume= 0.d0 MudSystem%Saved_Op_MudOrKick= 0 !write(*,*) 'Op_Capacity===' , sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts)) !write(*,*) 'Op_MudDischarged_Volume%Length()===' , Op_MudDischarged_Volume%Length() ! do imud=1, MudSystem%Op_MudDischarged_Volume%Length() !write(*,*) 'imud, Op_MudDischarged_Volume%Array(imud)=' , imud,Op_MudDischarged_Volume%Array(imud) MudSystem%OpMudVolumeSum= MudSystem%OpMudVolumeSum + MudSystem%Op_MudDischarged_Volume%Array(imud) if ( MudSystem%OpMudVolumeSum > sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) ) then IF (MudSystem%Op_MudOrKick%Array(imud) == 0) THEN MudSystem%Op_MudSaved_Density = MudSystem%Op_Density%Array(imud) MudSystem%Op_Saved_MudDischarged_Volume = MudSystem%OpMudVolumeSum - sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) ELSE MudSystem%Op_Kick_Saved_Volume = MudSystem%OpMudVolumeSum - sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) !write(*,*) 'cond 1- Op_MudOrKick%Array (imud),Op_Density%Array(imud):' ,Op_MudOrKick%Array (imud),Op_Density%Array(imud) MudSystem%Saved_Op_MudOrKick= MudSystem%Op_MudOrKick%Array (imud) MudSystem%Op_KickSaved_Density= MudSystem%Op_Density%Array(imud) MudSystem%iLoc= 2 END IF do ii= imud + 1, MudSystem%Op_MudDischarged_Volume%Length() IF (MudSystem%Op_MudOrKick%Array(ii) == 0) THEN MudSystem%Op_MudSaved_Density = ((MudSystem%Op_MudSaved_Density * MudSystem%Op_Saved_MudDischarged_Volume) + (MudSystem%Op_Density%Array(ii) * MudSystem%Op_MudDischarged_Volume%Array(ii))) / (MudSystem%Op_Saved_MudDischarged_Volume + MudSystem%Op_MudDischarged_Volume%Array(ii)) MudSystem%Op_Saved_MudDischarged_Volume = MudSystem%Op_Saved_MudDischarged_Volume + MudSystem%Op_MudDischarged_Volume%Array(ii) ELSE MudSystem%Op_Kick_Saved_Volume = MudSystem%Op_Kick_Saved_Volume + MudSystem%Op_MudDischarged_Volume%Array(ii) !write(*,*) 'cond 2- Op_MudOrKick%Array (ii),Op_Density%Array(ii):' ,Op_MudOrKick%Array (ii),Op_Density%Array(ii) MudSystem%Saved_Op_MudOrKick= MudSystem%Op_MudOrKick%Array (ii) MudSystem%Op_KickSaved_Density= MudSystem%Op_Density%Array(ii) MudSystem%iLoc= 2 END IF enddo exit ! exits do endif enddo !WRITE (*,*) 'Op_Saved_MudDischarged_Volume, Op_Kick_Saved_Volume',Op_Saved_MudDischarged_Volume, Op_Kick_Saved_Volume !write(*,*) ' iloc (c): ' , iloc !====================================================================== !====================================================================== !if (iLoc == 1) then MudSystem%MudSection= F_Counts%StringIntervalCounts+1 MudSystem%BackheadX= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1) !elseif (iLoc == 2) then ! MudSection= Kick_Forehead_section ! BackheadX= Kick_Forehead_X !endif !========================ANNULUS ENTRANCE==================== !if (KickMigration_2SideBit == .FALSE.) then ! because its effect is applied in Migration Code ! !write(*,*) 'iloc=====' , iLoc bejaye ROP_Bit%RateOfPenetration ==0. in bude: DeltaVolumeOp == 0.0 ! if (ABS(AnnulusSuctionDensity_OldMudSystem%St_Density%Last()) >= DensityMixTol .OR. (DeltaVolumeOp == 0.0 .and. ABS(Ann_Density%Array(iLoc)MudSystem%St_Density%Last())>=DensityMixTol .and. MudSystem%AnnulusFlowRate/=0.0d0) ) then ! new mud is pumped ! call Ann_Density%AddTo (iLocMudSystem%St_Density%Last()) ! call Ann_MudDischarged_Volume%AddTo (iLoc,0.0d0) ! call Ann_Mud_Forehead_X%AddTo (iLoc,BackheadX) ! call Ann_Mud_Forehead_section%AddTo (iLoc,MudSection) ! call Ann_Mud_Backhead_X%AddTo (iLoc,BackheadX) ! call Ann_Mud_Backhead_section%AddTo (iLoc,MudSection) ! call Ann_RemainedVolume_in_LastSection%AddTo (iLoc,0.0d0) ! call Ann_EmptyVolume_inBackheadLocation%AddTo (iLoc,0.0d0) ! call Ann_MudOrKick%AddTo (iLoc,0) ! call Ann_CuttingMud%AddTo (iLoc,0) ! !write(*,*) 'c) annLength=' , Ann_Density%Length() ! ! AnnulusSuctionDensity_Old=MudSystem%St_Density%Last() ! ! MudIsChanged= .true. ! endif ! ! Ann_MudDischarged_Volume%Array(iLoc)= Ann_MudDischarged_Volume%Array(iLoc)+ ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline) !(gal) ! !endif MudSystem%Ann_Mud_Backhead_section%Array(1)= MudSystem%MudSection !it is needed to be updated for a condition that one pipe is removed from Annulus due to trip out MudSystem%Ann_Mud_Backhead_X%Array(1)= MudSystem%BackheadX ! write(*,*) 'zero)Ann_Mud sum=' , sum(Ann_MudDischarged_Volume%Array(:)) ! ! !write(*,*) 'pump added-before add to ann==' ! ! do imud=1, Op_MudDischarged_Volume%Length() ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud) ! enddo ! ! do imud=1, Ann_MudDischarged_Volume%Length() ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud) ! enddo ! !write(*,*) '====pump added-before add to ann' !========================Tripping In==================== !write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp if (ROP_Bit%RateOfPenetration==0.) then ! .and. Op_MudOrKick%Last() == 0) then ! trip in mode(loole paeen) Mud !write(*,*) 'Tripping In' !write(*,*) 'before' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) !if ( MudIsChanged== .true. ) then ! call RemoveAnnulusMudArrays(iLoc) !endif if (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() == 0) then write(*,*) 'Kick influx enters Annulus' call MudSystem%Ann_Density%AddToFirst (MudSystem%Op_KickSaved_Density) call MudSystem%Ann_MudDischarged_Volume%AddToFirst (MudSystem%Op_Kick_Saved_Volume) call MudSystem%Ann_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)) call MudSystem%Ann_Mud_Forehead_section%AddToFirst (F_Counts%StringIntervalCounts+1) call MudSystem%Ann_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)) call MudSystem%Ann_Mud_Backhead_section%AddToFirst (F_Counts%StringIntervalCounts+1) call MudSystem%Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%Ann_MudOrKick%AddToFirst (MudSystem%Saved_Op_MudOrKick) !<<<<<<<< call MudSystem%Ann_CuttingMud%AddToFirst (0) elseif (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() /= 0) then MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) + MudSystem%Op_Kick_Saved_Volume endif if (MudSystem%Op_Saved_MudDischarged_Volume> 0.0) then MudSystem%NewDensity= MudSystem%Op_MudSaved_Density MudSystem%NewVolume= MudSystem%Op_Saved_MudDischarged_Volume !write(*,*) 'NewVolume=' , NewVolume !write(*,*) 'iloc=' , iloc,'Ann_MudDischarged_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) if ((ROP_Bit%RateOfPenetration==0 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%DensityMixTol) & .or. (ROP_Bit%RateOfPenetration>0. .and. MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==1 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%CuttingDensityMixTol) & .or. (ROP_Bit%RateOfPenetration>0. .and. MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==0 .and. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc) < 42.) ) then ! 1-Pockets are Merged MudSystem%Ann_Density%Array(MudSystem%iLoc)= (MudSystem%Ann_Density%Array(MudSystem%iLoc)*MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewDensity*MudSystem%NewVolume)/(MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume) MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0) MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0) !write(*,*) 'merge' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) else ! 2-Merging conditions are not meeted, so new pocket call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity) call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume) call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0) call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0) call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0) call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0) !write(*,*) 'd) annLength=' , Ann_Density%Length() !write(*,*) 'new' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) endif endif endif !========================Tripping In - End==================== !========================Drilling Mode======================== if (ROP_Bit%RateOfPenetration>0. .and. MudSystem%DeltaVolumeOp>0.0) then ! trip in mode(loole paeen) DrillingMode== .true. !write(*,*) 'Drilling Mode' !if ( MudIsChanged== .true. ) then ! call RemoveAnnulusMudArrays(iLoc) !endif !write(*,*) 'before' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) !MudSystem%NewDensity= MudSystem%St_Density%Last() * MudSystem%AnnulusFlowRate + 141.4296E-4*ROP_Bit%RateOfPenetration*ROP_Spec%DiameterOfBit**2)/(MudSystem%AnnulusFlowRate+6.7995E-4*ROP_Bit%RateOfPenetration*Diameter_of_Bit**2) MudSystem%NewDensity=MudSystem%St_Density%Last() !NewVolume= ((MudSystem%AnnulusFlowRate/60.0d0)*DeltaT_Mudline)+DeltaVolumeOp !!! Density in ppg, flow rate in gpm, ROP in ft/s, bit diameter in inch do imud=1, MudSystem%Op_MudDischarged_Volume%Length() if ( MudSystem%Op_MudOrKick%Array(imud) == 0 ) then MudSystem%Op_Density%Array(imud)= MudSystem%NewDensity endif enddo if (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() == 0) then write(*,*) 'Kick influx enters Annulus first time' !write(*,*) 'Saved_Op_MudOrKick=',Saved_Op_MudOrKick call MudSystem%Ann_Density%AddToFirst (MudSystem%Op_KickSaved_Density) call MudSystem%Ann_MudDischarged_Volume%AddToFirst (MudSystem%Op_Kick_Saved_Volume) call MudSystem%Ann_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)) call MudSystem%Ann_Mud_Forehead_section%AddToFirst (F_Counts%StringIntervalCounts+1) call MudSystem%Ann_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)) call MudSystem%Ann_Mud_Backhead_section%AddToFirst (F_Counts%StringIntervalCounts+1) call MudSystem%Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%Ann_MudOrKick%AddToFirst (MudSystem%Saved_Op_MudOrKick) !<<<<<<<< call MudSystem%Ann_CuttingMud%AddToFirst (0) elseif (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() /= 0) then MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) + MudSystem%Op_Kick_Saved_Volume endif if (MudSystem%Op_Saved_MudDischarged_Volume> 0.0) then !write(*,*) 'Op_Saved_Mud added' MudSystem%NewDensity= MudSystem%NewDensity !(drilling density) MudSystem%NewVolume= MudSystem%Op_Saved_MudDischarged_Volume + MudSystem%DeltaVolumeOp ! (DeltaVolumeOp: for Cuttings Volume) !write(*,*) 'NewVolume=' , NewVolume !write(*,*) 'iloc=' , iloc,'Ann_MudDischarged_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) if ( (MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==1 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%CuttingDensityMixTol ) & .or. (MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==0 .and. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc) < 42.) ) then ! 1-Pockets are Merged MudSystem%Ann_Density%Array(MudSystem%iLoc)= (MudSystem%Ann_Density%Array(MudSystem%iLoc)*MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewDensity*MudSystem%NewVolume)/(MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume) MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0) MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0) MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)= 1 !write(*,*) 'merge' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) else ! 2-Merging conditions are not meeted, so new pocket !write(*,*) 'before e) ', iloc, Ann_Density%Array(iLoc),MudSystem%NewDensity !write(*,*) 'before e) Ann_MudDischarged_Volume%Array(iLoc)=' , Ann_MudDischarged_Volume%Array(iLoc) call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity) call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume) call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0) call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0) call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0) call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,1) ! 1= cutting 0= mud !write(*,*) 'new' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1) !write(*,*) 'e) annLength=' , Ann_Density%Length() endif endif endif !=================================================================== !write(*,*) 'after add to ann==' ! ! do imud=1, Op_MudDischarged_Volume%Length() ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud) ! enddo ! ! do imud=1, Ann_MudDischarged_Volume%Length() ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud) ! enddo ! !write(*,*) '==after add to ann' MudSystem%NewVolume= ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) - MudSystem%Op_Saved_MudDischarged_Volume if (MudSystem%iLoc==2 .and. MudSystem%Op_MudOrKick%Last()==0 .and. MudSystem%NewVolume > 0.d0 ) then ! for avoid kick separation !write(*,*) 'avoid kick separation' MudSystem%NewDensity= MudSystem%Op_MudSaved_Density call RemoveOpMudArrays(MudSystem%Op_Density%Length()) ! mud here is removed and then will be added to iloc=2 in Ann if ( MudSystem%Ann_MudDischarged_Volume%Array(1) > ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline)- MudSystem%Op_Saved_MudDischarged_Volume) then! 1st in Ann = kick !write(*,*) 'mode1' MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) - (((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) -MudSystem%Op_Saved_MudDischarged_Volume) MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_Density%Length())= MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_Density%Length())+ (((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) - MudSystem%Op_Saved_MudDischarged_Volume) !kick else call RemoveAnnulusMudArrays(1) !kick is removed MudSystem%iLoc= 1 MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_Density%Length())= MudSystem%Op_MudDischarged_Volume%Array(MudSystem%Op_Density%Length())+ (((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) - MudSystem%Op_Saved_MudDischarged_Volume) !write(*,*) 'mode2' ! including a little expand endif if ((ROP_Bit%RateOfPenetration==0 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%DensityMixTol) & .or. (ROP_Bit%RateOfPenetration>0. .and. MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==1 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%CuttingDensityMixTol) & .or. (ROP_Bit%RateOfPenetration>0. .and. MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==0 .and. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc) < 42.) ) then ! 1-Pockets are Merged MudSystem%Ann_Density%Array(MudSystem%iLoc)= (MudSystem%Ann_Density%Array(MudSystem%iLoc)*MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewDensity*MudSystem%NewVolume)/(MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume) MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0) MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0) else ! 2-Merging conditions are not meeted, so new pocket call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity) call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume) call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX) call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection) call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0) call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0) call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0) call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0) !write(*,*) 'd) annLength=' , Ann_Density%Length() endif endif !=================================================================== if( MudSystem%Op_MudOrKick%Last() == 1 .and. MudSystem%Ann_MudOrKick%First() == 0 ) then write(*,*) '***error2****==' write(*,*) 'Op_Kick_Saved_Volume,Op_Saved_MudDischarged_Volume=' , MudSystem%Op_Kick_Saved_Volume,MudSystem%Op_Saved_MudDischarged_Volume write(*,*) 'after add to ann==' do imud=1, MudSystem%Op_MudDischarged_Volume%Length() write(*,*) 'Op:', imud, MudSystem%Op_MudDischarged_Volume%Array(imud), MudSystem%Op_Density%Array(imud) ,MudSystem%Op_MudOrKick%Array(imud) enddo do imud=1, MudSystem%Ann_MudDischarged_Volume%Length() write(*,*) 'Ann:', imud, MudSystem%Ann_MudDischarged_Volume%Array(imud), MudSystem%Ann_Density%Array(imud) ,MudSystem%Ann_MudOrKick%Array(imud) enddo write(*,*) '==after add to ann' write(*,*) 'NewVolume,Op_MudOrKick%Last=' , MudSystem%NewVolume,MudSystem%Op_MudOrKick%Last() write(*,*) '==***error2****' endif !=============== save Ann Mud data to transfer to the ChokeLine enterance MudSystem%AnnMudVolumeSum= 0.d0 !Ann_MudSaved_Density= 0.d0 !Ann_KickSaved_Density= 0.d0 MudSystem%Ann_Saved_MudDischarged_Volume= 0.d0 MudSystem%Ann_Kick_Saved_Volume= 0.d0 MudSystem%Saved_Ann_MudOrKick= 0 MudSystem%Ann_to_Choke_2mud= .false. do imud=1, MudSystem%Ann_MudDischarged_Volume%Length() MudSystem%AnnMudVolumeSum= MudSystem%AnnMudVolumeSum + MudSystem%Ann_MudDischarged_Volume%Array(imud) if ( MudSystem%AnnMudVolumeSum > sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) ) then IF (MudSystem%Ann_MudOrKick%Array(imud) == 0) THEN MudSystem%Ann_MudSaved_Density = MudSystem%Ann_Density%Array(imud) MudSystem%Ann_Saved_MudDischarged_Volume = MudSystem%AnnMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) ELSEIF (MudSystem%Ann_MudOrKick%Array(imud) > 0 .AND. MudSystem%Ann_MudOrKick%Array(imud) <100) THEN ! 104= AIR MudSystem%Ann_Kick_Saved_Volume = MudSystem%AnnMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) MudSystem%Saved_Ann_MudOrKick= MudSystem%Ann_MudOrKick%Array (imud) MudSystem%Ann_KickSaved_Density= MudSystem%Ann_Density%Array(imud) END IF do ii= imud + 1, MudSystem%Ann_MudDischarged_Volume%Length() IF (MudSystem%Ann_MudOrKick%Array(ii) == 0) THEN MudSystem%Ann_MudSaved_Density = ((MudSystem%Ann_MudSaved_Density * MudSystem%Ann_Saved_MudDischarged_Volume) + (MudSystem%Ann_Density%Array(ii) * MudSystem%Ann_MudDischarged_Volume%Array(ii))) / (MudSystem%Ann_Saved_MudDischarged_Volume + MudSystem%Ann_MudDischarged_Volume%Array(ii)) MudSystem%Ann_Saved_MudDischarged_Volume = MudSystem%Ann_Saved_MudDischarged_Volume + MudSystem%Ann_MudDischarged_Volume%Array(ii) MudSystem%Ann_to_Choke_2mud= .true. ELSEIF (MudSystem%Ann_MudOrKick%Array(ii) > 0 .AND. MudSystem%Ann_MudOrKick%Array(ii) <100) THEN ! 104= AIR MudSystem%Ann_Kick_Saved_Volume = MudSystem%Ann_Kick_Saved_Volume + MudSystem%Ann_MudDischarged_Volume%Array(ii) MudSystem%Saved_Ann_MudOrKick= MudSystem%Ann_MudOrKick%Array (ii) MudSystem%Ann_KickSaved_Density= MudSystem%Ann_Density%Array(ii) END IF enddo !WRITE (*,*) 'Ann_Saved_Mud_Volume, Ann_Kick_Saved_Volume', Ann_Saved_MudDischarged_Volume, Ann_Kick_Saved_Volume exit endif enddo MudSystem%Ann_Saved_MudDischarged_Volume_Final= MudSystem%Ann_Saved_MudDischarged_Volume !+ Ann_Kick_Saved_Volume MudSystem%Ann_Kick_Saved_Volume_Final= MudSystem%Ann_Kick_Saved_Volume IF (MudSystem%WellHeadIsOpen) MudSystem%MudVolume_InjectedFromAnn = MudSystem%Ann_Saved_MudDischarged_Volume_Final -((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) !WRITE (*,*) 'MudSystem%MudVolume_InjectedFromAnn=', MudSystem%MudVolume_InjectedFromAnn !====================================================================== !write(*,*) 'c)Ann_Mud sum=' , sum(Ann_MudDischarged_Volume%Array(:)) !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) !write(*,*) 'Ann_Saved_Mud=' , Ann_Saved_MudDischarged_Volume MudSystem%total_injected = MudSystem%total_injected + MudSystem%MudVolume_InjectedFromAnn if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then MudSystem%total_injected= 0. endif !write(*,*) ' total injected-tripin =' , total_injected !write(*,*) 'injected-tripin =' , MudSystem%MudVolume_InjectedFromAnn !======================== Annulus ==================== !MudIsChanged= .false. imud= 0 do while (imud < MudSystem%Ann_Mud_Forehead_X%Length()) imud = imud + 1 if (imud> 1) then MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Ann_Mud_Forehead_X%Array(imud-1) MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%Ann_Mud_Forehead_section%Array(imud-1) endif ! <<< Fracture Shoe Lost IF ( MudSystem%ShoeLost .and. Shoe%ShoeDepth < MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. Shoe%ShoeDepth >= MudSystem%Ann_Mud_Forehead_X%Array(imud) ) then !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline) MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) !(gal) if (MudSystem%Ann_MudDischarged_Volume%Array(imud) < 0.0) then !write(*,*) 'mud is removed by shoe lost, imud=' , imud call RemoveAnnulusMudArrays(imud) imud= imud-1 cycle endif ENDIF ! Fracture Shoe Lost >>> MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))) & / ABS(MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))) ! +1 for string , -1 for annulus MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))- MudSystem%Ann_Mud_Backhead_X%Array(imud))* & MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Backhead_section%Array(imud)) !(ft^3) MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal if ( MudSystem%Ann_MudDischarged_Volume%Array(imud) <= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%Ann_Mud_Backhead_section%Array(imud) MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Ann_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Backhead_section%Array(imud)) ! 7.48 is for gal to ft^3 else MudSystem%isection= MudSystem%Ann_Mud_Backhead_section%Array(imud)+1 MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud) do if (MudSystem%isection > MudSystem%NoPipeSections) then ! last pipe section(well exit) MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud) MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(MudSystem%NoPipeSections) MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%NoPipeSections if (MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well !write(*,*) 'remove******' call RemoveAnnulusMudArrays(imud) endif exit endif MudSystem%xx= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal) if (MudSystem%xx<= 1.0) then MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%isection MudSystem%Ann_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection) exit else MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) MudSystem%isection= MudSystem%isection+ 1 endif enddo endif ! write(*,*) 'imud=' , imud !write(*,*) 'Pinter4 **Ann_Length()=' , Ann_Mud_Forehead_X%Length() ! write(*,*) 'Ann_Density%Array (imud)=' , Ann_Density%Array (imud) ! ! !write(*,*) imud,'Ann_Mud_Forehead_X%Array(imud)=' , Ann_Mud_Forehead_X%Array(imud) !if (Ann_Mud_Forehead_X%Array(imud) < Xend_PipeSection(NoPipeSections)) then ! Ann_Mud_Forehead_X%Array(imud) = Xend_PipeSection(NoPipeSections) ! for error preventing !endif !write(*,*) imud, 'Ann_MudDischarged_Volume%Array(imud)=' , Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) enddo if (MudSystem%Ann_Mud_Forehead_X%Last() < MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)) then MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%Ann_Mud_Forehead_X%Length()) = MudSystem%Xend_PipeSection(MudSystem%NoPipeSections) ! for error preventing endif !========================ANNULUS END================= !write(*,*) 'sum(Ann_MudDischarged_Volume%Array())=' , sum(Ann_MudDischarged_Volume%Array(:)) !========================================================= !write(*,*) 'before======2' ! ! do imud=1, Op_MudDischarged_Volume%Length() ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud) ! enddo !write(*,*) '2======before' !========================Bottom Hole================= imud=0 do while (imud < MudSystem%Op_Mud_Forehead_X%Length()) imud = imud + 1 if (imud> 1) then MudSystem%Op_Mud_Backhead_X%Array(imud)= MudSystem%Op_Mud_Forehead_X%Array(imud-1) MudSystem%Op_Mud_Backhead_section%Array(imud)= MudSystem%Op_Mud_Forehead_section%Array(imud-1) endif !write(*,*) 'imud**=' , imud MudSystem%DirectionCoef= (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) & / ABS(MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) ! +1 for string , -1 for annulus MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))- MudSystem%Op_Mud_Backhead_X%Array(imud))* & MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) !(ft^3) MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal !write(*,*) ' Op_EmptyVolume_inBackheadLocation%Array(1) =' , Op_EmptyVolume_inBackheadLocation%Array(1) if ( MudSystem%Op_EmptyVolume_inBackheadLocation%Array(1) < 0.0) CALL ErrorStop1 ('Negative Empty volume') if ( MudSystem%Op_MudDischarged_Volume%Array(imud) <= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)) then MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%Op_Mud_Backhead_section%Array(imud) MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Op_Mud_Backhead_X%Array(imud)+ MudSystem%DirectionCoef*(MudSystem%Op_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) ! 7.48 is for gal to ft^3 else MudSystem%isection= MudSystem%Op_Mud_Backhead_section%Array(imud)+1 MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud) do if (MudSystem%isection > F_Counts%BottomHoleIntervalCounts) then ! last pipe section(well exit) !if( imud==1) KickDeltaVinAnnulus= Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space MudSystem%Op_MudDischarged_Volume%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_RemainedVolume_in_LastSection%Array(imud) MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts) MudSystem%Op_Mud_Forehead_section%Array(imud)= F_Counts%BottomHoleIntervalCounts if (MudSystem%Op_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well call RemoveOpMudArrays(imud) endif exit endif MudSystem%xx= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%OpSection_VolumeCapacity(MudSystem%isection) !(gal) if (MudSystem%xx<= 1.0) then MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%isection MudSystem%Op_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_OpSection(MudSystem%isection)- MudSystem%Xstart_OpSection(MudSystem%isection)))+ MudSystem%Xstart_OpSection(MudSystem%isection) exit else MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)- MudSystem%OpSection_VolumeCapacity(MudSystem%isection) MudSystem%isection= MudSystem%isection+ 1 endif enddo endif ! for OP remove: if (MudSystem%Op_Mud_Forehead_X%Array(imud)== MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) then MudSystem%totalLength = MudSystem%Op_MudDischarged_Volume%Length() do while(imud < MudSystem%totalLength) !imud = imud + 1 call RemoveOpMudArrays(MudSystem%totalLength) MudSystem%totalLength = MudSystem%totalLength - 1 enddo exit ! endif !if (Op_Mud_Forehead_X%Array(imud)== Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) then ! totalLength = Op_MudDischarged_Volume%Length() ! do while(imud <= totalLength) ! ! imud = imud + 1 ! call RemoveOpMudArrays(imud) ! totalLength = totalLength - 1 ! ! ! enddo ! ! exit ! ! !endif enddo !write(*,*) 'OpSection_VolumeCapacity sum=' , sum(OpSection_VolumeCapacity(:)) !========================Bottom Hole END================= !write(*,*) 'after sorting==' ! ! do imud=1, Op_MudDischarged_Volume%Length() ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud) ! enddo ! ! do imud=1, Ann_MudDischarged_Volume%Length() ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud) ! enddo ! ! ! ! !do imud=1, st_MudDischarged_Volume%Length() ! ! write(*,*) 'st:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud) ! !enddo ! !write(*,*) '==after sorting' ! write(*,*) 'after sorting st==' ! ! do imud=1, st_MudDischarged_Volume%Length() ! write(*,*) 'st-plot:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud)MudSystem%St_Density%Array(imud) ! enddo ! !write(*,*) '==after sorting st' !write(*,*) '**Ann_Kick_Saved_Final,Mud_InjectedFromAnn' , Ann_Kick_Saved_Volume_Final,MudSystem%MudVolume_InjectedFromAnn end subroutine Pump_and_TripIn subroutine ChokeLineMud ! is called in subroutine CirculationCodeSelect Use GeoElements_FluidModule USE CMudPropertiesVariables USE MudSystemVARIABLES USE Pumps_VARIABLES !USE CHOKEVARIABLES !USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure !use CManifolds use CDrillWatchVariables !use CHOKEVARIABLES !use CChokeManifoldVariables !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity USE sROP_Other_Variables USE sROP_Variables Use KickVariables USE PressureDisplayVARIABLES Use CError Use , intrinsic :: IEEE_Arithmetic implicit none integer i,ii,error_occured error_occured = 0 !write(*,*) 'begining chokeline==' !write(*,*) 'Ann last:', Ann_MudDischarged_Volume%Last(), Ann_Density%Last() ,Ann_MudOrKick%Last() ! !do imud=1, ChokeLine_MudDischarged_Volume%Length() ! write(*,*) 'ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud), ChokeLine_Density%Array(imud) ,ChokeLine_MudOrKick%Array(imud) !enddo !write(*,*) 'Ann_Kick_Saved_Volume_Final,MudSystem%MudVolume_InjectedFromAnn' , Ann_Kick_Saved_Volume_Final,MudSystem%MudVolume_InjectedFromAnn !write(*,*) 'begining chokeline==' MudSystem%ChokeLineFlowRate = MUD(4)%Q !WRITE (*,*) 'MUD(4)%Q', MUD(4)%Q if (MudSystem%NewPipeFilling == 0) then ! .or. UtubeFilling==0) then MudSystem%ChokeLineFlowRate= 0. endif do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2 if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then write(*,*) 'error_location is 1' error_occured = 1 endif enddo ! !do imud=1, st_MudDischarged_Volume%Length() ! write(*,*) 'st:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud) !enddo !========================CHOKE LINE ENTRANCE================= !if ( Ann_Kick_Saved_Volume > 0.0 .and. ( Ann_Saved_MudDischarged_Volume-((Qlost/60.0d0)*DeltaT_Mudline) ) == 0.0 ) then if ( MudSystem%Ann_Kick_Saved_Volume > 1.0e-5 .and. ( MudSystem%MudVolume_InjectedFromAnn ) <= 1.0e-5 ) then !WRITE (*,*) 'only kick enters to chokeline, Casing pressure = ', PressureGauges(2) if (MudSystem%ChokeLine_MudOrKick%First() == 0) then call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_KickSaved_Density) call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (0.d0) call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1) call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1) call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%ChokeLine_MudOrKick%AddToFirst (MudSystem%Saved_Ann_MudOrKick) MudSystem%ChokeLineDensity_Old= MudSystem%Ann_KickSaved_Density endif MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ MudSystem%Ann_Kick_Saved_Volume !(gal) endif do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2 if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then write(*,*) 'error_location is 2' error_occured = 1 endif enddo !if ( Ann_Kick_Saved_Volume == 0.0 .and. ( Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) > 0.0 ) then if ( MudSystem%Ann_Kick_Saved_Volume <= 1.0e-5 .and. MudSystem%MudVolume_InjectedFromAnn > 1.0e-5 ) then !WRITE (*,*) 'only mud enters to chokeline' if ((MudSystem%Ann_to_Choke_2mud == .false. .and. ABS(MudSystem%ChokeLineDensity_Old - MudSystem%Ann_MudSaved_Density) >= MudSystem%DensityMixTol) .or. MudSystem%ChokeLine_MudOrKick%First() /= 0) then ! new mud is pumped call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_MudSaved_Density) call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1) call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1) call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%ChokeLine_MudOrKick%AddToFirst (0) MudSystem%ChokeLineDensity_Old= MudSystem%Ann_MudSaved_Density endif !ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1)+ (Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) !(gal) MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ (MudSystem%MudVolume_InjectedFromAnn) !(gal) endif do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2 if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then write(*,*) 'error_location is 3' error_occured = 1 endif enddo !if ( Ann_Kick_Saved_Volume > 0.0 .and. (Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) > 0.0 .and. ChokeLine_MudOrKick%First() /= 0 ) then if ( MudSystem%Ann_Kick_Saved_Volume > 1.0e-5 .and. (MudSystem%MudVolume_InjectedFromAnn) > 1.0e-5 .and. MudSystem%ChokeLine_MudOrKick%First() /= 0 ) then WRITE (*,*) 'Kick Enters Choke line Last Time' MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ MudSystem%Ann_Kick_Saved_Volume !(gal) call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_MudSaved_Density) !call ChokeLine_MudDischarged_Volume%AddToFirst (Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (MudSystem%MudVolume_InjectedFromAnn) call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1) call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1) call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%ChokeLine_MudOrKick%AddToFirst (0) MudSystem%ChokeLineDensity_Old= MudSystem%Ann_MudSaved_Density !ELSE if ( Ann_Kick_Saved_Volume > 0.0 .and. ( Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) > 0.0 .and. ChokeLine_MudOrKick%First() == 0 ) then ELSE if ( MudSystem%Ann_Kick_Saved_Volume > 1.0e-5 .and. ( MudSystem%MudVolume_InjectedFromAnn ) > 1.0e-5 .and. MudSystem%ChokeLine_MudOrKick%First() == 0 ) then WRITE (*,*) 'Kick Enters Choke line First Time' !ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1)+ ( Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) !(gal) MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ ( MudSystem%MudVolume_InjectedFromAnn ) !(gal) call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_KickSaved_Density) call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (MudSystem%Ann_Kick_Saved_Volume) call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1) call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0) call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1) call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0) call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0) call MudSystem%ChokeLine_MudOrKick%AddToFirst (MudSystem%Saved_Ann_MudOrKick) MudSystem%ChokeLineDensity_Old= MudSystem%Ann_KickSaved_Density endif do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2 if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then write(*,*) 'error_location is 4' error_occured = 1 endif enddo if (error_occured == 1) then do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length() write(*,*) 'ChokeLine:', imud, MudSystem%ChokeLine_Density%Array(imud) ,MudSystem%ChokeLine_MudOrKick%Array(imud) enddo endif !========================================================== ! !write(*,*) 'after add chokeline==' ! ! do imud=1, ChokeLine_MudDischarged_Volume%Length() ! write(*,*) 'ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud), ChokeLine_Density%Array(imud) ,ChokeLine_MudOrKick%Array(imud) ! enddo ! !write(*,*) 'after add chokeline==' ! ! !=============== save Choke Mud data========================== MudSystem%ChokeMudVolumeSum= 0.d0 !Ann_MudSaved_Density= 0.d0 !Ann_KickSaved_Density= 0.d0 MudSystem%Choke_Saved_MudDischarged_Volume= 0.d0 MudSystem%Choke_Kick_Saved_Volume= 0.d0 MudSystem%Saved_Choke_MudOrKick= 0 do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length() MudSystem%ChokeMudVolumeSum= MudSystem%ChokeMudVolumeSum + MudSystem%ChokeLine_MudDischarged_Volume%Array(imud) if ( MudSystem%ChokeMudVolumeSum > MudSystem%ChokeLine_VolumeCapacity ) then IF (MudSystem%ChokeLine_MudOrKick%Array(imud) == 0) THEN MudSystem%Choke_MudSaved_Density = MudSystem%ChokeLine_Density%Array(imud) MudSystem%Choke_Saved_MudDischarged_Volume = MudSystem%ChokeMudVolumeSum - MudSystem%ChokeLine_VolumeCapacity ELSEIF (MudSystem%ChokeLine_MudOrKick%Array(imud) > 0 .AND. MudSystem%ChokeLine_MudOrKick%Array(imud) <100) THEN ! 104= AIR MudSystem%Choke_Kick_Saved_Volume = MudSystem%ChokeMudVolumeSum - MudSystem%ChokeLine_VolumeCapacity MudSystem%Saved_Choke_MudOrKick= MudSystem%ChokeLine_MudOrKick%Array (imud) MudSystem%Choke_KickSaved_Density= MudSystem%ChokeLine_Density%Array(imud) END IF do ii= imud + 1, MudSystem%ChokeLine_MudDischarged_Volume%Length() IF (MudSystem%ChokeLine_MudOrKick%Array(ii) == 0) THEN MudSystem%Choke_MudSaved_Density = ((MudSystem%Choke_MudSaved_Density * MudSystem%Choke_Saved_MudDischarged_Volume) + (MudSystem%ChokeLine_Density%Array(ii) * MudSystem%ChokeLine_MudDischarged_Volume%Array(ii))) / (MudSystem%Choke_Saved_MudDischarged_Volume + MudSystem%ChokeLine_MudDischarged_Volume%Array(ii)) MudSystem%Choke_Saved_MudDischarged_Volume = MudSystem%Choke_Saved_MudDischarged_Volume + MudSystem%ChokeLine_MudDischarged_Volume%Array(ii) ELSEIF (MudSystem%ChokeLine_MudOrKick%Array(ii) > 0 .AND. MudSystem%ChokeLine_MudOrKick%Array(ii) <100) THEN ! 104= AIR MudSystem%Choke_Kick_Saved_Volume = MudSystem%Choke_Kick_Saved_Volume + MudSystem%ChokeLine_MudDischarged_Volume%Array(ii) MudSystem%Saved_Choke_MudOrKick= MudSystem%ChokeLine_MudOrKick%Array (ii) MudSystem%Choke_KickSaved_Density= MudSystem%ChokeLine_Density%Array(ii) END IF enddo !WRITE (*,*) 'Choke_Saved_Mud_Volume, Choke_Kick_Saved_Volume', Choke_Saved_MudDischarged_Volume, Choke_Kick_Saved_Volume exit ! exits do endif enddo MudSystem%Choke_Saved_MudDischarged_Volume_Final= MudSystem%Choke_Saved_MudDischarged_Volume !+ Choke_Kick_Saved_Volume MudSystem%Choke_Kick_Saved_Volume_Final= MudSystem%Choke_Kick_Saved_Volume !====================================================================== ! !do imud=1, ChokeLine_MudDischarged_Volume%Length() ! write(*,*) 'a)ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud) ,ChokeLine_MudOrKick%Array(imud) !enddo !write(*,*) 'choke_Mud sum=' , sum(ChokeLine_MudDischarged_Volume%Array(:)) !write(*,*) 'choke_cap=' , ChokeLine_VolumeCapacity !write(*,*) 'Choke_Saved_Mud=' , Choke_Saved_MudDischarged_Volume_Final !write(*,*) 'Choke_Saved_Kick=' , Choke_Kick_Saved_Volume_Final !========================Choke Line================= imud=0 do while (imud < MudSystem%ChokeLine_Mud_Forehead_X%Length()) imud = imud + 1 if (imud> 1) then MudSystem%ChokeLine_Mud_Backhead_X%Array(imud)= MudSystem%ChokeLine_Mud_Forehead_X%Array(imud-1) MudSystem%ChokeLine_Mud_Backhead_section%Array(imud)= MudSystem%ChokeLine_Mud_Forehead_section%Array(imud-1) endif !DirectionCoef= (Xend_PipeSection(St_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(St_Mud_Backhead_section%Array(imud))) & ! / ABS(Xend_PipeSection(St_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(St_Mud_Backhead_section%Array(imud))) ! +1 for string , -1 for annulus MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)= (BopStackSpecification%ChokeLineLength- MudSystem%ChokeLine_Mud_Backhead_X%Array(imud))* MudSystem%Area_ChokeLineFt !(ft^3) MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal if ( MudSystem%ChokeLine_MudDischarged_Volume%Array(imud) <= MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)) then MudSystem%ChokeLine_Mud_Forehead_section%Array(imud)= MudSystem%ChokeLine_Mud_Backhead_section%Array(imud) MudSystem%ChokeLine_Mud_Forehead_X%Array(imud)= MudSystem%ChokeLine_Mud_Backhead_X%Array(imud)+ (MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_ChokeLineFt ! 7.48 is for gal to ft^3 else MudSystem%isection= MudSystem%ChokeLine_Mud_Backhead_section%Array(imud)+1 MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)= MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)- MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud) do if (MudSystem%isection > 1) then ! last pipe section(Chokeline exit) MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)= MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)- MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud) MudSystem%ChokeLine_Mud_Forehead_X%Array(imud)= BopStackSpecification%ChokeLineLength MudSystem%ChokeLine_Mud_Forehead_section%Array(imud)= 1 if (MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string call MudSystem%ChokeLine_MudDischarged_Volume%Remove (imud) call MudSystem%ChokeLine_Mud_Backhead_X%Remove (imud) call MudSystem%ChokeLine_Mud_Backhead_section%Remove (imud) call MudSystem%ChokeLine_Mud_Forehead_X%Remove (imud) call MudSystem%ChokeLine_Mud_Forehead_section%Remove (imud) call MudSystem%ChokeLine_Density%Remove (imud) call MudSystem%ChokeLine_RemainedVolume_in_LastSection%Remove (imud) call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Remove (imud) call MudSystem%ChokeLine_MudOrKick%Remove (imud) endif exit endif MudSystem%xx= MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%ChokeLine_VolumeCapacity !(gal) if (MudSystem%xx<= 1.0) then MudSystem%ChokeLine_Mud_Forehead_section%Array(imud)= MudSystem%isection MudSystem%ChokeLine_Mud_Forehead_X%Array(imud)= MudSystem%xx * BopStackSpecification%ChokeLineLength exit else MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)= MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)- MudSystem%ChokeLine_VolumeCapacity MudSystem%isection= MudSystem%isection+ 1 endif enddo endif enddo !========================Choke Line END================= !do imud=1, ChokeLine_MudDischarged_Volume%Length() ! write(*,*) 'b)ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud) ,ChokeLine_MudOrKick%Array(imud) !enddo MudSystem%ChokeOutletDensity= MudSystem%ChokeLine_Density%Last() ! used in MudSystem do i=1, MudSystem%ChokeLine_MudOrKick%Length() !write(*,555) i,'Choke_Volume(i), type=' ,ChokeLine_MudDischarged_Volume%Array(i),ChokeLine_MudOrKick%Array(i) IF (IEEE_Is_NaN(MudSystem%ChokeLine_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in Choke Volume-Plot') IF (MudSystem%ChokeLine_MudDischarged_Volume%Array(i)<=0.) call ErrorStop('Choke Volume= <=0' , MudSystem%ChokeLine_MudDischarged_Volume%Array(i)) enddo 555 FORMAT(I3,5X,A42,(f12.5),5X,I3) !write(*,*) 'after sorting chokeline==' !IF (ANY(ChokeLine_MudOrKick%Array(:) > 0)) THEN ! do imud=1, ChokeLine_MudDischarged_Volume%Length() ! write(*,*) 'ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud), ChokeLine_Density%Array(imud) ,ChokeLine_MudOrKick%Array(imud) ! enddo !END IF !do imud=1, Ann_MudDischarged_Volume%Length() ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud) !enddo ! !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:)) !write(*,*) '==after sorting chokeline' end subroutine ChokeLineMud subroutine Choke_GasSound ! is called in subroutine CirculationCodeSelect use CSounds !Use GeoElements_FluidModule !USE CMudPropertiesVariables USE MudSystemVARIABLES !USE Pumps_VARIABLES !!USE CHOKEVARIABLES !!USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure !!use CManifolds !use CDrillWatchVariables !!use CHOKEVARIABLES !!use CChokeManifoldVariables !use CTanksVariables, TripTankVolume2 => TripTankVolume, TripTankDensity2 => TripTankDensity !USE sROP_Other_Variables !USE sROP_Variables !Use KickVariables !USE PressureDisplayVARIABLES !Use CError !Use , intrinsic :: IEEE_Arithmetic if ( MudSystem%ChokeLine_MudOrKick%Last() > 0 .AND. MudSystem%WellToChokeManifoldOpen == .true.) then !WellToChokeManifoldWasOpen MudSystem%SoundGasThroughChoke = 100 !100:chon dar adadhaye kamtar az 100 seda ghaat mishavad. eslah shavad.5.8.98 !int (min(ChokeLineFlowRate/2. , 100.)) print* , 'SoundGasThroughChoke1=', MudSystem%SoundGasThroughChoke !WRITE (*,*) 'WellToChokeManifoldWasOpen-Sound', WellToChokeManifoldWasOpen WRITE (*,*) 'WellToChokeManifoldOpen', MudSystem%WellToChokeManifoldOpen else MudSystem%SoundGasThroughChoke = 0 print* , 'SoundGasThroughChoke2=', MudSystem%SoundGasThroughChoke endif !print* , 'SoundGasThroughChoke3=', SoundGasThroughChoke call SetSoundGasThroughChoke(MudSystem%SoundGasThroughChoke) end subroutine Choke_GasSound