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.
 
 
 
 
 
 

411 lines
22 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(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) + sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))
  28. MudSystem%DeltaWellCap= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) + sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts)) - MudSystem%WellCapOld
  29. MudSystem%WellCapOld= sum(MudSystem%PipeSection_VolumeCapacity(F_Counts%StringIntervalCounts+1:MudSystem%NoPipeSections)) + sum(MudSystem%OpSection_VolumeCapacity(1:F_Counts%BottomHoleIntervalCounts))
  30. write(*,*) 'cap_reset,DeltaWellCap=' , MudSystem%DeltaWellCap
  31. endif
  32. !========================ANNULUS END=================
  33. if ((MudSystem%Ann_Mud_Forehead_X%Last() - BopStackSpecification%AboveAnnularHeight) > 0.8 .or. MudSystem%Ann_Density%Last()==0.0) then ! for Line (BellNippleToWell-NonFullWell)
  34. MudSystem%WellisNOTFull= .true.
  35. else
  36. MudSystem%WellisNOTFull= .false.
  37. endif
  38. !WRITE(*,*) 'Ann_Mud_Forehead_X%Last() , KillHeight', Ann_Mud_Forehead_X%Last() , KillHeight
  39. if ((MudSystem%Ann_Mud_Forehead_X%Last() - BopStackSpecification%KillHeight)>0.8 .or. MudSystem%Ann_Density%Last()==0.0) then ! for Line j4 , WellToChokeManifold(Through 26)
  40. MudSystem%ChokeLineNOTFull= .true.
  41. else
  42. MudSystem%ChokeLineNOTFull= .false.
  43. endif
  44. !=========================================================
  45. jmud= 1
  46. jsection= 1
  47. jelement= 0 ! number of final mud elements
  48. call MudSystem%Xend_MudElement%Empty()
  49. call MudSystem%TVDend_MudElement%Empty()
  50. call MudSystem%Density_MudElement%Empty()
  51. call MudSystem%MudGeoType%Empty()
  52. call MudSystem%PipeID_MudElement%Empty()
  53. call MudSystem%PipeOD_MudElement%Empty()
  54. !call Angle_MudElement%Empty()
  55. call MudSystem%MudType_MudElement%Empty()
  56. DO WHILE(jmud <= MudSystem%Hz_Mud_Forehead_X%Length() .and. jsection<=1)
  57. jelement= jelement+1
  58. MudSystem%TrueMinValue= min(MudSystem%Hz_Mud_Forehead_X%Array(jmud), MudSystem%Xend_PipeSection(jsection))
  59. call MudSystem%Xend_MudElement%Add(MudSystem%TrueMinValue)
  60. call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth)
  61. call MudSystem%TVDend_MudElement%Add(MudSystem%MudCircVerticalDepth)
  62. call MudSystem%Density_MudElement%Add(MudSystem%Hz_Density%Array(jmud))
  63. call MudSystem%PipeID_MudElement%Add(MudSystem%ID_PipeSectionInch(jsection))
  64. call MudSystem%PipeOD_MudElement%Add(MudSystem%OD_PipeSectionInch(jsection))
  65. !call Angle_MudElement%Add(Angle_PipeSection(jsection))
  66. call MudSystem%MudType_MudElement%Add(MudSystem%Hz_MudOrKick%Array(jmud))
  67. if (MudSystem%Xend_MudElement%Array(jelement)== MudSystem%Hz_Mud_Forehead_X%Array(jmud)) then
  68. jmud= jmud+1
  69. else
  70. jsection= jsection+1
  71. endif
  72. ENDDO
  73. MudSystem%NoHorizontalMudElements= jelement
  74. jmud= 1
  75. jsection= 2
  76. DO WHILE(jmud <= MudSystem%St_Mud_Forehead_X%Length() .and. jsection<=F_Counts%StringIntervalCounts)
  77. jelement= jelement+1
  78. MudSystem%TrueMinValue= min(MudSystem%St_Mud_Forehead_X%Array(jmud), MudSystem%Xend_PipeSection(jsection))
  79. call MudSystem%Xend_MudElement%Add(MudSystem%TrueMinValue)
  80. call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth)
  81. call MudSystem%TVDend_MudElement%Add(MudSystem%MudCircVerticalDepth)
  82. call MudSystem%Density_MudElement%Add(MudSystem%St_Density%Array(jmud))
  83. call MudSystem%PipeID_MudElement%Add(MudSystem%ID_PipeSectionInch(jsection))
  84. call MudSystem%PipeOD_MudElement%Add(MudSystem%OD_PipeSectionInch(jsection))
  85. !call Angle_MudElement%Add(Angle_PipeSection(jsection))
  86. call MudSystem%MudType_MudElement%Add(MudSystem%St_MudOrKick%Array(jmud))
  87. if (MudSystem%Xend_MudElement%Array(jelement)== MudSystem%St_Mud_Forehead_X%Array(jmud)) then
  88. jmud= jmud+1
  89. else
  90. jsection= jsection+1
  91. endif
  92. ENDDO
  93. MudSystem%NoStringMudElements= jelement- MudSystem%NoHorizontalMudElements
  94. jmud= 1
  95. jsection= F_Counts%StringIntervalCounts+1
  96. DO WHILE(jmud<= MudSystem%Ann_Mud_Forehead_X%Length() .and. jsection<=MudSystem%NoPipeSections)
  97. jelement= jelement+1
  98. MudSystem%TrueMinValue= max(MudSystem%Ann_Mud_Forehead_X%Array(jmud), MudSystem%Xend_PipeSection(jsection))
  99. call MudSystem%Xend_MudElement%Add(MudSystem%TrueMinValue)
  100. call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth)
  101. call MudSystem%TVDend_MudElement%Add(MudSystem%MudCircVerticalDepth)
  102. call MudSystem%Density_MudElement%Add(MudSystem%Ann_Density%Array(jmud))
  103. call MudSystem%PipeID_MudElement%Add(MudSystem%ID_PipeSectionInch(jsection))
  104. call MudSystem%PipeOD_MudElement%Add(MudSystem%OD_PipeSectionInch(jsection))
  105. !call Angle_MudElement%Add(Angle_PipeSection(jsection))
  106. call MudSystem%MudType_MudElement%Add(MudSystem%Ann_MudOrKick%Array(jmud))
  107. if (MudSystem%Xend_MudElement%Array(jelement)== MudSystem%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, MudSystem%Xend_MudElement%Length()
  114. if ( i== MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+1) then
  115. call MudSystem%Xstart_MudElement%Add (MudSystem%Ann_Mud_Backhead_X%Array(1)) ! start of annulus
  116. call TVD_Calculator(MudSystem%Ann_Mud_Backhead_X%Array(1),MudSystem%MudCircVerticalDepth)
  117. call MudSystem%TVDstart_MudElement%Add(MudSystem%MudCircVerticalDepth)
  118. elseif ( i== MudSystem%NoHorizontalMudElements+1 ) then
  119. call MudSystem%Xstart_MudElement%Add (MudSystem%St_Mud_Backhead_X%Array(1)) ! start of stirng
  120. call TVD_Calculator(MudSystem%St_Mud_Backhead_X%Array(1),MudSystem%MudCircVerticalDepth)
  121. call MudSystem%TVDstart_MudElement%Add(MudSystem%MudCircVerticalDepth)
  122. else
  123. call MudSystem%Xstart_MudElement%Add(MudSystem%Xend_MudElement%Array(i-1)) ! normal calculation
  124. call MudSystem%TVDstart_MudElement%Add(MudSystem%TVDend_MudElement%Array(i-1)) ! normal calculation
  125. endif
  126. enddo
  127. MudSystem%NoCasingMudElements = jelement- MudSystem%NoStringMudElements- MudSystem%NoHorizontalMudElements
  128. !=========================For Torque and Drag========================
  129. if (allocated(MudSystem%TDXstart_MudElementArray)) deallocate(MudSystem%TDXstart_MudElementArray)
  130. allocate(MudSystem%TDXstart_MudElementArray(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+MudSystem%NoCasingMudElements))
  131. if (allocated(MudSystem%TDXend_MudElementArray)) deallocate(MudSystem%TDXend_MudElementArray)
  132. allocate(MudSystem%TDXend_MudElementArray(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+MudSystem%NoCasingMudElements))
  133. if (allocated(MudSystem%TDDensity_MudElementArray)) deallocate(MudSystem%TDDensity_MudElementArray)
  134. allocate(MudSystem%TDDensity_MudElementArray(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+MudSystem%NoCasingMudElements))
  135. MudSystem%TDNoHorizontalMudElements= MudSystem%NoHorizontalMudElements
  136. MudSystem%TDNoStringMudElements= MudSystem%NoStringMudElements
  137. MudSystem%TDNoCasingMudElements= MudSystem%NoCasingMudElements
  138. MudSystem%TDXstart_MudElementArray(:) = MudSystem%Xstart_MudElement%Array(:)
  139. MudSystem%TDXend_MudElementArray(:) = MudSystem%Xend_MudElement%Array(:)
  140. MudSystem%TDDensity_MudElementArray(:) = MudSystem%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 MudSystem%Xend_OpMudElement%Empty()
  151. call MudSystem%TVDend_OpMudElement%Empty()
  152. call MudSystem%Density_OpMudElement%Empty()
  153. call MudSystem%PipeID_OpMudElement%Empty()
  154. call MudSystem%PipeOD_OpMudElement%Empty()
  155. !call Angle_OpMudElement%Empty()
  156. call MudSystem%MudTypeOp_MudElement%Empty()
  157. DO WHILE(jopmud<= MudSystem%Op_Mud_Forehead_X%Length() .and. jopsection<=F_Counts%BottomHoleIntervalCounts)
  158. jopelement= jopelement+1
  159. MudSystem%TrueMinValue= max(MudSystem%Op_Mud_Forehead_X%Array(jopmud), MudSystem%Xend_OpSection(jopsection))
  160. call MudSystem%Xend_OpMudElement%Add(MudSystem%TrueMinValue)
  161. call TVD_Calculator(MudSystem%TrueMinValue,MudSystem%MudCircVerticalDepth)
  162. call MudSystem%TVDend_OpMudElement%Add(MudSystem%MudCircVerticalDepth)
  163. call MudSystem%Density_OpMudElement%Add(MudSystem%Op_Density%Array(jopmud))
  164. call MudSystem%PipeID_OpMudElement%Add(MudSystem%ID_OpSectionInch(jopsection))
  165. call MudSystem%PipeOD_OpMudElement%Add(MudSystem%OD_OpSectionInch(jopsection))
  166. !call Angle_MudElement%Add(Angle_PipeSection(jopsection))
  167. call MudSystem%MudTypeOp_MudElement%Add(MudSystem%Op_MudOrKick%Array(jopmud))
  168. if (MudSystem%Xend_OpMudElement%Array(jopelement)== MudSystem%Op_Mud_Forehead_X%Array(jopmud)) then
  169. jopmud= jopmud+1
  170. else
  171. jopsection= jopsection+1
  172. endif
  173. ENDDO
  174. do i= 2, MudSystem%Xend_OpMudElement%Length()
  175. call MudSystem%Xstart_OpMudElement%Add(MudSystem%Xend_OpMudElement%Array(i-1))
  176. call MudSystem%TVDstart_OpMudElement%Add(MudSystem%TVDend_OpMudElement%Array(i-1))
  177. enddo
  178. MudSystem%NoBottomHoleMudElements = jopelement
  179. !================================================================
  180. if(allocated(MudSystem%StringMudElement)) deallocate(MudSystem%StringMudElement)
  181. allocate(MudSystem%StringMudElement(MudSystem%NoStringMudElements))
  182. if(allocated(MudSystem%CasingMudElement)) deallocate(MudSystem%CasingMudElement)
  183. allocate(MudSystem%CasingMudElement(MudSystem%NoCasingMudElements+MudSystem%NoBottomHoleMudElements))
  184. MudSystem%istring=0
  185. MudSystem%icasing=0
  186. MudSystem%BitMudDensity= MudSystem%Density_MudElement%Array(MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements) ! (for ROP module)
  187. !================================================================
  188. !============================ UTUBE =============================
  189. !IF (UtubePossibility== .true. .and. Get_KellyConnection() /= KELLY_CONNECTION_STRING .and. WellHeadIsOpen) THEN
  190. IF (MudSystem%UtubePossibility== .true. .and. TD_StConn%FluidStringConnectionMode==0 .and. MudSystem%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(MudSystem%Op_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystem%Op_MudDischarged_Volume%Array(:) <= 0.0)) THEN
  210. do i = 1 , MudSystem%Op_MudOrKick%Length()
  211. write(*,555) i,'Op_Volume(i), type=' ,MudSystem%Op_MudDischarged_Volume%Array(i) , MudSystem%Op_MudOrKick%Array(i) , MudSystem%Op_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(MudSystem%Ann_MudDischarged_Volume%Array(:))) .OR. ANY(MudSystem%Ann_MudDischarged_Volume%Array(:) <= 0.0)) THEN
  216. do i = 1 , MudSystem%Ann_MudOrKick%Length()
  217. write(*,555) i,'Ann_Volume(i), type=' ,MudSystem%Ann_MudDischarged_Volume%Array(i) , MudSystem%Ann_MudOrKick%Array(i) , MudSystem%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. MudSystem%NoStringMudElementsForPlot= MudSystem%NoStringMudElements
  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=MudSystem%NoHorizontalMudElements+1, MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements ! 2-string elements
  232. if (MudSystem%Xend_MudElement%Array(i) <= 0.0) then
  233. MudSystem%NoStringMudElementsForPlot= MudSystem%NoStringMudElementsForPlot-1
  234. cycle
  235. endif
  236. MudSystem%istring= MudSystem%istring+1
  237. MudSystem%StringMudElement(MudSystem%istring)%StartMd = MudSystem%Xstart_MudElement%Array(i)
  238. MudSystem%StringMudElement(MudSystem%istring)%EndMd = MudSystem%Xend_MudElement%Array(i)
  239. !StringMudElement(istring)%Id = PipeID_MudElement%Array(i)
  240. !StringMudElement(istring)%Od = PipeOD_MudElement%Array(i)
  241. MudSystem%StringMudElement(MudSystem%istring)%Density = MudSystem%Density_MudElement%Array(i)
  242. if (MudSystem%MudType_MudElement%Array(i) == 104) then
  243. MudSystem%MudType_MudElement%Array(i)= 4 ! air
  244. elseif (MudSystem%MudType_MudElement%Array(i) > 0 .and. MudSystem%MudType_MudElement%Array(i) < 100) then ! all kicks
  245. MudSystem%MudType_MudElement%Array(i)= 1 ! gas kick
  246. endif
  247. MudSystem%StringMudElement(MudSystem%istring)%MudType = MudSystem%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=MudSystem%Xend_MudElement%Length(), MudSystem%NoHorizontalMudElements+MudSystem%NoStringMudElements+1 , -1 ! 3-casing elements
  251. MudSystem%icasing= MudSystem%icasing+1
  252. MudSystem%CasingMudElement(MudSystem%icasing)%StartMd = MudSystem%Xend_MudElement%Array(i)
  253. MudSystem%CasingMudElement(MudSystem%icasing)%EndMd = MudSystem%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. MudSystem%CasingMudElement(MudSystem%icasing)%Density = MudSystem%Density_MudElement%Array(i)
  260. if (MudSystem%MudType_MudElement%Array(i) == 104) then
  261. MudSystem%MudType_MudElement%Array(i)= 4 ! air
  262. elseif (MudSystem%MudType_MudElement%Array(i) > 0 .and. MudSystem%MudType_MudElement%Array(i) < 100) then
  263. MudSystem%MudType_MudElement%Array(i)= 1 ! gas kick
  264. endif
  265. MudSystem%CasingMudElement(MudSystem%icasing)%MudType = MudSystem%MudType_MudElement%Array(i)
  266. enddo
  267. do i= MudSystem%NoBottomHoleMudElements, 1 , -1 ! 4-open hole elements
  268. MudSystem%icasing= MudSystem%icasing+1
  269. MudSystem%CasingMudElement(MudSystem%icasing)%StartMd = MudSystem%Xend_OpMudElement%Array(i)
  270. MudSystem%CasingMudElement(MudSystem%icasing)%EndMd = MudSystem%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. MudSystem%CasingMudElement(MudSystem%icasing)%Density = MudSystem%Density_OpMudElement%Array(i)
  277. if (MudSystem%MudTypeOp_MudElement%Array(i) == 104) then
  278. MudSystem%MudTypeOp_MudElement%Array(i)= 4 ! air
  279. elseif (MudSystem%MudTypeOp_MudElement%Array(i) > 0 .and. MudSystem%MudTypeOp_MudElement%Array(i) < 100) then
  280. MudSystem%MudTypeOp_MudElement%Array(i)= 1 ! gas kick
  281. endif
  282. MudSystem%CasingMudElement(MudSystem%icasing)%MudType = MudSystem%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(MudSystem%NoStringMudElementsForPlot, MudSystem%StringMudElement) !for data display in string
  289. call SetAnnalusFluids(MudSystem%NoCasingMudElements+MudSystem%NoBottomHoleMudElements, MudSystem%CasingMudElement) !for data display in casing
  290. !===========================================================================================================================
  291. !===========================================================================================================================
  292. end subroutine PlotFinalMudElements