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.

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