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