|
- subroutine FillingWell_By_BellNipple ! is called in subroutine CirculationCodeSelect
-
- ! this subroutine is for lines: 1) BellNippleToWell-NonFullWell : MUD(8)%Q
- ! 2) PumpsToWell_KillLine : MUD(10)%Q
-
- Use GeoElements_FluidModule
- USE CMudPropertiesVariables
- USE MudSystemVARIABLES
- USE Pump_VARIABLES
- use CDrillWatchVariables
- use CTanksVariables, TripTankVolume2 => TripTankVolume, TripTankDensity2 => TripTankDensity
- USE sROP_Other_Variables
- USE sROP_Variables
- Use KickVariables
-
- implicit none
-
- real(8) deltaV,Xposition,FillingDensity
-
- integer kloc,SectionPosition
-
-
-
-
- ! Well Is Not Full
-
-
-
- if (Ann_MudOrKick%Last() == 104) then ! Last Element is air we must observe: Ann_Mud_Forehead_X%Last()=0.0
-
- write(*,*) 'FillingWell_By_BellNipple-Last Element is air'
-
- !write(*,*) '*Ann_Mud_Forehead_X%Last()=' , Ann_Mud_Forehead_X%Last()
- !write(*,*) '*Ann_MudOrKick%Last()=' , Ann_MudOrKick%Last()
-
-
-
- FillingDensity= BellNippleDensity
-
- !****************************
- if ( Ann_MudDischarged_Volume%Last() > (((MUD(8)%Q+MUD(10)%Q)/60.)*DeltaT_Mudline)) then ! air baghi mimune
-
- kloc= Ann_MudDischarged_Volume%Length()-1
-
-
-
- deltaV= ((MUD(8)%Q+MUD(10)%Q)/60.)*DeltaT_Mudline
-
- Ann_MudDischarged_Volume%Array(Ann_MudDischarged_Volume%Length())= Ann_MudDischarged_Volume%Array(Ann_MudDischarged_Volume%Length()) - deltaV
-
-
- !========================ANNULUS ENTRANCE====================
-
- if (ABS(Ann_Density%Array(kloc) - FillingDensity) >= DensityMixTol) then ! new mud is pumped
- call Ann_Density%AddTo (kloc, FillingDensity)
- call Ann_MudDischarged_Volume%AddTo (kloc, 0.0d0)
- call Ann_Mud_Forehead_X%AddTo (kloc, 0.0d0)
- call Ann_Mud_Forehead_section%AddTo (kloc, 1)
- call Ann_Mud_Backhead_X%AddTo (kloc, 0.0d0)
- call Ann_Mud_Backhead_section%AddTo (kloc, NoPipeSections)
- call Ann_RemainedVolume_in_LastSection%AddTo (kloc, 0.0d0)
- call Ann_EmptyVolume_inBackheadLocation%AddTo (kloc, 0.0d0)
- call Ann_MudOrKick%AddTo (kloc, 0)
- call Ann_CuttingMud%AddTo (kloc,0)
-
- !AnnulusSuctionDensity_Old= Hz_Density_Utube
- endif
-
- !========================ANNULUS====================
-
- Ann_MudDischarged_Volume%Array(kloc)= Ann_MudDischarged_Volume%Array(kloc)+ deltaV !(gal)
-
-
-
- else ! ( Ann_MudDischarged_Volume%Last() <= (((MUD(8)%Q+MUD(10)%Q)/60.)*DeltaT_Mudline)) then ! air baghi namune
-
-
-
-
- kloc= Ann_MudDischarged_Volume%Length()-1
-
- deltaV= Ann_MudDischarged_Volume%Last()
-
-
-
- if (ABS(Ann_Density%Array(kloc)-FillingDensity)< DensityMixTol .and. Ann_CuttingMud%Array(kloc)==0) then ! .OR. (Ann_MudDischarged_Volume%Array(kloc)< 42.) ) then ! 1-Pockets are Merged
- Ann_Density%Array(kloc)= (Ann_Density%Array(kloc)*Ann_MudDischarged_Volume%Array(kloc)+FillingDensity*deltaV)/(Ann_MudDischarged_Volume%Array(kloc)+deltaV)
- Ann_MudDischarged_Volume%Array(kloc)= Ann_MudDischarged_Volume%Array(kloc)+deltaV
- Ann_Mud_Forehead_X%Array(kloc)= Xend_PipeSection(NoPipeSections)
- Ann_Mud_Forehead_section%Array(kloc)= NoPipeSections
- !Ann_Mud_Backhead_X%Array(kloc)= no change
- !Ann_Mud_Backhead_section%Array(kloc)= no change
- Ann_RemainedVolume_in_LastSection%Array(kloc)= (0.0)
- Ann_EmptyVolume_inBackheadLocation%Array(kloc)= (0.0)
-
- call Ann_MudDischarged_Volume%Remove (kloc+1)
- call Ann_Mud_Backhead_X%Remove (kloc+1)
- call Ann_Mud_Backhead_section%Remove (kloc+1)
- call Ann_Mud_Forehead_X%Remove (kloc+1)
- call Ann_Mud_Forehead_section%Remove (kloc+1)
- call Ann_Density%Remove (kloc+1)
- call Ann_RemainedVolume_in_LastSection%Remove (kloc+1)
- call Ann_EmptyVolume_inBackheadLocation%Remove (kloc+1)
- call Ann_MudOrKick%Remove (kloc+1)
- call Ann_CuttingMud%Remove (kloc+1)
-
-
- else ! 2-Merging conditions are not meeted, so new pocket== air is replaced with filling mud
- Ann_Density%Array(kloc+1) =FillingDensity
- Ann_MudOrKick%Array(kloc+1)= 0
-
- endif
-
-
- endif
-
- ! end condition (Ann_MudOrKick%Last() == 104) ! Last Element is air
-
- !**********************************************************************************************************************************************************
-
-
-
-
- else ! (Ann_MudOrKick%Last() == 0) then ! Last Element is NOT air- so we must observe: Ann_Mud_Forehead_X%Last()/=0.0
-
- !write(*,*) 'FillingWell_By_BellNipple-Last Element is NOT air'
- !
- !write(*,*) '*Ann_Mud_Forehead_X%Last()=' , Ann_Mud_Forehead_X%Last()
- !write(*,*) '*Ann_MudOrKick%Last()=' , Ann_MudOrKick%Last()
-
-
- deltaV= ((MUD(8)%Q+MUD(10)%Q)/60.)*DeltaT_Mudline
-
- kloc= Ann_MudDischarged_Volume%Length()
-
-
-
-
-
- !========================ANNULUS ENTRANCE====================
-
- if (ABS(Ann_Density%Last() - FillingDensity) >= DensityMixTol .or. Ann_CuttingMud%Last()==1) then ! .OR. (Ann_MudDischarged_Volume%Array(kloc)>42.) ) then ! new mud is pumped
- Xposition= Ann_Mud_Forehead_X%Last()
- SectionPosition= Ann_Mud_Forehead_section%Last()
- call Ann_Density%Add (FillingDensity)
- call Ann_MudDischarged_Volume%Add (0.0d0)
- call Ann_Mud_Forehead_X%Add (Xposition)
- call Ann_Mud_Forehead_section%Add (SectionPosition)
- call Ann_Mud_Backhead_X%Add (Xposition)
- call Ann_Mud_Backhead_section%Add (SectionPosition)
- call Ann_RemainedVolume_in_LastSection%Add (0.0d0)
- call Ann_EmptyVolume_inBackheadLocation%Add (0.0d0)
- call Ann_MudOrKick%Add (0)
- call Ann_CuttingMud%Add (0)
-
- !AnnulusSuctionDensity_Old= Hz_Density_Utube
- !endif
-
- !========================ANNULUS====================
-
- Ann_MudDischarged_Volume%Array(Ann_MudDischarged_Volume%Length())= Ann_MudDischarged_Volume%Array(Ann_MudDischarged_Volume%Length())+ deltaV !(gal)
-
-
- else ! Merged with last Mud
- Ann_Density%Array(kloc)= (Ann_Density%Array(kloc)*Ann_MudDischarged_Volume%Array(kloc)+FillingDensity*deltaV)/(Ann_MudDischarged_Volume%Array(kloc)+deltaV)
- Ann_MudDischarged_Volume%Array(kloc)= Ann_MudDischarged_Volume%Array(kloc)+deltaV
- !Ann_Mud_Forehead_X%Array(kloc)= Xend_PipeSection(NoPipeSections)
- !Ann_Mud_Forehead_section%Array(kloc)= NoPipeSections
- !Ann_Mud_Backhead_X%Array(kloc)= no change
- !Ann_Mud_Backhead_section%Array(kloc)= no change
- Ann_RemainedVolume_in_LastSection%Array(kloc)= (0.0)
- Ann_EmptyVolume_inBackheadLocation%Array(kloc)= (0.0)
- endif
-
-
-
-
-
-
- endif
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
-
- end subroutine FillingWell_By_BellNipple
|