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.
 
 
 
 
 
 

396 lines
13 KiB

  1. SUBROUTINE PIPE_RAMS2
  2. USE VARIABLES
  3. USE CBopStackVariables
  4. USE CBopControlPanelVariables
  5. USE CEquipmentsConstants
  6. ! ! use CSimulationVariables
  7. implicit none
  8. !write(*,*) 'checkpoint 1'
  9. !=====================================================================
  10. ! PIPE RAMS 2- BOP CAMERON Type U 5000
  11. ! START CONDITIONS FOR PIPE RAMS 2
  12. !=====================================================================
  13. RAM(3)%SuccessionCounter = RAM(3)%SuccessionCounter + 1
  14. if (BopControlPanel%LowerRamsValve == 1.0 .and. PipeRam2%LowerRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then
  15. !write(*,*) 'close 1'
  16. if (BopStackInput%LowerRamsCloseLEDMine == LedOn) then
  17. RETURN
  18. end if
  19. if ( RAM(3)%SuccessionCounter /= RAM(3)%SuccessionCounterOld+1 ) then
  20. RAM(3)%SuccessionCounter = 0 ! also in starup
  21. RAM(3)%SuccessionCounterOld = 0 ! also in starup
  22. !return
  23. else
  24. RAM(3)%SuccessionCounterOld= RAM(3)%SuccessionCounter
  25. endif
  26. if ( RAM(3)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then
  27. !return
  28. RAM(3)%First_CloseTimecheck= 1
  29. BopControlPanel%LowerRamsOpenLED = LedOff
  30. BopStackInput%LowerRamsOpenLEDMine = LedOff
  31. BopControlPanel%LowerRamsCloseLED = LedOn !LedBlinking
  32. RAM(3)%FourwayValve = 1
  33. endif
  34. endif
  35. if (RAM(3)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then ! 1: Open , 0: Close
  36. !write(*,*) 'close 2'
  37. RAM(3)%FourwayValve = 0
  38. PipeRam2%closed=0
  39. !PipeRam2_closed_withPossibility= PipeRam2_closed * TD_BOPConnectionPossibility(4)
  40. RAM(3)%vdis_tot=0
  41. RAM(3)%vdis_bottles=0.
  42. RAM(3)%fvr_air=0.
  43. RAM(3)%vdis_elecp=0.
  44. Pumps%Qiter=7
  45. RAM(3)%Qzero=70
  46. RAM(3)%Q=RAM(3)%Qzero
  47. RAM(3)%flow=70
  48. RAM(3)%tol=0.0037
  49. if (PipeRam2%finished==1) then
  50. PipeRam2%LeverOld=-1.0
  51. else
  52. PipeRam2%LeverOld=BopControlPanel%LowerRamsValve
  53. endif
  54. PipeRam2%finished=0
  55. PipeRam2%IsClosing = .true.
  56. PipeRam2%IsOpening = .false.
  57. RAM(3)%bop_type = 3
  58. !AbopPipeRam=196.67
  59. PipeRam1%A=(BopStackSpecification%LowerRamClose*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.)
  60. PipeRam2%NeededVolume=PipeRam1%A*(PipeRam1%IDBase-max(PipeRam2%ODDrillpipe_in,PipeRam1%ODDrillpipe_inBase))/(2.*231) !galon for each BOP
  61. !write(*,*) 'close 1'
  62. endif
  63. if (BopControlPanel%LowerRamsValve == -1.0 .and. PipeRam2%LowerRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then
  64. !write(*,*) 'open 1'
  65. if (BopStackInput%LowerRamsOpenLEDMine == LedOn) then
  66. RETURN
  67. end if
  68. if ( RAM(3)%SuccessionCounter /= RAM(3)%SuccessionCounterOld+1 ) then
  69. RAM(3)%SuccessionCounter = 0 ! also in starup
  70. RAM(3)%SuccessionCounterOld = 0 ! also in starup
  71. !return
  72. else
  73. RAM(3)%SuccessionCounterOld= RAM(3)%SuccessionCounter
  74. endif
  75. if ( RAM(3)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then
  76. !return
  77. RAM(3)%First_OpenTimecheck= 1
  78. BopControlPanel%LowerRamsCloseLED = LedOff !new
  79. BopStackInput%LowerRamsCloseLEDMine = LedOff !new
  80. BopControlPanel%LowerRamsOpenLED = LedOn !LedBlinking
  81. RAM(3)%FourwayValve = 1
  82. endif
  83. endif
  84. if (RAM(3)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then ! 1: Open , 0: Close
  85. !write(*,*) 'open 2'
  86. RAM(3)%FourwayValve = 0
  87. PipeRam2%closed=0
  88. !PipeRam2_closed_withPossibility= PipeRam2_closed * TD_BOPConnectionPossibility(4)
  89. RAM(3)%vdis_tot=0
  90. RAM(3)%vdis_bottles=0.
  91. RAM(3)%fvr_air=0.
  92. RAM(3)%vdis_elecp=0.
  93. Pumps%Qiter=7
  94. RAM(3)%Qzero=70
  95. RAM(3)%Q=RAM(3)%Qzero
  96. RAM(3)%flow=70
  97. RAM(3)%tol=0.0037
  98. if (PipeRam2%finished==1) then
  99. PipeRam2%LeverOld=1.0
  100. else
  101. PipeRam2%LeverOld=BopControlPanel%LowerRamsValve
  102. endif
  103. PipeRam2%finished=0
  104. PipeRam2%IsOpening = .true.
  105. PipeRam2%IsClosing = .false.
  106. !if (LowerRamsOpenLED == LedOn) then
  107. ! RETURN
  108. !end if
  109. RAM(3)%bop_type = 3
  110. !AbopPipeRam=186.5
  111. PipeRam1%A=(BopStackSpecification%LowerRamOpen*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.)
  112. PipeRam2%NeededVolume=PipeRam1%A*(PipeRam1%IDBase-max(PipeRam2%ODDrillpipe_in,PipeRam1%ODDrillpipe_inBase))/(2.*231) !galon for each BOP
  113. !write(*,*) 'open 1'
  114. endif
  115. !=====================================================================
  116. if (PipeRam2%IsOpening .or. PipeRam2%IsClosing .or. RAM(3)%Bottles_Charged_MalfActive) then
  117. Annular%FirstSet= 0
  118. AnnularComputational%RamsFirstSet= 0
  119. CALL PIPE_RAMS2_SUB
  120. end if
  121. END SUBROUTINE PIPE_RAMS2
  122. SUBROUTINE PIPE_RAMS2_SUB
  123. USE VARIABLES
  124. USE CBopStackVariables
  125. USE CBopControlPanelVariables
  126. USE CEquipmentsConstants
  127. ! use CSimulationVariables
  128. implicit none
  129. ! FirstSet= 0
  130. ! RamsFirstSet= 0
  131. ! loop4: do while (finished_pipe2==0)
  132. !write(*,*) 'checkpoint 2'
  133. RAM(3)%SuccessionCounter = RAM(3)%SuccessionCounter + 1
  134. if (BopControlPanel%LowerRamsValve == 1.0 .and. PipeRam2%LeverOld == -1.0 .and. PipeRam2%LowerRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then
  135. !write(*,*) 'close 3'
  136. if ( RAM(3)%First_CloseTimecheck == 0 ) then
  137. if ( RAM(3)%SuccessionCounter /= RAM(3)%SuccessionCounterOld+1 ) then
  138. RAM(3)%SuccessionCounter = 0 ! also in starup
  139. RAM(3)%SuccessionCounterOld = 0 ! also in starup
  140. !return
  141. else
  142. RAM(3)%SuccessionCounterOld= RAM(3)%SuccessionCounter
  143. endif
  144. if ( RAM(3)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then
  145. !return
  146. BopControlPanel%LowerRamsOpenLED = LedOff
  147. BopStackInput%LowerRamsOpenLEDMine = LedOff
  148. BopControlPanel%LowerRamsCloseLED = LedOn !LedBlinking
  149. RAM(3)%FourwayValve = 1
  150. endif
  151. endif
  152. endif
  153. if (RAM(3)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then
  154. !write(*,*) 'close 4'
  155. RAM(3)%FourwayValve = 0
  156. PipeRam2%closed=0
  157. !PipeRam2_closed_withPossibility= PipeRam2_closed * TD_BOPConnectionPossibility(4)
  158. RAM(3)%p_bop=ShearRam%PA
  159. PipeRam2%LeverOld = BopControlPanel%LowerRamsValve
  160. CALL OpenLowerRams
  161. PipeRam2%Situation_forTD= 0 ! open - for TD code
  162. RAM(3)%bop_type = 3
  163. !AbopPipeRam=196.67
  164. PipeRam1%A=(BopStackSpecification%LowerRamClose*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.)
  165. PipeRam2%NeededVolume=PipeRam1%A*(PipeRam2%ID-max(PipeRam2%ODDrillpipe_in,PipeRam1%ODDrillpipe_inBase))/(2.*231)
  166. RAM(3)%vdis_bottles=0.
  167. RAM(3)%fvr_air=0.
  168. RAM(3)%vdis_elecp=0.
  169. PipeRam2%IsClosing = .true.
  170. PipeRam2%IsOpening = .false.
  171. !write(*,*) 'close 2'
  172. endif
  173. if (BopControlPanel%LowerRamsValve == -1.0 .and. PipeRam2%LeverOld == 1.0 .and. PipeRam2%LowerRamsFailureMalf==0 .and. BopStackAcc%RigAirMalf==0 .and. BopControlPanel%AirMasterValve==1) then
  174. !write(*,*) 'open 3'
  175. if ( RAM(3)%First_OpenTimecheck == 0 ) then
  176. if ( RAM(3)%SuccessionCounter /= RAM(3)%SuccessionCounterOld+1 ) then
  177. RAM(3)%SuccessionCounter = 0 ! also in starup
  178. RAM(3)%SuccessionCounterOld = 0 ! also in starup
  179. !return
  180. else
  181. RAM(3)%SuccessionCounterOld= RAM(3)%SuccessionCounter
  182. endif
  183. if ( RAM(3)%SuccessionCounter >= int(2.5/RamLine%DeltaT_BOP) ) then
  184. !return
  185. BopControlPanel%LowerRamsCloseLED = LedOff
  186. BopStackInput%LowerRamsCloseLEDMine = LedOff
  187. BopControlPanel%LowerRamsOpenLED = LedOn !LedBlinking
  188. RAM(3)%FourwayValve = 1
  189. endif
  190. endif
  191. endif
  192. if (RAM(3)%FourwayValve == 1 .and. RamLine%P_ACC>BopStackAcc%acc_MinPressure) then
  193. !write(*,*) 'open 4'
  194. RAM(3)%FourwayValve = 0
  195. PipeRam2%closed=0
  196. !PipeRam2_closed_withPossibility= PipeRam2_closed * TD_BOPConnectionPossibility(4)
  197. RAM(3)%p_bop=ShearRam%PA
  198. PipeRam2%LeverOld = BopControlPanel%LowerRamsValve
  199. CALL OpenLowerRams
  200. PipeRam2%Situation_forTD= 0 ! open - for TD code
  201. RAM(3)%bop_type = 3
  202. !AbopPipeRam=186.5
  203. PipeRam1%A=(BopStackSpecification%LowerRamOpen*231)/((PipeRam1%IDBase-PipeRam1%ODDrillpipe_inBase)/2.)
  204. PipeRam2%NeededVolume=PipeRam1%A*(PipeRam1%IDBase-PipeRam2%ID)/(2.*231)
  205. RAM(3)%vdis_bottles=0.
  206. RAM(3)%fvr_air=0.
  207. RAM(3)%vdis_elecp=0.
  208. PipeRam2%IsOpening = .true.
  209. PipeRam2%IsClosing = .false.
  210. !write(*,*) 'open 2'
  211. endif
  212. RAM(3)%First_CloseTimecheck = 0
  213. RAM(3)%First_OpenTimecheck = 0
  214. RAM(3)%time=RAM(3)%time+RamLine%DeltaT_BOP !overal time (s)
  215. !===================================================
  216. ! BOP
  217. !===================================================
  218. if (PipeRam2%closed==0) then !bop closing
  219. !write(*,*) 'BOP code is called'
  220. call bop_code(3,PipeRam2%H_Bop,3) !ramtype=3 3=RNUMBER
  221. endif !bop is closing
  222. !================================================================
  223. if (PipeRam2%closed==1) then
  224. RAM(3)%Q=0
  225. !p_bop=pram_reg
  226. RAM(3)%p_bop=ShearRam%PA
  227. RAMS%minloss(3,17)=0. !RNUMBER=3
  228. endif
  229. RAM(3)%timecounter_ram=RAM(3)%timecounter_ram+1
  230. ! MiddleRamsStatus = IDshearBop
  231. ! UpperRamsStatus = IDPipeRam1
  232. ! LowerRamsStatus = IDPipeRam2
  233. ! AnnularStatus = IDAnnular
  234. ! AccumulatorPressureGauge = p_acc
  235. ! ManifoldPressureGauge= pram_reg
  236. ! AnnularPressureGauge=Pannular_reg
  237. !
  238. !
  239. !
  240. ! WRITE(60,60) RAM(3)%time,RAM(3)%Q,RAM(3)%vdis_tot,p_acc, &
  241. ! pram_reg,Pannular_reg,RAM(3)%p_bop,IDshearBop, &
  242. ! IDPipeRam1,IDPipeRam2,IDAnnular
  243. !60 FORMAT(11(f18.5))
  244. ! call sleepqq(100)
  245. if (PipeRam2%closed==1) then
  246. ! if ((MiddleRamsValve==1. .and. MiddleRamsFailureMalf==0) .or. (MiddleRamsValve==-1.0 .and. MiddleRamsFailureMalf==0) .or. (UpperRamsValve==1. .and. UpperRamsFailureMalf==0) .or. (UpperRamsValve==-1.0 .and. UpperRamsFailureMalf==0) .or. (AnnularValve==1. .and. AnnularFailureMalf==0) .or. (AnnularValve==-1.0 .and. AnnularFailureMalf==0) .or. ChokeLineValve==1. .or. ChokeLineValve==-1.0 .or. KillLineValve==1. .or. KillLineValve==-1.0) then
  247. PipeRam2%finished=1
  248. ! endif
  249. endif
  250. ! if (IsStopped == .true.) return
  251. ! end do loop4 !while finished_pipe2==0
  252. if ( PipeRam2%finished==1 .and. RAM(3)%Bottles_Charged_MalfActive==.true.) then
  253. call bop_code(3,PipeRam2%H_Bop,3) !ramtype=3 3=RNUMBER
  254. ! call sleepqq(100)
  255. endif
  256. END SUBROUTINE PIPE_RAMS2_SUB