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.

Utube2_and_Trip_In.f90 32 KiB

1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517
  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. MudSystem%UtubeMode2Activated= .true.
  15. write(*,*) 'QUtubeOutput=' , QUtubeOutput
  16. !QUTubeInput=5000.
  17. MudSystem%StringFlowRate= QUtubeOutput ! (gpm)
  18. MudSystem%AnnulusFlowRate= QUtubeOutput
  19. MudSystem%StringFlowRateFinal= MudSystem%StringFlowRate
  20. MudSystem%AnnulusFlowRateFinal= MudSystem%AnnulusFlowRate
  21. !===========================================
  22. if (MudSystem%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 MudSystem%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. MudSystem%Hz_Density_Utube= 0.0
  43. MudSystem%Hz_MudOrKick_Utube= 104
  44. MudSystem%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)+ ((MudSystem%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(MudSystem%AnnulusSuctionDensity_Old - MudSystem%Hz_Density_Utube) >= MudSystem%DensityMixTol ) then ! new mud is pumped
  137. call MudSystem%Ann_Density%Add (MudSystem%Hz_Density_Utube)
  138. call MudSystem%Ann_MudDischarged_Volume%Add (0.0d0)
  139. call MudSystem%Ann_Mud_Forehead_X%Add (MudSystem%Xend_PipeSection(MudSystem%NoPipeSections))
  140. call MudSystem%Ann_Mud_Forehead_section%Add (MudSystem%NoPipeSections)
  141. call MudSystem%Ann_Mud_Backhead_X%Add (MudSystem%Xstart_PipeSection(MudSystem%NoPipeSections))
  142. call MudSystem%Ann_Mud_Backhead_section%Add (MudSystem%NoPipeSections)
  143. call MudSystem%Ann_RemainedVolume_in_LastSection%Add (0.0d0)
  144. call MudSystem%Ann_EmptyVolume_inBackheadLocation%Add (0.0d0)
  145. call MudSystem%Ann_MudOrKick%Add (MudSystem%Hz_MudOrKick_Utube) ! Hz_MudOrKick%Last() = 104
  146. call MudSystem%Ann_CuttingMud%Add (0)
  147. MudSystem%AnnulusSuctionDensity_Old= MudSystem%Hz_Density_Utube
  148. endif
  149. !========================ANNULUS====================
  150. MudSystem%Ann_MudDischarged_Volume%Array(MudSystem%Ann_MudDischarged_Volume%Length())= MudSystem%Ann_MudDischarged_Volume%Last()+ ((MudSystem%AnnulusFlowRate/60.)*MudSystem%DeltaT_Mudline) !(gal)
  151. imud= MudSystem%Ann_Mud_Forehead_X%Length() + 1
  152. do while (imud > 1)
  153. imud = imud - 1
  154. if (imud< MudSystem%Ann_Mud_Forehead_X%Length()) then
  155. MudSystem%Ann_Mud_Forehead_X%Array(imud)= MudSystem%Ann_Mud_Backhead_X%Array(imud+1)
  156. MudSystem%Ann_Mud_Forehead_section%Array(imud)= MudSystem%Ann_Mud_Backhead_section%Array(imud+1)
  157. endif
  158. ! <<< Fracture Shoe Lost
  159. 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
  160. !write(*,*) 'ShoeLost imud,AnnVolume(imud), VolumeLost:' , imud,Ann_MudDischarged_Volume%Array(imud), (( Qlost/60.0d0)*DeltaT_Mudline)
  161. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)-((MudSystem%Qlost/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  162. if (MudSystem%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. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))) &
  171. / ABS(MudSystem%Xend_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud)))
  172. ! +1 for string , -1 for annulus
  173. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%Ann_Mud_Forehead_X%Array(imud)- MudSystem%Xstart_PipeSection(MudSystem%Ann_Mud_Forehead_section%Array(imud)))* &
  174. MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Forehead_section%Array(imud)) !(ft^3)
  175. MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  176. if ( MudSystem%Ann_MudDischarged_Volume%Array(imud) <= MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)) then
  177. MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%Ann_Mud_Forehead_section%Array(imud)
  178. MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Ann_Mud_Forehead_X%Array(imud)- MudSystem%DirectionCoef*(MudSystem%Ann_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%Ann_Mud_Forehead_section%Array(imud))
  179. ! 7.48051948 is for gal to ft^3
  180. else
  181. MudSystem%isection= MudSystem%Ann_Mud_Forehead_section%Array(imud)-1
  182. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(imud)
  183. do
  184. if (MudSystem%isection < F_Counts%StringIntervalCounts+1) then ! last pipe section(well exit) F_Counts%StringIntervalCounts+1 is the first section in Annulus
  185. MudSystem%Ann_MudDischarged_Volume%Array(imud)= MudSystem%Ann_MudDischarged_Volume%Array(imud)- MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)
  186. MudSystem%Ann_Mud_Backhead_X%Array(imud)= MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts+1)
  187. MudSystem%Ann_Mud_Backhead_section%Array(imud)= F_Counts%StringIntervalCounts+1
  188. if (MudSystem%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. MudSystem%xx= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  194. if (MudSystem%xx<= 1.0) then
  195. MudSystem%Ann_Mud_Backhead_section%Array(imud)= MudSystem%isection
  196. MudSystem%Ann_Mud_Backhead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xstart_PipeSection(MudSystem%isection)- MudSystem%Xend_PipeSection(MudSystem%isection)))+ MudSystem%Xend_PipeSection(MudSystem%isection)
  197. exit
  198. else
  199. MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Ann_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  200. MudSystem%isection= MudSystem%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 < MudSystem%Op_Mud_Forehead_X%Length())
  227. imud = imud + 1
  228. if (imud> 1) then
  229. MudSystem%Op_Mud_Backhead_X%Array(imud)= MudSystem%Op_Mud_Forehead_X%Array(imud-1)
  230. MudSystem%Op_Mud_Backhead_section%Array(imud)= MudSystem%Op_Mud_Forehead_section%Array(imud-1)
  231. endif
  232. MudSystem%DirectionCoef= (MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))) &
  233. / ABS(MudSystem%Xend_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud))-MudSystem%Xstart_OpSection(MudSystem%Op_Mud_Backhead_section%Array(imud)))
  234. ! +1 for string , -1 for annulus
  235. 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))* &
  236. MudSystem%Area_OpSectionFt(MudSystem%Op_Mud_Backhead_section%Array(imud)) !(ft^3)
  237. MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  238. if ( MudSystem%Op_MudDischarged_Volume%Array(imud) <= MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)) then
  239. MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%Op_Mud_Backhead_section%Array(imud)
  240. 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))
  241. ! 7.48051948 is for gal to ft^3
  242. else
  243. MudSystem%isection= MudSystem%Op_Mud_Backhead_section%Array(imud)+1
  244. MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_EmptyVolume_inBackheadLocation%Array(imud)
  245. do
  246. if (MudSystem%isection > F_Counts%BottomHoleIntervalCounts) then ! last pipe section(well exit)
  247. if( imud==1) MudSystem%KickDeltaVinAnnulus= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud) ! Kick enters Annulus space
  248. MudSystem%Op_MudDischarged_Volume%Array(imud)= MudSystem%Op_MudDischarged_Volume%Array(imud)- MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)
  249. MudSystem%Op_Mud_Forehead_X%Array(imud)= MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)
  250. MudSystem%Op_Mud_Forehead_section%Array(imud)= F_Counts%BottomHoleIntervalCounts
  251. if (MudSystem%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. MudSystem%xx= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%OpSection_VolumeCapacity(MudSystem%isection) !(gal)
  257. if (MudSystem%xx<= 1.0) then
  258. MudSystem%Op_Mud_Forehead_section%Array(imud)= MudSystem%isection
  259. MudSystem%Op_Mud_Forehead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xend_OpSection(MudSystem%isection)- MudSystem%Xstart_OpSection(MudSystem%isection)))+ MudSystem%Xstart_OpSection(MudSystem%isection)
  260. exit
  261. else
  262. MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)= MudSystem%Op_RemainedVolume_in_LastSection%Array(imud)- MudSystem%OpSection_VolumeCapacity(MudSystem%isection)
  263. MudSystem%isection= MudSystem%isection+ 1
  264. endif
  265. enddo
  266. endif
  267. if (MudSystem%Op_Mud_Forehead_X%Array(imud)== MudSystem%Xend_OpSection(F_Counts%BottomHoleIntervalCounts)) then
  268. MudSystem%totalLength = MudSystem%Op_MudDischarged_Volume%Length()
  269. do while(imud < MudSystem%totalLength)
  270. !imud = imud + 1
  271. call RemoveOpMudArrays(MudSystem%totalLength)
  272. MudSystem%totalLength = MudSystem%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(MudSystem%St_Density%Last() - MudSystem%Ann_Density%First()) >= MudSystem%DensityMixTol) .OR. (MudSystem%DeltaVolumeOp == 0.0 .and. MudSystem%St_Density%Last() /= MudSystem%Ann_Density%Array(1) .and. MudSystem%StringFlowRate/=0.0d0)) then ! new mud is pumped
  289. !if ((ABS(StringDensity_Old - Ann_Density%First()) >= DensityMixTol) .OR. (DeltaVolumeOp == 0.0 .and. MudSystem%St_Density%Last() /= Ann_Density%Array(1) .and. MudSystem%StringFlowRate/=0.0d0)) then ! new mud is pumped
  290. call MudSystem%St_Density%Add (MudSystem%Ann_Density%First())
  291. call MudSystem%St_MudDischarged_Volume%Add (0.0d0)
  292. call MudSystem%St_Mud_Forehead_X%Add (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts))
  293. call MudSystem%St_Mud_Forehead_section%Add (F_Counts%StringIntervalCounts)
  294. call MudSystem%St_Mud_Backhead_X%Add (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts))
  295. call MudSystem%St_Mud_Backhead_section%Add (F_Counts%StringIntervalCounts)
  296. call MudSystem%St_RemainedVolume_in_LastSection%Add (0.0d0)
  297. call MudSystem%St_EmptyVolume_inBackheadLocation%Add (0.0d0)
  298. call MudSystem%St_MudOrKick%Add (0)
  299. !StringDensity_Old= Ann_Density%First()
  300. MudSystem%MudIsChanged= .true.
  301. endif
  302. MudSystem%St_MudDischarged_Volume%Array(MudSystem%St_MudDischarged_Volume%Length())= MudSystem%St_MudDischarged_Volume%Last()+ ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline) !(gal)
  303. !========================Tripping In====================
  304. !write(*,*) 'DeltaVolumeOp=' , DeltaVolumeOp
  305. write(*,*) 'DeltaVolumeOp=' , MudSystem%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%Ann_Density%First()*((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)+MudSystem%Op_Density%Last()*MudSystem%DeltaVolumeOp)/(((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)+MudSystem%DeltaVolumeOp)
  309. MudSystem%NewVolume= ((MudSystem%StringFlowRate/60.0d0)*MudSystem%DeltaT_Mudline)+MudSystem%DeltaVolumeOp
  310. !write(*,*) 'St_MudDischarged_Volume%Last()=', St_MudDischarged_Volume%Last(), 'NewVolume=', NewVolume
  311. if (abs(MudSystem%St_Density%Last()-MudSystem%NewDensity)< MudSystem%DensityMixTol) then ! .OR. (St_MudDischarged_Volume%Last()< 42.) ) then !+ NewVolume)< 42.) then ! 1-Pockets are Merged
  312. MudSystem%St_Density%Array(MudSystem%St_Density%Length())= (MudSystem%St_Density%Last()*MudSystem%St_MudDischarged_Volume%Last()+MudSystem%NewDensity*MudSystem%NewVolume)/(MudSystem%St_MudDischarged_Volume%Last()+MudSystem%NewVolume)
  313. MudSystem%St_MudDischarged_Volume%Array(MudSystem%St_Density%Length())= MudSystem%St_MudDischarged_Volume%Last()+MudSystem%DeltaVolumeOp
  314. MudSystem%St_Mud_Forehead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts))
  315. MudSystem%St_Mud_Forehead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts)
  316. MudSystem%St_Mud_Backhead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts))
  317. MudSystem%St_Mud_Backhead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts)
  318. MudSystem%St_RemainedVolume_in_LastSection%Array(MudSystem%St_Density%Length())= (0.0d0)
  319. MudSystem%St_EmptyVolume_inBackheadLocation%Array(MudSystem%St_Density%Length())= (0.0d0)
  320. else ! 2-Merging conditions are not meeted, so new pocket
  321. call MudSystem%St_Density%Add (MudSystem%NewDensity)
  322. call MudSystem%St_MudDischarged_Volume%Add (MudSystem%NewVolume)
  323. call MudSystem%St_Mud_Forehead_X%Add (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts))
  324. call MudSystem%St_Mud_Forehead_section%Add (F_Counts%StringIntervalCounts)
  325. call MudSystem%St_Mud_Backhead_X%Add (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts))
  326. call MudSystem%St_Mud_Backhead_section%Add (F_Counts%StringIntervalCounts)
  327. call MudSystem%St_RemainedVolume_in_LastSection%Add (0.0d0)
  328. call MudSystem%St_EmptyVolume_inBackheadLocation%Add (0.0d0)
  329. call MudSystem%St_MudOrKick%Add (0)
  330. endif
  331. elseif (MudSystem%DeltaVolumeOp > 0.0 .and. MudSystem%MudIsChanged== .true.) then
  332. MudSystem%St_Density%Array(MudSystem%St_Density%Length())= MudSystem%NewDensity
  333. MudSystem%St_MudDischarged_Volume%Array(MudSystem%St_Density%Length())= MudSystem%NewVolume
  334. MudSystem%St_Mud_Forehead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xend_PipeSection(F_Counts%StringIntervalCounts))
  335. MudSystem%St_Mud_Forehead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts)
  336. MudSystem%St_Mud_Backhead_X%Array(MudSystem%St_Density%Length())= (MudSystem%Xstart_PipeSection(F_Counts%StringIntervalCounts))
  337. MudSystem%St_Mud_Backhead_section%Array(MudSystem%St_Density%Length())= (F_Counts%StringIntervalCounts)
  338. MudSystem%St_RemainedVolume_in_LastSection%Array(MudSystem%St_Density%Length())= (0.0d0)
  339. MudSystem%St_EmptyVolume_inBackheadLocation%Array(MudSystem%St_Density%Length())= (0.0d0)
  340. endif
  341. !========================Tripping In - End====================
  342. !======================== STRING ====================
  343. MudSystem%MudIsChanged= .false.
  344. imud= MudSystem%St_Mud_Forehead_X%Length() + 1
  345. do while (imud > 1)
  346. imud = imud - 1
  347. if (imud< MudSystem%St_Mud_Forehead_X%Length()) then
  348. MudSystem%St_Mud_Forehead_X%Array(imud)= MudSystem%St_Mud_Backhead_X%Array(imud+1)
  349. MudSystem%St_Mud_Forehead_section%Array(imud)= MudSystem%St_Mud_Backhead_section%Array(imud+1)
  350. endif
  351. MudSystem%DirectionCoef= (MudSystem%Xend_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud))) &
  352. / ABS(MudSystem%Xend_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud))-MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud)))
  353. ! +1 for string , -1 for annulus
  354. MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%DirectionCoef* (MudSystem%St_Mud_Forehead_X%Array(imud)- MudSystem%Xstart_PipeSection(MudSystem%St_Mud_Forehead_section%Array(imud)))* &
  355. MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Backhead_section%Array(imud)) !(ft^3)
  356. MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)* 7.48051948d0 ! ft^3 to gal
  357. if ( MudSystem%St_MudDischarged_Volume%Array(imud) <= MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)) then
  358. MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%St_Mud_Forehead_section%Array(imud)
  359. MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%St_Mud_Forehead_X%Array(imud)- MudSystem%DirectionCoef*(MudSystem%St_MudDischarged_Volume%Array(imud)/7.48051948d0)/MudSystem%Area_PipeSectionFt(MudSystem%St_Mud_Forehead_section%Array(imud))
  360. ! 7.48051948 is for gal to ft^3
  361. else
  362. MudSystem%isection= MudSystem%St_Mud_Backhead_section%Array(imud)-1
  363. MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_EmptyVolume_inBackheadLocation%Array(imud)
  364. do
  365. if (MudSystem%isection < 1) then ! last pipe section(string exit)
  366. MudSystem%St_MudDischarged_Volume%Array(imud)= MudSystem%St_MudDischarged_Volume%Array(imud)- MudSystem%St_RemainedVolume_in_LastSection%Array(imud)
  367. MudSystem%St_Mud_Backhead_X%Array(imud)= MudSystem%Xstart_PipeSection(2)
  368. MudSystem%St_Mud_Backhead_section%Array(imud)= 2
  369. if (MudSystem%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. MudSystem%xx= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)/ MudSystem%PipeSection_VolumeCapacity(MudSystem%isection) !(gal)
  375. if (MudSystem%xx<= 1.0) then
  376. MudSystem%St_Mud_Backhead_section%Array(imud)= MudSystem%isection
  377. MudSystem%St_Mud_Backhead_X%Array(imud)= (MudSystem%xx * (MudSystem%Xstart_PipeSection(MudSystem%isection)- MudSystem%Xend_PipeSection(MudSystem%isection)))+ MudSystem%Xend_PipeSection(MudSystem%isection)
  378. exit
  379. else
  380. MudSystem%St_RemainedVolume_in_LastSection%Array(imud)= MudSystem%St_RemainedVolume_in_LastSection%Array(imud)- MudSystem%PipeSection_VolumeCapacity(MudSystem%isection)
  381. MudSystem%isection= MudSystem%isection- 1
  382. endif
  383. enddo
  384. endif
  385. enddo
  386. !========================STRING END=================
  387. end subroutine Utube2_and_TripIn