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_RAM1.f90 13 KiB

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