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.

CDownHoleVariables.f90 12 KiB

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