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.
 
 
 
 
 
 

413 lines
21 KiB

  1. subroutine PlotFinalMudElements ! is called in subroutine CirculationCodeSelect
  2. Use GeoElements_FluidModule
  3. USE CMudPropertiesVariables
  4. USE MudSystemVARIABLES
  5. USE Pumps_VARIABLES
  6. Use TD_StringConnectionData
  7. !USE CHOKEVARIABLES
  8. !USE CDataDisplayConsoleVariables , StandPipePressureDataDisplay=>StandPipePressure
  9. !use CManifolds
  10. use CDrillWatchVariables
  11. !use CHOKEVARIABLES
  12. !use CChokeManifoldVariables
  13. !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
  14. USE sROP_Other_Variables
  15. USE sROP_Variables
  16. Use KickVariables
  17. USE CKellyConnectionEnumVariables
  18. USE UTUBEVARS
  19. use CLog1
  20. Use CError
  21. Use , intrinsic :: IEEE_Arithmetic
  22. implicit none
  23. integer jelement, jmud, jsection,ielement,i
  24. integer jopelement,jopmud,jopsection
  25. character(len=120) :: temp1, temp2
  26. if (ChokeControlPanel%ChokePanelStrokeResetSwitch == 1) then
  27. write(*,*) 'well cap=' , sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections)) + sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
  28. MudSystemDotDeltaWellCap= sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections)) + sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts)) - MudSystemDotWellCapOld
  29. MudSystemDotWellCapOld= sum(MudSystemDotPipeSection_VolumeCapacity(F_StringIntervalCounts+1:MudSystemDotNoPipeSections)) + sum(MudSystemDotOpSection_VolumeCapacity(1:F_BottomHoleIntervalCounts))
  30. write(*,*) 'cap_reset,DeltaWellCap=' , MudSystemDotDeltaWellCap
  31. endif
  32. !========================ANNULUS END=================
  33. if ((Ann_Mud_Forehead_X%Last() - BopStackSpecification%AboveAnnularHeight) > 0.8 .or. Ann_Density%Last()==0.0) then ! for Line (BellNippleToWell-NonFullWell)
  34. MudSystemDotWellisNOTFull= .true.
  35. else
  36. MudSystemDotWellisNOTFull= .false.
  37. endif
  38. !WRITE(*,*) 'Ann_Mud_Forehead_X%Last() , KillHeight', Ann_Mud_Forehead_X%Last() , KillHeight
  39. if ((Ann_Mud_Forehead_X%Last() - BopStackSpecification%KillHeight)>0.8 .or. Ann_Density%Last()==0.0) then ! for Line j4 , WellToChokeManifold(Through 26)
  40. MudSystemDotChokeLineNOTFull= .true.
  41. else
  42. MudSystemDotChokeLineNOTFull= .false.
  43. endif
  44. !=========================================================
  45. jmud= 1
  46. jsection= 1
  47. jelement= 0 ! number of final mud elements
  48. call Xend_MudElement%Empty()
  49. call TVDend_MudElement%Empty()
  50. call Density_MudElement%Empty()
  51. call MudGeoType%Empty()
  52. call PipeID_MudElement%Empty()
  53. call PipeOD_MudElement%Empty()
  54. !call Angle_MudElement%Empty()
  55. call MudType_MudElement%Empty()
  56. DO WHILE(jmud <= MudSystemDotHz_Mud_Forehead_X%Length() .and. jsection<=1)
  57. jelement= jelement+1
  58. TrueMinValue= min(MudSystemDotHz_Mud_Forehead_X%Array(jmud), MudSystemDotXend_PipeSection(jsection))
  59. call Xend_MudElement%Add(TrueMinValue)
  60. call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
  61. call TVDend_MudElement%Add(MudSystemDotMudCircVerticalDepth)
  62. call Density_MudElement%Add(MudSystemDotHz_Density%Array(jmud))
  63. call PipeID_MudElement%Add(MudSystemDotID_PipeSectionInch(jsection))
  64. call PipeOD_MudElement%Add(MudSystemDotOD_PipeSectionInch(jsection))
  65. !call Angle_MudElement%Add(Angle_PipeSection(jsection))
  66. call MudType_MudElement%Add(Hz_MudOrKick%Array(jmud))
  67. if (Xend_MudElement%Array(jelement)== MudSystemDotHz_Mud_Forehead_X%Array(jmud)) then
  68. jmud= jmud+1
  69. else
  70. jsection= jsection+1
  71. endif
  72. ENDDO
  73. MudSystemDotNoHorizontalMudElements= jelement
  74. jmud= 1
  75. jsection= 2
  76. DO WHILE(jmud <= MudSystemDotSt_Mud_Forehead_X%Length() .and. jsection<=F_StringIntervalCounts)
  77. jelement= jelement+1
  78. TrueMinValue= min(MudSystemDotSt_Mud_Forehead_X%Array(jmud), MudSystemDotXend_PipeSection(jsection))
  79. call Xend_MudElement%Add(TrueMinValue)
  80. call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
  81. call TVDend_MudElement%Add(MudSystemDotMudCircVerticalDepth)
  82. call Density_MudElement%Add(St_Density%Array(jmud))
  83. call PipeID_MudElement%Add(MudSystemDotID_PipeSectionInch(jsection))
  84. call PipeOD_MudElement%Add(MudSystemDotOD_PipeSectionInch(jsection))
  85. !call Angle_MudElement%Add(Angle_PipeSection(jsection))
  86. call MudType_MudElement%Add(St_MudOrKick%Array(jmud))
  87. if (Xend_MudElement%Array(jelement)== MudSystemDotSt_Mud_Forehead_X%Array(jmud)) then
  88. jmud= jmud+1
  89. else
  90. jsection= jsection+1
  91. endif
  92. ENDDO
  93. MudSystemDotNoStringMudElements= jelement- MudSystemDotNoHorizontalMudElements
  94. jmud= 1
  95. jsection= F_StringIntervalCounts+1
  96. DO WHILE(jmud<= Ann_Mud_Forehead_X%Length() .and. jsection<=MudSystemDotNoPipeSections)
  97. jelement= jelement+1
  98. TrueMinValue= max(Ann_Mud_Forehead_X%Array(jmud), MudSystemDotXend_PipeSection(jsection))
  99. call Xend_MudElement%Add(TrueMinValue)
  100. call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
  101. call TVDend_MudElement%Add(MudSystemDotMudCircVerticalDepth)
  102. call Density_MudElement%Add(Ann_Density%Array(jmud))
  103. call PipeID_MudElement%Add(MudSystemDotID_PipeSectionInch(jsection))
  104. call PipeOD_MudElement%Add(MudSystemDotOD_PipeSectionInch(jsection))
  105. !call Angle_MudElement%Add(Angle_PipeSection(jsection))
  106. call MudType_MudElement%Add(Ann_MudOrKick%Array(jmud))
  107. if (Xend_MudElement%Array(jelement)== Ann_Mud_Forehead_X%Array(jmud)) then
  108. jmud= jmud+1
  109. else
  110. jsection= jsection+1
  111. endif
  112. ENDDO
  113. do i= 2, Xend_MudElement%Length()
  114. if ( i== MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+1) then
  115. call Xstart_MudElement%Add (Ann_Mud_Backhead_X%Array(1)) ! start of annulus
  116. call TVD_Calculator(Ann_Mud_Backhead_X%Array(1),MudSystemDotMudCircVerticalDepth)
  117. call TVDstart_MudElement%Add(MudSystemDotMudCircVerticalDepth)
  118. elseif ( i== MudSystemDotNoHorizontalMudElements+1 ) then
  119. call Xstart_MudElement%Add (MudSystemDotSt_Mud_Backhead_X%Array(1)) ! start of stirng
  120. call TVD_Calculator(MudSystemDotSt_Mud_Backhead_X%Array(1),MudSystemDotMudCircVerticalDepth)
  121. call TVDstart_MudElement%Add(MudSystemDotMudCircVerticalDepth)
  122. else
  123. call Xstart_MudElement%Add(Xend_MudElement%Array(i-1)) ! normal calculation
  124. call TVDstart_MudElement%Add(TVDend_MudElement%Array(i-1)) ! normal calculation
  125. endif
  126. enddo
  127. MudSystemDotNoCasingMudElements = jelement- MudSystemDotNoStringMudElements- MudSystemDotNoHorizontalMudElements
  128. !=========================For Torque and Drag========================
  129. if (allocated(MudSystemDotTDXstart_MudElementArray)) deallocate(MudSystemDotTDXstart_MudElementArray)
  130. allocate(MudSystemDotTDXstart_MudElementArray(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+MudSystemDotNoCasingMudElements))
  131. if (allocated(MudSystemDotTDXend_MudElementArray)) deallocate(MudSystemDotTDXend_MudElementArray)
  132. allocate(MudSystemDotTDXend_MudElementArray(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+MudSystemDotNoCasingMudElements))
  133. if (allocated(MudSystemDotTDDensity_MudElementArray)) deallocate(MudSystemDotTDDensity_MudElementArray)
  134. allocate(MudSystemDotTDDensity_MudElementArray(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+MudSystemDotNoCasingMudElements))
  135. MudSystemDotTDNoHorizontalMudElements= MudSystemDotNoHorizontalMudElements
  136. MudSystemDotTDNoStringMudElements= MudSystemDotNoStringMudElements
  137. MudSystemDotTDNoCasingMudElements= MudSystemDotNoCasingMudElements
  138. MudSystemDotTDXstart_MudElementArray(:) = Xstart_MudElement%Array(:)
  139. MudSystemDotTDXend_MudElementArray(:) = Xend_MudElement%Array(:)
  140. MudSystemDotTDDensity_MudElementArray(:) = Density_MudElement%Array(:)
  141. !=====================================================================
  142. !do i=NoHorizontalMudElements+1, NoHorizontalMudElements+NoStringMudElements ! 2-string elements
  143. ! write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
  144. !enddo
  145. !================================================================
  146. ! Open Hole Mud Elements
  147. jopmud= 1
  148. jopsection= 1
  149. jopelement= 0 ! number of final mud elements
  150. call Xend_OpMudElement%Empty()
  151. call TVDend_OpMudElement%Empty()
  152. call Density_OpMudElement%Empty()
  153. call PipeID_OpMudElement%Empty()
  154. call PipeOD_OpMudElement%Empty()
  155. !call Angle_OpMudElement%Empty()
  156. call MudTypeOp_MudElement%Empty()
  157. DO WHILE(jopmud<= MudSystemDotOp_Mud_Forehead_X%Length() .and. jopsection<=F_BottomHoleIntervalCounts)
  158. jopelement= jopelement+1
  159. TrueMinValue= max(MudSystemDotOp_Mud_Forehead_X%Array(jopmud), MudSystemDotXend_OpSection(jopsection))
  160. call Xend_OpMudElement%Add(TrueMinValue)
  161. call TVD_Calculator(TrueMinValue,MudSystemDotMudCircVerticalDepth)
  162. call TVDend_OpMudElement%Add(MudSystemDotMudCircVerticalDepth)
  163. call Density_OpMudElement%Add(MudSystemDotOp_Density%Array(jopmud))
  164. call PipeID_OpMudElement%Add(MudSystemDotID_OpSectionInch(jopsection))
  165. call PipeOD_OpMudElement%Add(MudSystemDotOD_OpSectionInch(jopsection))
  166. !call Angle_MudElement%Add(Angle_PipeSection(jopsection))
  167. call MudTypeOp_MudElement%Add(Op_MudOrKick%Array(jopmud))
  168. if (Xend_OpMudElement%Array(jopelement)== MudSystemDotOp_Mud_Forehead_X%Array(jopmud)) then
  169. jopmud= jopmud+1
  170. else
  171. jopsection= jopsection+1
  172. endif
  173. ENDDO
  174. do i= 2, Xend_OpMudElement%Length()
  175. call Xstart_OpMudElement%Add(Xend_OpMudElement%Array(i-1))
  176. call TVDstart_OpMudElement%Add(TVDend_OpMudElement%Array(i-1))
  177. enddo
  178. MudSystemDotNoBottomHoleMudElements = jopelement
  179. !================================================================
  180. if(allocated(StringMudElement)) deallocate(StringMudElement)
  181. allocate(StringMudElement(MudSystemDotNoStringMudElements))
  182. if(allocated(CasingMudElement)) deallocate(CasingMudElement)
  183. allocate(CasingMudElement(MudSystemDotNoCasingMudElements+MudSystemDotNoBottomHoleMudElements))
  184. MudSystemDotistring=0
  185. MudSystemDoticasing=0
  186. MudSystemDotBitMudDensity= Density_MudElement%Array(MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements) ! (for ROP module)
  187. !================================================================
  188. !============================ UTUBE =============================
  189. !IF (UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadIsOpen) THEN
  190. IF (MudSystemDotUtubePossibility== .true. .and. TD_FluidStringConnectionMode==0 .and. WellHeadIsOpen .AND. NoGasPocket == 0) THEN
  191. CALL WellPressureDataTransfer
  192. !WRITE (*,*) ' U-Tube Done 1'
  193. CALL Utube
  194. !WRITE (*,*) ' U-Tube Done 2'
  195. if (QUtubeInput> 0.0) call Utube1_and_TripIn
  196. if (QUtubeOutput> 0.0) call Utube2_and_TripIn
  197. END IF
  198. !========================== UTUBE- end =========================
  199. ! do imud=1, st_MudDischarged_Volume%Length()
  200. ! write(*,*) 'st-plot:', imud, St_MudDischarged_Volume%Array(imud), St_Mud_Backhead_X%Array(imud) ,St_Mud_Forehead_X%Array(imud)
  201. !enddo
  202. !==================== Display ========================
  203. !do i=1, St_MudOrKick%Length()
  204. ! write(*,555) i,'St_Volume(i), type=' ,St_MudDischarged_Volume%Array(i),St_MudOrKick%Array(i)
  205. !
  206. ! IF (IEEE_Is_NaN(St_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in St Volume-Plot')
  207. ! IF (St_MudDischarged_Volume%Array(i)<0.) call ErrorStop('St Volume <0' , St_MudDischarged_Volume%Array(i))
  208. !enddo
  209. IF (ANY(IEEE_Is_NaN(MudSystemDotOp_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystemDotOp_MudDischarged_Volume%Array(:) <= 0.0)) THEN
  210. do i = 1 , Op_MudOrKick%Length()
  211. write(*,555) i,'Op_Volume(i), type=' ,MudSystemDotOp_MudDischarged_Volume%Array(i) , Op_MudOrKick%Array(i) , MudSystemDotOp_Density%Array(i)
  212. end do
  213. call ErrorStop('NaN in Op Volume-Plot or Op Volume <=0')
  214. END IF
  215. IF (ANY(IEEE_Is_NaN(MudSystemDotAnn_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystemDotAnn_MudDischarged_Volume%Array(:) <= 0.0)) THEN
  216. do i = 1 , Ann_MudOrKick%Length()
  217. write(*,555) i,'Ann_Volume(i), type=' ,MudSystemDotAnn_MudDischarged_Volume%Array(i) , Ann_MudOrKick%Array(i) , Ann_Density%Array(i)
  218. end do
  219. call ErrorStop('NaN in Ann Volume-Plot or Ann Volume <=0')
  220. END IF
  221. !do i=1, Ann_MudOrKick%Length()
  222. ! !write(*,555) i,'Ann_Volume(i), type=' ,Ann_MudDischarged_Volume%Array(i),Ann_MudOrKick%Array(i),Ann_Density%Array(i)
  223. !
  224. ! IF (IEEE_Is_NaN(Ann_MudDischarged_Volume%Array(i))) call ErrorStop('NaN in Ann Volume-Plot')
  225. ! IF (Ann_MudDischarged_Volume%Array(i)<=0.) call ErrorStop('Ann Volume <=0' , Ann_MudDischarged_Volume%Array(i))
  226. !enddo
  227. 555 FORMAT(I3,5X,A42,(f12.5),5X,I3,5X,(f12.5))
  228. MudSystemDotNoStringMudElementsForPlot= MudSystemDotNoStringMudElements
  229. ! 1-Horizontal Mud Elements are not shown
  230. !write(*,333) 'Horiz:', 1,'Xstart\=', Xstart_MudElement%Array(1), 'Xend=' , Xend_MudElement%Array(1), 'Density=' , Density_MudElement%Array(1), 'MudType=' , MudType_MudElement%Array(1)
  231. do i=MudSystemDotNoHorizontalMudElements+1, MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements ! 2-string elements
  232. if (Xend_MudElement%Array(i) <= 0.0) then
  233. MudSystemDotNoStringMudElementsForPlot= MudSystemDotNoStringMudElementsForPlot-1
  234. cycle
  235. endif
  236. MudSystemDotistring= MudSystemDotistring+1
  237. StringMudElement(MudSystemDotistring)%StartMd = Xstart_MudElement%Array(i)
  238. StringMudElement(MudSystemDotistring)%EndMd = Xend_MudElement%Array(i)
  239. !StringMudElement(istring)%Id = PipeID_MudElement%Array(i)
  240. !StringMudElement(istring)%Od = PipeOD_MudElement%Array(i)
  241. StringMudElement(MudSystemDotistring)%Density = Density_MudElement%Array(i)
  242. if (MudType_MudElement%Array(i) == 104) then
  243. MudType_MudElement%Array(i)= 4 ! air
  244. elseif (MudType_MudElement%Array(i) > 0 .and. MudType_MudElement%Array(i) < 100) then ! all kicks
  245. MudType_MudElement%Array(i)= 1 ! gas kick
  246. endif
  247. StringMudElement(MudSystemDotistring)%MudType = MudType_MudElement%Array(i)
  248. !write(*,333) 'STRING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
  249. enddo
  250. do i=Xend_MudElement%Length(), MudSystemDotNoHorizontalMudElements+MudSystemDotNoStringMudElements+1 , -1 ! 3-casing elements
  251. MudSystemDoticasing= MudSystemDoticasing+1
  252. CasingMudElement(MudSystemDoticasing)%StartMd = Xend_MudElement%Array(i)
  253. CasingMudElement(MudSystemDoticasing)%EndMd = Xstart_MudElement%Array(i)
  254. !CasingMudElement(icasing)%Id = PipeID_MudElement%Array(i)
  255. !CasingMudElement(icasing)%Od = PipeOD_MudElement%Array(i)
  256. !write(*,333) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'Density=' , Density_MudElement%Array(i), 'MudType=' , MudType_MudElement%Array(i)
  257. !call Log_1(temp1)
  258. !write(*,444) 'CASING:', i,'Xstart\=', Xstart_MudElement%Array(i), 'Xend=' , Xend_MudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i)
  259. CasingMudElement(MudSystemDoticasing)%Density = Density_MudElement%Array(i)
  260. if (MudType_MudElement%Array(i) == 104) then
  261. MudType_MudElement%Array(i)= 4 ! air
  262. elseif (MudType_MudElement%Array(i) > 0 .and. MudType_MudElement%Array(i) < 100) then
  263. MudType_MudElement%Array(i)= 1 ! gas kick
  264. endif
  265. CasingMudElement(MudSystemDoticasing)%MudType = MudType_MudElement%Array(i)
  266. enddo
  267. do i= MudSystemDotNoBottomHoleMudElements, 1 , -1 ! 4-open hole elements
  268. MudSystemDoticasing= MudSystemDoticasing+1
  269. CasingMudElement(MudSystemDoticasing)%StartMd = Xend_OpMudElement%Array(i)
  270. CasingMudElement(MudSystemDoticasing)%EndMd = Xstart_OpMudElement%Array(i)
  271. !CasingMudElement(icasing)%Id = PipeID_OpMudElement%Array(i)
  272. !CasingMudElement(icasing)%Od = PipeOD_OpMudElement%Array(i)
  273. !write(*,333) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'Density=' , Density_OpMudElement%Array(i), 'MudType=' , MudTypeOp_MudElement%Array(i)
  274. !call Log_1(temp2)
  275. !write(*,444) 'OpenHole:',i,'Xstart\=', Xstart_OpMudElement%Array(i), 'Xend=' , Xend_OpMudElement%Array(i), 'PipeID_MudElement%Array(i)=' , PipeID_MudElement%Array(i), 'PipeOD_MudElement%Array(i)=' , PipeOD_MudElement%Array(i)
  276. CasingMudElement(MudSystemDoticasing)%Density = Density_OpMudElement%Array(i)
  277. if (MudTypeOp_MudElement%Array(i) == 104) then
  278. MudTypeOp_MudElement%Array(i)= 4 ! air
  279. elseif (MudTypeOp_MudElement%Array(i) > 0 .and. MudTypeOp_MudElement%Array(i) < 100) then
  280. MudTypeOp_MudElement%Array(i)= 1 ! gas kick
  281. endif
  282. CasingMudElement(MudSystemDoticasing)%MudType = MudTypeOp_MudElement%Array(i)
  283. enddo
  284. 333 FORMAT(A10,I3,5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,(f12.5),5X,A8,I3)
  285. 444 FORMAT(A10,I2,5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3),5X,A8,(f12.3))
  286. ! shomare gozari be tartib HZ mud, ST mud, Casing
  287. ! shomare gzari OpenHole jodagane ast az 1
  288. call SetStringFluids(MudSystemDotNoStringMudElementsForPlot, StringMudElement) !for data display in string
  289. call SetAnnalusFluids(MudSystemDotNoCasingMudElements+MudSystemDotNoBottomHoleMudElements, CasingMudElement) !for data display in casing
  290. !===========================================================================================================================
  291. !===========================================================================================================================
  292. end subroutine PlotFinalMudElements