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.
 
 
 
 
 
 

532 rivejä
33 KiB

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