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.

Kick_Expansion_and_Contraction.f90 10 KiB

1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
1 year ago
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235
  1. subroutine Kick_Expansion ! is called in subroutine CirculationCodeSelect
  2. Use GeoElements_FluidModule
  3. USE CMudPropertiesVariables
  4. USE MudSystemVARIABLES
  5. USE Pumps_VARIABLES
  6. use CDrillWatchVariables
  7. !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
  8. USE sROP_Other_Variables
  9. USE sROP_Variables
  10. USE CReservoirVariables
  11. USE KickVARIABLES
  12. implicit none
  13. real(8) ExpansionVolume
  14. !write(*,*) 'Kick Expansion'
  15. ExpansionVolume= GasPocketDeltaVol%Array(NewInfluxNumber - KickNumber + 1) * 7.48
  16. IF ( Kickexpansion_DueToMudLost ) ExpansionVolume = ((Qlost/60.0d0)*DeltaT_Mudline)
  17. !============================== kick zire mate bashad ==============================
  18. if (Op_KickLoc > 0 .and. Ann_KickLoc==0) then ! .and. Op_KickLoc /= Op_MudOrKick%Length ()) then
  19. !write(*,*) 'expansion (1)'
  20. Op_MudDischarged_Volume%Array(Op_KickLoc)= Op_MudDischarged_Volume%Array(Op_KickLoc)+ ExpansionVolume
  21. !if (MUD(4)%Q > 0.) then
  22. !
  23. ! if (abs(ChokeLine_Density%Array(1)-Ann_Density%Last())< DensityMixTol) then
  24. ! ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1) + ExpansionVolume
  25. ! else
  26. ! call ChokeLine_Density%AddToFirst (Ann_Density%Last())
  27. ! call ChokeLine_MudDischarged_Volume%AddToFirst (ExpansionVolume) ! farz kardam ke hameye hajm ro ba yek density ezafe konim
  28. ! call ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
  29. ! call ChokeLine_Mud_Forehead_section%AddToFirst (1)
  30. ! call ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
  31. ! call ChokeLine_Mud_Backhead_section%AddToFirst (1)
  32. ! call ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  33. ! call ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  34. ! call ChokeLine_MudOrKick%AddToFirst (Ann_MudOrKick%Last())
  35. ! endif
  36. !
  37. !endif
  38. endif
  39. !========================================================================================
  40. !============================= foreheade dar fazaye annulus bashad ===========================
  41. ! agar kick be entehaye annulus reside bashe, expansion ra emaal nemikonim
  42. if (Ann_KickLoc > 0) then ! .and. Ann_KickLoc /= Ann_MudOrKick%Length ()) then
  43. !write(*,*) 'expansion (2)'
  44. !if ( sum(Ann_MudDischarged_Volume%Array(1:Ann_KickLoc)) + ExpansionVolume > sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) ) then ! agar khast az mate rad kone
  45. ! ExpansionVolume= sum(PipeSection_VolumeCapacity(F_StringIntervalCounts+1:NoPipeSections)) - sum(Ann_MudDischarged_Volume%Array(1:Ann_KickLoc))
  46. !endif
  47. Ann_MudDischarged_Volume%Array(Ann_KickLoc)= Ann_MudDischarged_Volume%Array(Ann_KickLoc)+ ExpansionVolume
  48. !if (MUD(4)%Q > 0.) then
  49. !
  50. !
  51. ! if (abs(ChokeLine_Density%Array(1)-Ann_Density%Last())< DensityMixTol) then
  52. ! ChokeLine_MudDischarged_Volume%Array(1)= ChokeLine_MudDischarged_Volume%Array(1) + ExpansionVolume
  53. ! else
  54. ! call ChokeLine_Density%AddToFirst (Ann_Density%Last())
  55. ! call ChokeLine_MudDischarged_Volume%AddToFirst (ExpansionVolume) ! farz kardam ke hameye hajm ro ba yek density ezafe konim
  56. ! call ChokeLine_Mud_Forehead_X%AddToFirst (0.0d0)
  57. ! call ChokeLine_Mud_Forehead_section%AddToFirst (1)
  58. ! call ChokeLine_Mud_Backhead_X%AddToFirst (0.0d0)
  59. ! call ChokeLine_Mud_Backhead_section%AddToFirst (1)
  60. ! call ChokeLine_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
  61. ! call ChokeLine_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
  62. ! call ChokeLine_MudOrKick%AddToFirst (Ann_MudOrKick%Last())
  63. ! endif
  64. !
  65. !endif
  66. endif
  67. !========================================================================================
  68. !=============================== foreheade dar choke line bashad =============================
  69. if (ChokeLine_KickLoc > 0 .and. Ann_KickLoc==0) then
  70. ChokeLine_MudDischarged_Volume%Array(ChokeLine_KickLoc)= ChokeLine_MudDischarged_Volume%Array(ChokeLine_KickLoc)+ ExpansionVolume
  71. endif
  72. !========================================================================================
  73. !write(*,*) 'Expansion======0'
  74. ! !do imud=1, Ann_MudDischarged_Volume%Length()
  75. ! ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  76. ! !enddo
  77. !
  78. ! do imud=1, Op_MudDischarged_Volume%Length()
  79. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  80. ! enddo
  81. !write(*,*) '0======expansion'
  82. end subroutine Kick_Expansion
  83. subroutine Kick_Contraction ! is called in subroutine CirculationCodeSelect
  84. Use GeoElements_FluidModule
  85. USE CMudPropertiesVariables
  86. USE MudSystemVARIABLES
  87. USE Pumps_VARIABLES
  88. use CDrillWatchVariables
  89. !use CTanksVariables, TripTankVolume2 => DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
  90. USE sROP_Other_Variables
  91. USE sROP_Variables
  92. USE CReservoirVariables
  93. USE KickVARIABLES
  94. USE CError
  95. implicit none
  96. integer jelement, jmud, jsection,ielement,i
  97. integer jopelement,jopmud,jopsection
  98. real(8) ContractionVolume
  99. !*********************************************************
  100. ! contraction is always with pump flow
  101. !*********************************************************
  102. !write(*,*) 'Kick Contraction'
  103. !MUD(2)%Q= total_pumps%Total_Pump_GPM
  104. StringFlowRate= MUD(2)%Q
  105. AnnulusFlowRate= MUD(2)%Q
  106. if (NewPipeFilling == 0) then
  107. StringFlowRate= 0.
  108. AnnulusFlowRate= 0.
  109. endif
  110. !if (WellHeadIsOpen) then
  111. ContractionVolume= - GasPocketDeltaVol%Array(NewInfluxNumber - KickNumber + 1) * 7.48
  112. !else
  113. !ContractionVolume = (StringFlowRate/60.0d0)*DeltaT_Mudline + DeltaVolumePipe
  114. if (KickNumber == 1 .and. WellHeadIsOpen==.false.) ContractionVolume = ContractionVolume + (StringFlowRate/60.0d0)*DeltaT_Mudline + DeltaVolumePipe
  115. !endif
  116. !**************************************************************************************************************************************************************************
  117. ! pump mud is added in "pump&TripIn" code
  118. IF (Op_KickLoc > 0 .and. Ann_KickLoc == 0) then ! All of kick is under bit (iloc == 1)
  119. Op_MudDischarged_Volume%Array(Op_KickLoc)= Op_MudDischarged_Volume%Array(Op_KickLoc) - ( ContractionVolume )
  120. ELSE IF (Op_KickLoc == 0 .AND. Ann_KickLoc > 0 .AND. ChokeLine_KickLoc == 0) THEN ! All of kick is an Annulus (iloc == 1)
  121. Ann_MudDischarged_Volume%Array(Ann_KickLoc)= Ann_MudDischarged_Volume%Array(Ann_KickLoc) - ( ContractionVolume )
  122. ELSE IF (Ann_KickLoc == 0 .AND. ChokeLine_KickLoc > 0) THEN ! kick is in chokeline only
  123. ChokeLine_MudDischarged_Volume%Array(ChokeLine_KickLoc)= ChokeLine_MudDischarged_Volume%Array(ChokeLine_KickLoc) - ( ContractionVolume )
  124. ELSE IF (Op_KickLoc > 0 .AND. Ann_KickLoc > 0) THEN ! Kick is around bit (iloc==2)
  125. if (Ann_MudDischarged_Volume%Array(1) > ContractionVolume ) then
  126. Ann_MudDischarged_Volume%Array(1)= Ann_MudDischarged_Volume%Array(1) - ( ContractionVolume )
  127. elseif (Op_MudDischarged_Volume%Last() > ContractionVolume ) then
  128. Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length())= Op_MudDischarged_Volume%Array(Op_MudDischarged_Volume%Length()) - ( ContractionVolume )
  129. else
  130. Call ErrorStop ('kick contraction error 1')
  131. endif
  132. ELSE IF (Ann_KickLoc > 0 .AND. ChokeLine_KickLoc > 0) THEN
  133. if (ChokeLine_MudDischarged_Volume%Array(1) > ContractionVolume ) then
  134. ChokeLine_MudDischarged_Volume%Array(1) = ChokeLine_MudDischarged_Volume%Array(1) - ( ContractionVolume )
  135. elseif (Ann_MudDischarged_Volume%Last() > ContractionVolume ) then
  136. Ann_MudDischarged_Volume%Array(Ann_MudDischarged_Volume%Length())= Ann_MudDischarged_Volume%Array(Ann_MudDischarged_Volume%Length()) - ( ContractionVolume )
  137. else
  138. Call ErrorStop ('kick contraction error 2')
  139. endif
  140. endif
  141. ! write(*,*) 'contract======0'
  142. !! !do imud=1, Ann_MudDischarged_Volume%Length()
  143. !! ! write(*,*) 'Ann:', imud, Ann_MudDischarged_Volume%Array(imud), Ann_Density%Array(imud) ,Ann_MudOrKick%Array(imud)
  144. !! !enddo
  145. !!
  146. ! do imud=1, Op_MudDischarged_Volume%Length()
  147. ! write(*,*) 'Op:', imud, Op_MudDischarged_Volume%Array(imud), Op_Density%Array(imud) ,Op_MudOrKick%Array(imud)
  148. ! enddo
  149. !write(*,*) '0======contract'
  150. end subroutine Kick_Contraction