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.

PIPE_RAM2.f90 12 KiB

1 year ago
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397
  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 (LowerRamsValve == 1.0 .and. LowerRamsFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1) then
  15. !write(*,*) 'close 1'
  16. if (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/DeltaT_BOP) ) then
  27. !return
  28. RAM(3)%First_CloseTimecheck= 1
  29. LowerRamsOpenLED = LedOff
  30. LowerRamsOpenLEDMine = LedOff
  31. LowerRamsCloseLED = LedOn !LedBlinking
  32. RAM(3)%FourwayValve = 1
  33. endif
  34. endif
  35. if (RAM(3)%FourwayValve == 1 .and. p_acc>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. 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 (finished_pipe2==1) then
  50. PipeRams2LeverOld=-1.0
  51. else
  52. PipeRams2LeverOld=LowerRamsValve
  53. endif
  54. finished_pipe2=0
  55. PipeRam2IsClosing = .true.
  56. PipeRam2IsOpening = .false.
  57. RAM(3)%bop_type = 3
  58. !AbopPipeRam=196.67
  59. AbopPipeRam=(LowerRamClose*231)/((IDPipeRamBase-ODDrillpipe_inPipeRam1Base)/2.)
  60. NeededVolumePipeRams2=AbopPipeRam*(IDPipeRamBase-max(ODDrillpipe_inPipeRam2,ODDrillpipe_inPipeRam1Base))/(2.*231) !galon for each BOP
  61. !write(*,*) 'close 1'
  62. endif
  63. if (LowerRamsValve == -1.0 .and. LowerRamsFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1) then
  64. !write(*,*) 'open 1'
  65. if (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/DeltaT_BOP) ) then
  76. !return
  77. RAM(3)%First_OpenTimecheck= 1
  78. LowerRamsCloseLed = LedOff !new
  79. LowerRamsCloseLedMine = LedOff !new
  80. LowerRamsOpenLED = LedOn !LedBlinking
  81. RAM(3)%FourwayValve = 1
  82. endif
  83. endif
  84. if (RAM(3)%FourwayValve == 1 .and. p_acc>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. 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 (finished_pipe2==1) then
  99. PipeRams2LeverOld=1.0
  100. else
  101. PipeRams2LeverOld=LowerRamsValve
  102. endif
  103. finished_pipe2=0
  104. PipeRam2IsOpening = .true.
  105. PipeRam2IsClosing = .false.
  106. !if (LowerRamsOpenLED == LedOn) then
  107. ! RETURN
  108. !end if
  109. RAM(3)%bop_type = 3
  110. !AbopPipeRam=186.5
  111. AbopPipeRam=(LowerRamOpen*231)/((IDPipeRamBase-ODDrillpipe_inPipeRam1Base)/2.)
  112. NeededVolumePipeRams2=AbopPipeRam*(IDPipeRamBase-max(ODDrillpipe_inPipeRam2,ODDrillpipe_inPipeRam1Base))/(2.*231) !galon for each BOP
  113. !write(*,*) 'open 1'
  114. endif
  115. !=====================================================================
  116. if (PipeRam2IsOpening .or. PipeRam2IsClosing .or. RAM(3)%Bottles_Charged_MalfActive) then
  117. CALL PIPE_RAMS2_SUB
  118. end if
  119. END SUBROUTINE PIPE_RAMS2
  120. SUBROUTINE PIPE_RAMS2_SUB
  121. USE VARIABLES
  122. USE CBopStackVariables
  123. USE CBopControlPanelVariables
  124. USE CEquipmentsConstants
  125. USE CSimulationVariables
  126. implicit none
  127. FirstSet= 0
  128. RamsFirstSet= 0
  129. loop4: do while (finished_pipe2==0)
  130. !write(*,*) 'checkpoint 2'
  131. RAM(3)%SuccessionCounter = RAM(3)%SuccessionCounter + 1
  132. if (LowerRamsValve == 1.0 .and. PipeRams2LeverOld == -1.0 .and. LowerRamsFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1) then
  133. !write(*,*) 'close 3'
  134. if ( RAM(3)%First_CloseTimecheck == 0 ) then
  135. if ( RAM(3)%SuccessionCounter /= RAM(3)%SuccessionCounterOld+1 ) then
  136. RAM(3)%SuccessionCounter = 0 ! also in starup
  137. RAM(3)%SuccessionCounterOld = 0 ! also in starup
  138. !return
  139. else
  140. RAM(3)%SuccessionCounterOld= RAM(3)%SuccessionCounter
  141. endif
  142. if ( RAM(3)%SuccessionCounter >= int(2.5/DeltaT_BOP) ) then
  143. !return
  144. LowerRamsOpenLED = LedOff
  145. LowerRamsOpenLEDMine = LedOff
  146. LowerRamsCloseLED = LedOn !LedBlinking
  147. RAM(3)%FourwayValve = 1
  148. endif
  149. endif
  150. endif
  151. if (RAM(3)%FourwayValve == 1 .and. p_acc>acc_MinPressure) then
  152. !write(*,*) 'close 4'
  153. RAM(3)%FourwayValve = 0
  154. PipeRam2_closed=0
  155. !PipeRam2_closed_withPossibility= PipeRam2_closed * TD_BOPConnectionPossibility(4)
  156. RAM(3)%p_bop=pa
  157. PipeRams2LeverOld = LowerRamsValve
  158. CALL OpenLowerRams
  159. PipeRam2_Situation_forTD= 0 ! open - for TD code
  160. RAM(3)%bop_type = 3
  161. !AbopPipeRam=196.67
  162. AbopPipeRam=(LowerRamClose*231)/((IDPipeRamBase-ODDrillpipe_inPipeRam1Base)/2.)
  163. NeededVolumePipeRams2=AbopPipeRam*(IDPipeRam2-max(ODDrillpipe_inPipeRam2,ODDrillpipe_inPipeRam1Base))/(2.*231)
  164. RAM(3)%vdis_bottles=0.
  165. RAM(3)%fvr_air=0.
  166. RAM(3)%vdis_elecp=0.
  167. PipeRam2IsClosing = .true.
  168. PipeRam2IsOpening = .false.
  169. !write(*,*) 'close 2'
  170. endif
  171. if (LowerRamsValve == -1.0 .and. PipeRams2LeverOld == 1.0 .and. LowerRamsFailureMalf==0 .and. RigAirMalf==0 .and. AirMasterValve==1) then
  172. !write(*,*) 'open 3'
  173. if ( RAM(3)%First_OpenTimecheck == 0 ) then
  174. if ( RAM(3)%SuccessionCounter /= RAM(3)%SuccessionCounterOld+1 ) then
  175. RAM(3)%SuccessionCounter = 0 ! also in starup
  176. RAM(3)%SuccessionCounterOld = 0 ! also in starup
  177. !return
  178. else
  179. RAM(3)%SuccessionCounterOld= RAM(3)%SuccessionCounter
  180. endif
  181. if ( RAM(3)%SuccessionCounter >= int(2.5/DeltaT_BOP) ) then
  182. !return
  183. LowerRamsCloseLED = LedOff
  184. LowerRamsCloseLEDMine = LedOff
  185. LowerRamsOpenLED = LedOn !LedBlinking
  186. RAM(3)%FourwayValve = 1
  187. endif
  188. endif
  189. endif
  190. if (RAM(3)%FourwayValve == 1 .and. p_acc>acc_MinPressure) then
  191. !write(*,*) 'open 4'
  192. RAM(3)%FourwayValve = 0
  193. PipeRam2_closed=0
  194. !PipeRam2_closed_withPossibility= PipeRam2_closed * TD_BOPConnectionPossibility(4)
  195. RAM(3)%p_bop=pa
  196. PipeRams2LeverOld = LowerRamsValve
  197. CALL OpenLowerRams
  198. PipeRam2_Situation_forTD= 0 ! open - for TD code
  199. RAM(3)%bop_type = 3
  200. !AbopPipeRam=186.5
  201. AbopPipeRam=(LowerRamOpen*231)/((IDPipeRamBase-ODDrillpipe_inPipeRam1Base)/2.)
  202. NeededVolumePipeRams2=AbopPipeRam*(IDPipeRamBase-IDPipeRam2)/(2.*231)
  203. RAM(3)%vdis_bottles=0.
  204. RAM(3)%fvr_air=0.
  205. RAM(3)%vdis_elecp=0.
  206. PipeRam2IsOpening = .true.
  207. PipeRam2IsClosing = .false.
  208. !write(*,*) 'open 2'
  209. endif
  210. RAM(3)%First_CloseTimecheck = 0
  211. RAM(3)%First_OpenTimecheck = 0
  212. RAM(3)%time=RAM(3)%time+DeltaT_BOP !overal time (s)
  213. !===================================================
  214. ! BOP
  215. !===================================================
  216. if (PipeRam2_closed==0) then !bop closing
  217. !write(*,*) 'BOP code is called'
  218. call bop_code(3,H_PipeRam2Bop,3) !ramtype=3 3=RNUMBER
  219. endif !bop is closing
  220. !================================================================
  221. if (PipeRam2_closed==1) then
  222. RAM(3)%Q=0
  223. !p_bop=pram_reg
  224. RAM(3)%p_bop=pa
  225. RAMS%minloss(3,17)=0. !RNUMBER=3
  226. endif
  227. RAM(3)%timecounter_ram=RAM(3)%timecounter_ram+1
  228. ! MiddleRamsStatus = IDshearBop
  229. ! UpperRamsStatus = IDPipeRam1
  230. ! LowerRamsStatus = IDPipeRam2
  231. ! AnnularStatus = IDAnnular
  232. ! AccumulatorPressureGauge = p_acc
  233. ! ManifoldPressureGauge= pram_reg
  234. ! AnnularPressureGauge=Pannular_reg
  235. !
  236. !
  237. !
  238. ! WRITE(60,60) RAM(3)%time,RAM(3)%Q,RAM(3)%vdis_tot,p_acc, &
  239. ! pram_reg,Pannular_reg,RAM(3)%p_bop,IDshearBop, &
  240. ! IDPipeRam1,IDPipeRam2,IDAnnular
  241. !60 FORMAT(11(f18.5))
  242. call sleepqq(100)
  243. if (PipeRam2_closed==1) then
  244. ! 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
  245. finished_pipe2=1
  246. ! endif
  247. endif
  248. if (IsStopped == .true.) return
  249. end do loop4 !while finished_pipe2==0
  250. if ( finished_pipe2==1 .and. RAM(3)%Bottles_Charged_MalfActive==.true.) then
  251. call bop_code(3,H_PipeRam2Bop,3) !ramtype=3 3=RNUMBER
  252. call sleepqq(100)
  253. endif
  254. END SUBROUTINE PIPE_RAMS2_SUB