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.
 
 
 
 
 
 

1627 lines
91 KiB

  1. subroutine Pump_and_TripIn ! 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
  20. !===========================================================WELL============================================================
  21. !===========================================================WELL============================================================
  22. MudSystem%StringFlowRate= MUD(2)%Q
  23. MudSystem%AnnulusFlowRate= MUD(2)%Q
  24. !write(*,*) 'Trip In'
  25. !========================Horizontal PIPE ENTRANCE=================
  26. if (ABS(MudSystem%SuctionDensity_Old - MudSystem%Suction_Density_MudSystem) >= MudSystem%DensityMixTol) then ! new mud is pumped
  27. call MudSystem%Hz_Density%AddToFirst (MudSystem%Suction_Density_MudSystem)
  28. call MudSystem%Hz_MudDischarged_Volume%AddToFirst (0.0d0)
  29. call MudSystem%Hz_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(1))
  30. call MudSystem%Hz_Mud_Forehead_section%AddToFirst (1)
  31. call MudSystem%Hz_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(1))
  32. call MudSystem%Hz_Mud_Backhead_section%AddToFirst (1)
  33. call MudSystem%Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  34. call MudSystem%Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  35. call MudSystem%Hz_MudOrKick%AddToFirst (0)
  36. MudSystem%SuctionDensity_Old= MudSystem%Suction_Density_MudSystem
  37. endif
  38. !========================Horizontal PIPE STRING=================
  39. MudSystem%Hz_MudDischarged_Volume%Array(1)= MudSystem%Hz_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  40. MudSystem%total_add = MudSystem%total_add + ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)
  41. if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
  42. MudSystem%total_add= 0.
  43. endif
  44. !write(*,*) ' total decrease(add to HZ)=' , total_add
  45. !write(*,*) ' add to HZ=' , ((MudSystem%StringFlowRate/60.0d0)*DeltaT_Mudline)
  46. imud=0
  47. do while (imud < MudSystem%Hz_Mud_Forehead_X%Length())
  48. imud = imud + 1
  49. if (imud> 1) then
  50. MudSystem%Hz_Mud_Backhead_X%Array(imud)= MudSystem%Hz_Mud_Forehead_X%Array(imud-1)
  51. MudSystem%Hz_Mud_Backhead_section%Array(imud)= MudSystem%Hz_Mud_Forehead_section%Array(imud-1)
  52. endif
  53. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))) &
  54. / ABS(MudSystem%Xend_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Hz_Mud_Backhead_section%Array(imud)))
  55. ! +1 for string , -1 for annulus
  56. 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))* &
  57. MudSystem%Area_PipeSectionFt(MudSystem%Hz_Mud_Backhead_section%Array(imud)) !(ft^3)
  58. MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  59. if ( MudSystem%Hz_MudDischarged_Volume%Array(imud) <= MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)) then
  60. MudSystem%Hz_Mud_Forehead_section%Array(imud)= MudSystem%Hz_Mud_Backhead_section%Array(imud)
  61. 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))
  62. else
  63. MudSystem%isection= MudSystem%Hz_Mud_Backhead_section%Array(imud)+1
  64. MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Hz_MudDischarged_Volume%Array(imud)- MudSystem%Hz_EmptyVolume_inBackheadLocation%Array(imud)
  65. do
  66. if (MudSystem%isection > 1) then ! (horizontal pipe exit)
  67. MudSystem%Hz_MudDischarged_Volume%Array(imud)= MudSystem%Hz_MudDischarged_Volume%Array(imud)- MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)
  68. MudSystem%Hz_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(1)
  69. MudSystem%Hz_Mud_Forehead_section%Array(imud)= 1
  70. if (MudSystem%Hz_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
  71. call RemoveHzMudArrays(imud)
  72. endif
  73. exit
  74. endif
  75. MudSystem%xx= MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  76. if (MudSystem%xx<= 1.0) then
  77. MudSystem%Hz_Mud_Forehead_section%Array(imud)= MudSystem%isection
  78. MudSystem%Hz_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection)
  79. exit
  80. else
  81. MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Hz_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  82. MudSystem%isection= MudSystem%isection+ 1
  83. endif
  84. enddo
  85. endif
  86. enddo
  87. !========================Horizontal PIPE END=================
  88. !========================Utube1 Air Element Removing=================
  89. !if (UtubeMode1Activated== .true.) then ! StringUpdate == .true.
  90. !
  91. !
  92. ! !StringDensity_Old=MudSystem%St_Density%Array(2)
  93. !
  94. ! write(*,*) 'StringDensity_Old=' , StringDensity_Old
  95. !
  96. ! UtubeMode1Activated= .false.
  97. !endif
  98. !========================Utube1 Air Element Removing End=================
  99. !!========================Utube2 Removing from Annulus================= not needed 97.04.26
  100. !
  101. ! if (UtubeMode2Activated== .true.) then ! StringUpdate == .true.
  102. !
  103. ! if (Ann_MudOrKick%Last() == 104) then !movaghati. albate age merge anjam shode bashe moshkeli nist
  104. ! call RemoveAnnulusMudArrays(Ann_MudOrKick%Length())
  105. ! endif
  106. !
  107. ! UtubeMode2Activated= .false.
  108. ! endif
  109. !
  110. !
  111. !!========================Utube2 Removing from Annulus End=================
  112. !========================New Pipe Filling=================
  113. !if (F_StringIntervalCounts > F_StringIntervalCountsOld) then ! StringUpdate == .true.
  114. if (MudSystem%AddedElementsToString > 0) then ! StringUpdate == .true.
  115. !NoPipeAdded= F_Counts%StringIntervalCounts - F_StringIntervalCountsOld
  116. MudSystem%NewPipeFilling=0
  117. IF (MudSystem%St_MudOrKick%First() == 104) then
  118. 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
  119. else
  120. call MudSystem%St_Density%AddToFirst (0.d0)
  121. call MudSystem%St_MudDischarged_Volume%AddToFirst (sum(MudSystem%PipeSection_VolumeCapacity(2:1+MudSystem%AddedElementsToString)))
  122. call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  123. call MudSystem%St_Mud_Forehead_section%AddToFirst (2)
  124. call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  125. call MudSystem%St_Mud_Backhead_section%AddToFirst (2)
  126. call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.d0)
  127. call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.d0)
  128. call MudSystem%St_MudOrKick%AddToFirst (104)
  129. endif
  130. endif
  131. !F_StringIntervalCountsOld= F_StringIntervalCounts
  132. if (MudSystem%NewPipeFilling == 0) then ! 2= is the first element of string (1= is for Hz pipe)
  133. MudSystem%LackageMudVolume= MudSystem%St_MudDischarged_Volume%Array(1) ! = Air element
  134. write(*,*) 'LackageMudVolume=' , MudSystem%LackageMudVolume
  135. if (ABS(MudSystem%St_Density%Array(2) - MudSystem%Hz_Density%Last()) >= MudSystem%DensityMixTol) then ! new mud is pumped
  136. call MudSystem%St_Density%AddTo (2,MudSystem%Hz_Density%Last())
  137. call MudSystem%St_MudDischarged_Volume%AddTo (2, 0.d0)
  138. call MudSystem%St_Mud_Forehead_X%AddTo (2,MudSystem%Xstart_PipeSection(2))
  139. call MudSystem%St_Mud_Forehead_section%AddTo (2 , 2)
  140. call MudSystem%St_Mud_Backhead_X%AddTo (2,MudSystem%Xstart_PipeSection(2))
  141. call MudSystem%St_Mud_Backhead_section%AddTo (2 ,2)
  142. call MudSystem%St_RemainedVolume_in_LastSection%AddTo (2,0.d0)
  143. call MudSystem%St_EmptyVolume_inBackheadLocation%AddTo (2,0.d0)
  144. call MudSystem%St_MudOrKick%AddTo (2,0)
  145. !StringDensity_Old= Hz_Density%Last()
  146. endif
  147. MudSystem%St_MudDischarged_Volume%Array(2)= MudSystem%St_MudDischarged_Volume%Array(2)+ min( ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline), MudSystem%LackageMudVolume) !(gal)
  148. MudSystem%St_MudDischarged_Volume%Array(1)= MudSystem%St_MudDischarged_Volume%Array(1)- min( ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline), MudSystem%LackageMudVolume) ! air(gal)
  149. !LackageMudVolumeAfterFilling= sum(PipeSection_VolumeCapacity(2:F_StringIntervalCounts)) - sum(St_MudDischarged_Volume%Array(:))
  150. MudSystem%LackageMudVolumeAfterFilling= MudSystem%St_MudDischarged_Volume%Array(1) ! last time it should be zero
  151. if (MudSystem%LackageMudVolumeAfterFilling == 0.) then
  152. MudSystem%NewPipeFilling= 1
  153. call RemoveStringMudArrays(1)
  154. MudSystem%St_Mud_Backhead_X%Array(1) = MudSystem%Xstart_PipeSection(2)
  155. MudSystem%St_Mud_Backhead_section%Array(1) = 2
  156. endif
  157. endif
  158. !========================New Pipe Filling End=================
  159. if (MudSystem%NewPipeFilling == 0) then
  160. MudSystem%StringFlowRate= 0.
  161. MudSystem%AnnulusFlowRate= 0.
  162. endif
  163. MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate
  164. MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate
  165. !========================STRING ENTRANCE=================
  166. if (MudSystem%StringFlowRateFinal > 0.0 .and. ABS(MudSystem%St_Density%First() - MudSystem%Hz_Density%Last()) >= MudSystem%DensityMixTol) then ! new mud is pumped
  167. call MudSystem%St_Density%AddToFirst (MudSystem%Hz_Density%Last())
  168. call MudSystem%St_MudDischarged_Volume%AddToFirst (0.0d0)
  169. call MudSystem%St_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  170. call MudSystem%St_Mud_Forehead_section%AddToFirst (2)
  171. call MudSystem%St_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(2))
  172. call MudSystem%St_Mud_Backhead_section%AddToFirst (2)
  173. call MudSystem%St_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  174. call MudSystem%St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  175. call MudSystem%St_MudOrKick%AddToFirst (0)
  176. !StringDensity_Old= Hz_Density%Last()
  177. endif
  178. MudSystem%St_MudDischarged_Volume%Array(1)= MudSystem%St_MudDischarged_Volume%Array(1)+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  179. !=============== save String Mud data===========
  180. MudSystem%StMudVolumeSum= 0.d0
  181. !St_MudSaved_Density= 0.d0
  182. MudSystem%St_Saved_MudDischarged_Volume= 0.d0
  183. !Saved_St_MudOrKick= 0
  184. !Ann_to_Choke_2mud= .false.
  185. do imud=1, MudSystem%St_MudDischarged_Volume%Length()
  186. MudSystem%StMudVolumeSum = MudSystem%StMudVolumeSum + MudSystem%St_MudDischarged_Volume%Array(imud)
  187. if ( MudSystem%StMudVolumeSum > sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts)) ) then
  188. !IF (St_MudOrKick%Array(imud) == 0) THEN
  189. MudSystem%St_MudSaved_Density =MudSystem%St_Density%Array(imud)
  190. MudSystem%St_Saved_MudDischarged_Volume = MudSystem%StMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(2:F_Counts%StringIntervalCounts))
  191. !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  192. ! St_Kick_Saved_Volume = StMudVolumeSum - sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  193. ! Saved_St_MudOrKick= St_MudOrKick%Array (imud)
  194. ! St_KickSaved_Density=MudSystem%St_Density%Array(imud)
  195. !END IF
  196. do ii= imud + 1, MudSystem%St_MudDischarged_Volume%Length()
  197. !IF (St_MudOrKick%Array(ii) == 0) THEN
  198. 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))
  199. MudSystem%St_Saved_MudDischarged_Volume = MudSystem%St_Saved_MudDischarged_Volume + MudSystem%St_MudDischarged_Volume%Array(ii)
  200. !ELSEIF (St_MudOrKick%Array(imud) > 0 .AND. St_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  201. ! St_Kick_Saved_Volume = St_Kick_Saved_Volume + St_MudDischarged_Volume%Array(ii)
  202. ! Saved_St_MudOrKick= St_MudOrKick%Array (ii)
  203. ! St_KickSaved_Density=MudSystem%St_Density%Array(ii)
  204. !END IF
  205. enddo
  206. !WRITE (*,*) 'St_Saved_Mud_Volume, St_Kick_Saved_Volume', St_Saved_MudDischarged_Volume, St_Kick_Saved_Volume
  207. exit ! exits do
  208. endif
  209. enddo
  210. MudSystem%St_Saved_MudDischarged_Volume_Final = MudSystem%St_Saved_MudDischarged_Volume
  211. IF (MudSystem%WellHeadIsOpen) MudSystem%MudVolume_InjectedToBH = MudSystem%St_Saved_MudDischarged_Volume_Final
  212. !======================================================================
  213. !========================STRING=================
  214. imud=0
  215. do while (imud < MudSystem%St_Mud_Forehead_X%Length())
  216. imud = imud + 1
  217. if (imud> 1) then
  218. MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%St_Mud_Forehead_X%Array(imud-1)
  219. MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%St_Mud_Forehead_section%Array(imud-1)
  220. endif
  221. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))) &
  222. / ABS(MudSystem%Xend_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Backhead_section%Array(imud)))
  223. ! +1 for string , -1 for annulus
  224. 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))* &
  225. MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) !(ft^3)
  226. MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  227. !write(*,*) 'St_Mud_Backhead_section%Array(1)=' , St_Mud_Backhead_section%Array(1)
  228. !write(*,*) 'Xend_PipeSection(St_Mud_Backhead_section%Array(1))=' , Xend_PipeSection(St_Mud_Backhead_section%Array(1))
  229. !
  230. !write(*,*) 'St_EmptyVolume_inBackheadLocation%Array(1)=' , St_EmptyVolume_inBackheadLocation%Array(1)
  231. !write(*,*) 'St_Mud_Backhead_X%Array(1)=' , St_Mud_Backhead_X%Array(1)
  232. if ( MudSystem%St_MudDischarged_Volume%Array(imud) <= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)) then
  233. MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%St_Mud_Backhead_section%Array(imud)
  234. 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))
  235. ! 7.48 is for gal to ft^3
  236. else
  237. MudSystem%isection= MudSystem%St_Mud_Backhead_section%Array(imud)+1
  238. MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)
  239. do
  240. if (MudSystem%isection > F_Counts%StringIntervalCounts) then ! last pipe section(string exit) F_Counts%StringIntervalCounts includes Horizontal line
  241. MudSystem%St_MudDischarged_Volume%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_RemainedVolume_in_LastSection%Array(imud)
  242. MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts)
  243. MudSystem%St_Mud_Forehead_section%Array(imud)= F_Counts%StringIntervalCounts
  244. if (MudSystem%St_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
  245. call RemoveStringMudArrays(imud)
  246. endif
  247. exit
  248. endif
  249. MudSystem%xx= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  250. if (MudSystem%xx<= 1.0) then
  251. MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%isection
  252. MudSystem%St_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection)
  253. exit
  254. else
  255. MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  256. MudSystem%isection= MudSystem%isection+ 1
  257. endif
  258. enddo
  259. endif
  260. enddo
  261. !write(*,*) ' a before=='
  262. !
  263. ! do imud=1, Op_MudDischarged_Volume%Length()
  264. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  265. ! enddo
  266. !
  267. ! do imud=1, Ann_MudDischarged_Volume%Length()
  268. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  269. ! enddo
  270. !
  271. !write(*,*) '==== a before'
  272. !write(*,*) ' iloc (a): ' , iloc
  273. !========================STRING END=================
  274. IF (MudSystem%Op_MudOrKick%Last() /= 0 .and. MudSystem%Op_MudOrKick%Last()==MudSystem%Ann_MudOrKick%First()) MudSystem%iLoc=2 ! it may be 1,2,3 or more, all of them are kick
  275. !write(*,*) ' iloc (b): ' , iloc
  276. !=============================Add PumpFlowRate to Bottom Hole ==============================
  277. !if ( MudSystem%AnnulusFlowRate>0.0 ) then
  278. if ( MudSystem%MudVolume_InjectedToBH > 0.0 ) then
  279. if (KickOffBottom) then ! (kickOffBottom = F) means kick is next to the bottom hole and usually kick is entering the
  280. AddLocation= MudSystem%Op_Density%Length()-MudSystem%iLoc+1+1 ! well, thus pumped mud should be placed above the kick
  281. else
  282. AddLocation= MudSystem%Op_Density%Length()+1
  283. endif
  284. !write(*,*) 'AddLocation====' , AddLocation
  285. if ( AddLocation== 0) CALL ErrorStop ('AddLocation=0')
  286. if ( ABS(MudSystem%St_Density%Last() - MudSystem%Op_Density%Array(AddLocation-1)) >= MudSystem%DensityMixTol ) then
  287. !write(*,*) 'new pocket**'
  288. !write(*,*) MudSystem%St_Density%Last()=' ,MudSystem%St_Density%Last()
  289. !write(*,*) 'Op_Density%Array(AddLocation-1)=' , Op_Density%Array(AddLocation-1)
  290. call MudSystem%Op_Density% AddTo (AddLocation,MudSystem%St_Density%Last())
  291. !call Op_MudDischarged_Volume%AddTo (AddLocation,((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline))
  292. call MudSystem%Op_MudDischarged_Volume%AddTo (AddLocation,MudSystem%MudVolume_InjectedToBH)
  293. call MudSystem%Op_Mud_Forehead_X%AddTo (AddLocation,MudSystem%Xstart_OpSection(1))
  294. call MudSystem%Op_Mud_Forehead_section%AddTo (AddLocation,1)
  295. call MudSystem%Op_Mud_Backhead_X%AddTo (AddLocation,MudSystem%Xstart_OpSection(1))
  296. call MudSystem%Op_Mud_Backhead_section%AddTo (AddLocation,1)
  297. call MudSystem%Op_RemainedVolume_in_LastSection%AddTo (AddLocation,0.0d0)
  298. call MudSystem%Op_EmptyVolume_inBackheadLocation%AddTo (AddLocation,0.0d0)
  299. call MudSystem%Op_MudOrKick%AddTo (AddLocation,0)
  300. else
  301. !write(*,*) 'merge**'
  302. !write(*,*) 'density before=' , Op_Density%Array(AddLocation-1)
  303. !write(*,*) MudSystem%St_Density%Last() for mix=' ,MudSystem%St_Density%Last()
  304. !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))
  305. !Op_MudDischarged_Volume%Array(AddLocation-1)= Op_MudDischarged_Volume%Array(AddLocation-1) + ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline)
  306. 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)
  307. MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1)= MudSystem%Op_MudDischarged_Volume%Array(AddLocation-1) + MudSystem%MudVolume_InjectedToBH
  308. !write(*,*) 'density after=' , Op_Density%Array(AddLocation-1)
  309. endif
  310. endif
  311. !=======================Add PumpFlowRate to Bottom Hole- End ==============================
  312. !=============== save OP Mud data to transfer to the annulus enterance due to tripin or kick
  313. MudSystem%OpMudVolumeSum= 0.d0
  314. !Op_MudSaved_Density= 0.d0
  315. !Op_KickSaved_Density= 0.d0
  316. MudSystem%Op_Saved_MudDischarged_Volume= 0.d0
  317. MudSystem%Op_Kick_Saved_Volume= 0.d0
  318. MudSystem%Saved_Op_MudOrKick= 0
  319. !write(*,*) 'Op_Capacity===' , sum(OpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
  320. !write(*,*) 'Op_MudDischarged_Volume%Length()===' , Op_MudDischarged_Volume%Length()
  321. !
  322. do imud=1, MudSystem%Op_MudDischarged_Volume%Length()
  323. !write(*,*) 'imud, Op_MudDischarged_Volume%Array(imud)=' , imud,Op_MudDischarged_Volume%Array(imud)
  324. MudSystem%OpMudVolumeSum= MudSystem%OpMudVolumeSum + MudSystem%Op_MudDischarged_Volume%Array(imud)
  325. if ( MudSystem%OpMudVolumeSum > sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) ) then
  326. IF (MudSystem%Op_MudOrKick%Array(imud) == 0) THEN
  327. MudSystem%Op_MudSaved_Density = MudSystem%Op_Density%Array(imud)
  328. MudSystem%Op_Saved_MudDischarged_Volume = MudSystem%OpMudVolumeSum - sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))
  329. ELSE
  330. MudSystem%Op_Kick_Saved_Volume = MudSystem%OpMudVolumeSum - sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))
  331. !write(*,*) 'cond 1- Op_MudOrKick%Array (imud),Op_Density%Array(imud):' ,Op_MudOrKick%Array (imud),Op_Density%Array(imud)
  332. MudSystem%Saved_Op_MudOrKick= MudSystem%Op_MudOrKick%Array (imud)
  333. MudSystem%Op_KickSaved_Density= MudSystem%Op_Density%Array(imud)
  334. MudSystem%iLoc= 2
  335. END IF
  336. do ii= imud + 1, MudSystem%Op_MudDischarged_Volume%Length()
  337. IF (MudSystem%Op_MudOrKick%Array(ii) == 0) THEN
  338. 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))
  339. MudSystem%Op_Saved_MudDischarged_Volume = MudSystem%Op_Saved_MudDischarged_Volume + MudSystem%Op_MudDischarged_Volume%Array(ii)
  340. ELSE
  341. MudSystem%Op_Kick_Saved_Volume = MudSystem%Op_Kick_Saved_Volume + MudSystem%Op_MudDischarged_Volume%Array(ii)
  342. !write(*,*) 'cond 2- Op_MudOrKick%Array (ii),Op_Density%Array(ii):' ,Op_MudOrKick%Array (ii),Op_Density%Array(ii)
  343. MudSystem%Saved_Op_MudOrKick= MudSystem%Op_MudOrKick%Array (ii)
  344. MudSystem%Op_KickSaved_Density= MudSystem%Op_Density%Array(ii)
  345. MudSystem%iLoc= 2
  346. END IF
  347. enddo
  348. exit ! exits do
  349. endif
  350. enddo
  351. !WRITE (*,*) 'Op_Saved_MudDischarged_Volume, Op_Kick_Saved_Volume',Op_Saved_MudDischarged_Volume, Op_Kick_Saved_Volume
  352. !write(*,*) ' iloc (c): ' , iloc
  353. !======================================================================
  354. !======================================================================
  355. !if (iLoc == 1) then
  356. MudSystem%MudSection= F_Counts%StringIntervalCounts+1
  357. MudSystem%BackheadX= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)
  358. !elseif (iLoc == 2) then
  359. ! MudSection= Kick_Forehead_section
  360. ! BackheadX= Kick_Forehead_X
  361. !endif
  362. !========================ANNULUS ENTRANCE====================
  363. !if (KickMigration_2SideBit == .FALSE.) then ! because its effect is applied in Migration Code
  364. ! !write(*,*) 'iloc=====' , iLoc bejaye ROP_Bit%RateOfPenetration ==0. in bude: DeltaVolumeOp == 0.0
  365. ! if (ABS(AnnulusSuctionDensity_OldMudSystem%St_Density%Last()) >= DensityMixTol .OR. (DeltaVolumeOp == 0.0 .and. ABS(Ann_Density%Array(iLoc)MudSystem%St_Density%Last())>=DensityMixTol .and. MudSystem%AnnulusFlowRate/=0.0d0) ) then ! new mud is pumped
  366. ! call Ann_Density%AddTo (iLocMudSystem%St_Density%Last())
  367. ! call Ann_MudDischarged_Volume%AddTo (iLoc,0.0d0)
  368. ! call Ann_Mud_Forehead_X%AddTo (iLoc,BackheadX)
  369. ! call Ann_Mud_Forehead_section%AddTo (iLoc,MudSection)
  370. ! call Ann_Mud_Backhead_X%AddTo (iLoc,BackheadX)
  371. ! call Ann_Mud_Backhead_section%AddTo (iLoc,MudSection)
  372. ! call Ann_RemainedVolume_in_LastSection%AddTo (iLoc,0.0d0)
  373. ! call Ann_EmptyVolume_inBackheadLocation%AddTo (iLoc,0.0d0)
  374. ! call Ann_MudOrKick%AddTo (iLoc,0)
  375. ! call Ann_CuttingMud%AddTo (iLoc,0)
  376. ! !write(*,*) 'c) annLength=' , Ann_Density%Length()
  377. !
  378. ! AnnulusSuctionDensity_Old=MudSystem%St_Density%Last()
  379. !
  380. ! MudIsChanged= .true.
  381. ! endif
  382. !
  383. ! Ann_MudDischarged_Volume%Array(iLoc)= Ann_MudDischarged_Volume%Array(iLoc)+ ((MudSystem%AnnulusFlowRate/60.d0)*DeltaT_Mudline) !(gal)
  384. !
  385. !endif
  386. 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
  387. MudSystem%Ann_Mud_Backhead_X%Array(1)= MudSystem%BackheadX
  388. ! write(*,*) 'zero)Ann_Mud sum=' , sum(Ann_MudDischarged_Volume%Array(:))
  389. !
  390. !
  391. !write(*,*) 'pump added-before add to ann=='
  392. !
  393. ! do imud=1, Op_MudDischarged_Volume%Length()
  394. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  395. ! enddo
  396. !
  397. ! do imud=1, Ann_MudDischarged_Volume%Length()
  398. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  399. ! enddo
  400. !
  401. !write(*,*) '====pump added-before add to ann'
  402. !========================Tripping In====================
  403. !write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp
  404. if (ROP_Bit%RateOfPenetration==0.) then ! .and. Op_MudOrKick%Last() == 0) then ! trip in mode(loole paeen) Mud
  405. !write(*,*) 'Tripping In'
  406. !write(*,*) 'before' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  407. !if ( MudIsChanged== .true. ) then
  408. ! call RemoveAnnulusMudArrays(iLoc)
  409. !endif
  410. if (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() == 0) then
  411. write(*,*) 'Kick influx enters Annulus'
  412. call MudSystem%Ann_Density%AddToFirst (MudSystem%Op_KickSaved_Density)
  413. call MudSystem%Ann_MudDischarged_Volume%AddToFirst (MudSystem%Op_Kick_Saved_Volume)
  414. call MudSystem%Ann_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1))
  415. call MudSystem%Ann_Mud_Forehead_section%AddToFirst (F_Counts%StringIntervalCounts+1)
  416. call MudSystem%Ann_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1))
  417. call MudSystem%Ann_Mud_Backhead_section%AddToFirst (F_Counts%StringIntervalCounts+1)
  418. call MudSystem%Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  419. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  420. call MudSystem%Ann_MudOrKick%AddToFirst (MudSystem%Saved_Op_MudOrKick) !<<<<<<<<
  421. call MudSystem%Ann_CuttingMud%AddToFirst (0)
  422. elseif (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() /= 0) then
  423. MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) + MudSystem%Op_Kick_Saved_Volume
  424. endif
  425. if (MudSystem%Op_Saved_MudDischarged_Volume> 0.0) then
  426. MudSystem%NewDensity= MudSystem%Op_MudSaved_Density
  427. MudSystem%NewVolume= MudSystem%Op_Saved_MudDischarged_Volume
  428. !write(*,*) 'NewVolume=' , NewVolume
  429. !write(*,*) 'iloc=' , iloc,'Ann_MudDischarged_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  430. if ((ROP_Bit%RateOfPenetration==0 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%DensityMixTol) &
  431. .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) &
  432. .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
  433. 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)
  434. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume
  435. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  436. MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  437. MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  438. MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  439. MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0)
  440. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0)
  441. !write(*,*) 'merge' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  442. else ! 2-Merging conditions are not meeted, so new pocket
  443. call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity)
  444. call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume)
  445. call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  446. call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  447. call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  448. call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  449. call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0)
  450. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0)
  451. call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0)
  452. call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0)
  453. !write(*,*) 'd) annLength=' , Ann_Density%Length()
  454. !write(*,*) 'new' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  455. endif
  456. endif
  457. endif
  458. !========================Tripping In - End====================
  459. !========================Drilling Mode========================
  460. if (ROP_Bit%RateOfPenetration>0. .and. MudSystem%DeltaVolumeOp>0.0) then ! trip in mode(loole paeen) DrillingMode== .true.
  461. !write(*,*) 'Drilling Mode'
  462. !if ( MudIsChanged== .true. ) then
  463. ! call RemoveAnnulusMudArrays(iLoc)
  464. !endif
  465. !write(*,*) 'before' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  466. !MudSystem%NewDensity= MudSystem%St_Density%Last() * MudSystem%AnnulusFlowRate + 141.4296E-4*ROP_Bit%RateOfPenetration*ROP_Spec%DiameterOfBit**2)/(MudSystem%AnnulusFlowRate+6.7995E-4*ROP_Bit%RateOfPenetration*Diameter_of_Bit**2)
  467. MudSystem%NewDensity=MudSystem%St_Density%Last()
  468. !NewVolume= ((MudSystem%AnnulusFlowRate/60.0d0)*DeltaT_Mudline)+DeltaVolumeOp
  469. !!! Density in ppg, flow rate in gpm, ROP in ft/s, bit diameter in inch
  470. do imud=1, MudSystem%Op_MudDischarged_Volume%Length()
  471. if ( MudSystem%Op_MudOrKick%Array(imud) == 0 ) then
  472. MudSystem%Op_Density%Array(imud)= MudSystem%NewDensity
  473. endif
  474. enddo
  475. if (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() == 0) then
  476. write(*,*) 'Kick influx enters Annulus first time'
  477. !write(*,*) 'Saved_Op_MudOrKick=',Saved_Op_MudOrKick
  478. call MudSystem%Ann_Density%AddToFirst (MudSystem%Op_KickSaved_Density)
  479. call MudSystem%Ann_MudDischarged_Volume%AddToFirst (MudSystem%Op_Kick_Saved_Volume)
  480. call MudSystem%Ann_Mud_Forehead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1))
  481. call MudSystem%Ann_Mud_Forehead_section%AddToFirst (F_Counts%StringIntervalCounts+1)
  482. call MudSystem%Ann_Mud_Backhead_X%AddToFirst (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1))
  483. call MudSystem%Ann_Mud_Backhead_section%AddToFirst (F_Counts%StringIntervalCounts+1)
  484. call MudSystem%Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  485. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  486. call MudSystem%Ann_MudOrKick%AddToFirst (MudSystem%Saved_Op_MudOrKick) !<<<<<<<<
  487. call MudSystem%Ann_CuttingMud%AddToFirst (0)
  488. elseif (MudSystem%Op_Kick_Saved_Volume > 0.0 .and. MudSystem%Ann_MudOrKick%First() /= 0) then
  489. MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) + MudSystem%Op_Kick_Saved_Volume
  490. endif
  491. if (MudSystem%Op_Saved_MudDischarged_Volume> 0.0) then
  492. !write(*,*) 'Op_Saved_Mud added'
  493. MudSystem%NewDensity= MudSystem%NewDensity !(drilling density)
  494. MudSystem%NewVolume= MudSystem%Op_Saved_MudDischarged_Volume + MudSystem%DeltaVolumeOp ! (DeltaVolumeOp: for Cuttings Volume)
  495. !write(*,*) 'NewVolume=' , NewVolume
  496. !write(*,*) 'iloc=' , iloc,'Ann_MudDischarged_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  497. if ( (MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==1 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%CuttingDensityMixTol ) &
  498. .or. (MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)==0 .and. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc) < 42.) ) then ! 1-Pockets are Merged
  499. 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)
  500. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume
  501. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  502. MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  503. MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  504. MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  505. MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0)
  506. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0)
  507. MudSystem%Ann_CuttingMud%Array(MudSystem%iLoc)= 1
  508. !write(*,*) 'merge' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  509. else ! 2-Merging conditions are not meeted, so new pocket
  510. !write(*,*) 'before e) ', iloc, Ann_Density%Array(iLoc),MudSystem%NewDensity
  511. !write(*,*) 'before e) Ann_MudDischarged_Volume%Array(iLoc)=' , Ann_MudDischarged_Volume%Array(iLoc)
  512. call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity)
  513. call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume)
  514. call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  515. call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  516. call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  517. call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  518. call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0)
  519. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0)
  520. call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0)
  521. call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,1) ! 1= cutting 0= mud
  522. !write(*,*) 'new' ,'Ann_Volume%Array(1)=' , Ann_MudDischarged_Volume%Array(1)
  523. !write(*,*) 'e) annLength=' , Ann_Density%Length()
  524. endif
  525. endif
  526. endif
  527. !===================================================================
  528. !write(*,*) 'after add to ann=='
  529. !
  530. ! do imud=1, Op_MudDischarged_Volume%Length()
  531. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  532. ! enddo
  533. !
  534. ! do imud=1, Ann_MudDischarged_Volume%Length()
  535. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  536. ! enddo
  537. !
  538. !write(*,*) '==after add to ann'
  539. MudSystem%NewVolume= ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) - MudSystem%Op_Saved_MudDischarged_Volume
  540. if (MudSystem%iLoc==2 .and. MudSystem%Op_MudOrKick%Last()==0 .and. MudSystem%NewVolume > 0.d0 ) then ! for avoid kick separation
  541. !write(*,*) 'avoid kick separation'
  542. MudSystem%NewDensity= MudSystem%Op_MudSaved_Density
  543. call RemoveOpMudArrays(MudSystem%Op_Density%Length()) ! mud here is removed and then will be added to iloc=2 in Ann
  544. if ( MudSystem%Ann_MudDischarged_Volume%Array(1) > ((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline)- MudSystem%Op_Saved_MudDischarged_Volume) then! 1st in Ann = kick
  545. !write(*,*) 'mode1'
  546. MudSystem%Ann_MudDischarged_Volume%Array(1)= MudSystem%Ann_MudDischarged_Volume%Array(1) - (((MudSystem%AnnulusFlowRate/60.d0)*MudSystem%DeltaT_Mudline) -MudSystem%Op_Saved_MudDischarged_Volume)
  547. 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
  548. else
  549. call RemoveAnnulusMudArrays(1) !kick is removed
  550. MudSystem%iLoc= 1
  551. 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)
  552. !write(*,*) 'mode2'
  553. ! including a little expand
  554. endif
  555. if ((ROP_Bit%RateOfPenetration==0 .and. abs(MudSystem%Ann_Density%Array(MudSystem%iLoc)-MudSystem%NewDensity)< MudSystem%DensityMixTol) &
  556. .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) &
  557. .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
  558. 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)
  559. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)= MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%iLoc)+MudSystem%NewVolume
  560. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  561. MudSystem%Ann_Mud_Forehead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  562. MudSystem%Ann_Mud_Backhead_X%Array(MudSystem%iLoc)= MudSystem%BackheadX
  563. MudSystem%Ann_Mud_Backhead_section%Array(MudSystem%iLoc)= MudSystem%MudSection
  564. MudSystem%Ann_RemainedVolume_in_LastSection%Array(MudSystem%iLoc)= (0.0d0)
  565. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(MudSystem%iLoc)= (0.0d0)
  566. else ! 2-Merging conditions are not meeted, so new pocket
  567. call MudSystem%Ann_Density%AddTo (MudSystem%iLoc,MudSystem%NewDensity)
  568. call MudSystem%Ann_MudDischarged_Volume%AddTo (MudSystem%iLoc,MudSystem%NewVolume)
  569. call MudSystem%Ann_Mud_Forehead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  570. call MudSystem%Ann_Mud_Forehead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  571. call MudSystem%Ann_Mud_Backhead_X%AddTo (MudSystem%iLoc,MudSystem%BackheadX)
  572. call MudSystem%Ann_Mud_Backhead_section%AddTo (MudSystem%iLoc,MudSystem%MudSection)
  573. call MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (MudSystem%iLoc,0.0d0)
  574. call MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystem%iLoc,0.0d0)
  575. call MudSystem%Ann_MudOrKick%AddTo (MudSystem%iLoc,0)
  576. call MudSystem%Ann_CuttingMud%AddTo (MudSystem%iLoc,0)
  577. !write(*,*) 'd) annLength=' , Ann_Density%Length()
  578. endif
  579. endif
  580. !===================================================================
  581. if( MudSystem%Op_MudOrKick%Last() == 1 .and. MudSystem%Ann_MudOrKick%First() == 0 ) then
  582. write(*,*) '***error2****=='
  583. write(*,*) 'Op_Kick_Saved_Volume,Op_Saved_MudDischarged_Volume=' , MudSystem%Op_Kick_Saved_Volume,MudSystem%Op_Saved_MudDischarged_Volume
  584. write(*,*) 'after add to ann=='
  585. do imud=1, MudSystem%Op_MudDischarged_Volume%Length()
  586. write(*,*) 'Op:', imud, MudSystem%Op_MudDischarged_Volume%Array(imud), MudSystem%Op_Density%Array(imud) ,MudSystem%Op_MudOrKick%Array(imud)
  587. enddo
  588. do imud=1, MudSystem%Ann_MudDischarged_Volume%Length()
  589. write(*,*) 'Ann:', imud, MudSystem%Ann_MudDischarged_Volume%Array(imud), MudSystem%Ann_Density%Array(imud) ,MudSystem%Ann_MudOrKick%Array(imud)
  590. enddo
  591. write(*,*) '==after add to ann'
  592. write(*,*) 'NewVolume,Op_MudOrKick%Last=' , MudSystem%NewVolume,MudSystem%Op_MudOrKick%Last()
  593. write(*,*) '==***error2****'
  594. endif
  595. !=============== save Ann Mud data to transfer to the ChokeLine enterance
  596. MudSystem%AnnMudVolumeSum= 0.d0
  597. !Ann_MudSaved_Density= 0.d0
  598. !Ann_KickSaved_Density= 0.d0
  599. MudSystem%Ann_Saved_MudDischarged_Volume= 0.d0
  600. MudSystem%Ann_Kick_Saved_Volume= 0.d0
  601. MudSystem%Saved_Ann_MudOrKick= 0
  602. MudSystem%Ann_to_Choke_2mud= .false.
  603. do imud=1, MudSystem%Ann_MudDischarged_Volume%Length()
  604. MudSystem%AnnMudVolumeSum= MudSystem%AnnMudVolumeSum + MudSystem%Ann_MudDischarged_Volume%Array(imud)
  605. if ( MudSystem%AnnMudVolumeSum > sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) ) then
  606. IF (MudSystem%Ann_MudOrKick%Array(imud) == 0) THEN
  607. MudSystem%Ann_MudSaved_Density = MudSystem%Ann_Density%Array(imud)
  608. MudSystem%Ann_Saved_MudDischarged_Volume = MudSystem%AnnMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections))
  609. ELSEIF (MudSystem%Ann_MudOrKick%Array(imud) > 0 .AND. MudSystem%Ann_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  610. MudSystem%Ann_Kick_Saved_Volume = MudSystem%AnnMudVolumeSum - sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections))
  611. MudSystem%Saved_Ann_MudOrKick= MudSystem%Ann_MudOrKick%Array (imud)
  612. MudSystem%Ann_KickSaved_Density= MudSystem%Ann_Density%Array(imud)
  613. END IF
  614. do ii= imud + 1, MudSystem%Ann_MudDischarged_Volume%Length()
  615. IF (MudSystem%Ann_MudOrKick%Array(ii) == 0) THEN
  616. 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))
  617. MudSystem%Ann_Saved_MudDischarged_Volume = MudSystem%Ann_Saved_MudDischarged_Volume + MudSystem%Ann_MudDischarged_Volume%Array(ii)
  618. MudSystem%Ann_to_Choke_2mud= .true.
  619. ELSEIF (MudSystem%Ann_MudOrKick%Array(ii) > 0 .AND. MudSystem%Ann_MudOrKick%Array(ii) <100) THEN ! 104= AIR
  620. MudSystem%Ann_Kick_Saved_Volume = MudSystem%Ann_Kick_Saved_Volume + MudSystem%Ann_MudDischarged_Volume%Array(ii)
  621. MudSystem%Saved_Ann_MudOrKick= MudSystem%Ann_MudOrKick%Array (ii)
  622. MudSystem%Ann_KickSaved_Density= MudSystem%Ann_Density%Array(ii)
  623. END IF
  624. enddo
  625. !WRITE (*,*) 'Ann_Saved_Mud_Volume, Ann_Kick_Saved_Volume', Ann_Saved_MudDischarged_Volume, Ann_Kick_Saved_Volume
  626. exit
  627. endif
  628. enddo
  629. MudSystem%Ann_Saved_MudDischarged_Volume_Final= MudSystem%Ann_Saved_MudDischarged_Volume !+ Ann_Kick_Saved_Volume
  630. MudSystem%Ann_Kick_Saved_Volume_Final= MudSystem%Ann_Kick_Saved_Volume
  631. IF (MudSystem%WellHeadIsOpen) MudSystem%MudVolume_InjectedFromAnn = MudSystem%Ann_Saved_MudDischarged_Volume_Final -((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline)
  632. !WRITE (*,*) 'MudSystem%MudVolume_InjectedFromAnn=', MudSystem%MudVolume_InjectedFromAnn
  633. !======================================================================
  634. !write(*,*) 'c)Ann_Mud sum=' , sum(Ann_MudDischarged_Volume%Array(:))
  635. !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  636. !write(*,*) 'Ann_Saved_Mud=' , Ann_Saved_MudDischarged_Volume
  637. MudSystem%total_injected = MudSystem%total_injected + MudSystem%MudVolume_InjectedFromAnn
  638. if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
  639. MudSystem%total_injected= 0.
  640. endif
  641. !write(*,*) ' total injected-tripin =' , total_injected
  642. !write(*,*) 'injected-tripin =' , MudSystem%MudVolume_InjectedFromAnn
  643. !======================== Annulus ====================
  644. !MudIsChanged= .false.
  645. imud= 0
  646. do while (imud < MudSystem%Ann_Mud_Forehead_X%Length())
  647. imud = imud + 1
  648. if (imud> 1) then
  649. MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Ann_Mud_Forehead_X%Array(imud-1)
  650. MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%Ann_Mud_Forehead_section%Array(imud-1)
  651. endif
  652. ! <<< Fracture Shoe Lost
  653. IF ( MudSystem%ShoeLost .and. Shoe%ShoeDepth < MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. Shoe%ShoeDepth >= MudSystem%Ann_Mud_Forehead_X%Array(imud) ) then
  654. !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline)
  655. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  656. if (MudSystem%Ann_MudDischarged_Volume%Array(imud) < 0.0) then
  657. !write(*,*) 'mud is removed by shoe lost, imud=' , imud
  658. call RemoveAnnulusMudArrays(imud)
  659. imud= imud-1
  660. cycle
  661. endif
  662. ENDIF
  663. ! Fracture Shoe Lost >>>
  664. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))) &
  665. / ABS(MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Backhead_section%Array(imud)))
  666. ! +1 for string , -1 for annulus
  667. 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))* &
  668. MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Backhead_section%Array(imud)) !(ft^3)
  669. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  670. if ( MudSystem%Ann_MudDischarged_Volume%Array(imud) <= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then
  671. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%Ann_Mud_Backhead_section%Array(imud)
  672. 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))
  673. ! 7.48 is for gal to ft^3
  674. else
  675. MudSystem%isection= MudSystem%Ann_Mud_Backhead_section%Array(imud)+1
  676. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)
  677. do
  678. if (MudSystem%isection > MudSystem%NoPipeSections) then ! last pipe section(well exit)
  679. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)
  680. MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)
  681. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%NoPipeSections
  682. if (MudSystem%Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
  683. !write(*,*) 'remove******'
  684. call RemoveAnnulusMudArrays(imud)
  685. endif
  686. exit
  687. endif
  688. MudSystem%xx= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  689. if (MudSystem%xx<= 1.0) then
  690. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%isection
  691. MudSystem%Ann_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_PipeSection(MudSystem%isection)- MudSystem%Xstart_PipeSection(MudSystem%isection)))+ MudSystem%Xstart_PipeSection(MudSystem%isection)
  692. exit
  693. else
  694. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  695. MudSystem%isection= MudSystem%isection+ 1
  696. endif
  697. enddo
  698. endif
  699. ! write(*,*) 'imud=' , imud
  700. !write(*,*) 'Pinter4 **Ann_Length()=' , Ann_Mud_Forehead_X%Length()
  701. ! write(*,*) 'Ann_Density%Array (imud)=' , Ann_Density%Array (imud)
  702. !
  703. !
  704. !write(*,*) imud,'Ann_Mud_Forehead_X%Array(imud)=' , Ann_Mud_Forehead_X%Array(imud)
  705. !if (Ann_Mud_Forehead_X%Array(imud) < Xend_PipeSection(NoPipeSections)) then
  706. ! Ann_Mud_Forehead_X%Array(imud) = Xend_PipeSection(NoPipeSections) ! for error preventing
  707. !endif
  708. !write(*,*) imud, 'Ann_MudDischarged_Volume%Array(imud)=' , Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud)
  709. enddo
  710. if (MudSystem%Ann_Mud_Forehead_X%Last() < MudSystem%Xend_PipeSection(MudSystem%NoPipeSections)) then
  711. MudSystem%Ann_Mud_Forehead_X%Array(MudSystem%Ann_Mud_Forehead_X%Length()) = MudSystem%Xend_PipeSection(MudSystem%NoPipeSections) ! for error preventing
  712. endif
  713. !========================ANNULUS END=================
  714. !write(*,*) 'sum(Ann_MudDischarged_Volume%Array())=' , sum(Ann_MudDischarged_Volume%Array(:))
  715. !=========================================================
  716. !write(*,*) 'before======2'
  717. !
  718. ! do imud=1, Op_MudDischarged_Volume%Length()
  719. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  720. ! enddo
  721. !write(*,*) '2======before'
  722. !========================Bottom Hole=================
  723. imud=0
  724. do while (imud < MudSystem%Op_Mud_Forehead_X%Length())
  725. imud = imud + 1
  726. if (imud> 1) then
  727. MudSystem%Op_Mud_Backhead_X%Array(imud)= MudSystem%Op_Mud_Forehead_X%Array(imud-1)
  728. MudSystem%Op_Mud_Backhead_section%Array(imud)= MudSystem%Op_Mud_Forehead_section%Array(imud-1)
  729. endif
  730. !write(*,*) 'imud**=' , imud
  731. MudSystem%DirectionCoef= (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) &
  732. / ABS(MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud)))
  733. ! +1 for string , -1 for annulus
  734. 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))* &
  735. MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) !(ft^3)
  736. MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  737. !write(*,*) ' Op_EmptyVolume_inBackheadLocation%Array(1) =' , Op_EmptyVolume_inBackheadLocation%Array(1)
  738. if ( MudSystem%Op_EmptyVolume_inBackheadLocation%Array(1) < 0.0) CALL ErrorStop1 ('Negative Empty volume')
  739. if ( MudSystem%Op_MudDischarged_Volume%Array(imud) <= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)) then
  740. MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%Op_Mud_Backhead_section%Array(imud)
  741. 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))
  742. ! 7.48 is for gal to ft^3
  743. else
  744. MudSystem%isection= MudSystem%Op_Mud_Backhead_section%Array(imud)+1
  745. MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)
  746. do
  747. if (MudSystem%isection > F_Counts%BottomHoleIntervalCounts) then ! last pipe section(well exit)
  748. !if( imud==1) KickDeltaVinAnnulus= Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space
  749. MudSystem%Op_MudDischarged_Volume%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)
  750. MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)
  751. MudSystem%Op_Mud_Forehead_section%Array(imud)= F_Counts%BottomHoleIntervalCounts
  752. if (MudSystem%Op_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
  753. call RemoveOpMudArrays(imud)
  754. endif
  755. exit
  756. endif
  757. MudSystem%xx= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%OpSection_VolumeCapacity(MudSystem%isection) !(gal)
  758. if (MudSystem%xx<= 1.0) then
  759. MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%isection
  760. MudSystem%Op_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_OpSection(MudSystem%isection)- MudSystem%Xstart_OpSection(MudSystem%isection)))+ MudSystem%Xstart_OpSection(MudSystem%isection)
  761. exit
  762. else
  763. MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)- MudSystem%OpSection_VolumeCapacity(MudSystem%isection)
  764. MudSystem%isection= MudSystem%isection+ 1
  765. endif
  766. enddo
  767. endif
  768. ! for OP remove:
  769. if (MudSystem%Op_Mud_Forehead_X%Array(imud)== MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) then
  770. MudSystem%totalLength = MudSystem%Op_MudDischarged_Volume%Length()
  771. do while(imud < MudSystem%totalLength)
  772. !imud = imud + 1
  773. call RemoveOpMudArrays(MudSystem%totalLength)
  774. MudSystem%totalLength = MudSystem%totalLength - 1
  775. enddo
  776. exit !
  777. endif
  778. !if (Op_Mud_Forehead_X%Array(imud)== Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) then
  779. ! totalLength = Op_MudDischarged_Volume%Length()
  780. ! do while(imud <= totalLength)
  781. !
  782. ! imud = imud + 1
  783. ! call RemoveOpMudArrays(imud)
  784. ! totalLength = totalLength - 1
  785. !
  786. !
  787. ! enddo
  788. !
  789. ! exit !
  790. !
  791. !endif
  792. enddo
  793. !write(*,*) 'OpSection_VolumeCapacity sum=' , sum(OpSection_VolumeCapacity(:))
  794. !========================Bottom Hole END=================
  795. !write(*,*) 'after sorting=='
  796. !
  797. ! do imud=1, Op_MudDischarged_Volume%Length()
  798. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  799. ! enddo
  800. !
  801. ! do imud=1, Ann_MudDischarged_Volume%Length()
  802. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  803. ! enddo
  804. !
  805. ! !
  806. ! !do imud=1, st_MudDischarged_Volume%Length()
  807. ! ! write(*,*) 'st:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud)
  808. ! !enddo
  809. !
  810. !write(*,*) '==after sorting'
  811. ! write(*,*) 'after sorting st=='
  812. !
  813. ! do imud=1, st_MudDischarged_Volume%Length()
  814. ! write(*,*) 'st-plot:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud)MudSystem%St_Density%Array(imud)
  815. ! enddo
  816. !
  817. !write(*,*) '==after sorting st'
  818. !write(*,*) '**Ann_Kick_Saved_Final,Mud_InjectedFromAnn' , Ann_Kick_Saved_Volume_Final,MudSystem%MudVolume_InjectedFromAnn
  819. end subroutine Pump_and_TripIn
  820. subroutine ChokeLineMud ! is called in subroutine CirculationCodeSelect
  821. Use GeoElements_FluidModule
  822. USE CMudPropertiesVariables
  823. USE MudSystemVARIABLES
  824. USE Pumps_VARIABLES
  825. !USE CHOKEVARIABLES
  826. !USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure
  827. !use CManifolds
  828. use CDrillWatchVariables
  829. !use CHOKEVARIABLES
  830. !use CChokeManifoldVariables
  831. !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
  832. USE sROP_Other_Variables
  833. USE sROP_Variables
  834. Use KickVariables
  835. USE PressureDisplayVARIABLES
  836. Use CError
  837. Use , intrinsic :: IEEE_Arithmetic
  838. implicit none
  839. integer i,ii,error_occured
  840. error_occured = 0
  841. !write(*,*) 'begining chokeline=='
  842. !write(*,*) 'Ann last:', Ann_MudDischarged_Volume%Last(), Ann_Density%Last() ,Ann_MudOrKick%Last()
  843. !
  844. !do imud=1, ChokeLine_MudDischarged_Volume%Length()
  845. ! write(*,*) 'ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud), ChokeLine_Density%Array(imud) ,ChokeLine_MudOrKick%Array(imud)
  846. !enddo
  847. !write(*,*) 'Ann_Kick_Saved_Volume_Final,MudSystem%MudVolume_InjectedFromAnn' , Ann_Kick_Saved_Volume_Final,MudSystem%MudVolume_InjectedFromAnn
  848. !write(*,*) 'begining chokeline=='
  849. MudSystem%ChokeLineFlowRate = MUD(4)%Q
  850. !WRITE (*,*) 'MUD(4)%Q', MUD(4)%Q
  851. if (MudSystem%NewPipeFilling == 0) then ! .or. UtubeFilling==0) then
  852. MudSystem%ChokeLineFlowRate= 0.
  853. endif
  854. do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2
  855. if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then
  856. write(*,*) 'error_location is 1'
  857. error_occured = 1
  858. endif
  859. enddo
  860. !
  861. !do imud=1, st_MudDischarged_Volume%Length()
  862. ! write(*,*) 'st:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud)
  863. !enddo
  864. !========================CHOKE LINE ENTRANCE=================
  865. !if ( Ann_Kick_Saved_Volume > 0.0 .and. ( Ann_Saved_MudDischarged_Volume-((Qlost/60.0d0)*DeltaT_Mudline) ) == 0.0 ) then
  866. if ( MudSystem%Ann_Kick_Saved_Volume > 1.0e-5 .and. ( MudSystem%MudVolume_InjectedFromAnn ) <= 1.0e-5 ) then
  867. !WRITE (*,*) 'only kick enters to chokeline, Casing pressure = ', PressureGauges(2)
  868. if (MudSystem%ChokeLine_MudOrKick%First() == 0) then
  869. call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_KickSaved_Density)
  870. call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (0.d0)
  871. call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
  872. call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1)
  873. call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
  874. call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1)
  875. call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  876. call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  877. call MudSystem%ChokeLine_MudOrKick%AddToFirst (MudSystem%Saved_Ann_MudOrKick)
  878. MudSystem%ChokeLineDensity_Old= MudSystem%Ann_KickSaved_Density
  879. endif
  880. MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ MudSystem%Ann_Kick_Saved_Volume !(gal)
  881. endif
  882. do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2
  883. if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then
  884. write(*,*) 'error_location is 2'
  885. error_occured = 1
  886. endif
  887. enddo
  888. !if ( Ann_Kick_Saved_Volume == 0.0 .and. ( Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) > 0.0 ) then
  889. if ( MudSystem%Ann_Kick_Saved_Volume <= 1.0e-5 .and. MudSystem%MudVolume_InjectedFromAnn > 1.0e-5 ) then
  890. !WRITE (*,*) 'only mud enters to chokeline'
  891. if ((MudSystem%Ann_to_Choke_2mud == .false. .and. ABS(MudSystem%ChokeLineDensity_Old - MudSystem%Ann_MudSaved_Density) >= MudSystem%DensityMixTol) .or. MudSystem%ChokeLine_MudOrKick%First() /= 0) then ! new mud is pumped
  892. call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_MudSaved_Density)
  893. call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (0.0d0)
  894. call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
  895. call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1)
  896. call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
  897. call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1)
  898. call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  899. call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  900. call MudSystem%ChokeLine_MudOrKick%AddToFirst (0)
  901. MudSystem%ChokeLineDensity_Old= MudSystem%Ann_MudSaved_Density
  902. endif
  903. !ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1)+ (Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) !(gal)
  904. MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ (MudSystem%MudVolume_InjectedFromAnn) !(gal)
  905. endif
  906. do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2
  907. if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then
  908. write(*,*) 'error_location is 3'
  909. error_occured = 1
  910. endif
  911. enddo
  912. !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
  913. if ( MudSystem%Ann_Kick_Saved_Volume > 1.0e-5 .and. (MudSystem%MudVolume_InjectedFromAnn) > 1.0e-5 .and. MudSystem%ChokeLine_MudOrKick%First() /= 0 ) then
  914. WRITE (*,*) 'Kick Enters Choke line Last Time'
  915. MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ MudSystem%Ann_Kick_Saved_Volume !(gal)
  916. call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_MudSaved_Density)
  917. !call ChokeLine_MudDischarged_Volume%AddToFirst (Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) )
  918. call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (MudSystem%MudVolume_InjectedFromAnn)
  919. call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
  920. call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1)
  921. call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
  922. call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1)
  923. call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  924. call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  925. call MudSystem%ChokeLine_MudOrKick%AddToFirst (0)
  926. MudSystem%ChokeLineDensity_Old= MudSystem%Ann_MudSaved_Density
  927. !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
  928. ELSE if ( MudSystem%Ann_Kick_Saved_Volume > 1.0e-5 .and. ( MudSystem%MudVolume_InjectedFromAnn ) > 1.0e-5 .and. MudSystem%ChokeLine_MudOrKick%First() == 0 ) then
  929. WRITE (*,*) 'Kick Enters Choke line First Time'
  930. !ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1)+ ( Ann_Saved_MudDischarged_Volume - ((Qlost/60.0d0)*DeltaT_Mudline) ) !(gal)
  931. MudSystem%ChokeLine_MudDischarged_Volume%Array(1)= MudSystem%ChokeLine_MudDischarged_Volume%Array(1)+ ( MudSystem%MudVolume_InjectedFromAnn ) !(gal)
  932. call MudSystem%ChokeLine_Density%AddToFirst (MudSystem%Ann_KickSaved_Density)
  933. call MudSystem%ChokeLine_MudDischarged_Volume%AddToFirst (MudSystem%Ann_Kick_Saved_Volume)
  934. call MudSystem%ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
  935. call MudSystem%ChokeLine_Mud_Forehead_section%AddToFirst (1)
  936. call MudSystem%ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
  937. call MudSystem%ChokeLine_Mud_Backhead_section%AddToFirst (1)
  938. call MudSystem%ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  939. call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  940. call MudSystem%ChokeLine_MudOrKick%AddToFirst (MudSystem%Saved_Ann_MudOrKick)
  941. MudSystem%ChokeLineDensity_Old= MudSystem%Ann_KickSaved_Density
  942. endif
  943. do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()-2
  944. if ( MudSystem%ChokeLine_MudOrKick%Array(imud) ==1 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+1) ==0 .and. MudSystem%ChokeLine_MudOrKick%Array(imud+2) ==1 ) then
  945. write(*,*) 'error_location is 4'
  946. error_occured = 1
  947. endif
  948. enddo
  949. if (error_occured == 1) then
  950. do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()
  951. write(*,*) 'ChokeLine:', imud, MudSystem%ChokeLine_Density%Array(imud) ,MudSystem%ChokeLine_MudOrKick%Array(imud)
  952. enddo
  953. endif
  954. !==========================================================
  955. !
  956. !write(*,*) 'after add chokeline=='
  957. !
  958. ! do imud=1, ChokeLine_MudDischarged_Volume%Length()
  959. ! write(*,*) 'ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud), ChokeLine_Density%Array(imud) ,ChokeLine_MudOrKick%Array(imud)
  960. ! enddo
  961. !
  962. !write(*,*) 'after add chokeline=='
  963. !
  964. !
  965. !=============== save Choke Mud data==========================
  966. MudSystem%ChokeMudVolumeSum= 0.d0
  967. !Ann_MudSaved_Density= 0.d0
  968. !Ann_KickSaved_Density= 0.d0
  969. MudSystem%Choke_Saved_MudDischarged_Volume= 0.d0
  970. MudSystem%Choke_Kick_Saved_Volume= 0.d0
  971. MudSystem%Saved_Choke_MudOrKick= 0
  972. do imud=1, MudSystem%ChokeLine_MudDischarged_Volume%Length()
  973. MudSystem%ChokeMudVolumeSum= MudSystem%ChokeMudVolumeSum + MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)
  974. if ( MudSystem%ChokeMudVolumeSum > MudSystem%ChokeLine_VolumeCapacity ) then
  975. IF (MudSystem%ChokeLine_MudOrKick%Array(imud) == 0) THEN
  976. MudSystem%Choke_MudSaved_Density = MudSystem%ChokeLine_Density%Array(imud)
  977. MudSystem%Choke_Saved_MudDischarged_Volume = MudSystem%ChokeMudVolumeSum - MudSystem%ChokeLine_VolumeCapacity
  978. ELSEIF (MudSystem%ChokeLine_MudOrKick%Array(imud) > 0 .AND. MudSystem%ChokeLine_MudOrKick%Array(imud) <100) THEN ! 104= AIR
  979. MudSystem%Choke_Kick_Saved_Volume = MudSystem%ChokeMudVolumeSum - MudSystem%ChokeLine_VolumeCapacity
  980. MudSystem%Saved_Choke_MudOrKick= MudSystem%ChokeLine_MudOrKick%Array (imud)
  981. MudSystem%Choke_KickSaved_Density= MudSystem%ChokeLine_Density%Array(imud)
  982. END IF
  983. do ii= imud + 1, MudSystem%ChokeLine_MudDischarged_Volume%Length()
  984. IF (MudSystem%ChokeLine_MudOrKick%Array(ii) == 0) THEN
  985. MudSystem%Choke_MudSaved_Density = ((MudSystem%Choke_MudSaved_Density * MudSystem%Choke_Saved_MudDischarged_Volume) + (MudSystem%ChokeLine_Density%Array(ii) * MudSystem%ChokeLine_MudDischarged_Volume%Array(ii))) / (MudSystem%Choke_Saved_MudDischarged_Volume + MudSystem%ChokeLine_MudDischarged_Volume%Array(ii))
  986. MudSystem%Choke_Saved_MudDischarged_Volume = MudSystem%Choke_Saved_MudDischarged_Volume + MudSystem%ChokeLine_MudDischarged_Volume%Array(ii)
  987. ELSEIF (MudSystem%ChokeLine_MudOrKick%Array(ii) > 0 .AND. MudSystem%ChokeLine_MudOrKick%Array(ii) <100) THEN ! 104= AIR
  988. MudSystem%Choke_Kick_Saved_Volume = MudSystem%Choke_Kick_Saved_Volume + MudSystem%ChokeLine_MudDischarged_Volume%Array(ii)
  989. MudSystem%Saved_Choke_MudOrKick= MudSystem%ChokeLine_MudOrKick%Array (ii)
  990. MudSystem%Choke_KickSaved_Density= MudSystem%ChokeLine_Density%Array(ii)
  991. END IF
  992. enddo
  993. !WRITE (*,*) 'Choke_Saved_Mud_Volume, Choke_Kick_Saved_Volume', Choke_Saved_MudDischarged_Volume, Choke_Kick_Saved_Volume
  994. exit ! exits do
  995. endif
  996. enddo
  997. MudSystem%Choke_Saved_MudDischarged_Volume_Final= MudSystem%Choke_Saved_MudDischarged_Volume !+ Choke_Kick_Saved_Volume
  998. MudSystem%Choke_Kick_Saved_Volume_Final= MudSystem%Choke_Kick_Saved_Volume
  999. !======================================================================
  1000. !
  1001. !do imud=1, ChokeLine_MudDischarged_Volume%Length()
  1002. ! write(*,*) 'a)ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud) ,ChokeLine_MudOrKick%Array(imud)
  1003. !enddo
  1004. !write(*,*) 'choke_Mud sum=' , sum(ChokeLine_MudDischarged_Volume%Array(:))
  1005. !write(*,*) 'choke_cap=' , ChokeLine_VolumeCapacity
  1006. !write(*,*) 'Choke_Saved_Mud=' , Choke_Saved_MudDischarged_Volume_Final
  1007. !write(*,*) 'Choke_Saved_Kick=' , Choke_Kick_Saved_Volume_Final
  1008. !========================Choke Line=================
  1009. imud=0
  1010. do while (imud < MudSystem%ChokeLine_Mud_Forehead_X%Length())
  1011. imud = imud + 1
  1012. if (imud> 1) then
  1013. MudSystem%ChokeLine_Mud_Backhead_X%Array(imud)= MudSystem%ChokeLine_Mud_Forehead_X%Array(imud-1)
  1014. MudSystem%ChokeLine_Mud_Backhead_section%Array(imud)= MudSystem%ChokeLine_Mud_Forehead_section%Array(imud-1)
  1015. endif
  1016. !DirectionCoef= (Xend_PipeSection(St_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(St_Mud_Backhead_section%Array(imud))) &
  1017. ! / ABS(Xend_PipeSection(St_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(St_Mud_Backhead_section%Array(imud)))
  1018. ! +1 for string , -1 for annulus
  1019. MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)= (BopStackSpecification%ChokeLineLength- MudSystem%ChokeLine_Mud_Backhead_X%Array(imud))* MudSystem%Area_ChokeLineFt !(ft^3)
  1020. MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  1021. if ( MudSystem%ChokeLine_MudDischarged_Volume%Array(imud) <= MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)) then
  1022. MudSystem%ChokeLine_Mud_Forehead_section%Array(imud)= MudSystem%ChokeLine_Mud_Backhead_section%Array(imud)
  1023. MudSystem%ChokeLine_Mud_Forehead_X%Array(imud)= MudSystem%ChokeLine_Mud_Backhead_X%Array(imud)+ (MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_ChokeLineFt
  1024. ! 7.48 is for gal to ft^3
  1025. else
  1026. MudSystem%isection= MudSystem%ChokeLine_Mud_Backhead_section%Array(imud)+1
  1027. MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)= MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)- MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Array(imud)
  1028. do
  1029. if (MudSystem%isection > 1) then ! last pipe section(Chokeline exit)
  1030. MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)= MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)- MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)
  1031. MudSystem%ChokeLine_Mud_Forehead_X%Array(imud)= BopStackSpecification%ChokeLineLength
  1032. MudSystem%ChokeLine_Mud_Forehead_section%Array(imud)= 1
  1033. if (MudSystem%ChokeLine_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
  1034. call MudSystem%ChokeLine_MudDischarged_Volume%Remove (imud)
  1035. call MudSystem%ChokeLine_Mud_Backhead_X%Remove (imud)
  1036. call MudSystem%ChokeLine_Mud_Backhead_section%Remove (imud)
  1037. call MudSystem%ChokeLine_Mud_Forehead_X%Remove (imud)
  1038. call MudSystem%ChokeLine_Mud_Forehead_section%Remove (imud)
  1039. call MudSystem%ChokeLine_Density%Remove (imud)
  1040. call MudSystem%ChokeLine_RemainedVolume_in_LastSection%Remove (imud)
  1041. call MudSystem%ChokeLine_EmptyVolume_inBackheadLocation%Remove (imud)
  1042. call MudSystem%ChokeLine_MudOrKick%Remove (imud)
  1043. endif
  1044. exit
  1045. endif
  1046. MudSystem%xx= MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%ChokeLine_VolumeCapacity !(gal)
  1047. if (MudSystem%xx<= 1.0) then
  1048. MudSystem%ChokeLine_Mud_Forehead_section%Array(imud)= MudSystem%isection
  1049. MudSystem%ChokeLine_Mud_Forehead_X%Array(imud)= MudSystem%xx * BopStackSpecification%ChokeLineLength
  1050. exit
  1051. else
  1052. MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)= MudSystem%ChokeLine_RemainedVolume_in_LastSection%Array(imud)- MudSystem%ChokeLine_VolumeCapacity
  1053. MudSystem%isection= MudSystem%isection+ 1
  1054. endif
  1055. enddo
  1056. endif
  1057. enddo
  1058. !========================Choke Line END=================
  1059. !do imud=1, ChokeLine_MudDischarged_Volume%Length()
  1060. ! write(*,*) 'b)ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud) ,ChokeLine_MudOrKick%Array(imud)
  1061. !enddo
  1062. MudSystem%ChokeOutletDensity= MudSystem%ChokeLine_Density%Last() ! used in MudSystem
  1063. do i=1, MudSystem%ChokeLine_MudOrKick%Length()
  1064. !write(*,555) i,'Choke_Volume(i), type=' ,ChokeLine_MudDischarged_Volume%Array(i),ChokeLine_MudOrKick%Array(i)
  1065. IF (IEEE_Is_NaN(MudSystem%ChokeLine_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in Choke Volume-Plot')
  1066. IF (MudSystem%ChokeLine_MudDischarged_Volume%Array(i)<=0.) call ErrorStop('Choke Volume= <=0' , MudSystem%ChokeLine_MudDischarged_Volume%Array(i))
  1067. enddo
  1068. 555 FORMAT(I3,5X,A42,(f12.5),5X,I3)
  1069. !write(*,*) 'after sorting chokeline=='
  1070. !IF (ANY(ChokeLine_MudOrKick%Array(:) > 0)) THEN
  1071. ! do imud=1, ChokeLine_MudDischarged_Volume%Length()
  1072. ! write(*,*) 'ChokeLine:', imud, ChokeLine_MudDischarged_Volume%Array(imud), ChokeLine_Density%Array(imud) ,ChokeLine_MudOrKick%Array(imud)
  1073. ! enddo
  1074. !END IF
  1075. !do imud=1, Ann_MudDischarged_Volume%Length()
  1076. ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  1077. !enddo
  1078. !
  1079. !write(*,*) 'Ann cap=' , sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections))
  1080. ! write(*,*) 'Ann mud sum vol=' , sum(Ann_MudDischarged_Volume%Array(:))
  1081. !write(*,*) '==after sorting chokeline'
  1082. end subroutine ChokeLineMud
  1083. subroutine Choke_GasSound ! is called in subroutine CirculationCodeSelect
  1084. use CSounds
  1085. !Use GeoElements_FluidModule
  1086. !USE CMudPropertiesVariables
  1087. USE MudSystemVARIABLES
  1088. !USE Pumps_VARIABLES
  1089. !!USE CHOKEVARIABLES
  1090. !!USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure
  1091. !!use CManifolds
  1092. !use CDrillWatchVariables
  1093. !!use CHOKEVARIABLES
  1094. !!use CChokeManifoldVariables
  1095. !use CTanksVariables, TripTankVolume2 => TripTankVolume, TripTankDensity2 => TripTankDensity
  1096. !USE sROP_Other_Variables
  1097. !USE sROP_Variables
  1098. !Use KickVariables
  1099. !USE PressureDisplayVARIABLES
  1100. !Use CError
  1101. !Use , intrinsic :: IEEE_Arithmetic
  1102. if ( MudSystem%ChokeLine_MudOrKick%Last() > 0 .AND. MudSystem%WellToChokeManifoldOpen == .true.) then
  1103. !WellToChokeManifoldWasOpen
  1104. MudSystem%SoundGasThroughChoke = 100 !100:chon dar adadhaye kamtar az 100 seda ghaat mishavad. eslah shavad.5.8.98 !int (min(ChokeLineFlowRate/2. , 100.))
  1105. print* , 'SoundGasThroughChoke1=', MudSystem%SoundGasThroughChoke
  1106. !WRITE (*,*) 'WellToChokeManifoldWasOpen-Sound', WellToChokeManifoldWasOpen
  1107. WRITE (*,*) 'WellToChokeManifoldOpen', MudSystem%WellToChokeManifoldOpen
  1108. else
  1109. MudSystem%SoundGasThroughChoke = 0
  1110. print* , 'SoundGasThroughChoke2=', MudSystem%SoundGasThroughChoke
  1111. endif
  1112. !print* , 'SoundGasThroughChoke3=', SoundGasThroughChoke
  1113. call SetSoundGasThroughChoke(MudSystem%SoundGasThroughChoke)
  1114. end subroutine Choke_GasSound