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