Simulation Core
Você não pode selecionar mais de 25 tópicos Os tópicos devem começar com uma letra ou um número, podem incluir traços ('-') e podem ter até 35 caracteres.
 
 
 
 
 
 

427 linhas
14 KiB

  1. SUBROUTINE ANNULAR
  2. USE VARIABLES
  3. USE CBopControlPanelVariables
  4. USE PressureDisplayVARIABLES
  5. USE CEquipmentsConstants
  6. USE CBopStackVariables
  7. implicit none
  8. !write(*,*) 'checkpoint 1'
  9. !=====================================================================
  10. ! ANNULAR PREVENTER- BOP CAMERON Type U 5000
  11. ! START CONDITIONS FOR ANNULAR PREVENTER
  12. !=====================================================================
  13. RAM(1)%SuccessionCounter = RAM(1)%SuccessionCounter + 1
  14. if (AnnularValve == 1.0 .and. AnnularFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1) then
  15. if (AnnularCloseLedMine == LedOn) then
  16. RETURN
  17. end if
  18. if ( RAM(1)%SuccessionCounter /= RAM(1)%SuccessionCounterOld+1 ) then
  19. RAM(1)%SuccessionCounter = 0 ! also in starup
  20. RAM(1)%SuccessionCounterOld = 0 ! also in starup
  21. !return
  22. else
  23. RAM(1)%SuccessionCounterOld= RAM(1)%SuccessionCounter
  24. endif
  25. if ( RAM(1)%SuccessionCounter >= int(2.5/DeltaT_BOP) ) then
  26. !return
  27. RAM(1)%First_CloseTimecheck= 1
  28. AnnularOpenLed = LedOff
  29. AnnularOpenLedMine = LedOff
  30. AnnularCloseLed = LedOn !LedBlinking
  31. RAM(1)%FourwayValve = 1
  32. endif
  33. endif
  34. if (RAM(1)%FourwayValve == 1 .and. p_acc>acc_MinPressure .and. Pannular_reg>AnnularMovingPressure) then ! 1: Open , 0: Close
  35. RAM(1)%FourwayValve = 0
  36. Annular_closed=0
  37. !Annular_closed_withPossibility= Annular_closed * TD_BOPConnectionPossibility(1)
  38. RAM(1)%vdis_tot=0
  39. RAM(1)%vdis_bottles=0.
  40. RAM(1)%fvr_air=0.
  41. RAM(1)%vdis_elecp=0.
  42. Qiter=7
  43. RAM(1)%Qzero=70
  44. RAM(1)%Q=RAM(1)%Qzero
  45. RAM(1)%flow=70
  46. tolAnnular=0.0018
  47. if (finished_Annular==1) then
  48. AnnularLeverOld=-1.0
  49. else
  50. AnnularLeverOld=AnnularValve
  51. endif
  52. finished_Annular=0
  53. AnnularIsClosing = .true.
  54. AnnularIsOpening = .false.
  55. RAM(2)%bop_type = 3
  56. !AbopAnnular=963.1 !(in^2)
  57. AbopAnnular=(AnnularPreventerClose*231.)/((IDAnnularBase-ODDrillpipe_inAnnularBase)/2.) ! 231 in^3 = 1 gal
  58. NeededVolumeAnnular=AbopAnnular*(IDAnnularBase-max(ODDrillpipe_inAnnular,ODDrillpipe_inAnnularBase))/(2.*231) !=17.98 galon for IDAnnularBase=13 5/8 , ODDrillpipe_inAnnularBase=5
  59. !WRITE(*,*) 'a)NeededVolumeAnnular=' , NeededVolumeAnnular
  60. !write(*,*) 'close 1'
  61. endif
  62. if (AnnularValve == -1.0 .and. AnnularFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1 ) then
  63. if (AnnularOpenLedMine == LedOn) then
  64. RETURN
  65. end if
  66. !CasingPressure : PressureGauges(2) *****temp conditionssssss
  67. !note: (AnnularSealingPressure) is only for opening while well is pressurised
  68. if ( RAM(1)%SuccessionCounter /= RAM(1)%SuccessionCounterOld+1 ) then
  69. RAM(1)%SuccessionCounter = 0 ! also in starup
  70. RAM(1)%SuccessionCounterOld = 0 ! also in starup
  71. !return
  72. else
  73. RAM(1)%SuccessionCounterOld= RAM(1)%SuccessionCounter
  74. endif
  75. if ( RAM(1)%SuccessionCounter >= int(2.5/DeltaT_BOP) ) then
  76. !return
  77. RAM(1)%First_OpenTimecheck= 1
  78. AnnularCloseLed = LedOff !new
  79. AnnularCloseLedMine = LedOff !new
  80. AnnularOpenLed = LedOn !LedBlinking
  81. RAM(1)%FourwayValve = 1
  82. endif
  83. endif
  84. if (RAM(1)%FourwayValve == 1 .and. Pannular_reg>AnnularMovingPressure .and. p_acc>acc_MinPressure &
  85. .and. (Annular_closed==0 .or. (Annular_closed==1 .and.PressureGauges(2) <=100.0) .or. (Annular_closed==1 .and.PressureGauges(2)>100.0 .and. Pannular_reg>=AnnularSealingPressure))) then ! 1: Open , 0: Close
  86. !write(*,*) 'open 2'
  87. RAM(1)%FourwayValve = 0
  88. Annular_closed=0
  89. !Annular_closed_withPossibility= Annular_closed * TD_BOPConnectionPossibility(1)
  90. RAM(1)%vdis_tot=0
  91. RAM(1)%vdis_bottles=0.
  92. RAM(1)%fvr_air=0.
  93. RAM(1)%vdis_elecp=0.
  94. Qiter=7
  95. RAM(1)%Qzero=70
  96. RAM(1)%Q=RAM(1)%Qzero
  97. RAM(1)%flow=70
  98. tolAnnular=0.0018
  99. if (finished_Annular==1) then
  100. AnnularLeverOld=1.0
  101. else
  102. AnnularLeverOld=AnnularValve
  103. endif
  104. finished_Annular=0
  105. AnnularIsOpening = .true.
  106. AnnularIsClosing = .false.
  107. !if (AnnularOpenLed == LedOn) then
  108. ! RETURN
  109. !end if
  110. RAM(1)%bop_type = 3
  111. !AbopAnnular=758.48 !(in^2)
  112. AbopAnnular=(AnnularPreventerOpen*231)/((IDAnnularBase-max(ODDrillpipe_inAnnular,ODDrillpipe_inAnnularBase))/2.)
  113. NeededVolumeAnnular=AbopAnnular*(IDAnnularBase-ODDrillpipe_inAnnular)/(2.*231) !=14.16 galon for IDAnnularBase=13 5/8 , ODDrillpipe_inAnnular=5
  114. !write(*,*) 'open 1'
  115. endif
  116. !=====================================================================
  117. if (AnnularIsOpening .or. AnnularIsClosing .or. RAM(1)%Bottles_Charged_MalfActive) then
  118. CALL ANNULAR_SUB
  119. end if
  120. END SUBROUTINE ANNULAR
  121. SUBROUTINE ANNULAR_SUB
  122. USE VARIABLES
  123. USE PressureDisplayVARIABLES
  124. USE CBopControlPanelVariables
  125. USE CEquipmentsConstants
  126. USE CBopStackVariables
  127. USE CSimulationVariables
  128. implicit none
  129. FirstSet= 0
  130. RamsFirstSet= 0
  131. loop5: do while (finished_Annular==0)
  132. !write(*,*) 'checkpoint 2'
  133. RAM(1)%SuccessionCounter = RAM(1)%SuccessionCounter + 1
  134. ! CALL CPU_TIME(Annular_StartTime)
  135. if (AnnularValve == 1.0 .and. AnnularLeverOld == -1.0 .and. AnnularFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1) then
  136. if ( RAM(1)%First_CloseTimecheck == 0 ) then
  137. if ( RAM(1)%SuccessionCounter /= RAM(1)%SuccessionCounterOld+1 ) then
  138. RAM(1)%SuccessionCounter = 0 ! also in starup
  139. RAM(1)%SuccessionCounterOld = 0 ! also in starup
  140. !return
  141. else
  142. RAM(1)%SuccessionCounterOld= RAM(1)%SuccessionCounter
  143. endif
  144. if ( RAM(1)%SuccessionCounter >= int(2.5/DeltaT_BOP) ) then
  145. !return
  146. AnnularOpenLed = LedOff
  147. AnnularOpenLedMine = LedOff
  148. AnnularCloseLed = LedOn !LedBlinking
  149. RAM(1)%FourwayValve = 1
  150. endif
  151. endif
  152. !write(*,*) 'chekkk 1'
  153. endif
  154. if (RAM(1)%FourwayValve == 1 .and. Pannular_reg>AnnularMovingPressure .and. p_acc>acc_MinPressure) then
  155. !write(*,*) 'close 4'
  156. RAM(1)%FourwayValve = 0
  157. Annular_closed=0
  158. !Annular_closed_withPossibility= Annular_closed * TD_BOPConnectionPossibility(1)
  159. p_annular=pa_annular
  160. AnnularLeverOld = AnnularValve
  161. CALL OpenAnnular
  162. Annular_Situation_forTD= 0 ! open - for TD code
  163. RAM(1)%bop_type = 3
  164. !AbopAnnular=963.1 !(in^2)
  165. AbopAnnular=(AnnularPreventerClose*231)/((IDAnnularBase-ODDrillpipe_inAnnularBase)/2.)
  166. !write(*,*) 'NeededVolumeShearRams1=',NeededVolumeShearRams
  167. NeededVolumeAnnular=AbopAnnular*(IDAnnular-max(ODDrillpipe_inAnnular,ODDrillpipe_inAnnularBase))/(2*231.)
  168. ! write(*,*) 'NeededVolumeAnnular=',NeededVolumeAnnular
  169. RAM(1)%vdis_bottles=0.
  170. RAM(1)%fvr_air=0.
  171. RAM(1)%vdis_elecp=0.
  172. AnnularIsClosing = .true.
  173. AnnularIsOpening = .false.
  174. !write(*,*) 'close 2'
  175. endif
  176. if (AnnularValve == -1.0 .and. AnnularLeverOld == 1.0 .and. p_acc>acc_MinPressure .and. AnnularFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1 ) then
  177. !CasingPressure : PressureGauges(2) *****temp conditionssssss
  178. !note: (AnnularSealingPressure) is only for opening while well is pressurised
  179. if ( RAM(1)%First_OpenTimecheck == 0 ) then
  180. if ( RAM(1)%SuccessionCounter /= RAM(1)%SuccessionCounterOld+1 ) then
  181. RAM(1)%SuccessionCounter = 0 ! also in starup
  182. RAM(1)%SuccessionCounterOld = 0 ! also in starup
  183. !return
  184. else
  185. RAM(1)%SuccessionCounterOld= RAM(1)%SuccessionCounter
  186. endif
  187. if ( RAM(1)%SuccessionCounter >= int(2.5/DeltaT_BOP) ) then
  188. !return
  189. AnnularCloseLed = LedOff
  190. AnnularCloseLedMine= LedOff
  191. AnnularOpenLed = LedOn !LedBlinking
  192. RAM(1)%FourwayValve = 1
  193. endif
  194. endif
  195. !write(*,*) 'chekkk 2'
  196. endif
  197. if (RAM(1)%FourwayValve == 1 .and. Pannular_reg>AnnularMovingPressure &
  198. .and. (Annular_closed==0 .or. (Annular_closed==1 .and.PressureGauges(2) <=100.0) .or. (Annular_closed==1 .and.PressureGauges(2)>100.0 .and. Pannular_reg>=AnnularSealingPressure))) then
  199. !write(*,*) 'open 4'
  200. RAM(1)%FourwayValve = 0
  201. Annular_closed=0
  202. !Annular_closed_withPossibility= Annular_closed * TD_BOPConnectionPossibility(1)
  203. p_annular=pa_annular
  204. AnnularLeverOld = AnnularValve
  205. CALL OpenAnnular
  206. Annular_Situation_forTD= 0 ! open - for TD code
  207. RAM(1)%bop_type = 3
  208. !AbopAnnular=758.48 !(in^2)
  209. AbopAnnular=(AnnularPreventerOpen*231)/((IDAnnularBase-ODDrillpipe_inAnnularBase)/2.)
  210. NeededVolumeAnnular=AbopAnnular*(IDAnnularBase-IDAnnular)/(2*231.)
  211. RAM(1)%vdis_bottles=0.
  212. RAM(1)%fvr_air=0.
  213. RAM(1)%vdis_elecp=0.
  214. AnnularIsOpening = .true.
  215. AnnularIsClosing = .false.
  216. !write(*,*) 'open 2'
  217. endif
  218. RAM(1)%First_CloseTimecheck = 0
  219. RAM(1)%First_OpenTimecheck = 0
  220. RAM(1)%time=RAM(1)%time+DeltaT_BOP !overal time (s)
  221. !===================================================
  222. ! BOP
  223. !===================================================
  224. if (Annular_closed==0) then !bop closing
  225. !write(*,*) 'AnnularIsClosing,AnnularIsOpening' , AnnularIsClosing,AnnularIsOpening
  226. call bop_codeAnnular(1) !ramtype=4 1=RNUMBER
  227. endif !bop is closing
  228. !================================================================
  229. if (Annular_closed==1) then
  230. RAM(1)%Q=0
  231. !p_bop=pram_reg
  232. p_annular=pa_annular
  233. endif
  234. RAM(1)%timecounter_ram=RAM(1)%timecounter_ram+1
  235. ! MiddleRamsStatus = IDshearBop
  236. ! UpperRamsStatus = IDPipeRam1
  237. ! LowerRamsStatus = IDPipeRam2
  238. ! AnnularStatus = IDAnnular
  239. ! AccumulatorPressureGauge = p_acc
  240. ! ManifoldPressureGauge= pram_reg
  241. ! AnnularPressureGauge=Pannular_reg
  242. !
  243. !
  244. !
  245. ! WRITE(60,60) RAM(1)%time,RAM(1)%Q,RAM(1)%vdis_tot,p_acc, &
  246. ! pram_reg,Pannular_reg,RAM(1)%p_bop,IDshearBop, &
  247. ! IDPipeRam1,IDPipeRam2,IDAnnular
  248. !60 FORMAT(11(f18.5))
  249. call sleepqq(100)
  250. !CALL CPU_TIME(Annular_EndTime)
  251. !
  252. !
  253. !PUMP(1)%INT_CPU_TIME=IDINT((Annular_EndTime-Annular_StartTime)*1000.)
  254. !PUMP(1)%Dt_ref=IDINT(DeltaT_BOP*1000.)
  255. !
  256. !call sleepqq(PUMP(1)%Dt_ref-PUMP(1)%INT_CPU_TIME)
  257. if (Annular_closed==1) then
  258. ! if ((MiddleRamsValve==1. .and. MiddleRamsFailureMalf==0) .or. (MiddleRamsValve==-1.0 .and. MiddleRamsFailureMalf==0) .or. (LowerRamsValve==1. .and. LowerRamsFailureMalf==0) .or. (LowerRamsValve==-1.0 .and. LowerRamsFailureMalf==0) .or. (UpperRamsValve==1. .and. UpperRamsFailureMalf==0) .or. (UpperRamsValve==-1.0 .and. UpperRamsFailureMalf==0) .or. ChokeLineValve==1. .or. ChokeLineValve==-1.0 .or. KillLineValve==1. .or. KillLineValve==-1.0) then
  259. finished_Annular=1
  260. ! endif
  261. endif
  262. if (IsStopped == .true.) return
  263. end do loop5 !while finished_Annular==0
  264. if ( finished_Annular==1 .and. RAM(1)%Bottles_Charged_MalfActive==.true.) then
  265. call bop_codeAnnular(1) !ramtype=4 1=RNUMBER
  266. call sleepqq(100)
  267. endif
  268. END SUBROUTINE ANNULAR_SUB