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.

KILL_LINE.f90 10 KiB

1 year ago
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308
  1. SUBROUTINE KILL_LINE
  2. USE VARIABLES
  3. USE CAccumulatorVariables
  4. USE CBopStackVariables
  5. USE CBopControlPanelVariables
  6. USE CEquipmentsConstants
  7. USE CSimulationVariables
  8. implicit none
  9. !=====================================================================
  10. ! KILL LINE 1- BOP CAMERON Type U 5000
  11. ! START CONDITIONS FOR KILL LINE 1
  12. !=====================================================================
  13. RAM(6)%SuccessionCounter = RAM(6)%SuccessionCounter + 1
  14. if (KillLineValve == -1.0 .and. RigAirMalf==0 .and. AirMasterValve==1 .and. p_acc>acc_MinPressure) then
  15. if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
  16. RAM(6)%SuccessionCounter = 0 ! also in starup
  17. RAM(6)%SuccessionCounterOld = 0 ! also in starup
  18. return
  19. else
  20. RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
  21. endif
  22. if ( RAM(6)%SuccessionCounter < int(2.5/DeltaT_BOP) ) then
  23. return
  24. endif
  25. RAM(6)%First_CloseTimecheck= 1
  26. if (KillLineOpenLedMine == LedOn) then
  27. RETURN
  28. end if
  29. KillLine_closed=0
  30. RAM(6)%vdis_tot=0
  31. RAM(6)%vdis_bottles=0.
  32. RAM(6)%fvr_air=0.
  33. RAM(6)%vdis_elecp=0.
  34. Qiter=7
  35. RAM(6)%Qzero=70
  36. RAM(6)%Q=RAM(6)%Qzero
  37. RAM(6)%flow=70
  38. RAM(6)%tol=0.0037
  39. if (finished_KillLine==1) then
  40. KillLineLeverOld= 1.0
  41. else
  42. KillLineLeverOld=KillLineValve
  43. endif
  44. finished_KillLine=0
  45. KillLineIsOpening = .true.
  46. KillLineCloseLed = LedOff
  47. KillLineCloseLedMine = LedOff
  48. KillLineOpenLed = LedOn !LedBlinking
  49. RAM(6)%bop_type = 3
  50. !AbopKillLine=196.67
  51. AbopKillLine=(KillClose*231)/((IDKillLineBase-ODDrillpipe_inKillLineBase)/2.)
  52. NeededVolumeKillLine=AbopKillLine*(IDKillLineBase-max(ODDrillpipe_inKillLine,ODDrillpipe_inKillLineBase))/(2.*231) !1.5 galon for each BOP
  53. endif
  54. if (KillLineValve == 1.0 .and. RigAirMalf==0 .and. AirMasterValve==1 .and. p_acc>acc_MinPressure) then
  55. if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
  56. RAM(6)%SuccessionCounter = 0 ! also in starup
  57. RAM(6)%SuccessionCounterOld = 0 ! also in starup
  58. return
  59. else
  60. RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
  61. endif
  62. if ( RAM(6)%SuccessionCounter < int(2.5/DeltaT_BOP) ) then
  63. return
  64. endif
  65. RAM(6)%First_OpenTimecheck= 1
  66. if (KillLineCloseLedMine == LedOn) then
  67. RETURN
  68. end if
  69. KillLine_closed=0
  70. RAM(6)%vdis_tot=0
  71. RAM(6)%vdis_bottles=0.
  72. RAM(6)%fvr_air=0.
  73. RAM(6)%vdis_elecp=0.
  74. Qiter=7
  75. RAM(6)%Qzero=70
  76. RAM(6)%Q=RAM(6)%Qzero
  77. RAM(6)%flow=70
  78. RAM(6)%tol=0.0037
  79. if (finished_KillLine==1) then
  80. KillLineLeverOld= -1.0
  81. else
  82. KillLineLeverOld=KillLineValve
  83. endif
  84. finished_KillLine=0
  85. KillLineIsClosing = .true.
  86. !if (KillLineCloseLed == LedOn) then
  87. ! RETURN
  88. !end if
  89. KillLineCloseLed = LedOff !new
  90. KillLineCloseLedMine = LedOff !new
  91. KillLineCloseLed = LedOn !LedBlinking
  92. RAM(6)%bop_type = 3
  93. !AbopKillLine=196.67
  94. AbopKillLine=(KillOpen*231)/((IDKillLineBase-ODDrillpipe_inKillLineBase)/2.)
  95. NeededVolumeKillLine=AbopKillLine*(IDKillLineBase-max(ODDrillpipe_inKillLine,ODDrillpipe_inKillLineBase))/(2.*231) !1.5 galon for each BOP
  96. endif
  97. !==========================================================================
  98. if (KillLineIsOpening .or. KillLineIsClosing) then
  99. CALL KILL_LINE_SUB
  100. end if
  101. END SUBROUTINE KILL_LINE
  102. SUBROUTINE KILL_LINE_SUB
  103. USE VARIABLES
  104. USE CAccumulatorVariables
  105. USE CBopStackVariables
  106. USE CBopControlPanelVariables
  107. USE CEquipmentsConstants
  108. USE CSimulationVariables
  109. implicit none
  110. FirstSet= 0
  111. RamsFirstSet= 0
  112. loop6: do while (finished_KillLine==0)
  113. RAM(6)%SuccessionCounter = RAM(6)%SuccessionCounter + 1
  114. if (KillLineValve == 1.0 .and. KillLineLeverOld == -1.0 .and. RigAirMalf==0 .and. AirMasterValve==1 .and. p_acc>acc_MinPressure) then
  115. if ( RAM(6)%First_CloseTimecheck == 0 ) then
  116. if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
  117. RAM(6)%SuccessionCounter = 0 ! also in starup
  118. RAM(6)%SuccessionCounterOld = 0 ! also in starup
  119. return
  120. else
  121. RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
  122. endif
  123. if ( RAM(6)%SuccessionCounter < int(2.5/DeltaT_BOP) ) then
  124. return
  125. endif
  126. endif
  127. KillLine_closed=0
  128. RAM(6)%p_bop=pa
  129. KillLineLeverOld = KillLineValve
  130. KillLineOpenLed = LedOff
  131. KillLineOpenLedMine = LedOff
  132. KillLineCloseLed = LedOn !LedBlinking
  133. CALL OpenKillLine
  134. RAM(6)%bop_type = 3
  135. !AbopKillLine=196.67
  136. AbopKillLine=(KillClose*231)/((IDKillLineBase-ODDrillpipe_inKillLineBase)/2.)
  137. NeededVolumeKillLine=AbopKillLine*(IDKillLine-max(ODDrillpipe_inKillLine,ODDrillpipe_inKillLineBase))/(2.*231)
  138. RAM(6)%vdis_bottles=0.
  139. RAM(6)%fvr_air=0.
  140. RAM(6)%vdis_elecp=0.
  141. KillLineIsClosing = .true.
  142. KillLineIsOpening = .false.
  143. endif
  144. if (KillLineValve == -1.0 .and. KillLineLeverOld == 1.0 .and. p_acc>acc_MinPressure .and. RigAirMalf==0 .and. AirMasterValve==1) then
  145. if ( RAM(6)%First_OpenTimecheck == 0 ) then
  146. if ( RAM(6)%SuccessionCounter /= RAM(6)%SuccessionCounterOld+1 ) then
  147. RAM(6)%SuccessionCounter = 0 ! also in starup
  148. RAM(6)%SuccessionCounterOld = 0 ! also in starup
  149. return
  150. else
  151. RAM(6)%SuccessionCounterOld= RAM(6)%SuccessionCounter
  152. endif
  153. if ( RAM(6)%SuccessionCounter < int(2.5/DeltaT_BOP) ) then
  154. return
  155. endif
  156. endif
  157. KillLine_closed=0
  158. RAM(6)%p_bop=pa
  159. KillLineLeverOld = KillLineValve
  160. KillLineCloseLed = LedOff
  161. KillLineCloseLedMine = LedOff
  162. KillLineOpenLed = LedOn !LedBlinking
  163. CALL OpenKillLine
  164. RAM(6)%bop_type = 3
  165. !AbopKillLine=196.67
  166. AbopKillLine=(KillOpen*231)/((IDKillLineBase-ODDrillpipe_inKillLineBase)/2.)
  167. NeededVolumeKillLine=AbopKillLine*(IDKillLineBase-IDKillLine)/(2.*231)
  168. RAM(6)%vdis_bottles=0.
  169. RAM(6)%fvr_air=0.
  170. RAM(6)%vdis_elecp=0.
  171. KillLineIsOpening = .true.
  172. KillLineIsClosing = .false.
  173. endif
  174. RAM(6)%First_CloseTimecheck = 0
  175. RAM(6)%First_OpenTimecheck = 0
  176. RAM(6)%time=RAM(6)%time+DeltaT_BOP !overal time (s)
  177. !===================================================
  178. ! BOP
  179. !===================================================
  180. if (KillLine_closed==0) then !bop closing
  181. call bop_code(5,H_KillLineBop,6) !ramtype=5 6=RNUMBER
  182. endif !bop is closing
  183. !================================================================
  184. if (KillLine_closed==1) then
  185. RAM(6)%Q=0
  186. !p_bop=pram_reg
  187. RAM(6)%p_bop=pa
  188. RAMS%minloss(6,17)=0. !RNUMBER=6
  189. endif
  190. RAM(6)%timecounter_ram=RAM(6)%timecounter_ram+1
  191. ! MiddleRamsStatus = IDshearBop
  192. ! UpperRamsStatus = IDPipeRam1
  193. ! LowerRamsStatus = IDPipeRam2
  194. ! AnnularStatus = IDAnnular
  195. ! AccumulatorPressureGauge = p_acc
  196. ! ManifoldPressureGauge= pram_reg
  197. ! AnnularPressureGauge=Pannular_reg
  198. !
  199. !
  200. !
  201. ! WRITE(60,60) RAM(6)%time,RAM(6)%Q,RAM(6)%vdis_tot,p_acc, &
  202. ! pram_reg,Pannular_reg,RAM(6)%p_bop,IDshearBop, &
  203. ! IDPipeRam1,IDPipeRam2,IDAnnular
  204. !60 FORMAT(11(f18.5))
  205. call sleepqq(100)
  206. if (KillLine_closed==1) then
  207. ! if ((UpperRamsValve==1. .and. UpperRamsFailureMalf==0) .or. (UpperRamsValve==-1.0 .and. UpperRamsFailureMalf==0) .or. (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) then
  208. finished_KillLine=1
  209. ! endif
  210. endif
  211. if (IsStopped == .true.) return
  212. end do loop6 !while finished_KillLine==0
  213. END SUBROUTINE KILL_LINE_SUB