|
- 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============================================================
-
- MudSystemDotStringFlowRate= MUD(2)%Q
- MudSystemDotAnnulusFlowRate= MUD(2)%Q
-
-
- !write(*,*) 'Trip In'
-
-
- !========================Horizontal PIPE ENTRANCE=================
-
- if (ABS(SuctionDensity_Old - Suction_Density_MudSystem) >= MudSystemDotDensityMixTol) then ! new mud is pumped
-
- call MudSystemDotHz_Density%AddToFirst (Suction_Density_MudSystem)
- call MudSystemDotHz_MudDischarged_Volume%AddToFirst (0.0d0)
- call MudSystemDotHz_Mud_Forehead_X%AddToFirst (MudSystemDotXstart_PipeSection(1))
- call Hz_Mud_Forehead_section%AddToFirst (1)
- call MudSystemDotHz_Mud_Backhead_X%AddToFirst (MudSystemDotXstart_PipeSection(1))
- call Hz_Mud_Backhead_section%AddToFirst (1)
- call MudSystemDotHz_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call MudSystemDotHz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call Hz_MudOrKick%AddToFirst (0)
-
- SuctionDensity_Old= Suction_Density_MudSystem
- endif
-
- !========================Horizontal PIPE STRING=================
-
- MudSystemDotHz_MudDischarged_Volume%Array(1)= MudSystemDotHz_MudDischarged_Volume%Array(1)+ ((MudSystemDotStringFlowRate/60.0d0)*DeltaT_Mudline) !(gal)
-
- MudSystemDottotal_add = MudSystemDottotal_add + ((MudSystemDotStringFlowRate/60.0d0)*DeltaT_Mudline)
-
- if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
- MudSystemDottotal_add= 0.
- endif
-
-
- !write(*,*) ' total decrease(add to HZ)=' , total_add
- !write(*,*) ' add to HZ=' , ((StringFlowRate/60.0d0)*DeltaT_Mudline)
-
- MudSystemDotimud=0
- do while (MudSystemDotimud < MudSystemDotHz_Mud_Forehead_X%Length())
- MudSystemDotimud = MudSystemDotimud + 1
-
- if (MudSystemDotimud> 1) then
- MudSystemDotHz_Mud_Backhead_X%Array(MudSystemDotimud)= MudSystemDotHz_Mud_Forehead_X%Array(MudSystemDotimud-1)
- Hz_Mud_Backhead_section%Array(MudSystemDotimud)= Hz_Mud_Forehead_section%Array(MudSystemDotimud-1)
- endif
-
-
- MudSystemDotDirectionCoef= (MudSystemDotXend_PipeSection(Hz_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(Hz_Mud_Backhead_section%Array(MudSystemDotimud))) &
- / ABS(MudSystemDotXend_PipeSection(Hz_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(Hz_Mud_Backhead_section%Array(MudSystemDotimud)))
- ! +1 for string , -1 for annulus
-
-
- MudSystemDotHz_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotDirectionCoef* (MudSystemDotXend_PipeSection(Hz_Mud_Backhead_section%Array(MudSystemDotimud))- MudSystemDotHz_Mud_Backhead_X%Array(MudSystemDotimud))* &
- MudSystemDotArea_PipeSectionFt(Hz_Mud_Backhead_section%Array(MudSystemDotimud)) !(ft^3)
- MudSystemDotHz_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotHz_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 7.48051948d0 ! ft^3 to gal
-
-
- if ( MudSystemDotHz_MudDischarged_Volume%Array(MudSystemDotimud) <= MudSystemDotHz_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
- Hz_Mud_Forehead_section%Array(MudSystemDotimud)= Hz_Mud_Backhead_section%Array(MudSystemDotimud)
- MudSystemDotHz_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotHz_Mud_Backhead_X%Array(MudSystemDotimud)+ MudSystemDotDirectionCoef*(MudSystemDotHz_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_PipeSectionFt(Hz_Mud_Backhead_section%Array(MudSystemDotimud))
-
- else
-
-
- MudSystemDotisection= Hz_Mud_Backhead_section%Array(MudSystemDotimud)+1
- MudSystemDotHz_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotHz_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotHz_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
-
- do
- if (MudSystemDotisection > 1) then ! (horizontal pipe exit)
- MudSystemDotHz_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotHz_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotHz_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
- MudSystemDotHz_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotXend_PipeSection(1)
- Hz_Mud_Forehead_section%Array(MudSystemDotimud)= 1
-
- if (MudSystemDotHz_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the string
- call RemoveHzMudArrays(MudSystemDotimud)
- endif
-
- exit
- endif
-
- MudSystemDotxx= MudSystemDotHz_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection) !(gal)
-
- if (MudSystemDotxx<= 1.0) then
- Hz_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
- MudSystemDotHz_Mud_Forehead_X%Array(MudSystemDotimud)= (MudSystemDotxx * (MudSystemDotXend_PipeSection(MudSystemDotisection)- MudSystemDotXstart_PipeSection(MudSystemDotisection)))+ MudSystemDotXstart_PipeSection(MudSystemDotisection)
- exit
- else
- MudSystemDotHz_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotHz_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection)
- MudSystemDotisection= MudSystemDotisection+ 1
-
- endif
-
- enddo
-
- endif
-
- enddo
- !========================Horizontal PIPE END=================
-
-
- !========================Utube1 Air Element Removing=================
-
- !if (UtubeMode1Activated== .true.) then ! StringUpdate == .true.
- !
- !
- ! !StringDensity_Old= 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 (MudSystemDotAddedElementsToString > 0) then ! StringUpdate == .true.
-
- !NoPipeAdded= F_StringIntervalCounts - F_StringIntervalCountsOld
-
-
- MudSystemDotNewPipeFilling=0
-
- IF (St_MudOrKick%First() == 104) then
- MudSystemDotSt_MudDischarged_Volume%Array(1) = MudSystemDotSt_MudDischarged_Volume%Array(1) + sum(MudSystemDotPipeSection_VolumeCapacity(2:1+MudSystemDotAddedElementsToString)) ! new pipe is filled by air
- else
- call St_Density%AddToFirst (0.d0)
- call MudSystemDotSt_MudDischarged_Volume%AddToFirst (sum(MudSystemDotPipeSection_VolumeCapacity(2:1+MudSystemDotAddedElementsToString)))
- call MudSystemDotSt_Mud_Forehead_X%AddToFirst (MudSystemDotXstart_PipeSection(2))
- call St_Mud_Forehead_section%AddToFirst (2)
- call MudSystemDotSt_Mud_Backhead_X%AddToFirst (MudSystemDotXstart_PipeSection(2))
- call St_Mud_Backhead_section%AddToFirst (2)
- call MudSystemDotSt_RemainedVolume_in_LastSection%AddToFirst (0.d0)
- call MudSystemDotSt_EmptyVolume_inBackheadLocation%AddToFirst (0.d0)
- call St_MudOrKick%AddToFirst (104)
- endif
-
- endif
-
- !F_StringIntervalCountsOld= F_StringIntervalCounts
-
-
-
- if (MudSystemDotNewPipeFilling == 0) then ! 2= is the first element of string (1= is for Hz pipe)
-
-
- MudSystemDotLackageMudVolume= MudSystemDotSt_MudDischarged_Volume%Array(1) ! = Air element
-
-
- write(*,*) 'LackageMudVolume=' , MudSystemDotLackageMudVolume
-
-
-
- if (ABS(St_Density%Array(2) - MudSystemDotHz_Density%Last()) >= MudSystemDotDensityMixTol) then ! new mud is pumped
- call St_Density%AddTo (2,MudSystemDotHz_Density%Last())
- call MudSystemDotSt_MudDischarged_Volume%AddTo (2, 0.d0)
- call MudSystemDotSt_Mud_Forehead_X%AddTo (2,MudSystemDotXstart_PipeSection(2))
- call St_Mud_Forehead_section%AddTo (2 , 2)
- call MudSystemDotSt_Mud_Backhead_X%AddTo (2,MudSystemDotXstart_PipeSection(2))
- call St_Mud_Backhead_section%AddTo (2 ,2)
- call MudSystemDotSt_RemainedVolume_in_LastSection%AddTo (2,0.d0)
- call MudSystemDotSt_EmptyVolume_inBackheadLocation%AddTo (2,0.d0)
- call St_MudOrKick%AddTo (2,0)
-
- !StringDensity_Old= Hz_Density%Last()
- endif
-
-
- MudSystemDotSt_MudDischarged_Volume%Array(2)= MudSystemDotSt_MudDischarged_Volume%Array(2)+ min( ((MudSystemDotStringFlowRate/60.0d0)*DeltaT_Mudline), MudSystemDotLackageMudVolume) !(gal)
-
- MudSystemDotSt_MudDischarged_Volume%Array(1)= MudSystemDotSt_MudDischarged_Volume%Array(1)- min( ((MudSystemDotStringFlowRate/60.0d0)*DeltaT_Mudline), MudSystemDotLackageMudVolume) ! air(gal)
-
- !LackageMudVolumeAfterFilling= sum(PipeSection_VolumeCapacity(2:F_StringIntervalCounts)) - sum(St_MudDischarged_Volume%Array(:))
-
- MudSystemDotLackageMudVolumeAfterFilling= MudSystemDotSt_MudDischarged_Volume%Array(1) ! last time it should be zero
-
-
-
- if (MudSystemDotLackageMudVolumeAfterFilling == 0.) then
- MudSystemDotNewPipeFilling= 1
- call RemoveStringMudArrays(1)
- MudSystemDotSt_Mud_Backhead_X%Array(1) = MudSystemDotXstart_PipeSection(2)
- St_Mud_Backhead_section%Array(1) = 2
- endif
-
- endif
-
- !========================New Pipe Filling End=================
-
-
-
-
- if (MudSystemDotNewPipeFilling == 0) then
- MudSystemDotStringFlowRate= 0.
- MudSystemDotAnnulusFlowRate= 0.
- endif
-
- MudSystemDotStringFlowRateFinal= MudSystemDotStringFlowRate
- MudSystemDotAnnulusFlowRateFinal= MudSystemDotAnnulusFlowRate
-
-
-
-
- !========================STRING ENTRANCE=================
-
- if (MudSystemDotStringFlowRateFinal > 0.0 .and. ABS(St_Density%First() - MudSystemDotHz_Density%Last()) >= MudSystemDotDensityMixTol) then ! new mud is pumped
- call St_Density%AddToFirst (MudSystemDotHz_Density%Last())
- call MudSystemDotSt_MudDischarged_Volume%AddToFirst (0.0d0)
- call MudSystemDotSt_Mud_Forehead_X%AddToFirst (MudSystemDotXstart_PipeSection(2))
- call St_Mud_Forehead_section%AddToFirst (2)
- call MudSystemDotSt_Mud_Backhead_X%AddToFirst (MudSystemDotXstart_PipeSection(2))
- call St_Mud_Backhead_section%AddToFirst (2)
- call MudSystemDotSt_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call MudSystemDotSt_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call St_MudOrKick%AddToFirst (0)
-
- !StringDensity_Old= Hz_Density%Last()
- endif
-
-
- MudSystemDotSt_MudDischarged_Volume%Array(1)= MudSystemDotSt_MudDischarged_Volume%Array(1)+ ((MudSystemDotStringFlowRate/60.0d0)*DeltaT_Mudline) !(gal)
-
- !=============== save String Mud data===========
-
-
-
-
- MudSystemDotStMudVolumeSum= 0.d0
- !St_MudSaved_Density= 0.d0
- MudSystemDotSt_Saved_MudDischarged_Volume= 0.d0
- !Saved_St_MudOrKick= 0
- !Ann_to_Choke_2mud= .false.
-
- do MudSystemDotimud=1, MudSystemDotSt_MudDischarged_Volume%Length()
-
- MudSystemDotStMudVolumeSum = MudSystemDotStMudVolumeSum + MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)
-
- if ( MudSystemDotStMudVolumeSum > sum(MudSystemDotPipeSection_VolumeCapacity(2:F_StringIntervalCounts)) ) then
-
- !IF (St_MudOrKick%Array(imud) == 0) THEN
- MudSystemDotSt_MudSaved_Density = St_Density%Array(MudSystemDotimud)
- MudSystemDotSt_Saved_MudDischarged_Volume = MudSystemDotStMudVolumeSum - sum(MudSystemDotPipeSection_VolumeCapacity(2:F_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= St_Density%Array(imud)
- !END IF
-
- do ii= MudSystemDotimud + 1, MudSystemDotSt_MudDischarged_Volume%Length()
- !IF (St_MudOrKick%Array(ii) == 0) THEN
- MudSystemDotSt_MudSaved_Density = ((MudSystemDotSt_MudSaved_Density * MudSystemDotSt_Saved_MudDischarged_Volume) + (St_Density%Array(ii) * MudSystemDotSt_MudDischarged_Volume%Array(ii))) / (MudSystemDotSt_Saved_MudDischarged_Volume + MudSystemDotSt_MudDischarged_Volume%Array(ii))
- MudSystemDotSt_Saved_MudDischarged_Volume = MudSystemDotSt_Saved_MudDischarged_Volume + MudSystemDotSt_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= 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
- MudSystemDotSt_Saved_MudDischarged_Volume_Final = MudSystemDotSt_Saved_MudDischarged_Volume
-
- IF (WellHeadIsOpen) MudSystemDotMudVolume_InjectedToBH = MudSystemDotSt_Saved_MudDischarged_Volume_Final
- !======================================================================
-
- !========================STRING=================
-
- MudSystemDotimud=0
- do while (MudSystemDotimud < MudSystemDotSt_Mud_Forehead_X%Length())
- MudSystemDotimud = MudSystemDotimud + 1
-
- if (MudSystemDotimud> 1) then
- MudSystemDotSt_Mud_Backhead_X%Array(MudSystemDotimud)= MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud-1)
- St_Mud_Backhead_section%Array(MudSystemDotimud)= St_Mud_Forehead_section%Array(MudSystemDotimud-1)
- endif
-
- MudSystemDotDirectionCoef= (MudSystemDotXend_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))) &
- / ABS(MudSystemDotXend_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud)))
- ! +1 for string , -1 for annulus
-
-
- MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotDirectionCoef* (MudSystemDotXend_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))- MudSystemDotSt_Mud_Backhead_X%Array(MudSystemDotimud))* &
- MudSystemDotArea_PipeSectionFt(St_Mud_Backhead_section%Array(MudSystemDotimud)) !(ft^3)
- MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 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 ( MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud) <= MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
- St_Mud_Forehead_section%Array(MudSystemDotimud)= St_Mud_Backhead_section%Array(MudSystemDotimud)
- MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotSt_Mud_Backhead_X%Array(MudSystemDotimud)+ MudSystemDotDirectionCoef*(MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_PipeSectionFt(St_Mud_Backhead_section%Array(MudSystemDotimud))
- ! 7.48 is for gal to ft^3
-
- else
-
- MudSystemDotisection= St_Mud_Backhead_section%Array(MudSystemDotimud)+1
- MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
-
- do
- if (MudSystemDotisection > F_StringIntervalCounts) then ! last pipe section(string exit) F_StringIntervalCounts includes Horizontal line
- MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
- MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotXend_PipeSection(F_StringIntervalCounts)
- St_Mud_Forehead_section%Array(MudSystemDotimud)= F_StringIntervalCounts
-
- if (MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the string
- call RemoveStringMudArrays(MudSystemDotimud)
- endif
-
- exit
- endif
-
- MudSystemDotxx= MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection) !(gal)
-
- if (MudSystemDotxx<= 1.0) then
- St_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
- MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud)= (MudSystemDotxx * (MudSystemDotXend_PipeSection(MudSystemDotisection)- MudSystemDotXstart_PipeSection(MudSystemDotisection)))+ MudSystemDotXstart_PipeSection(MudSystemDotisection)
- exit
- else
- MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection)
- MudSystemDotisection= MudSystemDotisection+ 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 (Op_MudOrKick%Last() /= 0 .and. Op_MudOrKick%Last()==Ann_MudOrKick%First()) MudSystemDotiLoc=2 ! it may be 1,2,3 or more, all of them are kick
- !write(*,*) ' iloc (b): ' , iloc
-
- !=============================Add PumpFlowRate to Bottom Hole ==============================
- !if ( AnnulusFlowRate>0.0 ) then
- if ( MudSystemDotMudVolume_InjectedToBH > 0.0 ) then
-
-
- if (KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the
- AddLocation= MudSystemDotOp_Density%Length()-MudSystemDotiLoc+1+1 ! well, thus pumped mud should be placed above the kick
- else
- AddLocation= MudSystemDotOp_Density%Length()+1
- endif
- !write(*,*) 'AddLocation====' , AddLocation
- if ( AddLocation== 0) CALL ErrorStop ('AddLocation=0')
-
-
- if ( ABS(St_Density%Last() - MudSystemDotOp_Density%Array(AddLocation-1)) >= MudSystemDotDensityMixTol ) then
- !write(*,*) 'new pocket**'
- !write(*,*) 'St_Density%Last()=' , St_Density%Last()
- !write(*,*) 'Op_Density%Array(AddLocation-1)=' , Op_Density%Array(AddLocation-1)
-
-
- call MudSystemDotOp_Density% AddTo (AddLocation,St_Density%Last())
- !call Op_MudDischarged_Volume%AddTo (AddLocation,((AnnulusFlowRate/60.d0)*DeltaT_Mudline))
- call MudSystemDotOp_MudDischarged_Volume%AddTo (AddLocation,MudSystemDotMudVolume_InjectedToBH)
- call MudSystemDotOp_Mud_Forehead_X%AddTo (AddLocation,MudSystemDotXstart_OpSection(1))
- call Op_Mud_Forehead_section%AddTo (AddLocation,1)
- call MudSystemDotOp_Mud_Backhead_X%AddTo (AddLocation,MudSystemDotXstart_OpSection(1))
- call Op_Mud_Backhead_section%AddTo (AddLocation,1)
- call MudSystemDotOp_RemainedVolume_in_LastSection%AddTo (AddLocation,0.0d0)
- call MudSystemDotOp_EmptyVolume_inBackheadLocation%AddTo (AddLocation,0.0d0)
- call Op_MudOrKick%AddTo (AddLocation,0)
- else
- !write(*,*) 'merge**'
- !write(*,*) 'density before=' , Op_Density%Array(AddLocation-1)
- !write(*,*) 'St_Density%Last() for mix=' , St_Density%Last()
-
- !Op_Density%Array(AddLocation-1)= (Op_Density%Array(AddLocation-1)*Op_MudDischarged_Volume%Array(AddLocation-1)+St_Density%Last()*((AnnulusFlowRate/60.d0)*DeltaT_Mudline))/(Op_MudDischarged_Volume%Array(AddLocation-1)+((AnnulusFlowRate/60.d0)*DeltaT_Mudline))
- !Op_MudDischarged_Volume%Array(AddLocation-1)= Op_MudDischarged_Volume%Array(AddLocation-1) + ((AnnulusFlowRate/60.d0)*DeltaT_Mudline)
-
- MudSystemDotOp_Density%Array(AddLocation-1)= (MudSystemDotOp_Density%Array(AddLocation-1)*MudSystemDotOp_MudDischarged_Volume%Array(AddLocation-1)+St_Density%Last()*MudSystemDotMudVolume_InjectedToBH)/(MudSystemDotOp_MudDischarged_Volume%Array(AddLocation-1)+MudSystemDotMudVolume_InjectedToBH)
- MudSystemDotOp_MudDischarged_Volume%Array(AddLocation-1)= MudSystemDotOp_MudDischarged_Volume%Array(AddLocation-1) + MudSystemDotMudVolume_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
- MudSystemDotOpMudVolumeSum= 0.d0
- !Op_MudSaved_Density= 0.d0
- !Op_KickSaved_Density= 0.d0
- MudSystemDotOp_Saved_MudDischarged_Volume= 0.d0
- MudSystemDotOp_Kick_Saved_Volume= 0.d0
- MudSystemDotSaved_Op_MudOrKick= 0
-
-
-
- !write(*,*) 'Op_Capacity===' , sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
- !write(*,*) 'Op_MudDischarged_Volume%Length()===' , Op_MudDischarged_Volume%Length()
- !
-
- do MudSystemDotimud=1, MudSystemDotOp_MudDischarged_Volume%Length()
- !write(*,*) 'imud, Op_MudDischarged_Volume%Array(imud)=' , imud,Op_MudDischarged_Volume%Array(imud)
-
- MudSystemDotOpMudVolumeSum= MudSystemDotOpMudVolumeSum + MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)
-
- if ( MudSystemDotOpMudVolumeSum > sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts)) ) then
-
- IF (Op_MudOrKick%Array(MudSystemDotimud) == 0) THEN
- MudSystemDotOp_MudSaved_Density = MudSystemDotOp_Density%Array(MudSystemDotimud)
- MudSystemDotOp_Saved_MudDischarged_Volume = MudSystemDotOpMudVolumeSum - sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
- ELSE
- MudSystemDotOp_Kick_Saved_Volume = MudSystemDotOpMudVolumeSum - sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
- !write(*,*) 'cond 1- Op_MudOrKick%Array (imud),Op_Density%Array(imud):' ,Op_MudOrKick%Array (imud),Op_Density%Array(imud)
- MudSystemDotSaved_Op_MudOrKick= Op_MudOrKick%Array (MudSystemDotimud)
- MudSystemDotOp_KickSaved_Density= MudSystemDotOp_Density%Array(MudSystemDotimud)
- MudSystemDotiLoc= 2
- END IF
-
- do ii= MudSystemDotimud + 1, MudSystemDotOp_MudDischarged_Volume%Length()
- IF (Op_MudOrKick%Array(ii) == 0) THEN
- MudSystemDotOp_MudSaved_Density = ((MudSystemDotOp_MudSaved_Density * MudSystemDotOp_Saved_MudDischarged_Volume) + (MudSystemDotOp_Density%Array(ii) * MudSystemDotOp_MudDischarged_Volume%Array(ii))) / (MudSystemDotOp_Saved_MudDischarged_Volume + MudSystemDotOp_MudDischarged_Volume%Array(ii))
- MudSystemDotOp_Saved_MudDischarged_Volume = MudSystemDotOp_Saved_MudDischarged_Volume + MudSystemDotOp_MudDischarged_Volume%Array(ii)
- ELSE
- MudSystemDotOp_Kick_Saved_Volume = MudSystemDotOp_Kick_Saved_Volume + MudSystemDotOp_MudDischarged_Volume%Array(ii)
- !write(*,*) 'cond 2- Op_MudOrKick%Array (ii),Op_Density%Array(ii):' ,Op_MudOrKick%Array (ii),Op_Density%Array(ii)
- MudSystemDotSaved_Op_MudOrKick= Op_MudOrKick%Array (ii)
- MudSystemDotOp_KickSaved_Density= MudSystemDotOp_Density%Array(ii)
- MudSystemDotiLoc= 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
- MudSystemDotMudSection= F_StringIntervalCounts+1
- MudSystemDotBackheadX= MudSystemDotXstart_PipeSection(F_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 Rate_of_Penetration ==0. in bude: DeltaVolumeOp == 0.0
- ! if (ABS(AnnulusSuctionDensity_Old-St_Density%Last()) >= DensityMixTol .OR. (DeltaVolumeOp == 0.0 .and. ABS(Ann_Density%Array(iLoc)-St_Density%Last())>=DensityMixTol .and. AnnulusFlowRate/=0.0d0) ) then ! new mud is pumped
- ! call Ann_Density%AddTo (iLoc,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= St_Density%Last()
- !
- ! MudIsChanged= .true.
- ! endif
- !
- ! Ann_MudDischarged_Volume%Array(iLoc)= Ann_MudDischarged_Volume%Array(iLoc)+ ((AnnulusFlowRate/60.d0)*DeltaT_Mudline) !(gal)
- !
- !endif
-
-
-
-
-
-
- Ann_Mud_Backhead_section%Array(1)= MudSystemDotMudSection !it is needed to be updated for a condition that one pipe is removed from Annulus due to trip out
- Ann_Mud_Backhead_X%Array(1)= MudSystemDotBackheadX
-
-
-
- ! 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 (Rate_of_Penetration==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 (MudSystemDotOp_Kick_Saved_Volume > 0.0 .and. Ann_MudOrKick%First() == 0) then
- write(*,*) 'Kick influx enters Annulus'
- call Ann_Density%AddToFirst (MudSystemDotOp_KickSaved_Density)
- call MudSystemDotAnn_MudDischarged_Volume%AddToFirst (MudSystemDotOp_Kick_Saved_Volume)
- call Ann_Mud_Forehead_X%AddToFirst (MudSystemDotXstart_PipeSection(F_StringIntervalCounts+1))
- call Ann_Mud_Forehead_section%AddToFirst (F_StringIntervalCounts+1)
- call Ann_Mud_Backhead_X%AddToFirst (MudSystemDotXstart_PipeSection(F_StringIntervalCounts+1))
- call Ann_Mud_Backhead_section%AddToFirst (F_StringIntervalCounts+1)
- call Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call Ann_MudOrKick%AddToFirst (MudSystemDotSaved_Op_MudOrKick) !<<<<<<<<
- call Ann_CuttingMud%AddToFirst (0)
- elseif (MudSystemDotOp_Kick_Saved_Volume > 0.0 .and. Ann_MudOrKick%First() /= 0) then
- MudSystemDotAnn_MudDischarged_Volume%Array(1)= MudSystemDotAnn_MudDischarged_Volume%Array(1) + MudSystemDotOp_Kick_Saved_Volume
- endif
-
-
- if (MudSystemDotOp_Saved_MudDischarged_Volume> 0.0) then
- NewDensity= MudSystemDotOp_MudSaved_Density
- MudSystemDotNewVolume= MudSystemDotOp_Saved_MudDischarged_Volume
- !write(*,*) 'NewVolume=' , NewVolume
- !write(*,*) 'iloc=' , iloc,'Ann_MudDischarged_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
-
-
-
- if ((Rate_of_Penetration==0 .and. abs(Ann_Density%Array(MudSystemDotiLoc)-NewDensity)< MudSystemDotDensityMixTol) &
- .or. (Rate_of_Penetration>0. .and. Ann_CuttingMud%Array(MudSystemDotiLoc)==1 .and. abs(Ann_Density%Array(MudSystemDotiLoc)-NewDensity)< MudSystemDotCuttingDensityMixTol) &
- .or. (Rate_of_Penetration>0. .and. Ann_CuttingMud%Array(MudSystemDotiLoc)==0 .and. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc) < 42.) ) then ! 1-Pockets are Merged
-
- Ann_Density%Array(MudSystemDotiLoc)= (Ann_Density%Array(MudSystemDotiLoc)*MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+NewDensity*MudSystemDotNewVolume)/(MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotNewVolume)
- MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotNewVolume
- Ann_Mud_Forehead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
- Ann_Mud_Forehead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
- Ann_Mud_Backhead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
- Ann_Mud_Backhead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
- Ann_RemainedVolume_in_LastSection%Array(MudSystemDotiLoc)= (0.0d0)
- Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotiLoc)= (0.0d0)
- !write(*,*) 'merge' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
-
- else ! 2-Merging conditions are not meeted, so new pocket
- call Ann_Density%AddTo (MudSystemDotiLoc,NewDensity)
- call MudSystemDotAnn_MudDischarged_Volume%AddTo (MudSystemDotiLoc,MudSystemDotNewVolume)
- call Ann_Mud_Forehead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
- call Ann_Mud_Forehead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
- call Ann_Mud_Backhead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
- call Ann_Mud_Backhead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
- call Ann_RemainedVolume_in_LastSection%AddTo (MudSystemDotiLoc,0.0d0)
- call Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystemDotiLoc,0.0d0)
- call Ann_MudOrKick%AddTo (MudSystemDotiLoc,0)
- call Ann_CuttingMud%AddTo (MudSystemDotiLoc,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 (Rate_of_Penetration>0. .and. MudSystemDotDeltaVolumeOp>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)
-
-
- !NewDensity= (St_Density%Last() * AnnulusFlowRate + 141.4296E-4*Rate_of_Penetration*Diameter_of_Bit**2)/(AnnulusFlowRate+6.7995E-4*Rate_of_Penetration*Diameter_of_Bit**2)
-
- NewDensity= St_Density%Last()
-
-
- !NewVolume= ((AnnulusFlowRate/60.0d0)*DeltaT_Mudline)+DeltaVolumeOp
- !!! Density in ppg, flow rate in gpm, ROP in ft/s, bit diameter in inch
-
-
- do MudSystemDotimud=1, MudSystemDotOp_MudDischarged_Volume%Length()
- if ( Op_MudOrKick%Array(MudSystemDotimud) == 0 ) then
- MudSystemDotOp_Density%Array(MudSystemDotimud)= NewDensity
-
- endif
- enddo
-
-
-
- if (MudSystemDotOp_Kick_Saved_Volume > 0.0 .and. Ann_MudOrKick%First() == 0) then
- write(*,*) 'Kick influx enters Annulus first time'
- !write(*,*) 'Saved_Op_MudOrKick=',Saved_Op_MudOrKick
- call Ann_Density%AddToFirst (MudSystemDotOp_KickSaved_Density)
- call MudSystemDotAnn_MudDischarged_Volume%AddToFirst (MudSystemDotOp_Kick_Saved_Volume)
- call Ann_Mud_Forehead_X%AddToFirst (MudSystemDotXstart_PipeSection(F_StringIntervalCounts+1))
- call Ann_Mud_Forehead_section%AddToFirst (F_StringIntervalCounts+1)
- call Ann_Mud_Backhead_X%AddToFirst (MudSystemDotXstart_PipeSection(F_StringIntervalCounts+1))
- call Ann_Mud_Backhead_section%AddToFirst (F_StringIntervalCounts+1)
- call Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call Ann_MudOrKick%AddToFirst (MudSystemDotSaved_Op_MudOrKick) !<<<<<<<<
- call Ann_CuttingMud%AddToFirst (0)
- elseif (MudSystemDotOp_Kick_Saved_Volume > 0.0 .and. Ann_MudOrKick%First() /= 0) then
- MudSystemDotAnn_MudDischarged_Volume%Array(1)= MudSystemDotAnn_MudDischarged_Volume%Array(1) + MudSystemDotOp_Kick_Saved_Volume
- endif
-
-
- if (MudSystemDotOp_Saved_MudDischarged_Volume> 0.0) then
- !write(*,*) 'Op_Saved_Mud added'
- NewDensity= NewDensity !(drilling density)
- MudSystemDotNewVolume= MudSystemDotOp_Saved_MudDischarged_Volume + MudSystemDotDeltaVolumeOp ! (DeltaVolumeOp: for Cuttings Volume)
- !write(*,*) 'NewVolume=' , NewVolume
- !write(*,*) 'iloc=' , iloc,'Ann_MudDischarged_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
-
- if ( (Ann_CuttingMud%Array(MudSystemDotiLoc)==1 .and. abs(Ann_Density%Array(MudSystemDotiLoc)-NewDensity)< MudSystemDotCuttingDensityMixTol ) &
- .or. (Ann_CuttingMud%Array(MudSystemDotiLoc)==0 .and. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc) < 42.) ) then ! 1-Pockets are Merged
-
- Ann_Density%Array(MudSystemDotiLoc)= (Ann_Density%Array(MudSystemDotiLoc)*MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+NewDensity*MudSystemDotNewVolume)/(MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotNewVolume)
- MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotNewVolume
- Ann_Mud_Forehead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
- Ann_Mud_Forehead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
- Ann_Mud_Backhead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
- Ann_Mud_Backhead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
- Ann_RemainedVolume_in_LastSection%Array(MudSystemDotiLoc)= (0.0d0)
- Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotiLoc)= (0.0d0)
- Ann_CuttingMud%Array(MudSystemDotiLoc)= 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),NewDensity
- !write(*,*) 'before e) Ann_MudDischarged_Volume%Array(iLoc)=' , Ann_MudDischarged_Volume%Array(iLoc)
-
-
- call Ann_Density%AddTo (MudSystemDotiLoc,NewDensity)
- call MudSystemDotAnn_MudDischarged_Volume%AddTo (MudSystemDotiLoc,MudSystemDotNewVolume)
- call Ann_Mud_Forehead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
- call Ann_Mud_Forehead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
- call Ann_Mud_Backhead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
- call Ann_Mud_Backhead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
- call Ann_RemainedVolume_in_LastSection%AddTo (MudSystemDotiLoc,0.0d0)
- call Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystemDotiLoc,0.0d0)
- call Ann_MudOrKick%AddTo (MudSystemDotiLoc,0)
- call Ann_CuttingMud%AddTo (MudSystemDotiLoc,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'
-
- MudSystemDotNewVolume= ((MudSystemDotAnnulusFlowRate/60.d0)*DeltaT_Mudline) - MudSystemDotOp_Saved_MudDischarged_Volume
-
- if (MudSystemDotiLoc==2 .and. Op_MudOrKick%Last()==0 .and. MudSystemDotNewVolume > 0.d0 ) then ! for avoid kick separation
- !write(*,*) 'avoid kick separation'
-
-
- NewDensity= MudSystemDotOp_MudSaved_Density
-
- call RemoveOpMudArrays(MudSystemDotOp_Density%Length()) ! mud here is removed and then will be added to iloc=2 in Ann
- if ( MudSystemDotAnn_MudDischarged_Volume%Array(1) > ((MudSystemDotAnnulusFlowRate/60.d0)*DeltaT_Mudline)- MudSystemDotOp_Saved_MudDischarged_Volume) then! 1st in Ann = kick
- !write(*,*) 'mode1'
- MudSystemDotAnn_MudDischarged_Volume%Array(1)= MudSystemDotAnn_MudDischarged_Volume%Array(1) - (((MudSystemDotAnnulusFlowRate/60.d0)*DeltaT_Mudline) -MudSystemDotOp_Saved_MudDischarged_Volume)
- MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotOp_Density%Length())= MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotOp_Density%Length())+ (((MudSystemDotAnnulusFlowRate/60.d0)*DeltaT_Mudline) - MudSystemDotOp_Saved_MudDischarged_Volume) !kick
- else
- call RemoveAnnulusMudArrays(1) !kick is removed
- MudSystemDotiLoc= 1
- MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotOp_Density%Length())= MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotOp_Density%Length())+ (((MudSystemDotAnnulusFlowRate/60.d0)*DeltaT_Mudline) - MudSystemDotOp_Saved_MudDischarged_Volume)
- !write(*,*) 'mode2'
-
- ! including a little expand
- endif
-
-
- if ((Rate_of_Penetration==0 .and. abs(Ann_Density%Array(MudSystemDotiLoc)-NewDensity)< MudSystemDotDensityMixTol) &
- .or. (Rate_of_Penetration>0. .and. Ann_CuttingMud%Array(MudSystemDotiLoc)==1 .and. abs(Ann_Density%Array(MudSystemDotiLoc)-NewDensity)< MudSystemDotCuttingDensityMixTol) &
- .or. (Rate_of_Penetration>0. .and. Ann_CuttingMud%Array(MudSystemDotiLoc)==0 .and. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc) < 42.) ) then ! 1-Pockets are Merged
-
- Ann_Density%Array(MudSystemDotiLoc)= (Ann_Density%Array(MudSystemDotiLoc)*MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+NewDensity*MudSystemDotNewVolume)/(MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotNewVolume)
- MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotNewVolume
- Ann_Mud_Forehead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
- Ann_Mud_Forehead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
- Ann_Mud_Backhead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
- Ann_Mud_Backhead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
- Ann_RemainedVolume_in_LastSection%Array(MudSystemDotiLoc)= (0.0d0)
- Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotiLoc)= (0.0d0)
- else ! 2-Merging conditions are not meeted, so new pocket
- call Ann_Density%AddTo (MudSystemDotiLoc,NewDensity)
- call MudSystemDotAnn_MudDischarged_Volume%AddTo (MudSystemDotiLoc,MudSystemDotNewVolume)
- call Ann_Mud_Forehead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
- call Ann_Mud_Forehead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
- call Ann_Mud_Backhead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
- call Ann_Mud_Backhead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
- call Ann_RemainedVolume_in_LastSection%AddTo (MudSystemDotiLoc,0.0d0)
- call Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystemDotiLoc,0.0d0)
- call Ann_MudOrKick%AddTo (MudSystemDotiLoc,0)
- call Ann_CuttingMud%AddTo (MudSystemDotiLoc,0)
- !write(*,*) 'd) annLength=' , Ann_Density%Length()
-
- endif
-
-
- endif
- !===================================================================
- if( Op_MudOrKick%Last() == 1 .and. Ann_MudOrKick%First() == 0 ) then
-
- write(*,*) '***error2****=='
-
- write(*,*) 'Op_Kick_Saved_Volume,Op_Saved_MudDischarged_Volume=' , MudSystemDotOp_Kick_Saved_Volume,MudSystemDotOp_Saved_MudDischarged_Volume
-
-
- write(*,*) 'after add to ann=='
-
- do MudSystemDotimud=1, MudSystemDotOp_MudDischarged_Volume%Length()
- write(*,*) 'Op:', MudSystemDotimud, MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud), MudSystemDotOp_Density%Array(MudSystemDotimud) ,Op_MudOrKick%Array(MudSystemDotimud)
- enddo
-
- do MudSystemDotimud=1, MudSystemDotAnn_MudDischarged_Volume%Length()
- write(*,*) 'Ann:', MudSystemDotimud, MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud), Ann_Density%Array(MudSystemDotimud) ,Ann_MudOrKick%Array(MudSystemDotimud)
- enddo
-
- write(*,*) '==after add to ann'
-
- write(*,*) 'NewVolume,Op_MudOrKick%Last=' , MudSystemDotNewVolume,Op_MudOrKick%Last()
- write(*,*) '==***error2****'
-
- endif
-
-
-
-
-
- !=============== save Ann Mud data to transfer to the ChokeLine enterance
- MudSystemDotAnnMudVolumeSum= 0.d0
- !Ann_MudSaved_Density= 0.d0
- !Ann_KickSaved_Density= 0.d0
- MudSystemDotAnn_Saved_MudDischarged_Volume= 0.d0
- MudSystemDotAnn_Kick_Saved_Volume= 0.d0
- MudSystemDotSaved_Ann_MudOrKick= 0
- MudSystemDotAnn_to_Choke_2mud= .false.
-
-
-
-
- do MudSystemDotimud=1, MudSystemDotAnn_MudDischarged_Volume%Length()
-
- MudSystemDotAnnMudVolumeSum= MudSystemDotAnnMudVolumeSum + MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)
-
- if ( MudSystemDotAnnMudVolumeSum > sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections)) ) then
-
- IF (Ann_MudOrKick%Array(MudSystemDotimud) == 0) THEN
- MudSystemDotAnn_MudSaved_Density = Ann_Density%Array(MudSystemDotimud)
- MudSystemDotAnn_Saved_MudDischarged_Volume = MudSystemDotAnnMudVolumeSum - sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections))
- ELSEIF (Ann_MudOrKick%Array(MudSystemDotimud) > 0 .AND. Ann_MudOrKick%Array(MudSystemDotimud) <100) THEN ! 104= AIR
- MudSystemDotAnn_Kick_Saved_Volume = MudSystemDotAnnMudVolumeSum - sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections))
- MudSystemDotSaved_Ann_MudOrKick= Ann_MudOrKick%Array (MudSystemDotimud)
- MudSystemDotAnn_KickSaved_Density= Ann_Density%Array(MudSystemDotimud)
- END IF
-
- do ii= MudSystemDotimud + 1, MudSystemDotAnn_MudDischarged_Volume%Length()
- IF (Ann_MudOrKick%Array(ii) == 0) THEN
- MudSystemDotAnn_MudSaved_Density = ((MudSystemDotAnn_MudSaved_Density * MudSystemDotAnn_Saved_MudDischarged_Volume) + (Ann_Density%Array(ii) * MudSystemDotAnn_MudDischarged_Volume%Array(ii))) / (MudSystemDotAnn_Saved_MudDischarged_Volume + MudSystemDotAnn_MudDischarged_Volume%Array(ii))
- MudSystemDotAnn_Saved_MudDischarged_Volume = MudSystemDotAnn_Saved_MudDischarged_Volume + MudSystemDotAnn_MudDischarged_Volume%Array(ii)
- MudSystemDotAnn_to_Choke_2mud= .true.
- ELSEIF (Ann_MudOrKick%Array(ii) > 0 .AND. Ann_MudOrKick%Array(ii) <100) THEN ! 104= AIR
- MudSystemDotAnn_Kick_Saved_Volume = MudSystemDotAnn_Kick_Saved_Volume + MudSystemDotAnn_MudDischarged_Volume%Array(ii)
- MudSystemDotSaved_Ann_MudOrKick= Ann_MudOrKick%Array (ii)
- MudSystemDotAnn_KickSaved_Density= 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
- MudSystemDotAnn_Saved_MudDischarged_Volume_Final= MudSystemDotAnn_Saved_MudDischarged_Volume !+ Ann_Kick_Saved_Volume
- MudSystemDotAnn_Kick_Saved_Volume_Final= MudSystemDotAnn_Kick_Saved_Volume
- IF (WellHeadIsOpen) MudVolume_InjectedFromAnn = MudSystemDotAnn_Saved_MudDischarged_Volume_Final -((MudSystemDotQlost/60.0d0)*DeltaT_Mudline)
- !WRITE (*,*) 'MudVolume_InjectedFromAnn=', 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
-
- MudSystemDottotal_injected = MudSystemDottotal_injected + MudVolume_InjectedFromAnn
-
- if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
- MudSystemDottotal_injected= 0.
- endif
-
- !write(*,*) ' total injected-tripin =' , total_injected
- !write(*,*) 'injected-tripin =' , MudVolume_InjectedFromAnn
-
-
-
-
-
- !======================== Annulus ====================
-
- !MudIsChanged= .false.
-
- MudSystemDotimud= 0
-
- do while (MudSystemDotimud < Ann_Mud_Forehead_X%Length())
- MudSystemDotimud = MudSystemDotimud + 1
-
- if (MudSystemDotimud> 1) then
- Ann_Mud_Backhead_X%Array(MudSystemDotimud)= Ann_Mud_Forehead_X%Array(MudSystemDotimud-1)
- Ann_Mud_Backhead_section%Array(MudSystemDotimud)= Ann_Mud_Forehead_section%Array(MudSystemDotimud-1)
- endif
-
-
-
- ! <<< Fracture Shoe Lost
- IF ( MudSystemDotShoeLost .and. Shoe%ShoeDepth < Ann_Mud_Backhead_X%Array(MudSystemDotimud) .and. Shoe%ShoeDepth >= Ann_Mud_Forehead_X%Array(MudSystemDotimud) ) then
- !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline)
- MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)-((MudSystemDotQlost/60.0d0)*DeltaT_Mudline) !(gal)
- if (MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud) < 0.0) then
- !write(*,*) 'mud is removed by shoe lost, imud=' , imud
- call RemoveAnnulusMudArrays(MudSystemDotimud)
- MudSystemDotimud= MudSystemDotimud-1
- cycle
- endif
-
- ENDIF
- ! Fracture Shoe Lost >>>
-
-
- MudSystemDotDirectionCoef= (MudSystemDotXend_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))) &
- / ABS(MudSystemDotXend_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud)))
- ! +1 for string , -1 for annulus
-
-
- Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotDirectionCoef* (MudSystemDotXend_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))- Ann_Mud_Backhead_X%Array(MudSystemDotimud))* &
- MudSystemDotArea_PipeSectionFt(Ann_Mud_Backhead_section%Array(MudSystemDotimud)) !(ft^3)
- Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 7.48051948d0 ! ft^3 to gal
-
-
- if ( MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud) <= Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
- Ann_Mud_Forehead_section%Array(MudSystemDotimud)= Ann_Mud_Backhead_section%Array(MudSystemDotimud)
- Ann_Mud_Forehead_X%Array(MudSystemDotimud)= Ann_Mud_Backhead_X%Array(MudSystemDotimud)+ MudSystemDotDirectionCoef*(MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_PipeSectionFt(Ann_Mud_Backhead_section%Array(MudSystemDotimud))
- ! 7.48 is for gal to ft^3
-
- else
-
- MudSystemDotisection= Ann_Mud_Backhead_section%Array(MudSystemDotimud)+1
- Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)- Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
-
- do
- if (MudSystemDotisection > MudSystemDotNoPipeSections) then ! last pipe section(well exit)
- MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)- Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
- Ann_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotXend_PipeSection(MudSystemDotNoPipeSections)
- Ann_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotNoPipeSections
-
- if (MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the well
- !write(*,*) 'remove******'
- call RemoveAnnulusMudArrays(MudSystemDotimud)
- endif
- exit
- endif
-
- MudSystemDotxx= Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection) !(gal)
-
- if (MudSystemDotxx<= 1.0) then
- Ann_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
- Ann_Mud_Forehead_X%Array(MudSystemDotimud)= (MudSystemDotxx * (MudSystemDotXend_PipeSection(MudSystemDotisection)- MudSystemDotXstart_PipeSection(MudSystemDotisection)))+ MudSystemDotXstart_PipeSection(MudSystemDotisection)
- exit
- else
- Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection)
- MudSystemDotisection= MudSystemDotisection+ 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 (Ann_Mud_Forehead_X%Last() < MudSystemDotXend_PipeSection(MudSystemDotNoPipeSections)) then
- Ann_Mud_Forehead_X%Array(Ann_Mud_Forehead_X%Length()) = MudSystemDotXend_PipeSection(MudSystemDotNoPipeSections) ! 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=================
- MudSystemDotimud=0
- do while (MudSystemDotimud < MudSystemDotOp_Mud_Forehead_X%Length())
- MudSystemDotimud = MudSystemDotimud + 1
-
- if (MudSystemDotimud> 1) then
- MudSystemDotOp_Mud_Backhead_X%Array(MudSystemDotimud)= MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud-1)
- Op_Mud_Backhead_section%Array(MudSystemDotimud)= Op_Mud_Forehead_section%Array(MudSystemDotimud-1)
- endif
- !write(*,*) 'imud**=' , imud
- MudSystemDotDirectionCoef= (MudSystemDotXend_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))) &
- / ABS(MudSystemDotXend_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud)))
- ! +1 for string , -1 for annulus
-
-
- MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotDirectionCoef* (MudSystemDotXend_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))- MudSystemDotOp_Mud_Backhead_X%Array(MudSystemDotimud))* &
- MudSystemDotArea_OpSectionFt(Op_Mud_Backhead_section%Array(MudSystemDotimud)) !(ft^3)
- MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 7.48051948d0 ! ft^3 to gal
- !write(*,*) ' Op_EmptyVolume_inBackheadLocation%Array(1) =' , Op_EmptyVolume_inBackheadLocation%Array(1)
- if ( MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(1) < 0.0) CALL ErrorStop1 ('Negative Empty volume')
-
- if ( MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud) <= MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
- Op_Mud_Forehead_section%Array(MudSystemDotimud)= Op_Mud_Backhead_section%Array(MudSystemDotimud)
- MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotOp_Mud_Backhead_X%Array(MudSystemDotimud)+ MudSystemDotDirectionCoef*(MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_OpSectionFt(Op_Mud_Backhead_section%Array(MudSystemDotimud))
- ! 7.48 is for gal to ft^3
-
- else
-
-
- MudSystemDotisection= Op_Mud_Backhead_section%Array(MudSystemDotimud)+1
- MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
-
- do
- if (MudSystemDotisection > F_BottomHoleIntervalCounts) then ! last pipe section(well exit)
- !if( imud==1) KickDeltaVinAnnulus= Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space
- MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
- MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotXend_OpSection(F_BottomHoleIntervalCounts)
- Op_Mud_Forehead_section%Array(MudSystemDotimud)= F_BottomHoleIntervalCounts
-
- if (MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the well
- call RemoveOpMudArrays(MudSystemDotimud)
- endif
-
- exit
- endif
-
- MudSystemDotxx= MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotOpSection_VolumeCapacity(MudSystemDotisection) !(gal)
-
- if (MudSystemDotxx<= 1.0) then
- Op_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
- MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)= (MudSystemDotxx * (MudSystemDotXend_OpSection(MudSystemDotisection)- MudSystemDotXstart_OpSection(MudSystemDotisection)))+ MudSystemDotXstart_OpSection(MudSystemDotisection)
- exit
- else
- MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotOpSection_VolumeCapacity(MudSystemDotisection)
- MudSystemDotisection= MudSystemDotisection+ 1
-
- endif
-
- enddo
-
- endif
- ! for OP remove:
-
- if (MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)== MudSystemDotXend_OpSection(F_BottomHoleIntervalCounts)) then
- MudSystemDottotalLength = MudSystemDotOp_MudDischarged_Volume%Length()
- do while(MudSystemDotimud < MudSystemDottotalLength)
-
- !imud = imud + 1
- call RemoveOpMudArrays(MudSystemDottotalLength)
- MudSystemDottotalLength = MudSystemDottotalLength - 1
-
-
- enddo
-
- exit !
-
- endif
-
-
-
-
- !if (Op_Mud_Forehead_X%Array(imud)== Xend_OpSection(F_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),St_Density%Array(imud)
- ! enddo
- !
- !write(*,*) '==after sorting st'
-
-
-
-
- !write(*,*) '**Ann_Kick_Saved_Final,Mud_InjectedFromAnn' , Ann_Kick_Saved_Volume_Final,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,MudVolume_InjectedFromAnn' , Ann_Kick_Saved_Volume_Final,MudVolume_InjectedFromAnn
-
- !write(*,*) 'begining chokeline=='
-
-
-
-
-
-
-
- MudSystemDotChokeLineFlowRate = MUD(4)%Q
- !WRITE (*,*) 'MUD(4)%Q', MUD(4)%Q
-
-
- if (MudSystemDotNewPipeFilling == 0) then ! .or. UtubeFilling==0) then
- MudSystemDotChokeLineFlowRate= 0.
- endif
-
-
- do MudSystemDotimud=1, MudSystemDotChokeLine_MudDischarged_Volume%Length()-2
- if ( ChokeLine_MudOrKick%Array(MudSystemDotimud) ==1 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+1) ==0 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+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 ( MudSystemDotAnn_Kick_Saved_Volume > 1.0e-5 .and. ( MudVolume_InjectedFromAnn ) <= 1.0e-5 ) then
-
- !WRITE (*,*) 'only kick enters to chokeline, Casing pressure = ', PressureGauges(2)
-
- if (ChokeLine_MudOrKick%First() == 0) then
- call MudSystemDotChokeLine_Density%AddToFirst (MudSystemDotAnn_KickSaved_Density)
- call MudSystemDotChokeLine_MudDischarged_Volume%AddToFirst (0.d0)
- call MudSystemDotChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Forehead_section%AddToFirst (1)
- call MudSystemDotChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Backhead_section%AddToFirst (1)
- call MudSystemDotChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call ChokeLine_MudOrKick%AddToFirst (MudSystemDotSaved_Ann_MudOrKick)
-
- ChokeLineDensity_Old= MudSystemDotAnn_KickSaved_Density
-
- endif
-
- MudSystemDotChokeLine_MudDischarged_Volume%Array(1)= MudSystemDotChokeLine_MudDischarged_Volume%Array(1)+ MudSystemDotAnn_Kick_Saved_Volume !(gal)
-
- endif
-
-
- do MudSystemDotimud=1, MudSystemDotChokeLine_MudDischarged_Volume%Length()-2
- if ( ChokeLine_MudOrKick%Array(MudSystemDotimud) ==1 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+1) ==0 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+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 ( MudSystemDotAnn_Kick_Saved_Volume <= 1.0e-5 .and. MudVolume_InjectedFromAnn > 1.0e-5 ) then
-
- !WRITE (*,*) 'only mud enters to chokeline'
-
-
- if ((MudSystemDotAnn_to_Choke_2mud == .false. .and. ABS(ChokeLineDensity_Old - MudSystemDotAnn_MudSaved_Density) >= MudSystemDotDensityMixTol) .or. ChokeLine_MudOrKick%First() /= 0) then ! new mud is pumped
- call MudSystemDotChokeLine_Density%AddToFirst (MudSystemDotAnn_MudSaved_Density)
- call MudSystemDotChokeLine_MudDischarged_Volume%AddToFirst (0.0d0)
- call MudSystemDotChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Forehead_section%AddToFirst (1)
- call MudSystemDotChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Backhead_section%AddToFirst (1)
- call MudSystemDotChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call ChokeLine_MudOrKick%AddToFirst (0)
-
- ChokeLineDensity_Old= MudSystemDotAnn_MudSaved_Density
- endif
-
- !ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1)+ (Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) !(gal)
- MudSystemDotChokeLine_MudDischarged_Volume%Array(1)= MudSystemDotChokeLine_MudDischarged_Volume%Array(1)+ (MudVolume_InjectedFromAnn) !(gal)
-
-
-
- endif
-
-
-
- do MudSystemDotimud=1, MudSystemDotChokeLine_MudDischarged_Volume%Length()-2
- if ( ChokeLine_MudOrKick%Array(MudSystemDotimud) ==1 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+1) ==0 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+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 ( MudSystemDotAnn_Kick_Saved_Volume > 1.0e-5 .and. (MudVolume_InjectedFromAnn) > 1.0e-5 .and. ChokeLine_MudOrKick%First() /= 0 ) then
-
- WRITE (*,*) 'Kick Enters Choke line Last Time'
-
- MudSystemDotChokeLine_MudDischarged_Volume%Array(1)= MudSystemDotChokeLine_MudDischarged_Volume%Array(1)+ MudSystemDotAnn_Kick_Saved_Volume !(gal)
-
-
-
- call MudSystemDotChokeLine_Density%AddToFirst (MudSystemDotAnn_MudSaved_Density)
- !call ChokeLine_MudDischarged_Volume%AddToFirst (Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) )
- call MudSystemDotChokeLine_MudDischarged_Volume%AddToFirst (MudVolume_InjectedFromAnn)
- call MudSystemDotChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Forehead_section%AddToFirst (1)
- call MudSystemDotChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Backhead_section%AddToFirst (1)
- call MudSystemDotChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call ChokeLine_MudOrKick%AddToFirst (0)
-
- ChokeLineDensity_Old= MudSystemDotAnn_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 ( MudSystemDotAnn_Kick_Saved_Volume > 1.0e-5 .and. ( MudVolume_InjectedFromAnn ) > 1.0e-5 .and. 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)
- MudSystemDotChokeLine_MudDischarged_Volume%Array(1)= MudSystemDotChokeLine_MudDischarged_Volume%Array(1)+ ( MudVolume_InjectedFromAnn ) !(gal)
-
-
-
-
- call MudSystemDotChokeLine_Density%AddToFirst (MudSystemDotAnn_KickSaved_Density)
- call MudSystemDotChokeLine_MudDischarged_Volume%AddToFirst (MudSystemDotAnn_Kick_Saved_Volume)
- call MudSystemDotChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Forehead_section%AddToFirst (1)
- call MudSystemDotChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
- call ChokeLine_Mud_Backhead_section%AddToFirst (1)
- call MudSystemDotChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
- call MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
- call ChokeLine_MudOrKick%AddToFirst (MudSystemDotSaved_Ann_MudOrKick)
-
- ChokeLineDensity_Old= MudSystemDotAnn_KickSaved_Density
-
-
- endif
-
- do MudSystemDotimud=1, MudSystemDotChokeLine_MudDischarged_Volume%Length()-2
- if ( ChokeLine_MudOrKick%Array(MudSystemDotimud) ==1 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+1) ==0 .and. ChokeLine_MudOrKick%Array(MudSystemDotimud+2) ==1 ) then
- write(*,*) 'error_location is 4'
- error_occured = 1
-
- endif
- enddo
-
- if (error_occured == 1) then
-
- do MudSystemDotimud=1, MudSystemDotChokeLine_MudDischarged_Volume%Length()
- write(*,*) 'ChokeLine:', MudSystemDotimud, MudSystemDotChokeLine_Density%Array(MudSystemDotimud) ,ChokeLine_MudOrKick%Array(MudSystemDotimud)
- 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==========================
- MudSystemDotChokeMudVolumeSum= 0.d0
- !Ann_MudSaved_Density= 0.d0
- !Ann_KickSaved_Density= 0.d0
- MudSystemDotChoke_Saved_MudDischarged_Volume= 0.d0
- MudSystemDotChoke_Kick_Saved_Volume= 0.d0
- MudSystemDotSaved_Choke_MudOrKick= 0
-
-
-
-
- do MudSystemDotimud=1, MudSystemDotChokeLine_MudDischarged_Volume%Length()
-
- MudSystemDotChokeMudVolumeSum= MudSystemDotChokeMudVolumeSum + MudSystemDotChokeLine_MudDischarged_Volume%Array(MudSystemDotimud)
-
- if ( MudSystemDotChokeMudVolumeSum > MudSystemDotChokeLine_VolumeCapacity ) then
-
- IF (ChokeLine_MudOrKick%Array(MudSystemDotimud) == 0) THEN
- MudSystemDotChoke_MudSaved_Density = MudSystemDotChokeLine_Density%Array(MudSystemDotimud)
- MudSystemDotChoke_Saved_MudDischarged_Volume = MudSystemDotChokeMudVolumeSum - MudSystemDotChokeLine_VolumeCapacity
- ELSEIF (ChokeLine_MudOrKick%Array(MudSystemDotimud) > 0 .AND. ChokeLine_MudOrKick%Array(MudSystemDotimud) <100) THEN ! 104= AIR
- MudSystemDotChoke_Kick_Saved_Volume = MudSystemDotChokeMudVolumeSum - MudSystemDotChokeLine_VolumeCapacity
- MudSystemDotSaved_Choke_MudOrKick= ChokeLine_MudOrKick%Array (MudSystemDotimud)
- MudSystemDotChoke_KickSaved_Density= MudSystemDotChokeLine_Density%Array(MudSystemDotimud)
- END IF
-
- do ii= MudSystemDotimud + 1, MudSystemDotChokeLine_MudDischarged_Volume%Length()
-
- IF (ChokeLine_MudOrKick%Array(ii) == 0) THEN
- MudSystemDotChoke_MudSaved_Density = ((MudSystemDotChoke_MudSaved_Density * MudSystemDotChoke_Saved_MudDischarged_Volume) + (MudSystemDotChokeLine_Density%Array(ii) * MudSystemDotChokeLine_MudDischarged_Volume%Array(ii))) / (MudSystemDotChoke_Saved_MudDischarged_Volume + MudSystemDotChokeLine_MudDischarged_Volume%Array(ii))
- MudSystemDotChoke_Saved_MudDischarged_Volume = MudSystemDotChoke_Saved_MudDischarged_Volume + MudSystemDotChokeLine_MudDischarged_Volume%Array(ii)
- ELSEIF (ChokeLine_MudOrKick%Array(ii) > 0 .AND. ChokeLine_MudOrKick%Array(ii) <100) THEN ! 104= AIR
- MudSystemDotChoke_Kick_Saved_Volume = MudSystemDotChoke_Kick_Saved_Volume + MudSystemDotChokeLine_MudDischarged_Volume%Array(ii)
- MudSystemDotSaved_Choke_MudOrKick= ChokeLine_MudOrKick%Array (ii)
- MudSystemDotChoke_KickSaved_Density= MudSystemDotChokeLine_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
- MudSystemDotChoke_Saved_MudDischarged_Volume_Final= MudSystemDotChoke_Saved_MudDischarged_Volume !+ Choke_Kick_Saved_Volume
- MudSystemDotChoke_Kick_Saved_Volume_Final= MudSystemDotChoke_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=================
-
- MudSystemDotimud=0
- do while (MudSystemDotimud < MudSystemDotChokeLine_Mud_Forehead_X%Length())
- MudSystemDotimud = MudSystemDotimud + 1
-
- if (MudSystemDotimud> 1) then
- MudSystemDotChokeLine_Mud_Backhead_X%Array(MudSystemDotimud)= MudSystemDotChokeLine_Mud_Forehead_X%Array(MudSystemDotimud-1)
- ChokeLine_Mud_Backhead_section%Array(MudSystemDotimud)= ChokeLine_Mud_Forehead_section%Array(MudSystemDotimud-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
-
-
- MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= (BopStackSpecification%ChokeLineLength- MudSystemDotChokeLine_Mud_Backhead_X%Array(MudSystemDotimud))* MudSystemDotArea_ChokeLineFt !(ft^3)
-
- MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 7.48051948d0 ! ft^3 to gal
-
- if ( MudSystemDotChokeLine_MudDischarged_Volume%Array(MudSystemDotimud) <= MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
- ChokeLine_Mud_Forehead_section%Array(MudSystemDotimud)= ChokeLine_Mud_Backhead_section%Array(MudSystemDotimud)
- MudSystemDotChokeLine_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotChokeLine_Mud_Backhead_X%Array(MudSystemDotimud)+ (MudSystemDotChokeLine_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_ChokeLineFt
- ! 7.48 is for gal to ft^3
-
- else
-
- MudSystemDotisection= ChokeLine_Mud_Backhead_section%Array(MudSystemDotimud)+1
- MudSystemDotChokeLine_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotChokeLine_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
-
- do
- if (MudSystemDotisection > 1) then ! last pipe section(Chokeline exit)
- MudSystemDotChokeLine_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotChokeLine_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotChokeLine_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
- MudSystemDotChokeLine_Mud_Forehead_X%Array(MudSystemDotimud)= BopStackSpecification%ChokeLineLength
- ChokeLine_Mud_Forehead_section%Array(MudSystemDotimud)= 1
- if (MudSystemDotChokeLine_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the string
- call MudSystemDotChokeLine_MudDischarged_Volume%Remove (MudSystemDotimud)
- call MudSystemDotChokeLine_Mud_Backhead_X%Remove (MudSystemDotimud)
- call ChokeLine_Mud_Backhead_section%Remove (MudSystemDotimud)
- call MudSystemDotChokeLine_Mud_Forehead_X%Remove (MudSystemDotimud)
- call ChokeLine_Mud_Forehead_section%Remove (MudSystemDotimud)
- call MudSystemDotChokeLine_Density%Remove (MudSystemDotimud)
- call MudSystemDotChokeLine_RemainedVolume_in_LastSection%Remove (MudSystemDotimud)
- call MudSystemDotChokeLine_EmptyVolume_inBackheadLocation%Remove (MudSystemDotimud)
- call ChokeLine_MudOrKick%Remove (MudSystemDotimud)
-
- endif
- exit
- endif
-
- MudSystemDotxx= MudSystemDotChokeLine_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotChokeLine_VolumeCapacity !(gal)
-
- if (MudSystemDotxx<= 1.0) then
- ChokeLine_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
- MudSystemDotChokeLine_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotxx * BopStackSpecification%ChokeLineLength
- exit
- else
- MudSystemDotChokeLine_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotChokeLine_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotChokeLine_VolumeCapacity
- MudSystemDotisection= MudSystemDotisection+ 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
-
- ChokeOutletDensity= MudSystemDotChokeLine_Density%Last() ! used in MudSystem
-
-
-
-
-
- do i=1, ChokeLine_MudOrKick%Length()
- !write(*,555) i,'Choke_Volume(i), type=' ,ChokeLine_MudDischarged_Volume%Array(i),ChokeLine_MudOrKick%Array(i)
-
- IF (IEEE_Is_NaN(MudSystemDotChokeLine_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in Choke Volume-Plot')
- IF (MudSystemDotChokeLine_MudDischarged_Volume%Array(i)<=0.) call ErrorStop('Choke Volume= <=0' , MudSystemDotChokeLine_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 ( ChokeLine_MudOrKick%Last() > 0 .AND. WellToChokeManifoldOpen == .true.) then
- !WellToChokeManifoldWasOpen
-
- MudSystemDotSoundGasThroughChoke = 100 !100:chon dar adadhaye kamtar az 100 seda ghaat mishavad. eslah shavad.5.8.98 !int (min(ChokeLineFlowRate/2. , 100.))
- print* , 'SoundGasThroughChoke1=', MudSystemDotSoundGasThroughChoke
- !WRITE (*,*) 'WellToChokeManifoldWasOpen-Sound', WellToChokeManifoldWasOpen
- WRITE (*,*) 'WellToChokeManifoldOpen', WellToChokeManifoldOpen
- else
- MudSystemDotSoundGasThroughChoke = 0
- print* , 'SoundGasThroughChoke2=', MudSystemDotSoundGasThroughChoke
- endif
- !print* , 'SoundGasThroughChoke3=', SoundGasThroughChoke
-
-
-
- call SetSoundGasThroughChoke(MudSystemDotSoundGasThroughChoke)
-
-
- end subroutine Choke_GasSound
|