Simulation Core
您最多选择25个主题 主题必须以字母或数字开头,可以包含连字符 (-),并且长度不得超过35个字符
 
 
 
 
 
 

292 行
11 KiB

  1. module CDownHoleVariables
  2. use CDownHoleTypes
  3. use CStringConfigurationVariables
  4. use CDownHoleActions
  5. use CLog4
  6. implicit none
  7. public
  8. logical :: AnnDrillMud
  9. logical :: AnnCirculateMud
  10. integer :: AnnalusFluidsCount = 0
  11. integer :: StringFluidsCount = 0
  12. type(CFluid), allocatable, target :: AnnalusFluids(:)
  13. type(CFluid), allocatable :: StringFluids(:)
  14. integer :: StringCount = 0
  15. type(CStringComponent), allocatable :: String(:)
  16. type(CBopElement), allocatable :: BopElements(:)
  17. real(8) :: DrillPipePressure
  18. real(8) :: CasingPressure
  19. real(8) :: ShoePressure
  20. real(8) :: BottomHolePressure
  21. real(8) :: FormationPressure
  22. real :: InfluxRate
  23. real :: KickVolume
  24. real :: SecondKickVolume
  25. real :: PermeabilityExposedHeight
  26. real(8) :: Density
  27. real(8) :: Pressure
  28. real(8) :: Temperature
  29. real(8) :: Height
  30. real(8) :: Volume
  31. contains
  32. subroutine SetAnnalusFluids(count, array)
  33. implicit none
  34. integer, intent(in) :: count
  35. integer :: i, offset
  36. type(CFluid), intent(inout), target :: array(count)
  37. type(CFluid), pointer :: item
  38. AnnalusFluidsCount = count
  39. print*, 'AnnalusFluidsCount = ', count
  40. if(size(AnnalusFluids) > 0) then
  41. deallocate(AnnalusFluids)
  42. end if
  43. if(count > 0) then
  44. offset = 0;
  45. item => array(1)
  46. if(item%StartMd > 0) then
  47. AnnalusFluidsCount = AnnalusFluidsCount + 1
  48. offset = 1;
  49. allocate(AnnalusFluids(AnnalusFluidsCount))
  50. AnnalusFluids(1)%StartMd = 0
  51. AnnalusFluids(1)%EndMd = item%StartMd
  52. AnnalusFluids(1)%Density = 0
  53. AnnalusFluids(1)%MudType = FLUID_NO_MUD
  54. endif
  55. !if(associated(AnnalusMudCountPtr)) then
  56. ! call AnnalusMudCountPtr(AnnalusFluidsCount)
  57. !end if
  58. if(.not.allocated(AnnalusFluids))allocate(AnnalusFluids(AnnalusFluidsCount))
  59. !print*, '============START-AN============'
  60. if(item%StartMd < 0) AnnalusFluids(1)%StartMd = 0
  61. do i = 1, count
  62. item => array(i)
  63. AnnalusFluids(i + offset)%StartMd = item%StartMd
  64. if(i==1) AnnalusFluids(i)%StartMd = 0
  65. !print*, 'AnnalusFluids(',i,')%StartMd=', AnnalusFluids(i)%StartMd
  66. AnnalusFluids(i + offset)%EndMd = item%EndMd
  67. !print*, 'AnnalusFluids(',i,')%EndMd=', AnnalusFluids(i)%EndMd
  68. AnnalusFluids(i + offset)%Density = item%Density
  69. !print*, 'AnnalusFluids(',i,')%Density=', AnnalusFluids(i)%Density
  70. AnnalusFluids(i + offset)%MudType = item%MudType
  71. !print*, 'AnnalusFluids(',i,')%MudType=', AnnalusFluids(i)%MudType
  72. !print*, '----------------------------'
  73. end do
  74. !print*, '============END-AN============'
  75. !if(associated(AnnalusMudArrayPtr)) then
  76. ! !AnnalusFluidsPtr => AnnalusFluids
  77. ! call AnnalusMudArrayPtr(AnnalusFluids)
  78. !end if
  79. end if
  80. end subroutine SetAnnalusFluids
  81. subroutine SetStringFluids(count, array)
  82. implicit none
  83. integer, intent(in) :: count
  84. integer :: i, offset !, startArr
  85. type(CFluid), intent(inout), target :: array(count)
  86. type(CFluid), pointer :: item
  87. StringFluidsCount = count
  88. print*, 'StringFluidsCount = ', count
  89. if(size(StringFluids) > 0) then
  90. deallocate(StringFluids)
  91. end if
  92. !startArr = 1
  93. if(count > 0) then
  94. offset = 0;
  95. item => array(1)
  96. !
  97. !if(item%StartMd <= 0 .and. item%EndMd <= 0) then
  98. ! StringFluidsCount = StringFluidsCount - 1
  99. ! count = count - 1
  100. ! offset = offset + 1
  101. ! startArr = startArr + 1
  102. !endif
  103. !
  104. !if(count <= 0) return
  105. if(item%StartMd > 0) then
  106. StringFluidsCount = StringFluidsCount + 1
  107. offset = offset + 1
  108. allocate(StringFluids(StringFluidsCount))
  109. StringFluids(1)%StartMd = 0
  110. StringFluids(1)%EndMd = item%StartMd
  111. StringFluids(1)%Density = 0
  112. StringFluids(1)%MudType = FLUID_NO_MUD
  113. endif
  114. !if(associated(StringMudCountPtr)) then
  115. ! call StringMudCountPtr(count)
  116. !end if
  117. if(.not.allocated(StringFluids))allocate(StringFluids(StringFluidsCount))
  118. !print*, '============START-ST============'
  119. !print*, 'count=', count
  120. do i = 1, count
  121. item => array(i)
  122. StringFluids(i + offset)%StartMd = item%StartMd
  123. if(i==1) StringFluids(i)%StartMd = 0
  124. !print*, 'StringFluids(i)%StartMd=', StringFluids(i)%StartMd
  125. StringFluids(i + offset)%EndMd = item%EndMd
  126. !print*, 'StringFluids(i)%EndMd=', StringFluids(i)%EndMd
  127. StringFluids(i + offset)%Density = item%Density
  128. StringFluids(i + offset)%MudType = item%MudType
  129. !print*, '----------------------------'
  130. end do
  131. !!if(item%StartMd < 0) StringFluids(1)%StartMd = 0
  132. !!print*, '============END-ST============'
  133. !if(associated(StringMudArrayPtr)) then
  134. ! call StringMudArrayPtr(StringFluids)
  135. !end if
  136. end if
  137. end subroutine SetStringFluids
  138. subroutine SetString(count, array)
  139. use CLog3
  140. implicit none
  141. integer, intent(in) :: count
  142. integer :: i !, j
  143. type(CStringComponents), intent(inout), target :: array(count)
  144. type(CStringComponents), pointer :: item
  145. StringCount = count
  146. if(size(String) > 0) then
  147. deallocate(String)
  148. end if
  149. if(count > 0) then
  150. !if(associated(StringComponentCountPtr)) then
  151. ! call StringComponentCountPtr(count)
  152. !end if
  153. allocate(String(count))
  154. !j = 0
  155. !print*, '============CMP-ST============'
  156. !call Log_3( '============CMP-ST============')
  157. !do i = count, 1, -1
  158. do i = 1, count
  159. item => array(i)
  160. !String(i)%Length = item%Length
  161. !String(i)%TopDepth = item%TopDepth
  162. !String(i)%DownDepth = item%DownDepth
  163. !String(i)%Od = item%Od
  164. !String(i)%Id = item%Id
  165. String(i)%ComponentType= item%ComponentType
  166. !j = j + 1
  167. String(i)%StartMd = item%TopDepth
  168. String(i)%EndMd = item%DownDepth
  169. String(i)%ComponentType=0
  170. !if(item%ComponentType > 4 ) then
  171. ! String(i)%ComponentType=0
  172. ! String(i)%StartMd = 0
  173. !endif
  174. if(item%ComponentType == 3) String(i)%ComponentType=0
  175. if(item%ComponentType == 4) String(i)%ComponentType=1
  176. if(item%ComponentType == 2) String(i)%ComponentType=2
  177. if(item%ComponentType == 1) String(i)%ComponentType=3
  178. !print*, 'item%ComponentType=', item%ComponentType
  179. !print*, 'String(i)%ComponentType=', String(i)%ComponentType
  180. !print*, 'String(i)%StartMd=', String(i)%StartMd
  181. !print*, 'String(i)%EndMd=', String(i)%EndMd
  182. !print*, '----------------------------'
  183. !call Log_3( 'item%ComponentType=', item%ComponentType)
  184. !call Log_3( 'String(i)%ComponentType=', String(i)%ComponentType)
  185. !call Log_3( 'String(i)%StartMd=', String(i)%StartMd)
  186. !call Log_3( 'String(i)%EndMd=', String(i)%EndMd)
  187. !call Log_3( '----------------------------')
  188. end do
  189. !!print*, '============CMP-ST============'
  190. !!call Log_3( '============CMP-ST============')
  191. !if(associated(StringComponentArrayPtr)) then
  192. ! call StringComponentArrayPtr(String)
  193. !end if
  194. end if
  195. end subroutine SetString
  196. subroutine SetBopElements(array)
  197. use CLog4
  198. implicit none
  199. integer, parameter :: count = 4
  200. integer :: i = 1 !, j
  201. type(CBopElement), intent(inout), target :: array(count)
  202. type(CBopElement), pointer :: item
  203. if(size(BopElements) > 0) deallocate(BopElements)
  204. allocate(BopElements(count))
  205. do i = 1, count
  206. item => array(i)
  207. !call Log_4('item%ElementStart', item%ElementStart)
  208. !call Log_4('item%ElementEnd', item%ElementEnd)
  209. !call Log_4('item%ElementType', item%ElementType)
  210. !call Log_4('=====================================================')
  211. BopElements(i)%ElementStart = item%ElementStart
  212. BopElements(i)%ElementEnd = item%ElementEnd
  213. BopElements(i)%ElementType = item%ElementType
  214. end do
  215. !if(associated(BopElementsPtr)) call BopElementsPtr(BopElements)
  216. end subroutine SetBopElements
  217. subroutine GetAnnalusFluidInfo(md)
  218. !DEC$ ATTRIBUTES DLLEXPORT::GetAnnalusFluidInfo
  219. !DEC$ ATTRIBUTES ALIAS: 'GetAnnalusFluidInfo' :: GetAnnalusFluidInfo
  220. !use ElementFinderVars
  221. implicit none
  222. integer, intent(in) :: md
  223. call AnnulusPropertyCalculator(md, Density, Pressure, Temperature)
  224. !ObservationPoint(2)%MeasureDepth = md
  225. !Density = md + Density - 10
  226. !Pressure = md + Pressure - 20
  227. !Temperature = md + Temperature - 30
  228. !Height = Height * 100.0
  229. !Volume = Volume * 200.0
  230. !
  231. !call Log_4('GetAnnalusFluidInfo=', md)
  232. !call Log_4('A_Height=', Height)
  233. !call Log_4('A_Volume=', Volume)
  234. #ifdef deb
  235. print*, 'GetAnnalusFluidInfo=', md
  236. #endif
  237. end subroutine GetAnnalusFluidInfo
  238. subroutine GetStringFluidInfo(md)
  239. !DEC$ ATTRIBUTES DLLEXPORT::GetStringFluidInfo
  240. !DEC$ ATTRIBUTES ALIAS: 'GetStringFluidInfo' :: GetStringFluidInfo
  241. implicit none
  242. integer, intent(in) :: md
  243. call StringPropertyCalculator(md, Density, Pressure, Temperature)
  244. !ObservationPoint(1)%MeasureDepth = md
  245. !Density = md + Density + 100
  246. !Pressure = md + Pressure + 200
  247. !Temperature = md + Temperature + 300
  248. !Height = Height * 100.0
  249. !Volume = Volume * 200.0
  250. !
  251. !call Log_4('GetStringFluidInfo=', md)
  252. !call Log_4('S_Height=', Height)
  253. !call Log_4('S_Volume=', Volume)
  254. #ifdef deb
  255. print*, 'GetStringFluidInfo=', md
  256. #endif
  257. end subroutine GetStringFluidInfo
  258. end module CDownHoleVariables