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.
 
 
 
 
 
 

519 lines
37 KiB

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