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.
 
 
 
 
 
 

376 lines
12 KiB

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