Simulation Core
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
 
 
 
 
 
 

1365 lines
79 KiB

  1. subroutine TripOut_and_Pump ! is called in subroutine CirculationCodeSelect
  2. Use GeoElements_FluidModule
  3. USE CMudPropertiesVariables
  4. USE MudSystemVARIABLES
  5. USE Pumps_VARIABLES
  6. !USE CHOKEVARIABLES
  7. !USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure
  8. !use CManifolds
  9. use CDrillWatchVariables
  10. !use CHOKEVARIABLES
  11. !use CChokeManifoldVariables
  12. !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
  13. USE sROP_Other_Variables
  14. USE sROP_Variables
  15. Use KickVariables
  16. Use CShoeVariables
  17. use CError
  18. implicit none
  19. integer i,ii,AddLocation, iloc_edited, iloc_changedTo2
  20. Real(8) ExcessMudVolume_Remained,SavedDensityForOp
  21. !===========================================================WELL============================================================
  22. !===========================================================WELL============================================================
  23. MudSystem%StringFlowRate= MUD(2)%Q
  24. MudSystem%AnnulusFlowRate= MUD(2)%Q
  25. !write(*,*) 'MUD(2)%Q=====' , MUD(2)%Q
  26. write(*,*) 'Trip Out'
  27. ! write(*,*) 'check point 1=='
  28. !
  29. !
  30. !
  31. ! do imud=1, Ann_MudDischarged_Volume%Length()
  32. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  33. ! enddo
  34. !
  35. ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  36. ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  37. !
  38. !
  39. !write(*,*) '==check point 1'
  40. !========================Horizontal PIPE ENTRANCE=================
  41. if (ABS(MudSystem%SuctionDensity_Old - MudSystem%Suction_Density_MudSystem) >= MudSystem%DensityMixTol) then ! new mud is pumped
  42. call MudSystem%Hz_Density%AddToFirst (MudSystem%Suction_Density_MudSystem)
  43. call MudSystem%Hz_MudDischarged_Volume%AddToFirst (0.0d0)
  44. call MudSystem%Hz_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(1))
  45. call MudSystem%Hz_Mud_Forehead_section%AddToFirst (1)
  46. call MudSystem%Hz_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(1))
  47. call MudSystem%Hz_Mud_Backhead_section%AddToFirst (1)
  48. call MudSystem%Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  49. call MudSystem%Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  50. call MudSystem%Hz_MudOrKick%AddToFirst (0)
  51. MudSystem%SuctionDensity_Old= MudSystem%Suction_Density_MudSystem
  52. endif
  53. !========================Horizontal PIPE STRING=================
  54. MudSystem%Hz_MudDischarged_Volume%Array(1)= MudSystem%Hz_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  55. MudSystem%total_add = MudSystem%total_add + ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)
  56. if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
  57. MudSystem%total_add= 0.
  58. endif
  59. !write(*,*) ' total decrease(add to HZ)=' , total_add
  60. !write(*,*) ' add to HZ=' , ((MudSystem%StringFlowRate/60.0d0)*DeltaT_Mudline)
  61. imud=0
  62. do while (imud < MudSystem%Hz_Mud_Forehead_X%Length())
  63. imud = imud + 1
  64. if (imud> 1) then
  65. MudSystem%Hz_Mud_Backhead_X%Array(imud)= MudSystem%Hz_Mud_Forehead_X%Array(imud-1)
  66. MudSystem%Hz_Mud_Backhead_section%Array(imud)= MudSystem%Hz_Mud_Forehead_section%Array(imud-1)
  67. endif
  68. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))) &
  69. / ABS(MudSystem%Xend_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud)))
  70. ! +1 for string , -1 for annulus
  71. 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))* &
  72. MudSystem%Area_PipeSectionFt(MudSystem%Hz_Mud_Backhead_section%Array(imud)) !(ft^3)
  73. MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  74. if ( MudSystem%Hz_MudDischarged_Volume%Array(imud) <= MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)) then
  75. MudSystem%Hz_Mud_Forehead_section%Array(imud)= MudSystem%Hz_Mud_Backhead_section%Array(imud)
  76. 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))
  77. else
  78. MudSystem%isection= MudSystem%Hz_Mud_Backhead_section%Array(imud)+1
  79. MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Hz_MudDischarged_Volume%Array(imud)- MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)
  80. do
  81. if (MudSystem%isection > 1) then ! (horizontal pipe exit)
  82. MudSystem%Hz_MudDischarged_Volume%Array(imud)= MudSystem%Hz_MudDischarged_Volume%Array(imud)- MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)
  83. MudSystem%Hz_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(1)
  84. MudSystem%Hz_Mud_Forehead_section%Array(imud)= 1
  85. if (MudSystem%Hz_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
  86. call RemoveHzMudArrays(imud)
  87. endif
  88. exit
  89. endif
  90. MudSystem%xx= MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  91. if (MudSystem%xx<= 1.0) then
  92. MudSystem%Hz_Mud_Forehead_section%Array(imud)= MudSystem%isection
  93. MudSystem%Hz_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection)
  94. exit
  95. else
  96. MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  97. MudSystem%isection= MudSystem%isection+ 1
  98. endif
  99. enddo
  100. endif
  101. enddo
  102. !========================Horizontal PIPE END=================
  103. !========================Utube1 Air Element Removing=================
  104. !if (UtubeMode1Activated== .true.) then ! StringUpdate == .true.
  105. !
  106. ! StringDensity_Old= MudSystem%St_Density%Array(2)
  107. !
  108. ! UtubeMode1Activated= .false.
  109. !endif
  110. !========================Utube1 Air Element Removing=================
  111. !========================Utube2 Removing from Annulus=================
  112. if (MudSystem%UtubeMode2Activated== .true.) then ! StringUpdate == .true.
  113. MudSystem%TotalAddedVolume=0.
  114. if (MudSystem%Ann_MudOrKick%Last() == 104) then !movaghati. albate age merge anjam shode bashe moshkeli nist
  115. call RemoveAnnulusMudArrays(MudSystem%Ann_MudOrKick%Length())
  116. endif
  117. MudSystem%UtubeMode2Activated= .false.
  118. endif
  119. !========================Utube2 Removing from Annulus End=================
  120. !========================New Pipe Filling=================
  121. if (MudSystem%AddedElementsToString > 0) then ! StringUpdate == .true.
  122. !NoPipeAdded= F_StringIntervalCounts - F_StringIntervalCountsOld
  123. MudSystem%NewPipeFilling=0
  124. IF (MudSystem%St_MudOrKick%First() == 104) then
  125. 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
  126. else
  127. call MudSystem%St_Density%AddToFirst (0.d0)
  128. call MudSystem%St_MudDischarged_Volume%AddToFirst (sum(MudSystem%PipeSection_VolumeCapacity(2:1+MudSystem%AddedElementsToString)))
  129. call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  130. call MudSystem%St_Mud_Forehead_section%AddToFirst (2)
  131. call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  132. call MudSystem%St_Mud_Backhead_section%AddToFirst (2)
  133. call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.d0)
  134. call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.d0)
  135. call MudSystem%St_MudOrKick%AddToFirst (104)
  136. endif
  137. endif
  138. !F_StringIntervalCountsOld= F_StringIntervalCounts
  139. if (MudSystem%NewPipeFilling == 0) then ! 2= is the first element of string (1= is for Hz pipe)
  140. MudSystem%LackageMudVolume= MudSystem%St_MudDischarged_Volume%Array(1) ! = Air element
  141. !write(*,*) 'LackageMudVolume=' , LackageMudVolume
  142. if (ABS(MudSystem%St_Density%Array(2) - MudSystem%Hz_Density%Last()) >= MudSystem%DensityMixTol) then ! new mud is pumped
  143. call MudSystem%St_Density%AddTo (2,MudSystem%Hz_Density%Last())
  144. call MudSystem%St_MudDischarged_Volume%AddTo (2,0.d0)
  145. call MudSystem%St_Mud_Forehead_X%AddTo (2,MudSystem%Xstart_PipeSection(2))
  146. call MudSystem%St_Mud_Forehead_section%AddTo (2 , 2)
  147. call MudSystem%St_Mud_Backhead_X%AddTo (2,MudSystem%Xstart_PipeSection(2))
  148. call MudSystem%St_Mud_Backhead_section%AddTo (2 ,2)
  149. call MudSystem%St_RemainedVolume_in_LastSection%AddTo (2,0.d0)
  150. call MudSystem%St_EmptyVolume_inBackheadLocation%AddTo (2,0.d0)
  151. call MudSystem%St_MudOrKick%AddTo (2,0)
  152. !StringDensity_Old= Hz_Density%Last()
  153. endif
  154. MudSystem%St_MudDischarged_Volume%Array(2)= MudSystem%St_MudDischarged_Volume%Array(2)+ min( ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline), MudSystem%LackageMudVolume) !(gal)
  155. MudSystem%St_MudDischarged_Volume%Array(1)= MudSystem%St_MudDischarged_Volume%Array(1)- min( ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline), MudSystem%LackageMudVolume) ! air(gal)
  156. !LackageMudVolumeAfterFilling= sum(PipeSection_VolumeCapacity(2:F_StringIntervalCounts)) - sum(St_MudDischarged_Volume%Array(:))
  157. MudSystem%LackageMudVolumeAfterFilling= MudSystem%St_MudDischarged_Volume%Array(1) ! last time it should be zero
  158. if (MudSystem%LackageMudVolumeAfterFilling == 0.) then
  159. MudSystem%NewPipeFilling= 1
  160. call RemoveStringMudArrays(1)
  161. MudSystem%St_Mud_Backhead_X%Array(1) = MudSystem%Xstart_PipeSection(2)
  162. MudSystem%St_Mud_Backhead_section%Array(1) = 2
  163. endif
  164. endif
  165. !========================New Pipe Filling End=================
  166. if (MudSystem%NewPipeFilling == 0) then
  167. MudSystem%StringFlowRate= 0.
  168. MudSystem%AnnulusFlowRate= 0.
  169. endif
  170. MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate
  171. MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate
  172. !========================STRING ENTRANCE=================
  173. if (MudSystem%StringFlowRateFinal > 0.0 .and. ABS(MudSystem%St_Density%First() - MudSystem%Hz_Density%Last()) >= MudSystem%DensityMixTol) then ! new mud is pumped
  174. !if (ABS(StringDensity_Old - Hz_Density%Last()) >= DensityMixTol) then ! new mud is pumped
  175. call MudSystem%St_Density%AddToFirst (MudSystem%Hz_Density%Last())
  176. call MudSystem%St_MudDischarged_Volume%AddToFirst (0.0d0)
  177. call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  178. call MudSystem%St_Mud_Forehead_section%AddToFirst (2)
  179. call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  180. call MudSystem%St_Mud_Backhead_section%AddToFirst (2)
  181. call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  182. call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  183. call MudSystem%St_MudOrKick%AddToFirst (0)
  184. !StringDensity_Old= Hz_Density%Last()
  185. endif
  186. MudSystem%St_MudDischarged_Volume%Array(1)= MudSystem%St_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  187. !=============== save String Mud data===========
  188. MudSystem%StMudVolumeSum= 0.d0
  189. !St_MudSaved_Density= 0.d0
  190. MudSystem%St_Saved_MudDischarged_Volume= 0.d0
  191. !Saved_St_MudOrKick= 0
  192. !Ann_to_Choke_2mud= .false.
  193. do imud=1, MudSystem%St_MudDischarged_Volume%Length()
  194. MudSystem%StMudVolumeSum= MudSystem%StMudVolumeSum + MudSystem%St_MudDischarged_Volume%Array(imud)
  195. if ( MudSystem%StMudVolumeSum > sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts)) ) then
  196. !IF (St_MudOrKick%Array(imud) == 0) THEN
  197. MudSystem%St_MudSaved_Density = MudSystem%St_Density%Array(imud)
  198. MudSystem%St_Saved_MudDischarged_Volume = MudSystem%StMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts))
  199. !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  200. ! St_Kick_Saved_Volume = StMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  201. ! Saved_St_MudOrKick= St_MudOrKick%Array (imud)
  202. ! St_KickSaved_Density= MudSystem%St_Density%Array(imud)
  203. !END IF
  204. do ii= imud + 1, MudSystem%St_MudDischarged_Volume%Length()
  205. !IF (St_MudOrKick%Array(ii) == 0) THEN
  206. 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))
  207. MudSystem%St_Saved_MudDischarged_Volume = MudSystem%St_Saved_MudDischarged_Volume + MudSystem%St_MudDischarged_Volume%Array(ii)
  208. !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  209. ! St_Kick_Saved_Volume = St_Kick_Saved_Volume + St_MudDischarged_Volume%Array(ii)
  210. ! Saved_St_MudOrKick= St_MudOrKick%Array (ii)
  211. ! St_KickSaved_Density= MudSystem%St_Density%Array(ii)
  212. !END IF
  213. enddo
  214. !WRITE (*,*) 'St_Saved_Mud_Volume, St_Kick_Saved_Volume', St_Saved_MudDischarged_Volume, St_Kick_Saved_Volume
  215. exit ! exits do
  216. endif
  217. enddo
  218. MudSystem%St_Saved_MudDischarged_Volume_Final= MudSystem%St_Saved_MudDischarged_Volume
  219. IF (MudSystem%WellHeadIsOpen) MudSystem%MudVolume_InjectedToBH = MudSystem%St_Saved_MudDischarged_Volume_Final
  220. !======================================================================
  221. !========================STRING=================
  222. imud=0
  223. do while (imud < MudSystem%St_Mud_Forehead_X%Length())
  224. imud = imud + 1
  225. if (imud> 1) then
  226. MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%St_Mud_Forehead_X%Array(imud-1)
  227. MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%St_Mud_Forehead_section%Array(imud-1)
  228. endif
  229. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))) &
  230. / ABS(MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud)))
  231. ! +1 for string , -1 for annulus
  232. 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))* &
  233. MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) !(ft^3)
  234. MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  235. if ( MudSystem%St_MudDischarged_Volume%Array(imud) <= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)) then
  236. MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%St_Mud_Backhead_section%Array(imud)
  237. 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))
  238. ! 7.48 is for gal to ft^3
  239. else
  240. MudSystem%isection= MudSystem%St_Mud_Backhead_section%Array(imud)+1
  241. MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)
  242. do
  243. if (MudSystem%isection > F_Counts%StringIntervalCounts) then ! last pipe section(string exit)
  244. MudSystem%St_MudDischarged_Volume%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_RemainedVolume_in_LastSection%Array(imud)
  245. MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)
  246. MudSystem%St_Mud_Forehead_section%Array(imud)= F_Counts%StringIntervalCounts
  247. if (MudSystem%St_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
  248. call RemoveStringMudArrays(imud)
  249. endif
  250. exit
  251. endif
  252. MudSystem%xx= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  253. if (MudSystem%xx<= 1.0) then
  254. MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%isection
  255. MudSystem%St_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection)
  256. exit
  257. else
  258. MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  259. MudSystem%isection= MudSystem%isection+ 1
  260. endif
  261. enddo
  262. endif
  263. enddo
  264. !========================STRING END=================
  265. !write(*,*) ' a before=='
  266. !
  267. ! do imud=1, Op_MudDischarged_Volume%Length()
  268. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  269. ! enddo
  270. !
  271. ! do imud=1, Ann_MudDischarged_Volume%Length()
  272. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  273. ! enddo
  274. !
  275. ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  276. ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  277. !
  278. !
  279. !write(*,*) '==== a before'
  280. iloc_changedTo2 = 0
  281. IF (MudSystem%Op_MudOrKick%Last() /= 0 .and. MudSystem%Op_MudOrKick%Last()==MudSystem%Ann_MudOrKick%First()) then
  282. MudSystem%iLoc=2 ! it may be 1,2,3 or more, all of them are kick
  283. iloc_changedTo2= 1
  284. endif
  285. iloc_edited= 0
  286. !write(*,*) sum(Op_MudDischarged_Volume%Array(:)) , ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline) , Ann_MudDischarged_Volume%First() , sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
  287. if (MudSystem%iLoc==2 .and. sum(MudSystem%Op_MudDischarged_Volume%Array(:))+((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline)+MudSystem%Ann_MudDischarged_Volume%First() < sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) ) then
  288. MudSystem%iLoc = 1
  289. iloc_edited = 1
  290. !write(*,*) 'hellooooooo'
  291. endif
  292. !write(*,*) 'ann-cap:' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1 :F_StringIntervalCounts+F_AnnulusIntervalCounts) )
  293. !write(*,*) 'iloc====' , iloc
  294. !MudVolume_InjectedToBH
  295. !=============================Add PumpFlowRate to Bottom Hole ==============================
  296. !if ( MudSystem%AnnulusFlowRate>0.0 ) then
  297. if ( MudSystem%MudVolume_InjectedToBH > 0.0 ) then
  298. if (KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the
  299. AddLocation= MudSystem%Op_Density%Length()-MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick
  300. else
  301. AddLocation= MudSystem%Op_Density%Length()+1
  302. endif
  303. !write(*,*) 'AddLocation====' , AddLocation
  304. if ( AddLocation== 0) CALL ErrorStop ('AddLocation=0')
  305. if ( ABS(MudSystem%St_Density%Last() - MudSystem%Op_Density%Array(AddLocation-1)) >= MudSystem%DensityMixTol ) then
  306. !write(*,*) 'new pocket**'
  307. !write(*,*) 'MudSystem%St_Density%Last()=' , MudSystem%St_Density%Last()
  308. !write(*,*) 'Op_Density%Array(AddLocation-1)=' , Op_Density%Array(AddLocation-1)
  309. call MudSystem%Op_Density% AddTo (AddLocation,MudSystem%St_Density%Last())
  310. !call Op_MudDischarged_Volume%AddTo (AddLocation,((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline))
  311. call MudSystem%Op_MudDischarged_Volume%AddTo (AddLocation,MudSystem%MudVolume_InjectedToBH)
  312. call MudSystem%Op_Mud_Forehead_X%AddTo (AddLocation,MudSystem%Xstart_OpSection(1))
  313. call MudSystem%Op_Mud_Forehead_section%AddTo (AddLocation,1)
  314. call MudSystem%Op_Mud_Backhead_X%AddTo (AddLocation,MudSystem%Xstart_OpSection(1))
  315. call MudSystem%Op_Mud_Backhead_section%AddTo (AddLocation,1)
  316. call MudSystem%Op_RemainedVolume_in_LastSection%AddTo (AddLocation,0.0d0)
  317. call MudSystem%Op_EmptyVolume_inBackheadLocation%AddTo (AddLocation,0.0d0)
  318. call MudSystem%Op_MudOrKick%AddTo (AddLocation,0)
  319. else
  320. !write(*,*) 'merge**'
  321. !write(*,*) 'density before=' , Op_Density%Array(AddLocation-1)
  322. !write(*,*) 'MudSystem%St_Density%Last() for mix=' , MudSystem%St_Density%Last()
  323. !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))
  324. !Op_MudDischarged_Volume%Array(AddLocation-1)= Op_MudDischarged_Volume%Array(AddLocation-1) + ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline)
  325. 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)
  326. MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)= MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1) + MudSystem%MudVolume_InjectedToBH
  327. !write(*,*) 'density after=' , Op_Density%Array(AddLocation-1)
  328. endif
  329. endif
  330. !=======================Add PumpFlowRate to Bottom Hole- End ==============================
  331. !write(*,*) 'pump added-before add to ann=='
  332. !
  333. ! do imud=1, Op_MudDischarged_Volume%Length()
  334. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  335. ! enddo
  336. !
  337. ! do imud=1, Ann_MudDischarged_Volume%Length()
  338. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  339. ! enddo
  340. !
  341. ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  342. ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  343. !
  344. !
  345. !
  346. !write(*,*) 'pump added====before add to ann'
  347. !=============== save OP Mud data to transfer to the annulus enterance due to tripin or kick
  348. MudSystem%OpMudVolumeSum= 0.d0
  349. !Op_MudSaved_Density= 0.d0
  350. !Op_KickSaved_Density= 0.d0
  351. MudSystem%Op_Saved_MudDischarged_Volume= 0.d0
  352. MudSystem%Op_Kick_Saved_Volume= 0.d0
  353. MudSystem%Saved_Op_MudOrKick= 0
  354. MudSystem%Op_NeededVolume_ToFill= 0.d0
  355. do imud=1, MudSystem%Op_MudDischarged_Volume%Length()
  356. MudSystem%OpMudVolumeSum= MudSystem%OpMudVolumeSum + MudSystem%Op_MudDischarged_Volume%Array(imud)
  357. if ( MudSystem%OpMudVolumeSum > sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) ) then !1st mode
  358. IF (MudSystem%Op_MudOrKick%Array(imud) == 0) THEN
  359. MudSystem%Op_MudSaved_Density = MudSystem%Op_Density%Array(imud)
  360. MudSystem%Op_Saved_MudDischarged_Volume = MudSystem%OpMudVolumeSum - sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))
  361. ELSE
  362. MudSystem%Op_Kick_Saved_Volume = MudSystem%OpMudVolumeSum - sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))
  363. MudSystem%Saved_Op_MudOrKick= MudSystem%Op_MudOrKick%Array (imud)
  364. MudSystem%Op_KickSaved_Density= MudSystem%Op_Density%Array(imud)
  365. MudSystem%iLoc= 2
  366. iloc_changedTo2= 2
  367. END IF
  368. do ii= imud + 1, MudSystem%Op_MudDischarged_Volume%Length()
  369. IF (MudSystem%Op_MudOrKick%Array(ii) == 0) THEN
  370. 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))
  371. MudSystem%Op_Saved_MudDischarged_Volume = MudSystem%Op_Saved_MudDischarged_Volume + MudSystem%Op_MudDischarged_Volume%Array(ii)
  372. ELSE
  373. MudSystem%Op_Kick_Saved_Volume = MudSystem%Op_Kick_Saved_Volume + MudSystem%Op_MudDischarged_Volume%Array(ii)
  374. MudSystem%Saved_Op_MudOrKick= MudSystem%Op_MudOrKick%Array (ii)
  375. MudSystem%Op_KickSaved_Density= MudSystem%Op_Density%Array(ii)
  376. MudSystem%iLoc= 2
  377. iloc_changedTo2= 3
  378. END IF
  379. enddo
  380. exit ! exits do
  381. endif
  382. enddo
  383. if ( sum(MudSystem%Op_MudDischarged_Volume%Array(:)) < sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) ) then !2nd & 3rd mode
  384. MudSystem%Op_NeededVolume_ToFill= sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) - sum(MudSystem%Op_MudDischarged_Volume%Array(:))
  385. endif
  386. !
  387. !write(*,*) 'Op_NeededVolume_ToFill=' , Op_NeededVolume_ToFill
  388. !write(*,*) 'Op_Saved_MudDischarged_Volume=' , Op_Saved_MudDischarged_Volume
  389. !write(*,*) 'Op_Kick_Saved_Volume=' , Op_Kick_Saved_Volume
  390. !
  391. !write(*,*) 'op cap=' , sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
  392. !write(*,*) ' op sum mud=' , sum(Op_MudDischarged_Volume%Array(:))
  393. !======================================================================
  394. !========================Tripping Out- 1st & 3rd Mode====================
  395. if ( (MudSystem%Op_Kick_Saved_Volume > 0.0 .or. MudSystem%Op_Saved_MudDischarged_Volume> 0.0) .or. & ! 1st Mode-Pump flow is more than trip out so fluid Level in Annulus Increases
  396. (MudSystem%Op_NeededVolume_ToFill < ABS(MudSystem%DeltaVolumeAnnulusCapacity)) ) then !3rd Mode-fluid Level in Annulus Increases
  397. !if ( Op_Kick_Saved_Volume > 0.0 .or. Op_Saved_MudDischarged_Volume> 0.0 ) write(*,*) 'trip out 1st mode'
  398. if ( MudSystem%Op_NeededVolume_ToFill > 0.0 .and. MudSystem%Op_NeededVolume_ToFill < ABS(MudSystem%DeltaVolumeAnnulusCapacity) ) then
  399. ! write(*,*) 'trip out 3rd mode'
  400. MudSystem%NewVolume= 0.d0 ! for condition iloc=1
  401. SavedDensityForOp= MudSystem%Ann_Density%Array(1)
  402. ExcessMudVolume_Remained= MudSystem%Op_NeededVolume_ToFill
  403. imud=1
  404. Do
  405. if(MudSystem%Ann_MudDischarged_Volume%Array(imud) < ExcessMudVolume_Remained) then
  406. ExcessMudVolume_Remained= ExcessMudVolume_Remained- MudSystem%Ann_MudDischarged_Volume%Array(imud)
  407. call MudSystem%Ann_MudDischarged_Volume%Remove (imud)
  408. call MudSystem%Ann_Mud_Backhead_X%Remove (imud)
  409. call MudSystem%Ann_Mud_Backhead_section%Remove (imud)
  410. call MudSystem%Ann_Mud_Forehead_X%Remove (imud)
  411. call MudSystem%Ann_Mud_Forehead_section%Remove (imud)
  412. call MudSystem%Ann_Density%Remove (imud)
  413. call MudSystem%Ann_RemainedVolume_in_LastSection%Remove (imud)
  414. call MudSystem%Ann_EmptyVolume_inBackheadLocation%Remove (imud)
  415. call MudSystem%Ann_MudOrKick%Remove (imud)
  416. elseif(MudSystem%Ann_MudDischarged_Volume%Array(imud) > ExcessMudVolume_Remained) then
  417. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- ExcessMudVolume_Remained
  418. exit
  419. else !(Ann_MudDischarged_Volume%Array(imud) == ExcessMudVolume_Remained)
  420. call MudSystem%Ann_MudDischarged_Volume%Remove (imud)
  421. call MudSystem%Ann_Mud_Backhead_X%Remove (imud)
  422. call MudSystem%Ann_Mud_Backhead_section%Remove (imud)
  423. call MudSystem%Ann_Mud_Forehead_X%Remove (imud)
  424. call MudSystem%Ann_Mud_Forehead_section%Remove (imud)
  425. call MudSystem%Ann_Density%Remove (imud)
  426. call MudSystem%Ann_RemainedVolume_in_LastSection%Remove (imud)
  427. call MudSystem%Ann_EmptyVolume_inBackheadLocation%Remove (imud)
  428. call MudSystem%Ann_MudOrKick%Remove (imud)
  429. exit
  430. endif
  431. enddo
  432. !write(*,*) 'Op_NeededVolume_ToFill=' ,Op_NeededVolume_ToFill
  433. !write(*,*) 'ABS(DeltaVolumeAnnulusCapacity)=' ,ABS(DeltaVolumeAnnulusCapacity)
  434. !write(*,*) 'Op_MudOrKick%Last()=' ,Op_MudOrKick%Last()
  435. !write(*,*) 'iloc=' ,iloc
  436. !write(*,*) 'iloc_edited=' ,iloc_edited
  437. endif
  438. ! (MudSystem%AnnulusFlowRate/60.)*DeltaT_Mudline) - DeltaVolumeOp will be added to annulus
  439. !if (iLoc == 1) then
  440. MudSystem%MudSection= F_Counts%StringIntervalCounts+1
  441. MudSystem%BackheadX= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)
  442. !elseif (iLoc == 2) then
  443. ! MudSection= Kick_Forehead_section
  444. ! BackheadX= Kick_Forehead_X
  445. !endif
  446. !========================ANNULUS ENTRANCE====================
  447. !if (KickMigration_2SideBit == .FALSE.) then
  448. ! if ( ABS(AnnulusSuctionDensity_Old - MudSystem%St_Density%Last()) >= DensityMixTol ) then ! new mud is pumped
  449. ! call Ann_Density%AddTo (iLoc,MudSystem%St_Density%Last())
  450. ! call Ann_MudDischarged_Volume%AddTo (iLoc,0.0d0)
  451. ! call Ann_Mud_Forehead_X%AddTo (iLoc,BackheadX)
  452. ! call Ann_Mud_Forehead_section%AddTo (iLoc,MudSection)
  453. ! call Ann_Mud_Backhead_X%AddTo (iLoc,BackheadX)
  454. ! call Ann_Mud_Backhead_section%AddTo (iLoc,MudSection)
  455. ! call Ann_RemainedVolume_in_LastSection%AddTo (iLoc,0.0d0)
  456. ! call Ann_EmptyVolume_inBackheadLocation%AddTo (iLoc,0.0d0)
  457. ! call Ann_MudOrKick%AddTo (iLoc,0)
  458. ! call Ann_CuttingMud%AddTo (iLoc,0)
  459. !
  460. ! AnnulusSuctionDensity_Old= MudSystem%St_Density%Last()
  461. !
  462. ! MudIsChanged= .true.
  463. ! endif
  464. !
  465. ! Ann_MudDischarged_Volume%Array(iLoc)= Ann_MudDischarged_Volume%Array(iLoc)+ ((MudSystem%AnnulusFlowRate/60.0d0)*DeltaT_Mudline) - ((2-iloc)*ABS(DeltaVolumePipe)) !(gal)
  466. !
  467. !endif
  468. 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)- (and add pipe)
  469. MudSystem%Ann_Mud_Backhead_X%Array(1)= MudSystem%BackheadX
  470. !iloc=1 : (2-iloc)=1 normal
  471. !iloc=2 : (2-iloc)=0 kick influx or migration is in annulus
  472. !========================Same to Tripping In====================
  473. !write(*,*) 'Op_Kick_Saved_Volume,Op_Saved_MudDischarged_Volume=' , Op_Kick_Saved_Volume,Op_Saved_MudDischarged_Volume
  474. if (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() == 0) then !1st Mode
  475. write(*,*) 'Kick influx enters Annulus'
  476. call MudSystem%Ann_Density%AddToFirst (MudSystem%Op_KickSaved_Density)
  477. call MudSystem%Ann_MudDischarged_Volume%AddToFirst (MudSystem%Op_Kick_Saved_Volume)
  478. call MudSystem%Ann_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1))
  479. call MudSystem%Ann_Mud_Forehead_section%AddToFirst (F_Counts%StringIntervalCounts+1)
  480. call MudSystem%Ann_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1))
  481. call MudSystem%Ann_Mud_Backhead_section%AddToFirst (F_Counts%StringIntervalCounts+1)
  482. call MudSystem%Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  483. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  484. call MudSystem%Ann_MudOrKick%AddToFirst (MudSystem%Saved_Op_MudOrKick) !<<<<<<<<
  485. call MudSystem%Ann_CuttingMud%AddToFirst (0)
  486. elseif (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() /= 0) then
  487. MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) + MudSystem%Op_Kick_Saved_Volume
  488. endif
  489. if ( MudSystem%Op_NeededVolume_ToFill > 0.0 .and. (MudSystem%Op_NeededVolume_ToFill < ABS(MudSystem%DeltaVolumeAnnulusCapacity)) .and. MudSystem%Op_MudOrKick%Last() == 0 .and. (MudSystem%iLoc==2 .or. iloc_edited==1)) then !3rd Mode
  490. !write(*,*) 'checkpoint 0'
  491. !! for avoid kick separation -Op_MudOrKick%Last() == 0: because of pump
  492. MudSystem%NewVolume= ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) ! =volume that should be added to iloc=2 in Ann
  493. call RemoveOpMudArrays(MudSystem%Op_Density%Length()) ! mud here is removed and then will be added to iloc=2 in Ann in %%1 section
  494. if ( MudSystem%Ann_MudDischarged_Volume%Array(1) > ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) ) then! 1st in Ann = kick ,, we expect: ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline)= OpMudVolLast
  495. MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) - ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline)
  496. 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) ! kick
  497. else
  498. call RemoveAnnulusMudArrays(1) !kick is removed
  499. MudSystem%iLoc= 1
  500. 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)
  501. write(*,*) 'little expand'
  502. ! including a little expand
  503. endif
  504. endif
  505. if (MudSystem%Op_Saved_MudDischarged_Volume> 0.0) then !1st Mode
  506. MudSystem%NewDensity= MudSystem%Op_MudSaved_Density
  507. !write(*,*) 'iloc,...' , iloc,((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline),Op_Saved_MudDischarged_Volume
  508. if (MudSystem%iLoc==1) then
  509. !write(*,*) 'checkpoint 1'
  510. MudSystem%NewVolume= MudSystem%Op_Saved_MudDischarged_Volume
  511. elseif (real(((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline)) - real(MudSystem%Op_Saved_MudDischarged_Volume) > 0.d0 ) then ! for avoid kick separation
  512. !write(*,*) 'checkpoint 2'
  513. MudSystem%NewVolume= ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) !- Op_Saved_MudDischarged_Volume
  514. call RemoveOpMudArrays(MudSystem%Op_Density%Length()) ! mud here is removed and then will be added to iloc=2 in Ann
  515. if ( MudSystem%Ann_MudDischarged_Volume%Array(1) > (((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) - MudSystem%Op_Saved_MudDischarged_Volume) ) then! 1st in Ann = kick
  516. MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) - (((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) - MudSystem%Op_Saved_MudDischarged_Volume)
  517. 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
  518. else
  519. call RemoveAnnulusMudArrays(1) !kick is removed
  520. MudSystem%iLoc =1
  521. 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)
  522. write(*,*) 'little expand'
  523. ! including a little expand
  524. endif
  525. else ! iloc==2 , ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline) == Op_Saved_MudDischarged_Volume
  526. !write(*,*) 'checkpoint 3'
  527. MudSystem%NewVolume= MudSystem%Op_Saved_MudDischarged_Volume ! it is normal mode
  528. endif
  529. endif
  530. !write(*,*) 'NewVolume=' ,NewVolume
  531. if( MudSystem%Ann_Density%Length() == 1 .and. MudSystem%iLoc ==2 ) then
  532. write(*,*) '***errorb****=='
  533. write(*,*) 'iloc_edited=' , iloc_edited
  534. write(*,*) 'iloc_changedTo2=' , iloc_changedTo2
  535. write(*,*) 'Op_Capacity===' , sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))
  536. WRITE (*,*) 'Op_Saved_MudDischarged_Volume, Op_Kick_Saved_Volume',MudSystem%Op_Saved_MudDischarged_Volume, MudSystem%Op_Kick_Saved_Volume
  537. do imud=1, MudSystem%Op_MudDischarged_Volume%Length()
  538. write(*,*) 'Op:', imud, MudSystem%Op_MudDischarged_Volume%Array(imud), MudSystem%Op_Density%Array(imud) ,MudSystem%Op_MudOrKick%Array(imud)
  539. enddo
  540. do imud=1, MudSystem%Ann_MudDischarged_Volume%Length()
  541. write(*,*) 'Ann:', imud, MudSystem%Ann_MudDischarged_Volume%Array(imud), MudSystem%Ann_Density%Array(imud) ,MudSystem%Ann_MudOrKick%Array(imud)
  542. enddo
  543. write(*,*) '==***errorb****'
  544. endif
  545. if ((ROP_Bit%RateOfPenetration==0 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%DensityMixTol) & !%%1 section
  546. .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) &
  547. .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
  548. !write(*,*) '%%1 section a)'
  549. 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)
  550. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume
  551. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  552. MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  553. MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  554. MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  555. MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0)
  556. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0)
  557. else ! 2-Merging conditions are not meeted, so new pocket
  558. !write(*,*) '%%1 section b)'
  559. call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity)
  560. call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume)
  561. call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  562. call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  563. call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  564. call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  565. call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0)
  566. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0)
  567. call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0)
  568. call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0)
  569. !write(*,*) 'd) annLength=' , Ann_Density%Length()
  570. endif
  571. !========================Same to Tripping In - End====================
  572. !write(*,*) 'b)Ann_Mud sum=' , sum(Ann_MudDischarged_Volume%Array(:))
  573. !write(*,*) 'no======2'
  574. !
  575. ! do imud=1, Op_MudDischarged_Volume%Length()
  576. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  577. ! enddo
  578. !
  579. ! do imud=1, Ann_MudDischarged_Volume%Length()
  580. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  581. ! enddo
  582. !
  583. !
  584. ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  585. ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  586. !
  587. !
  588. !write(*,*) '2======no'
  589. !=============== save Ann Mud data to transfer to the ChokeLine enterance
  590. MudSystem%AnnMudVolumeSum= 0.d0
  591. !Ann_MudSaved_Density= 0.d0
  592. !Ann_KickSaved_Density= 0.d0
  593. MudSystem%Ann_Saved_MudDischarged_Volume= 0.d0
  594. MudSystem%Ann_Kick_Saved_Volume= 0.d0
  595. MudSystem%Saved_Ann_MudOrKick= 0
  596. MudSystem%Ann_to_Choke_2mud= .false.
  597. do imud=1, MudSystem%Ann_MudDischarged_Volume%Length()
  598. MudSystem%AnnMudVolumeSum= MudSystem%AnnMudVolumeSum + MudSystem%Ann_MudDischarged_Volume%Array(imud)
  599. if ( MudSystem%AnnMudVolumeSum > sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) ) then
  600. IF (MudSystem%Ann_MudOrKick%Array(imud) == 0) THEN
  601. MudSystem%Ann_MudSaved_Density = MudSystem%Ann_Density%Array(imud)
  602. MudSystem%Ann_Saved_MudDischarged_Volume = MudSystem%AnnMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections))
  603. ELSEIF (MudSystem%Ann_MudOrKick%Array(imud) > 0 .AND. MudSystem%Ann_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  604. MudSystem%Ann_Kick_Saved_Volume = MudSystem%AnnMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections))
  605. MudSystem%Saved_Ann_MudOrKick= MudSystem%Ann_MudOrKick%Array (imud)
  606. MudSystem%Ann_KickSaved_Density= MudSystem%Ann_Density%Array(imud)
  607. END IF
  608. do ii= imud + 1, MudSystem%Ann_MudDischarged_Volume%Length()
  609. IF (MudSystem%Ann_MudOrKick%Array(ii) == 0) THEN
  610. 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))
  611. MudSystem%Ann_Saved_MudDischarged_Volume = MudSystem%Ann_Saved_MudDischarged_Volume + MudSystem%Ann_MudDischarged_Volume%Array(ii)
  612. MudSystem%Ann_to_Choke_2mud= .true.
  613. ELSEIF (MudSystem%Ann_MudOrKick%Array(ii) > 0 .AND. MudSystem%Ann_MudOrKick%Array(ii) <100) THEN ! 104= AIR
  614. MudSystem%Ann_Kick_Saved_Volume = MudSystem%Ann_Kick_Saved_Volume + MudSystem%Ann_MudDischarged_Volume%Array(ii)
  615. MudSystem%Saved_Ann_MudOrKick= MudSystem%Ann_MudOrKick%Array (ii)
  616. MudSystem%Ann_KickSaved_Density= MudSystem%Ann_Density%Array(ii)
  617. END IF
  618. enddo
  619. exit ! exits do
  620. endif
  621. enddo
  622. MudSystem%Ann_Saved_MudDischarged_Volume_Final= MudSystem%Ann_Saved_MudDischarged_Volume
  623. MudSystem%Ann_Kick_Saved_Volume_Final= MudSystem%Ann_Kick_Saved_Volume
  624. !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:NoPipeSections))
  625. !write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  626. IF (MudSystem%WellHeadIsOpen) MudSystem%MudVolume_InjectedFromAnn = MudSystem%Ann_Saved_MudDischarged_Volume_Final-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline)
  627. !NoGasPocket
  628. !write(*,*) 'Ann_Saved_Mud_Vol,Ann_Kick_Saved_Vol=' , Ann_Saved_MudDischarged_Volume,Ann_Kick_Saved_Volume
  629. !======================================================================
  630. !write(*,*) 'Ann_Saved_Mud=' , Ann_Saved_MudDischarged_Volume
  631. !======================== Annulus ====================
  632. !MudIsChanged= .false.
  633. imud= 0
  634. do while (imud < MudSystem%Ann_Mud_Forehead_X%Length())
  635. imud = imud + 1
  636. if (imud> 1) then
  637. MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Ann_Mud_Forehead_X%Array(imud-1)
  638. MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%Ann_Mud_Forehead_section%Array(imud-1)
  639. endif
  640. ! write(*,*) 'imud==' , imud
  641. !write(*,*) '***)Ann_Mud_Backhead_section(imud)= ' , Ann_Mud_Backhead_section%Array(imud), Ann_density%Array(imud)
  642. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))) &
  643. / ABS(MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud)))
  644. ! +1 for string , -1 for annulus
  645. 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))* &
  646. MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Backhead_section%Array(imud)) !(ft^3)
  647. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  648. if ( MudSystem%Ann_MudDischarged_Volume%Array(imud) <= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then
  649. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%Ann_Mud_Backhead_section%Array(imud)
  650. 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))
  651. ! 7.48 is for gal to ft^3
  652. else
  653. MudSystem%isection= MudSystem%Ann_Mud_Backhead_section%Array(imud)+1
  654. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)
  655. do
  656. if (MudSystem%isection > MudSystem%NoPipeSections) then ! last pipe section(well exit)
  657. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)
  658. MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)
  659. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%NoPipeSections
  660. if (MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
  661. call RemoveAnnulusMudArrays(imud)
  662. endif
  663. exit
  664. endif
  665. MudSystem%xx= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  666. if (MudSystem%xx<= 1.0) then
  667. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%isection
  668. MudSystem%Ann_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection)
  669. exit
  670. else
  671. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  672. MudSystem%isection= MudSystem%isection+ 1
  673. endif
  674. enddo
  675. endif
  676. enddo
  677. if (MudSystem%Ann_Mud_Forehead_X%Last() < MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)) then
  678. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%Ann_Mud_Forehead_X%Length()) = MudSystem%Xend_PipeSection(MudSystem%NoPipeSections) ! for error preventing
  679. endif
  680. !========================ANNULUS END=================
  681. !*************************************************************************************************************************
  682. !========================Tripping Out- 2nd Mode====================
  683. elseif ( MudSystem%Op_NeededVolume_ToFill > ABS(MudSystem%DeltaVolumeAnnulusCapacity) ) then !pump is off or Pump flow is less than trip out so fluid Level in Annulus decreases
  684. !write(*,*) 'trip out 2nd mode'
  685. SavedDensityForOp= MudSystem%Ann_Density%Array(1)
  686. !========================ANNULUS ENTRANCE====================
  687. ! <<< SIMILAR TO UTUBE 2 >>>
  688. if ( MudSystem%Ann_Density%Last() /= 0.0 ) then ! new mud is pumped
  689. call MudSystem%Ann_Density%Add (0.0d0)
  690. call MudSystem%Ann_MudDischarged_Volume%Add (0.0d0)
  691. call MudSystem%Ann_Mud_Forehead_X%Add (MudSystem%Xend_PipeSection(MudSystem%NoPipeSections))
  692. call MudSystem%Ann_Mud_Forehead_section%Add (MudSystem%NoPipeSections)
  693. call MudSystem%Ann_Mud_Backhead_X%Add (MudSystem%Xstart_PipeSection(MudSystem%NoPipeSections))
  694. call MudSystem%Ann_Mud_Backhead_section%Add (MudSystem%NoPipeSections)
  695. call MudSystem%Ann_RemainedVolume_in_LastSection%Add (0.0d0)
  696. call MudSystem%Ann_EmptyVolume_inBackheadLocation%Add (0.0d0)
  697. call MudSystem%Ann_MudOrKick%Add (104)
  698. call MudSystem%Ann_CuttingMud%Add (0)
  699. !AnnulusSuctionDensity_Old= Hz_Density%Last()
  700. endif
  701. MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%Ann_Mud_Forehead_section%Length())= MudSystem%NoPipeSections !it is needed to be updated for (a condition that one pipe is removed from Annulus due to trip out)- (and add pipe)
  702. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%Ann_Mud_Forehead_X%Length())= MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)
  703. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length())= MudSystem%Ann_MudDischarged_Volume%Last()+ (MudSystem%Op_NeededVolume_ToFill - ABS(MudSystem%DeltaVolumeAnnulusCapacity)) ! Op_NeededVolume_ToFill !ABS(DeltaVolumePipe) - ((MudSystem%AnnulusFlowRate/60.)*DeltaT_Mudline) !(gal)
  704. !===================================================================
  705. if ( (MudSystem%iLoc==2 .or. iloc_edited==1) .and. MudSystem%Op_MudOrKick%Last()==0 ) then ! for avoid kick separation
  706. !write(*,*) 'here mud should be removed from Op last'
  707. if (abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%Op_Density%Last())< MudSystem%DensityMixTol) then
  708. MudSystem%Ann_Density%Array(MudSystem%iLoc)= (MudSystem%Ann_Density%Array(MudSystem%iLoc)*MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%Op_Density%Last()*MudSystem%Op_MudDischarged_Volume%Last())/(MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%Op_MudDischarged_Volume%Last())
  709. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%Op_MudDischarged_Volume%Last() ! OP_Last is mud(effect of pump added mud)
  710. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  711. MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  712. MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  713. MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  714. MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0)
  715. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0)
  716. !write(*,*) 'merge' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  717. else ! 2-Merging conditions are not meeted, so new pocket
  718. call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%Op_Density%Last())
  719. call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%Op_MudDischarged_Volume%Last())
  720. call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  721. call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  722. call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  723. call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  724. call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0)
  725. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0)
  726. call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0)
  727. call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0)
  728. endif
  729. MudSystem%Op_NeededVolume_ToFill= MudSystem%Op_NeededVolume_ToFill + MudSystem%Op_MudDischarged_Volume%Last() ! OP_Last is mud(effect of pump added mud)
  730. call RemoveOpMudArrays(MudSystem%Op_MudOrKick%Length())
  731. endif
  732. !===================================================================
  733. !=============== save Ann Mud data to transfer to the ChokeLine enterance
  734. !AnnMudVolumeSum= 0.d0
  735. !!Ann_MudSaved_Density= 0.d0
  736. !!Ann_KickSaved_Density= 0.d0
  737. MudSystem%Ann_Saved_MudDischarged_Volume= 0.d0
  738. MudSystem%Ann_Kick_Saved_Volume= 0.d0
  739. !Saved_Ann_MudOrKick= 0
  740. !Ann_to_Choke_2mud= .false.
  741. !do imud=1, Ann_MudDischarged_Volume%Length()
  742. !
  743. ! AnnMudVolumeSum= AnnMudVolumeSum + Ann_MudDischarged_Volume%Array(imud)
  744. !
  745. ! if ( AnnMudVolumeSum > sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) ) then
  746. !
  747. ! IF (Ann_MudOrKick%Array(imud) == 0) THEN
  748. ! Ann_MudSaved_Density = Ann_Density%Array(imud)
  749. ! Ann_Saved_MudDischarged_Volume = AnnMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  750. ! ELSEIF (Ann_MudOrKick%Array(imud) > 0 .AND. Ann_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  751. ! Ann_Kick_Saved_Volume = AnnMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  752. ! Saved_Ann_MudOrKick= Ann_MudOrKick%Array (imud)
  753. ! Ann_KickSaved_Density= Ann_Density%Array(imud)
  754. ! END IF
  755. !
  756. ! do ii= imud + 1, Ann_MudDischarged_Volume%Length()
  757. ! IF (Ann_MudOrKick%Array(ii) == 0) THEN
  758. ! Ann_MudSaved_Density = ((Ann_MudSaved_Density * Ann_Saved_MudDischarged_Volume) + (Ann_Density%Array(ii) * Ann_MudDischarged_Volume%Array(ii))) / (Ann_Saved_MudDischarged_Volume + Ann_MudDischarged_Volume%Array(ii))
  759. ! Ann_Saved_MudDischarged_Volume = Ann_Saved_MudDischarged_Volume + Ann_MudDischarged_Volume%Array(ii)
  760. ! Ann_to_Choke_2mud= .true.
  761. ! ELSEIF (Ann_MudOrKick%Array(ii) > 0 .AND. Ann_MudOrKick%Array(ii) <100) THEN ! 104= AIR
  762. ! Ann_Kick_Saved_Volume = Ann_Kick_Saved_Volume + Ann_MudDischarged_Volume%Array(ii)
  763. ! Saved_Ann_MudOrKick= Ann_MudOrKick%Array (ii)
  764. ! Ann_KickSaved_Density= Ann_Density%Array(ii)
  765. ! END IF
  766. ! enddo
  767. !
  768. ! exit ! exits do
  769. !
  770. ! endif
  771. !
  772. !enddo
  773. ! write(*,*) 'check point 2=='
  774. !
  775. !
  776. !
  777. ! do imud=1, Ann_MudDischarged_Volume%Length()
  778. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  779. ! enddo
  780. !
  781. ! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  782. ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  783. !
  784. !
  785. !write(*,*) '==check point 2'
  786. MudSystem%Ann_Saved_MudDischarged_Volume_Final= MudSystem%Ann_Saved_MudDischarged_Volume
  787. MudSystem%Ann_Kick_Saved_Volume_Final= MudSystem%Ann_Kick_Saved_Volume
  788. !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  789. !write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  790. !write(*,*) 'Ann_Saved_MudDischarged_Volume_Final=' , Ann_Saved_MudDischarged_Volume_Final
  791. IF (MudSystem%WellHeadIsOpen) MudSystem%MudVolume_InjectedFromAnn = MudSystem%Ann_Saved_MudDischarged_Volume_Final-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline)
  792. !! NoGasPocket > 0 .AND.
  793. !write(*,*) 'Ann_Saved_Mud_Vol,Ann_Kick_Saved_Vol=' , Ann_Saved_MudDischarged_Volume,Ann_Kick_Saved_Volume
  794. !======================================================================
  795. !========================ANNULUS====================
  796. ! <<< SIMILAR TO UTUBE 2 >>>
  797. !write(*,*) Ann_MudOrKick%Last(), 'DeltaVolumePipe , after volume=' ,ABS(DeltaVolumePipe), Ann_MudDischarged_Volume%Last()
  798. imud= MudSystem%Ann_Mud_Forehead_X%Length() + 1
  799. do while (imud > 1)
  800. imud = imud - 1
  801. if (imud< MudSystem%Ann_Mud_Forehead_X%Length()) then
  802. MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Ann_Mud_Backhead_X%Array(imud+1)
  803. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%Ann_Mud_Backhead_section%Array(imud+1)
  804. endif
  805. ! <<< Fracture Shoe Lost
  806. IF ( MudSystem%ShoeLost .and. Shoe%ShoeDepth < MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. Shoe%ShoeDepth >= MudSystem%Ann_Mud_Forehead_X%Array(imud) ) then
  807. !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline)
  808. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  809. if (MudSystem%Ann_MudDischarged_Volume%Array(imud) < 0.0) then
  810. !write(*,*) 'mud is removed by shoe lost, imud=' , imud
  811. call RemoveAnnulusMudArrays(imud)
  812. imud= imud-1
  813. cycle
  814. endif
  815. MudSystem%LostInTripOutIsDone= .true.
  816. ENDIF
  817. ! Fracture Shoe Lost >>>
  818. !write(*,*) 'a)imud,Ann_Mud_Forehead_section=',imud,Ann_Mud_Forehead_section%Array(imud)
  819. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))) &
  820. / ABS(MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud)))
  821. ! +1 for string , -1 for annulus
  822. !write(*,*) 'b)imud,Forehead_X,Xstart_PipeSection=',imud,Ann_Mud_Forehead_X%Array(imud),Xstart_PipeSection(Ann_Mud_Forehead_section%Array(imud))
  823. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Ann_Mud_Forehead_X%Array(imud)- MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud)))* &
  824. MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Forehead_section%Array(imud)) !(ft^3)
  825. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  826. if ( MudSystem%Ann_MudDischarged_Volume%Array(imud) <= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then
  827. MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%Ann_Mud_Forehead_section%Array(imud)
  828. MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Ann_Mud_Forehead_X%Array(imud)- MudSystem%DirectionCoef*(MudSystem%Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Forehead_section%Array(imud))
  829. ! 7.48051948 is for gal to ft^3
  830. else
  831. MudSystem%isection= MudSystem%Ann_Mud_Forehead_section%Array(imud)-1
  832. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)
  833. do
  834. if (MudSystem%isection < F_Counts%StringIntervalCounts+1) then ! last pipe section(well exit) F_Counts%StringIntervalCounts+1 is the first section in Annulus
  835. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)
  836. MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)
  837. MudSystem%Ann_Mud_Backhead_section%Array(imud)= F_Counts%StringIntervalCounts+1
  838. if (MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
  839. call RemoveAnnulusMudArrays(imud)
  840. endif
  841. exit
  842. endif
  843. MudSystem%xx= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  844. if (MudSystem%xx<= 1.0) then
  845. MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%isection
  846. MudSystem%Ann_Mud_Backhead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xstart_PipeSection(MudSystem%isection)- MudSystem%Xend_PipeSection(MudSystem%isection)))+ MudSystem%Xend_PipeSection(MudSystem%isection)
  847. exit
  848. else
  849. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  850. MudSystem%isection= MudSystem%isection- 1
  851. endif
  852. enddo
  853. endif
  854. enddo
  855. !========================ANNULUS END=================
  856. endif ! end of 1st &3rd & 2nd Mode
  857. !*************************************************************************************************************************
  858. !======================== Bottom Hole Entrance ==========================
  859. !if (iloc == 1) then
  860. if ( MudSystem%Op_NeededVolume_ToFill > 0.0 ) then ! it is needed for 2nd & 3rd mode
  861. !write(*,*) 'op add for 2nd & 3rd mode done'
  862. if ( ABS(MudSystem%Op_Density%Last() - SavedDensityForOp ) >= MudSystem%DensityMixTol) then ! .OR. (Op_MudDischarged_Volume%Last()>42.) ) then ! 1-Merging conditions are not meeted, so new pocket
  863. call MudSystem%Op_Density%Add (SavedDensityForOp)
  864. call MudSystem%Op_MudDischarged_Volume%Add (MudSystem%Op_NeededVolume_ToFill)
  865. call MudSystem%Op_Mud_Forehead_X%Add (0.0d0)
  866. call MudSystem%Op_Mud_Forehead_section%Add (1)
  867. call MudSystem%Op_Mud_Backhead_X%Add (0.0d0)
  868. call MudSystem%Op_Mud_Backhead_section%Add (1)
  869. call MudSystem%Op_RemainedVolume_in_LastSection%Add (0.0d0)
  870. call MudSystem%Op_EmptyVolume_inBackheadLocation%Add (0.0d0)
  871. call MudSystem%Op_MudOrKick%Add (MudSystem%Ann_MudOrKick%Array(1))
  872. else ! 2-Pockets are Merged
  873. MudSystem%Op_Density%Array (MudSystem%Op_Density%Length())= (SavedDensityForOp*MudSystem%Op_NeededVolume_ToFill+MudSystem%Op_Density%Last()*MudSystem%Op_MudDischarged_Volume%Last())/(MudSystem%Op_MudDischarged_Volume%Last()+MudSystem%Op_NeededVolume_ToFill)
  874. MudSystem%Op_MudDischarged_Volume%Array (MudSystem%Op_Density%Length())= MudSystem%Op_MudDischarged_Volume%Array (MudSystem%Op_Density%Length()) + MudSystem%Op_NeededVolume_ToFill
  875. MudSystem%Op_RemainedVolume_in_LastSection%Array (MudSystem%Op_Density%Length())= 0.0
  876. MudSystem%Op_EmptyVolume_inBackheadLocation%Array (MudSystem%Op_Density%Length())= 0.0
  877. endif
  878. endif
  879. !============================= Bottom Hole ==============================
  880. imud=0
  881. do while (imud < MudSystem%Op_Mud_Forehead_X%Length())
  882. imud = imud + 1
  883. if (imud> 1) then
  884. MudSystem%Op_Mud_Backhead_X%Array(imud)= MudSystem%Op_Mud_Forehead_X%Array(imud-1)
  885. MudSystem%Op_Mud_Backhead_section%Array(imud)= MudSystem%Op_Mud_Forehead_section%Array(imud-1)
  886. endif
  887. MudSystem%DirectionCoef= (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) &
  888. / ABS(MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud)))
  889. ! +1 for string , -1 for annulus
  890. 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))* &
  891. MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) !(ft^3)
  892. MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  893. if ( MudSystem%Op_MudDischarged_Volume%Array(imud) <= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)) then
  894. MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%Op_Mud_Backhead_section%Array(imud)
  895. 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))
  896. ! 7.48051948 is for gal to ft^3
  897. else
  898. MudSystem%isection= MudSystem%Op_Mud_Backhead_section%Array(imud)+1
  899. MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)
  900. do
  901. if (MudSystem%isection > F_Counts%BottomHoleIntervalCounts) then ! last pipe section(well exit)
  902. !if( imud==1) KickDeltaVinAnnulus= Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space
  903. MudSystem%Op_MudDischarged_Volume%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)
  904. MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)
  905. MudSystem%Op_Mud_Forehead_section%Array(imud)= F_Counts%BottomHoleIntervalCounts
  906. if (MudSystem%Op_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
  907. call MudSystem%Op_MudDischarged_Volume%Remove (imud)
  908. call MudSystem%Op_Mud_Backhead_X%Remove (imud)
  909. call MudSystem%Op_Mud_Backhead_section%Remove (imud)
  910. call MudSystem%Op_Mud_Forehead_X%Remove (imud)
  911. call MudSystem%Op_Mud_Forehead_section%Remove (imud)
  912. call MudSystem%Op_Density%Remove (imud)
  913. call MudSystem%Op_RemainedVolume_in_LastSection%Remove (imud)
  914. call MudSystem%Op_EmptyVolume_inBackheadLocation%Remove (imud)
  915. call MudSystem%Op_MudOrKick%Remove (imud)
  916. endif
  917. exit
  918. endif
  919. MudSystem%xx= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%OpSection_VolumeCapacity(MudSystem%isection) !(gal)
  920. if (MudSystem%xx<= 1.0) then
  921. MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%isection
  922. MudSystem%Op_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_OpSection(MudSystem%isection)- MudSystem%Xstart_OpSection(MudSystem%isection)))+ MudSystem%Xstart_OpSection(MudSystem%isection)
  923. exit
  924. else
  925. MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)- MudSystem%OpSection_VolumeCapacity(MudSystem%isection)
  926. MudSystem%isection= MudSystem%isection+ 1
  927. endif
  928. enddo
  929. endif
  930. enddo
  931. !========================Bottom Hole END=================
  932. ! write(*,*) 'after sorting=='
  933. !!!
  934. ! do imud=1, Op_MudDischarged_Volume%Length()
  935. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  936. ! enddo
  937. !
  938. ! do imud=1, Ann_MudDischarged_Volume%Length()
  939. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  940. ! enddo
  941. !!!
  942. !! write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  943. !! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  944. !!!
  945. !!!
  946. !write(*,*) '==after sorting'
  947. !=========================================================
  948. MudSystem%total_injected = MudSystem%total_injected + MudSystem%MudVolume_InjectedFromAnn
  949. if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
  950. MudSystem%total_injected= 0.
  951. endif
  952. !write(*,*) ' MudSystem%MudVolume_InjectedFromAnn =' , MudSystem%MudVolume_InjectedFromAnn
  953. !write(*,*) ' total injected-tripout =' , total_injected
  954. !write(*,*) ' injected-tripout =' , MudSystem%MudVolume_InjectedFromAnn
  955. end subroutine TripOut_and_Pump