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.

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