Simulation Core
Du kannst nicht mehr als 25 Themen auswählen Themen müssen entweder mit einem Buchstaben oder einer Ziffer beginnen. Sie können Bindestriche („-“) enthalten und bis zu 35 Zeichen lang sein.

CDownHoleVariables.f90 12 KiB

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