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.
 
 
 
 
 
 

517 lines
29 KiB

  1. SUBROUTINE Utube2_and_TripIn ! is called in subroutine CirculationCodeSelect annulus to string
  2. Use UTUBEVARS
  3. Use GeoElements_FluidModule
  4. USE CMudPropertiesVariables
  5. USE MudSystemVARIABLES
  6. USE Pumps_VARIABLES
  7. use CDrillWatchVariables
  8. !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
  9. Use CShoeVariables
  10. implicit none
  11. write(*,*) 'Utube2 code'
  12. !===========================================================WELL============================================================
  13. !===========================================================WELL============================================================
  14. UtubeMode2Activated= .true.
  15. write(*,*) 'QUtubeOutput=' , QUtubeOutput
  16. !QUTubeInput=5000.
  17. StringFlowRate= QUtubeOutput ! (gpm)
  18. AnnulusFlowRate= QUtubeOutput
  19. StringFlowRateFinal= StringFlowRate
  20. AnnulusFlowRateFinal= AnnulusFlowRate
  21. !===========================================
  22. if (FirstSetUtube2==0) then
  23. ! call St_MudDischarged_Volume%AddToFirst (REAL(sum(F_Interval(1:F_StringIntervalCounts)%Volume))) !startup initial
  24. ! call St_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(1))
  25. ! call St_Mud_Backhead_section%AddToFirst (1)
  26. ! call St_Mud_Forehead_X%AddToFirst (Xend_PipeSection(F_StringIntervalCounts))
  27. ! call St_Mud_Forehead_section%AddToFirst (F_StringIntervalCounts)
  28. ! call St_Density%AddToFirst (REAL(ActiveDensity)) ! initial(ppg)
  29. ! call St_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  30. ! call St_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  31. !
  32. ! call Ann_MudDischarged_Volume%AddToFirst (REAL(sum(F_Interval((F_StringIntervalCounts+F_BottomHoleIntervalCounts+1):F_IntervalsTotalCounts)%Volume))) !startup initial
  33. ! call Ann_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(F_StringIntervalCounts+1))
  34. ! call Ann_Mud_Backhead_section%AddToFirst (F_StringIntervalCounts+1)
  35. ! call Ann_Mud_Forehead_X%AddToFirst (Xend_PipeSection(NoPipeSections))
  36. ! call Ann_Mud_Forehead_section%AddToFirst (NoPipeSections)
  37. ! call Ann_Density%AddToFirst (REAL(ActiveDensity)) ! initial(ppg)
  38. ! call Ann_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  39. ! call Ann_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  40. !Hz_Density%Array(:)= 0.0
  41. !Hz_MudOrKick%Array(:)= 104
  42. Hz_Density_Utube= 0.0
  43. Hz_MudOrKick_Utube= 104
  44. FirstSetUtube2= 1
  45. endif
  46. !========================Horizontal PIPE ENTRANCE=================
  47. !if (SuctionDensity_Old >= (ActiveDensity+0.05) .or. SuctionDensity_Old <= (ActiveDensity-0.05)) then ! new mud is pumped
  48. ! !ImudCount= ImudCount+1
  49. ! !SuctionMud= ImudCount
  50. ! call Hz_Density%AddToFirst (REAL(ActiveDensity)) !ActiveDensity : badan in moteghayer bayad avaz beshe
  51. ! call Hz_MudDischarged_Volume%AddToFirst (0.0d0)
  52. ! call Hz_Mud_Forehead_X%AddToFirst (Xstart_PipeSection(1))
  53. ! call Hz_Mud_Forehead_section%AddToFirst (1)
  54. ! call Hz_Mud_Backhead_X%AddToFirst (Xstart_PipeSection(1))
  55. ! call Hz_Mud_Backhead_section%AddToFirst (1)
  56. ! call Hz_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  57. ! call Hz_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  58. ! call Hz_MudOrKick%AddToFirst (0)
  59. ! deltaV= 0.
  60. !
  61. ! SuctionDensity_Old= ActiveDensity
  62. !endif
  63. !========================Horizontal PIPE STRING=================
  64. !commented
  65. ! Hz_MudDischarged_Volume%Array(1)= Hz_MudDischarged_Volume%Array(1)+ ((StringFlowRate/60.)*DeltaT_Mudline) !(gal)
  66. !
  67. !imud=0
  68. ! do while (imud < Hz_Mud_Forehead_X%Length())
  69. ! imud = imud + 1
  70. !
  71. ! if (imud> 1) then
  72. ! Hz_Mud_Backhead_X%Array(imud)= Hz_Mud_Forehead_X%Array(imud-1)
  73. ! Hz_Mud_Backhead_section%Array(imud)= Hz_Mud_Forehead_section%Array(imud-1)
  74. ! endif
  75. !
  76. !
  77. ! DirectionCoef= (Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(Hz_Mud_Backhead_section%Array(imud))) &
  78. ! / ABS(Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))-Xstart_PipeSection(Hz_Mud_Backhead_section%Array(imud)))
  79. ! ! +1 for string , -1 for annulus
  80. !
  81. !
  82. ! Hz_EmptyVolume_inBackheadLocation%Array(imud)= DirectionCoef* (Xend_PipeSection(Hz_Mud_Backhead_section%Array(imud))- Hz_Mud_Backhead_X%Array(imud))* &
  83. ! Area_PipeSectionFt(Hz_Mud_Backhead_section%Array(imud)) !(ft^3)
  84. ! Hz_EmptyVolume_inBackheadLocation%Array(imud)= Hz_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948 ! ft^3 to gal
  85. !
  86. !
  87. ! if ( Hz_MudDischarged_Volume%Array(imud) <= Hz_EmptyVolume_inBackheadLocation%Array(imud)) then
  88. ! Hz_Mud_Forehead_section%Array(imud)= Hz_Mud_Backhead_section%Array(imud)
  89. ! Hz_Mud_Forehead_X%Array(imud)= Hz_Mud_Backhead_X%Array(imud)+ DirectionCoef*(Hz_MudDischarged_Volume%Array(imud)/7.48051948)/Area_PipeSectionFt(Hz_Mud_Backhead_section%Array(imud))
  90. ! ! 7.48051948 is for gal to ft^3
  91. ! else
  92. !
  93. ! isection= Hz_Mud_Backhead_section%Array(imud)+1
  94. ! Hz_RemainedVolume_in_LastSection%Array(imud)= Hz_MudDischarged_Volume%Array(imud)- Hz_EmptyVolume_inBackheadLocation%Array(imud)
  95. !
  96. ! do
  97. ! if (isection > 1) then ! (horizontal pipe exit)
  98. ! Hz_MudDischarged_Volume%Array(imud)= Hz_MudDischarged_Volume%Array(imud)- Hz_RemainedVolume_in_LastSection%Array(imud)
  99. ! Hz_Mud_Forehead_X%Array(imud)= Xend_PipeSection(1)
  100. ! Hz_Mud_Forehead_section%Array(imud)= 1
  101. ! if (Hz_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
  102. ! call Hz_MudDischarged_Volume%Remove (imud)
  103. ! call Hz_Mud_Backhead_X%Remove (imud)
  104. ! call Hz_Mud_Backhead_section%Remove (imud)
  105. ! call Hz_Mud_Forehead_X%Remove (imud)
  106. ! call Hz_Mud_Forehead_section%Remove (imud)
  107. ! call Hz_Density%Remove (imud)
  108. ! call Hz_RemainedVolume_in_LastSection%Remove (imud)
  109. ! call Hz_EmptyVolume_inBackheadLocation%Remove (imud)
  110. ! call Hz_MudOrKick%Remove (imud)
  111. ! endif
  112. ! exit
  113. ! endif
  114. !
  115. ! xx= Hz_RemainedVolume_in_LastSection%Array(imud)/ PipeSection_VolumeCapacity(isection) !(gal)
  116. !
  117. ! if (xx<= 1.0) then
  118. ! Hz_Mud_Forehead_section%Array(imud)= isection
  119. ! Hz_Mud_Forehead_X%Array(imud)= (xx * (Xend_PipeSection(isection)- Xstart_PipeSection(isection)))+ Xstart_PipeSection(isection)
  120. ! exit
  121. ! else
  122. ! Hz_RemainedVolume_in_LastSection%Array(imud)= Hz_RemainedVolume_in_LastSection%Array(imud)- PipeSection_VolumeCapacity(isection)
  123. ! isection= isection+ 1
  124. !
  125. !
  126. ! endif
  127. !
  128. ! enddo
  129. !
  130. ! endif
  131. !
  132. ! enddo
  133. !commented
  134. !========================Horizontal PIPE END=================
  135. !========================ANNULUS ENTRANCE====================
  136. if (ABS(AnnulusSuctionDensity_Old - Hz_Density_Utube) >= DensityMixTol ) then ! new mud is pumped
  137. call Ann_Density%Add (Hz_Density_Utube)
  138. call Ann_MudDischarged_Volume%Add (0.0d0)
  139. call Ann_Mud_Forehead_X%Add (Xend_PipeSection(NoPipeSections))
  140. call Ann_Mud_Forehead_section%Add (NoPipeSections)
  141. call Ann_Mud_Backhead_X%Add (Xstart_PipeSection(NoPipeSections))
  142. call Ann_Mud_Backhead_section%Add (NoPipeSections)
  143. call Ann_RemainedVolume_in_LastSection%Add (0.0d0)
  144. call Ann_EmptyVolume_inBackheadLocation%Add (0.0d0)
  145. call Ann_MudOrKick%Add (Hz_MudOrKick_Utube) ! Hz_MudOrKick%Last() = 104
  146. call Ann_CuttingMud%Add (0)
  147. AnnulusSuctionDensity_Old= Hz_Density_Utube
  148. endif
  149. !========================ANNULUS====================
  150. Ann_MudDischarged_Volume%Array(Ann_MudDischarged_Volume%Length())= Ann_MudDischarged_Volume%Last()+ ((AnnulusFlowRate/60.)*DeltaT_Mudline) !(gal)
  151. imud= Ann_Mud_Forehead_X%Length() + 1
  152. do while (imud > 1)
  153. imud = imud - 1
  154. if (imud< Ann_Mud_Forehead_X%Length()) then
  155. Ann_Mud_Forehead_X%Array(imud)= Ann_Mud_Backhead_X%Array(imud+1)
  156. Ann_Mud_Forehead_section%Array(imud)= Ann_Mud_Backhead_section%Array(imud+1)
  157. endif
  158. ! <<< Fracture Shoe Lost
  159. IF ( ShoeLost .and. LostInTripOutIsDone== .false. .and. Shoe%ShoeDepth < Ann_Mud_Backhead_X%Array(imud) .and. Shoe%ShoeDepth >= Ann_Mud_Forehead_X%Array(imud) ) then
  160. !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline)
  161. Ann_MudDischarged_Volume%Array(imud)= Ann_MudDischarged_Volume%Array(imud)-((Qlost/60.0d0)*DeltaT_Mudline) !(gal)
  162. if (Ann_MudDischarged_Volume%Array(imud) < 0.0) then
  163. !write(*,*) 'mud is removed by shoe lost, imud=' , imud
  164. call RemoveAnnulusMudArrays(imud)
  165. imud= imud-1
  166. cycle
  167. endif
  168. ENDIF
  169. ! Fracture Shoe Lost >>>
  170. DirectionCoef= (Xend_PipeSection(Ann_Mud_Forehead_section%Array(imud))-Xstart_PipeSection(Ann_Mud_Forehead_section%Array(imud))) &
  171. / ABS(Xend_PipeSection(Ann_Mud_Forehead_section%Array(imud))-Xstart_PipeSection(Ann_Mud_Forehead_section%Array(imud)))
  172. ! +1 for string , -1 for annulus
  173. Ann_EmptyVolume_inBackheadLocation%Array(imud)= DirectionCoef* (Ann_Mud_Forehead_X%Array(imud)- Xstart_PipeSection(Ann_Mud_Forehead_section%Array(imud)))* &
  174. Area_PipeSectionFt(Ann_Mud_Forehead_section%Array(imud)) !(ft^3)
  175. Ann_EmptyVolume_inBackheadLocation%Array(imud)= Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  176. if ( Ann_MudDischarged_Volume%Array(imud) <= Ann_EmptyVolume_inBackheadLocation%Array(imud)) then
  177. Ann_Mud_Backhead_section%Array(imud)= Ann_Mud_Forehead_section%Array(imud)
  178. Ann_Mud_Backhead_X%Array(imud)= Ann_Mud_Forehead_X%Array(imud)- DirectionCoef*(Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/Area_PipeSectionFt(Ann_Mud_Forehead_section%Array(imud))
  179. ! 7.48051948 is for gal to ft^3
  180. else
  181. isection= Ann_Mud_Forehead_section%Array(imud)-1
  182. Ann_RemainedVolume_in_LastSection%Array(imud)= Ann_MudDischarged_Volume%Array(imud)- Ann_EmptyVolume_inBackheadLocation%Array(imud)
  183. do
  184. if (isection < F_StringIntervalCounts+1) then ! last pipe section(well exit) F_StringIntervalCounts+1 is the first section in Annulus
  185. Ann_MudDischarged_Volume%Array(imud)= Ann_MudDischarged_Volume%Array(imud)- Ann_RemainedVolume_in_LastSection%Array(imud)
  186. Ann_Mud_Backhead_X%Array(imud)= Xstart_PipeSection(F_StringIntervalCounts+1)
  187. Ann_Mud_Backhead_section%Array(imud)= F_StringIntervalCounts+1
  188. if (Ann_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
  189. call RemoveAnnulusMudArrays(imud)
  190. endif
  191. exit
  192. endif
  193. xx= Ann_RemainedVolume_in_LastSection%Array(imud)/ PipeSection_VolumeCapacity(isection) !(gal)
  194. if (xx<= 1.0) then
  195. Ann_Mud_Backhead_section%Array(imud)= isection
  196. Ann_Mud_Backhead_X%Array(imud)= (xx * (Xstart_PipeSection(isection)- Xend_PipeSection(isection)))+ Xend_PipeSection(isection)
  197. exit
  198. else
  199. Ann_RemainedVolume_in_LastSection%Array(imud)= Ann_RemainedVolume_in_LastSection%Array(imud)- PipeSection_VolumeCapacity(isection)
  200. isection= isection- 1
  201. endif
  202. enddo
  203. endif
  204. enddo
  205. !========================ANNULUS END=================
  206. !========================== tripping in for OP remove ===============================
  207. !if (DeltaVolumeOp>0. .and. DeltaVolumeOp< Op_MudDischarged_Volume%Last()) then
  208. ! Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length())= Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()) - DeltaVolumeOp
  209. !else
  210. ! Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()-1)= Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()-1) - (DeltaVolumeOp-Op_MudDischarged_Volume%Last())
  211. !
  212. ! call Op_MudDischarged_Volume%Remove (Op_MudDischarged_Volume%Length())
  213. ! call Op_Mud_Backhead_X%Remove (Op_MudDischarged_Volume%Length())
  214. ! call Op_Mud_Backhead_section%Remove (Op_MudDischarged_Volume%Length())
  215. ! call Op_Mud_Forehead_X%Remove (Op_MudDischarged_Volume%Length())
  216. ! call Op_Mud_Forehead_section%Remove (Op_MudDischarged_Volume%Length())
  217. ! call Op_Density%Remove (Op_MudDischarged_Volume%Length())
  218. ! call Op_RemainedVolume_in_LastSection%Remove (Op_MudDischarged_Volume%Length())
  219. ! call Op_EmptyVolume_inBackheadLocation%Remove (Op_MudDischarged_Volume%Length())
  220. ! call Op_MudOrKick%Remove (Op_MudDischarged_Volume%Length())
  221. !endif
  222. !
  223. !============================= Bottom Hole ==============================
  224. !Op_MudDischarged_Volume%Array(1)= Op_MudDischarged_Volume%Array(1)+ ((GasKickPumpFlowRate/60.)*DeltaT_Mudline) !(gal) due to KickFlux
  225. imud=0
  226. do while (imud < Op_Mud_Forehead_X%Length())
  227. imud = imud + 1
  228. if (imud> 1) then
  229. Op_Mud_Backhead_X%Array(imud)= Op_Mud_Forehead_X%Array(imud-1)
  230. Op_Mud_Backhead_section%Array(imud)= Op_Mud_Forehead_section%Array(imud-1)
  231. endif
  232. DirectionCoef= (Xend_OpSection(Op_Mud_Backhead_section%Array(imud))-Xstart_OpSection(Op_Mud_Backhead_section%Array(imud))) &
  233. / ABS(Xend_OpSection(Op_Mud_Backhead_section%Array(imud))-Xstart_OpSection(Op_Mud_Backhead_section%Array(imud)))
  234. ! +1 for string , -1 for annulus
  235. Op_EmptyVolume_inBackheadLocation%Array(imud)= DirectionCoef* (Xend_OpSection(Op_Mud_Backhead_section%Array(imud))- Op_Mud_Backhead_X%Array(imud))* &
  236. Area_OpSectionFt(Op_Mud_Backhead_section%Array(imud)) !(ft^3)
  237. Op_EmptyVolume_inBackheadLocation%Array(imud)= Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  238. if ( Op_MudDischarged_Volume%Array(imud) <= Op_EmptyVolume_inBackheadLocation%Array(imud)) then
  239. Op_Mud_Forehead_section%Array(imud)= Op_Mud_Backhead_section%Array(imud)
  240. Op_Mud_Forehead_X%Array(imud)= Op_Mud_Backhead_X%Array(imud)+ DirectionCoef*(Op_MudDischarged_Volume%Array(imud)/7.48051948d0)/Area_OpSectionFt(Op_Mud_Backhead_section%Array(imud))
  241. ! 7.48051948 is for gal to ft^3
  242. else
  243. isection= Op_Mud_Backhead_section%Array(imud)+1
  244. Op_RemainedVolume_in_LastSection%Array(imud)= Op_MudDischarged_Volume%Array(imud)- Op_EmptyVolume_inBackheadLocation%Array(imud)
  245. do
  246. if (isection > F_BottomHoleIntervalCounts) then ! last pipe section(well exit)
  247. if( imud==1) KickDeltaVinAnnulus= Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space
  248. Op_MudDischarged_Volume%Array(imud)= Op_MudDischarged_Volume%Array(imud)- Op_RemainedVolume_in_LastSection%Array(imud)
  249. Op_Mud_Forehead_X%Array(imud)= Xend_OpSection(F_BottomHoleIntervalCounts)
  250. Op_Mud_Forehead_section%Array(imud)= F_BottomHoleIntervalCounts
  251. if (Op_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the well
  252. call RemoveOpMudArrays(imud)
  253. endif
  254. exit
  255. endif
  256. xx= Op_RemainedVolume_in_LastSection%Array(imud)/ OpSection_VolumeCapacity(isection) !(gal)
  257. if (xx<= 1.0) then
  258. Op_Mud_Forehead_section%Array(imud)= isection
  259. Op_Mud_Forehead_X%Array(imud)= (xx * (Xend_OpSection(isection)- Xstart_OpSection(isection)))+ Xstart_OpSection(isection)
  260. exit
  261. else
  262. Op_RemainedVolume_in_LastSection%Array(imud)= Op_RemainedVolume_in_LastSection%Array(imud)- OpSection_VolumeCapacity(isection)
  263. isection= isection+ 1
  264. endif
  265. enddo
  266. endif
  267. if (Op_Mud_Forehead_X%Array(imud)== Xend_OpSection(F_BottomHoleIntervalCounts)) then
  268. totalLength = Op_MudDischarged_Volume%Length()
  269. do while(imud < totalLength)
  270. !imud = imud + 1
  271. call RemoveOpMudArrays(totalLength)
  272. totalLength = totalLength - 1
  273. enddo
  274. exit !
  275. endif
  276. !WRITE(*,*) imud,'Op_MudDischarged_Volume%Array(imud)' , Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud)
  277. enddo
  278. !write(*,*) 'Op_Mud_Forehead_X%Length()' , Op_Mud_Forehead_X%Length()
  279. !
  280. ! WRITE(*,*) 'Xend_PipeSection(F_StringIntervalCounts)' , Xend_PipeSection(F_StringIntervalCounts)
  281. ! WRITE(*,*) 'Op_Mud_Backhead_X%Array(1)' , Op_Mud_Backhead_X%Array(1)
  282. ! WRITE(*,*) 'Op_Mud_Forehead_X%Array(1)' , Op_Mud_Forehead_X%Array(1)
  283. ! WRITE(*,*) 'Op_Mud_Backhead_X%Array(2)' , Op_Mud_Backhead_X%Array(2)
  284. ! WRITE(*,*) 'Op_Mud_Forehead_X%Array(2)' , Op_Mud_Forehead_X%Array(2)
  285. !========================Bottom Hole END=================
  286. ! NO KICK
  287. !========================STRING ENTRANCE=================
  288. if ((ABS(St_Density%Last() - Ann_Density%First()) >= DensityMixTol) .OR. (DeltaVolumeOp == 0.0 .and. St_Density%Last() /= Ann_Density%Array(1) .and. StringFlowRate/=0.0d0)) then ! new mud is pumped
  289. !if ((ABS(StringDensity_Old - Ann_Density%First()) >= DensityMixTol) .OR. (DeltaVolumeOp == 0.0 .and. St_Density%Last() /= Ann_Density%Array(1) .and. StringFlowRate/=0.0d0)) then ! new mud is pumped
  290. call St_Density%Add (Ann_Density%First())
  291. call St_MudDischarged_Volume%Add (0.0d0)
  292. call St_Mud_Forehead_X%Add (Xend_PipeSection(F_StringIntervalCounts))
  293. call St_Mud_Forehead_section%Add (F_StringIntervalCounts)
  294. call St_Mud_Backhead_X%Add (Xstart_PipeSection(F_StringIntervalCounts))
  295. call St_Mud_Backhead_section%Add (F_StringIntervalCounts)
  296. call St_RemainedVolume_in_LastSection%Add (0.0d0)
  297. call St_EmptyVolume_inBackheadLocation%Add (0.0d0)
  298. call St_MudOrKick%Add (0)
  299. !StringDensity_Old= Ann_Density%First()
  300. MudIsChanged= .true.
  301. endif
  302. St_MudDischarged_Volume%Array(St_MudDischarged_Volume%Length())= St_MudDischarged_Volume%Last()+ ((StringFlowRate/60.0d0)*DeltaT_Mudline) !(gal)
  303. !========================Tripping In====================
  304. !write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp
  305. write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp
  306. if (DeltaVolumeOp > 0.0 .and. MudIsChanged== .false.) then !.and. DrillingMode== .false.) then ! trip in mode(loole paeen)
  307. !write(*,*) 'Tripping In'
  308. NewDensity= (Ann_Density%First()*((StringFlowRate/60.0d0)*DeltaT_Mudline)+Op_Density%Last()*DeltaVolumeOp)/(((StringFlowRate/60.0d0)*DeltaT_Mudline)+DeltaVolumeOp)
  309. NewVolume= ((StringFlowRate/60.0d0)*DeltaT_Mudline)+DeltaVolumeOp
  310. !write(*,*) 'St_MudDischarged_Volume%Last()=', St_MudDischarged_Volume%Last(), 'NewVolume=', NewVolume
  311. if (abs(St_Density%Last()-NewDensity)< DensityMixTol) then ! .OR. (St_MudDischarged_Volume%Last()< 42.) ) then !+ NewVolume)< 42.) then ! 1-Pockets are Merged
  312. St_Density%Array(St_Density%Length())= (St_Density%Last()*St_MudDischarged_Volume%Last()+NewDensity*NewVolume)/(St_MudDischarged_Volume%Last()+NewVolume)
  313. St_MudDischarged_Volume%Array(St_Density%Length())= St_MudDischarged_Volume%Last()+DeltaVolumeOp
  314. St_Mud_Forehead_X%Array(St_Density%Length())= (Xend_PipeSection(F_StringIntervalCounts))
  315. St_Mud_Forehead_section%Array(St_Density%Length())= (F_StringIntervalCounts)
  316. St_Mud_Backhead_X%Array(St_Density%Length())= (Xstart_PipeSection(F_StringIntervalCounts))
  317. St_Mud_Backhead_section%Array(St_Density%Length())= (F_StringIntervalCounts)
  318. St_RemainedVolume_in_LastSection%Array(St_Density%Length())= (0.0d0)
  319. St_EmptyVolume_inBackheadLocation%Array(St_Density%Length())= (0.0d0)
  320. else ! 2-Merging conditions are not meeted, so new pocket
  321. call St_Density%Add (NewDensity)
  322. call St_MudDischarged_Volume%Add (NewVolume)
  323. call St_Mud_Forehead_X%Add (Xend_PipeSection(F_StringIntervalCounts))
  324. call St_Mud_Forehead_section%Add (F_StringIntervalCounts)
  325. call St_Mud_Backhead_X%Add (Xstart_PipeSection(F_StringIntervalCounts))
  326. call St_Mud_Backhead_section%Add (F_StringIntervalCounts)
  327. call St_RemainedVolume_in_LastSection%Add (0.0d0)
  328. call St_EmptyVolume_inBackheadLocation%Add (0.0d0)
  329. call St_MudOrKick%Add (0)
  330. endif
  331. elseif (DeltaVolumeOp > 0.0 .and. MudIsChanged== .true.) then
  332. St_Density%Array(St_Density%Length())= NewDensity
  333. St_MudDischarged_Volume%Array(St_Density%Length())= NewVolume
  334. St_Mud_Forehead_X%Array(St_Density%Length())= (Xend_PipeSection(F_StringIntervalCounts))
  335. St_Mud_Forehead_section%Array(St_Density%Length())= (F_StringIntervalCounts)
  336. St_Mud_Backhead_X%Array(St_Density%Length())= (Xstart_PipeSection(F_StringIntervalCounts))
  337. St_Mud_Backhead_section%Array(St_Density%Length())= (F_StringIntervalCounts)
  338. St_RemainedVolume_in_LastSection%Array(St_Density%Length())= (0.0d0)
  339. St_EmptyVolume_inBackheadLocation%Array(St_Density%Length())= (0.0d0)
  340. endif
  341. !========================Tripping In - End====================
  342. !======================== STRING ====================
  343. MudIsChanged= .false.
  344. imud= St_Mud_Forehead_X%Length() + 1
  345. do while (imud > 1)
  346. imud = imud - 1
  347. if (imud< St_Mud_Forehead_X%Length()) then
  348. St_Mud_Forehead_X%Array(imud)= St_Mud_Backhead_X%Array(imud+1)
  349. St_Mud_Forehead_section%Array(imud)= St_Mud_Backhead_section%Array(imud+1)
  350. endif
  351. DirectionCoef= (Xend_PipeSection(St_Mud_Forehead_section%Array(imud))-Xstart_PipeSection(St_Mud_Forehead_section%Array(imud))) &
  352. / ABS(Xend_PipeSection(St_Mud_Forehead_section%Array(imud))-Xstart_PipeSection(St_Mud_Forehead_section%Array(imud)))
  353. ! +1 for string , -1 for annulus
  354. St_EmptyVolume_inBackheadLocation%Array(imud)= DirectionCoef* (St_Mud_Forehead_X%Array(imud)- Xstart_PipeSection(St_Mud_Forehead_section%Array(imud)))* &
  355. Area_PipeSectionFt(St_Mud_Backhead_section%Array(imud)) !(ft^3)
  356. St_EmptyVolume_inBackheadLocation%Array(imud)= St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  357. if ( St_MudDischarged_Volume%Array(imud) <= St_EmptyVolume_inBackheadLocation%Array(imud)) then
  358. St_Mud_Backhead_section%Array(imud)= St_Mud_Forehead_section%Array(imud)
  359. St_Mud_Backhead_X%Array(imud)= St_Mud_Forehead_X%Array(imud)- DirectionCoef*(St_MudDischarged_Volume%Array(imud)/7.48051948d0)/Area_PipeSectionFt(St_Mud_Forehead_section%Array(imud))
  360. ! 7.48051948 is for gal to ft^3
  361. else
  362. isection= St_Mud_Backhead_section%Array(imud)-1
  363. St_RemainedVolume_in_LastSection%Array(imud)= St_MudDischarged_Volume%Array(imud)- St_EmptyVolume_inBackheadLocation%Array(imud)
  364. do
  365. if (isection < 1) then ! last pipe section(string exit)
  366. St_MudDischarged_Volume%Array(imud)= St_MudDischarged_Volume%Array(imud)- St_RemainedVolume_in_LastSection%Array(imud)
  367. St_Mud_Backhead_X%Array(imud)= Xstart_PipeSection(2)
  368. St_Mud_Backhead_section%Array(imud)= 2
  369. if (St_MudDischarged_Volume%Array(imud)<= 0.0d0) then ! imud is completely exited form the string
  370. call RemoveStringMudArrays(imud)
  371. endif
  372. exit
  373. endif
  374. xx= St_RemainedVolume_in_LastSection%Array(imud)/ PipeSection_VolumeCapacity(isection) !(gal)
  375. if (xx<= 1.0) then
  376. St_Mud_Backhead_section%Array(imud)= isection
  377. St_Mud_Backhead_X%Array(imud)= (xx * (Xstart_PipeSection(isection)- Xend_PipeSection(isection)))+ Xend_PipeSection(isection)
  378. exit
  379. else
  380. St_RemainedVolume_in_LastSection%Array(imud)= St_RemainedVolume_in_LastSection%Array(imud)- PipeSection_VolumeCapacity(isection)
  381. isection= isection- 1
  382. endif
  383. enddo
  384. endif
  385. enddo
  386. !========================STRING END=================
  387. end subroutine Utube2_and_TripIn