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 lines
34 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. MudSystemDotUtubeMode1Activated= .true.
  17. !write(*,*) 'QUTubeInput=' , QUTubeInput
  18. !Qinput=5000.
  19. MudSystemDotStringFlowRate= QUTubeInput ! (gpm)
  20. MudSystemDotAnnulusFlowRate= QUTubeInput
  21. MudSystemDotStringFlowRateFinal= MudSystemDotStringFlowRate
  22. MudSystemDotAnnulusFlowRateFinal= MudSystemDotAnnulusFlowRate
  23. !===========================================
  24. if (MudSystemDotFirstSetUtube1==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 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. MudSystemDotHz_Density_Utube= 0.0
  45. MudSystemDotHz_MudOrKick_Utube= 104
  46. MudSystemDotFirstSetUtube1= 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)+ ((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) St_Density%Length()=' , St_Density%Length()
  139. if (ABS(St_Density%First() - MudSystemDotHz_Density_Utube) >= MudSystemDotDensityMixTol) then ! new mud is pumped
  140. call St_Density%AddToFirst (MudSystemDotHz_Density_Utube)
  141. call MudSystemDotSt_MudDischarged_Volume%AddToFirst (0.0d0)
  142. call MudSystemDotSt_Mud_Forehead_X%AddToFirst (MudSystemDotXstart_PipeSection(2))
  143. call St_Mud_Forehead_section%AddToFirst (2)
  144. call MudSystemDotSt_Mud_Backhead_X%AddToFirst (MudSystemDotXstart_PipeSection(2))
  145. call St_Mud_Backhead_section%AddToFirst (2)
  146. call MudSystemDotSt_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  147. call MudSystemDotSt_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  148. call St_MudOrKick%AddToFirst (MudSystemDotHz_MudOrKick_Utube) ! Hz_MudOrKick%Last() = 104
  149. !StringDensity_Old= Hz_Density_Utube
  150. endif
  151. !write(*,*) 'b) St_Density%Length()=' , St_Density%Length()
  152. !write(*,*) 'b) St_Density%Array(1)=' , St_Density%Array(1)
  153. !write(*,*) 'b) St_MudOrKick%Array(1)=' , St_MudOrKick%Array(1)
  154. !========================STRING=================
  155. !WRITE (*,*) 'Utube1 StringFlowRate', StringFlowRate
  156. MudSystemDotSt_MudDischarged_Volume%Array(1)= MudSystemDotSt_MudDischarged_Volume%Array(1)+ ((MudSystemDotStringFlowRate/60.d0)*DeltaT_Mudline) !(gal)
  157. MudSystemDotimud=0
  158. do while (MudSystemDotimud < MudSystemDotSt_Mud_Forehead_X%Length())
  159. MudSystemDotimud = MudSystemDotimud + 1
  160. if (MudSystemDotimud> 1) then
  161. MudSystemDotSt_Mud_Backhead_X%Array(MudSystemDotimud)= MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud-1)
  162. St_Mud_Backhead_section%Array(MudSystemDotimud)= St_Mud_Forehead_section%Array(MudSystemDotimud-1)
  163. endif
  164. MudSystemDotDirectionCoef= (MudSystemDotXend_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))) &
  165. / ABS(MudSystemDotXend_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud)))
  166. ! +1 for string , -1 for annulus
  167. MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotDirectionCoef* (MudSystemDotXend_PipeSection(St_Mud_Backhead_section%Array(MudSystemDotimud))- MudSystemDotSt_Mud_Backhead_X%Array(MudSystemDotimud))* &
  168. MudSystemDotArea_PipeSectionFt(St_Mud_Backhead_section%Array(MudSystemDotimud)) !(ft^3)
  169. MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 7.48051948d0 ! ft^3 to gal
  170. if ( MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud) <= MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
  171. St_Mud_Forehead_section%Array(MudSystemDotimud)= St_Mud_Backhead_section%Array(MudSystemDotimud)
  172. MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotSt_Mud_Backhead_X%Array(MudSystemDotimud)+ MudSystemDotDirectionCoef*(MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_PipeSectionFt(St_Mud_Backhead_section%Array(MudSystemDotimud))
  173. ! 7.48 is for gal to ft^3
  174. else
  175. MudSystemDotisection= St_Mud_Backhead_section%Array(MudSystemDotimud)+1
  176. MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotSt_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
  177. do
  178. if (MudSystemDotisection > F_StringIntervalCounts) then ! last pipe section(string exit) F_StringIntervalCounts includes Horizontal line
  179. MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
  180. MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotXend_PipeSection(F_StringIntervalCounts)
  181. St_Mud_Forehead_section%Array(MudSystemDotimud)= F_StringIntervalCounts
  182. if (MudSystemDotSt_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the string
  183. call RemoveStringMudArrays(MudSystemDotimud)
  184. endif
  185. exit
  186. endif
  187. MudSystemDotxx= MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection) !(gal)
  188. if (MudSystemDotxx<= 1.0) then
  189. St_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
  190. MudSystemDotSt_Mud_Forehead_X%Array(MudSystemDotimud)= (MudSystemDotxx * (MudSystemDotXend_PipeSection(MudSystemDotisection)- MudSystemDotXstart_PipeSection(MudSystemDotisection)))+ MudSystemDotXstart_PipeSection(MudSystemDotisection)
  191. exit
  192. else
  193. MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotSt_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection)
  194. MudSystemDotisection= MudSystemDotisection+ 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. MudSystemDotimud=0
  220. do while (MudSystemDotimud < MudSystemDotOp_Mud_Forehead_X%Length())
  221. MudSystemDotimud = MudSystemDotimud + 1
  222. if (MudSystemDotimud> 1) then
  223. MudSystemDotOp_Mud_Backhead_X%Array(MudSystemDotimud)= MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud-1)
  224. Op_Mud_Backhead_section%Array(MudSystemDotimud)= Op_Mud_Forehead_section%Array(MudSystemDotimud-1)
  225. endif
  226. MudSystemDotDirectionCoef= (MudSystemDotXend_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))) &
  227. / ABS(MudSystemDotXend_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud)))
  228. ! +1 for string , -1 for annulus
  229. MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotDirectionCoef* (MudSystemDotXend_OpSection(Op_Mud_Backhead_section%Array(MudSystemDotimud))- MudSystemDotOp_Mud_Backhead_X%Array(MudSystemDotimud))* &
  230. MudSystemDotArea_OpSectionFt(Op_Mud_Backhead_section%Array(MudSystemDotimud)) !(ft^3)
  231. MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 7.48051948d0 ! ft^3 to gal
  232. if ( MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud) <= MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
  233. Op_Mud_Forehead_section%Array(MudSystemDotimud)= Op_Mud_Backhead_section%Array(MudSystemDotimud)
  234. MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotOp_Mud_Backhead_X%Array(MudSystemDotimud)+ MudSystemDotDirectionCoef*(MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_OpSectionFt(Op_Mud_Backhead_section%Array(MudSystemDotimud))
  235. ! 7.48 is for gal to ft^3
  236. else
  237. MudSystemDotisection= Op_Mud_Backhead_section%Array(MudSystemDotimud)+1
  238. MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotOp_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
  239. do
  240. if (MudSystemDotisection > F_BottomHoleIntervalCounts) then ! last pipe section(well exit)
  241. if( MudSystemDotimud==1) MudSystemDotKickDeltaVinAnnulus= MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud) ! Kick enters Annulus space
  242. MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)- MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
  243. MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotXend_OpSection(F_BottomHoleIntervalCounts)
  244. Op_Mud_Forehead_section%Array(MudSystemDotimud)= F_BottomHoleIntervalCounts
  245. if (MudSystemDotOp_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the well
  246. call RemoveOpMudArrays(MudSystemDotimud)
  247. endif
  248. exit
  249. endif
  250. MudSystemDotxx= MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotOpSection_VolumeCapacity(MudSystemDotisection) !(gal)
  251. if (MudSystemDotxx<= 1.0) then
  252. Op_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
  253. MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)= (MudSystemDotxx * (MudSystemDotXend_OpSection(MudSystemDotisection)- MudSystemDotXstart_OpSection(MudSystemDotisection)))+ MudSystemDotXstart_OpSection(MudSystemDotisection)
  254. exit
  255. else
  256. MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotOp_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotOpSection_VolumeCapacity(MudSystemDotisection)
  257. MudSystemDotisection= MudSystemDotisection+ 1
  258. endif
  259. enddo
  260. endif
  261. if (MudSystemDotOp_Mud_Forehead_X%Array(MudSystemDotimud)== MudSystemDotXend_OpSection(F_BottomHoleIntervalCounts)) then
  262. MudSystemDottotalLength = MudSystemDotOp_MudDischarged_Volume%Length()
  263. do while(MudSystemDotimud < MudSystemDottotalLength)
  264. !imud = imud + 1
  265. call RemoveOpMudArrays(MudSystemDottotalLength)
  266. MudSystemDottotalLength = MudSystemDottotalLength - 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 (MudSystemDotiLoc == 1) then
  281. MudSystemDotMudSection= F_StringIntervalCounts+1
  282. MudSystemDotBackheadX= MudSystemDotXstart_PipeSection(F_StringIntervalCounts+1)
  283. elseif (MudSystemDotiLoc == 2) then
  284. MudSystemDotMudSection= MudSystemDotKick_Forehead_section
  285. MudSystemDotBackheadX= MudSystemDotKick_Forehead_X
  286. endif
  287. !========================ANNULUS ENTRANCE====================
  288. !write(*,*) 'iloc=====' , iLoc
  289. if ((ABS(AnnulusSuctionDensity_Old - St_Density%Last()) >= MudSystemDotDensityMixTol) .OR. (MudSystemDotDeltaVolumeOp == 0.0 .and. ABS(Ann_Density%Array(MudSystemDotiLoc)-St_Density%Last())>=MudSystemDotDensityMixTol .and. MudSystemDotAnnulusFlowRate/=0.0d0) ) then ! new mud is pumped
  290. call Ann_Density%AddTo (MudSystemDotiLoc,St_Density%Last())
  291. call MudSystemDotAnn_MudDischarged_Volume%AddTo (MudSystemDotiLoc,0.0d0)
  292. call Ann_Mud_Forehead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
  293. call Ann_Mud_Forehead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
  294. call Ann_Mud_Backhead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
  295. call Ann_Mud_Backhead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
  296. call Ann_RemainedVolume_in_LastSection%AddTo (MudSystemDotiLoc,0.0d0)
  297. call Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystemDotiLoc,0.0d0)
  298. call Ann_MudOrKick%AddTo (MudSystemDotiLoc,0)
  299. call Ann_CuttingMud%AddTo (MudSystemDotiLoc,0)
  300. AnnulusSuctionDensity_Old= St_Density%Last()
  301. MudSystemDotMudIsChanged= .true.
  302. endif
  303. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+ ((MudSystemDotAnnulusFlowRate/60.0d0)*DeltaT_Mudline) !(gal)
  304. !========================Tripping In====================
  305. !write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp
  306. if (MudSystemDotDeltaVolumeOp > 0.0 .and. MudSystemDotMudIsChanged== .false.) then !.and. DrillingMode== .false.) then ! trip in mode(loole paeen)
  307. !write(*,*) 'Tripping In'
  308. NewDensity= (St_Density%Last()*((MudSystemDotAnnulusFlowRate/60.)*DeltaT_Mudline)+MudSystemDotOp_Density%Last()*MudSystemDotDeltaVolumeOp)/(((MudSystemDotAnnulusFlowRate/60.0d0)*DeltaT_Mudline)+MudSystemDotDeltaVolumeOp)
  309. MudSystemDotNewVolume= ((MudSystemDotAnnulusFlowRate/60.)*DeltaT_Mudline)+MudSystemDotDeltaVolumeOp
  310. !write(*,*) 'Ann_MudDischarged_Volume%Array(1)=', Ann_MudDischarged_Volume%Array(1), 'NewVolume=', NewVolume
  311. if (abs(Ann_Density%Array(MudSystemDotiLoc)-NewDensity)< MudSystemDotDensityMixTol) then ! 1-Pockets are Merged - (ROP is 0)
  312. Ann_Density%Array(MudSystemDotiLoc)= (Ann_Density%Array(MudSystemDotiLoc)*MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+NewDensity*MudSystemDotNewVolume)/(MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotNewVolume)
  313. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)+MudSystemDotDeltaVolumeOp
  314. Ann_Mud_Forehead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
  315. Ann_Mud_Forehead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
  316. Ann_Mud_Backhead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
  317. Ann_Mud_Backhead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
  318. Ann_RemainedVolume_in_LastSection%Array(MudSystemDotiLoc)= (0.0d0)
  319. Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotiLoc)= (0.0d0)
  320. else ! 2-Merging conditions are not meeted, so new pocket
  321. call Ann_Density%AddTo (MudSystemDotiLoc,NewDensity)
  322. call MudSystemDotAnn_MudDischarged_Volume%AddTo (MudSystemDotiLoc,MudSystemDotNewVolume)
  323. call Ann_Mud_Forehead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
  324. call Ann_Mud_Forehead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
  325. call Ann_Mud_Backhead_X%AddTo (MudSystemDotiLoc,MudSystemDotBackheadX)
  326. call Ann_Mud_Backhead_section%AddTo (MudSystemDotiLoc,MudSystemDotMudSection)
  327. call Ann_RemainedVolume_in_LastSection%AddTo (MudSystemDotiLoc,0.0d0)
  328. call Ann_EmptyVolume_inBackheadLocation%AddTo (MudSystemDotiLoc,0.0d0)
  329. call Ann_MudOrKick%AddTo (MudSystemDotiLoc,0)
  330. call Ann_CuttingMud%AddTo (MudSystemDotiLoc,0)
  331. endif
  332. elseif (MudSystemDotDeltaVolumeOp > 0.0 .and. MudSystemDotMudIsChanged== .true. .and. Rate_of_Penetration==0.) then
  333. Ann_Density%Array(MudSystemDotiLoc)= NewDensity
  334. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotiLoc)= MudSystemDotNewVolume
  335. Ann_Mud_Forehead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
  336. Ann_Mud_Forehead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
  337. Ann_Mud_Backhead_X%Array(MudSystemDotiLoc)= MudSystemDotBackheadX
  338. Ann_Mud_Backhead_section%Array(MudSystemDotiLoc)= MudSystemDotMudSection
  339. Ann_RemainedVolume_in_LastSection%Array(MudSystemDotiLoc)= (0.0d0)
  340. Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotiLoc)= (0.0d0)
  341. endif
  342. !========================Tripping In - End====================
  343. !======================== ANNULUS ====================
  344. MudSystemDotMudIsChanged= .false.
  345. MudSystemDotimud= 0
  346. do while (MudSystemDotimud < Ann_Mud_Forehead_X%Length())
  347. MudSystemDotimud = MudSystemDotimud + 1
  348. if (MudSystemDotimud> 1) then
  349. Ann_Mud_Backhead_X%Array(MudSystemDotimud)= Ann_Mud_Forehead_X%Array(MudSystemDotimud-1)
  350. Ann_Mud_Backhead_section%Array(MudSystemDotimud)= Ann_Mud_Forehead_section%Array(MudSystemDotimud-1)
  351. endif
  352. ! <<< Fracture Shoe Lost
  353. IF ( MudSystemDotShoeLost .and. MudSystemDotLostInTripOutIsDone== .false. .and. Shoe%ShoeDepth < Ann_Mud_Backhead_X%Array(MudSystemDotimud) .and. Shoe%ShoeDepth >= Ann_Mud_Forehead_X%Array(MudSystemDotimud) ) then
  354. !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline)
  355. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)-((MudSystemDotQlost/60.0d0)*DeltaT_Mudline) !(gal)
  356. if (MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud) < 0.0) then
  357. !write(*,*) 'mud is removed by shoe lost, imud=' , imud
  358. call RemoveAnnulusMudArrays(MudSystemDotimud)
  359. MudSystemDotimud= MudSystemDotimud-1
  360. cycle
  361. endif
  362. ENDIF
  363. ! Fracture Shoe Lost >>>
  364. MudSystemDotDirectionCoef= (MudSystemDotXend_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))) &
  365. / ABS(MudSystemDotXend_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))-MudSystemDotXstart_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud)))
  366. ! +1 for string , -1 for annulus
  367. Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= MudSystemDotDirectionCoef* (MudSystemDotXend_PipeSection(Ann_Mud_Backhead_section%Array(MudSystemDotimud))- Ann_Mud_Backhead_X%Array(MudSystemDotimud))* &
  368. MudSystemDotArea_PipeSectionFt(Ann_Mud_Backhead_section%Array(MudSystemDotimud)) !(ft^3)
  369. Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)= Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)* 7.48051948d0 ! ft^3 to gal
  370. if ( MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud) <= Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)) then
  371. Ann_Mud_Forehead_section%Array(MudSystemDotimud)= Ann_Mud_Backhead_section%Array(MudSystemDotimud)
  372. Ann_Mud_Forehead_X%Array(MudSystemDotimud)= Ann_Mud_Backhead_X%Array(MudSystemDotimud)+ MudSystemDotDirectionCoef*(MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)/7.48051948d0)/MudSystemDotArea_PipeSectionFt(Ann_Mud_Backhead_section%Array(MudSystemDotimud))
  373. ! 7.48 is for gal to ft^3
  374. else
  375. MudSystemDotisection= Ann_Mud_Backhead_section%Array(MudSystemDotimud)+1
  376. Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)- Ann_EmptyVolume_inBackheadLocation%Array(MudSystemDotimud)
  377. do
  378. if (MudSystemDotisection > MudSystemDotNoPipeSections) then ! last pipe section(well exit)
  379. MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)= MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)- Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)
  380. Ann_Mud_Forehead_X%Array(MudSystemDotimud)= MudSystemDotXend_PipeSection(MudSystemDotNoPipeSections)
  381. Ann_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotNoPipeSections
  382. if (MudSystemDotAnn_MudDischarged_Volume%Array(MudSystemDotimud)<= 0.0d0) then ! imud is completely exited form the well
  383. call RemoveAnnulusMudArrays(MudSystemDotimud)
  384. endif
  385. exit
  386. endif
  387. MudSystemDotxx= Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)/ MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection) !(gal)
  388. if (MudSystemDotxx<= 1.0) then
  389. Ann_Mud_Forehead_section%Array(MudSystemDotimud)= MudSystemDotisection
  390. Ann_Mud_Forehead_X%Array(MudSystemDotimud)= (MudSystemDotxx * (MudSystemDotXend_PipeSection(MudSystemDotisection)- MudSystemDotXstart_PipeSection(MudSystemDotisection)))+ MudSystemDotXstart_PipeSection(MudSystemDotisection)
  391. exit
  392. else
  393. Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)= Ann_RemainedVolume_in_LastSection%Array(MudSystemDotimud)- MudSystemDotPipeSection_VolumeCapacity(MudSystemDotisection)
  394. MudSystemDotisection= MudSystemDotisection+ 1
  395. endif
  396. enddo
  397. endif
  398. enddo
  399. !========================ANNULUS END=================
  400. !if ( WellisNOTFull == .false. ) then
  401. ! write(*,*) 'AnnulusFlowRate==' , AnnulusFlowRate
  402. ! call Set_FlowRate(real(100.*min(AnnulusFlowRate,PedalMeter)/(PedalMeter/10.), 8))
  403. !
  404. !
  405. !endif
  406. end subroutine Utube1_and_TripIn