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.
 
 
 
 
 
 

1389 lines
36 KiB

  1. module CManifolds
  2. use CStack
  3. use CArrangement
  4. use CPathChangeEvents
  5. use CDrillingConsoleVariables, only: IRSafetyValveLed, IRIBopLed, OpenKellyCockLed, CloseKellyCockLed, OpenSafetyValveLed, CloseSafetyValveLed
  6. implicit none
  7. public
  8. integer, parameter :: ValveCount = 128
  9. integer, parameter :: MinSource = 71
  10. integer, parameter :: MaxSource = 90
  11. integer, parameter :: MinRelation = 91
  12. integer, parameter :: MaxRelation = 128
  13. type(Arrangement) :: Valve(ValveCount)
  14. type(Path), allocatable :: OpenPaths(:)
  15. type(Stack) :: Fringe
  16. logical :: IsRepititveOutput
  17. logical :: IsSafetyValveInstalled
  18. logical :: IsSafetyValveInstalled_KellyMode
  19. logical :: IsSafetyValveInstalled_TripMode
  20. logical :: IsSafetyValveInstalled_TopDrive
  21. logical :: SafetyValve
  22. logical :: IsIBopInstalled
  23. logical :: IBop
  24. logical :: IsKellyCockInstalled
  25. logical :: KellyCock
  26. logical :: IsTopDriveIBopInstalled
  27. logical :: TopDriveIBop
  28. logical :: IsFloatValveInstalled
  29. logical :: FloatValve
  30. logical :: IsPathsDirty = .false.
  31. logical :: IsTraverse = .false.
  32. contains
  33. subroutine PathFinding_Setup()
  34. use CSimulationVariables
  35. implicit none
  36. IsTraverse = .false.
  37. call Setup()
  38. !call OnSimulationInitialization%Add(PathFinding_Init)
  39. !call OnSimulationStop%Add(PathFinding_Init)
  40. !call OnPathFindingStep%Add(PathFinding_Step)
  41. !call OnPathFindingOutput%Add(PathFinding_Output)
  42. call OnPathFindingMain%Add(PathFindingMainBody)
  43. end subroutine
  44. subroutine PathFinding_Init
  45. implicit none
  46. IsTraverse = .false.
  47. call Setup()
  48. end subroutine PathFinding_Init
  49. subroutine PathFinding_Step
  50. implicit none
  51. end subroutine PathFinding_Step
  52. subroutine PathFinding_Output
  53. implicit none
  54. end subroutine PathFinding_Output
  55. subroutine PathFindingMainBody
  56. use CSimulationVariables
  57. implicit none
  58. loop : do
  59. if(IsStopped) call Quit()
  60. call sleepqq(50)
  61. if (IsPathsDirty) then
  62. IsPathsDirty = .false.
  63. call Traverse()
  64. endif
  65. end do loop
  66. end subroutine PathFindingMainBody
  67. subroutine Traverse()
  68. use CLog5
  69. implicit none
  70. integer :: i, Duration
  71. integer, dimension(8) :: StartTime,EndTime !TODO: clean up
  72. call DATE_AND_TIME(values=StartTime) !TODO: clean up
  73. call BeforeTraverse%RunAll()
  74. if(allocated(OpenPaths)) deallocate(OpenPaths)
  75. do i=MinSource, MaxSource
  76. if(IsValveOpen(i)) then
  77. call AddRootNode(i)
  78. call AddChildren(Valve(i))
  79. endif
  80. enddo
  81. call PostProcess(OpenPaths)
  82. call AfterTraverse%RunAll()
  83. IsTraverse = .true.
  84. !TODO: clean up
  85. #ifdef Log5
  86. CALL DATE_AND_TIME(values=EndTime)
  87. Duration= EndTime(8) - StartTime(8)
  88. !print*, 'Duration= ', Duration, 'ms'
  89. call Log_5('Duration= ', Duration)
  90. call DisplayOpenPaths()
  91. call Log_5('==========================================')
  92. #endif
  93. endsubroutine
  94. subroutine PostProcess(pathArr)
  95. implicit none
  96. type(Path), allocatable, intent(inout) :: pathArr(:)
  97. integer :: i
  98. if(.not.allocated(pathArr)) return
  99. i = 1
  100. do
  101. call pathArr(i)%Purge(MinRelation, MaxRelation)
  102. if(pathArr(i)%Length() <= 2) then
  103. call RemovePath(pathArr, i)
  104. else
  105. i = i + 1
  106. endif
  107. if(i > size(pathArr)) exit
  108. enddo
  109. end subroutine
  110. subroutine AddRootNode(valve)
  111. implicit none
  112. integer, intent(in) :: valve
  113. call Fringe%Push(valve)
  114. end subroutine
  115. recursive subroutine AddChildren(node)
  116. implicit none
  117. type(Arrangement), intent(inout) :: node
  118. integer :: i,t
  119. do i=1, Valve(node%Number)%Length()
  120. t = Valve(node%Number)%Adjacent(i)
  121. if(IsValveOpen(t)) then
  122. if(Fringe%DoesHave(t)) cycle
  123. call Fringe%Push(t)
  124. if(Valve(t)%IsSource()) then
  125. call AddPath(OpenPaths, Fringe%List)
  126. call Fringe%Pop()
  127. cycle
  128. endif
  129. call AddChildren(Valve(node%Adjacent(i)))
  130. end if
  131. enddo
  132. call Fringe%Pop()
  133. end subroutine
  134. logical function IsValveOpen(no)
  135. implicit none
  136. integer, intent(in) :: no
  137. IsValveOpen = Valve(no)%Status
  138. end function
  139. subroutine AddPath(pathArr, p)
  140. implicit none
  141. type(Path), intent(in) :: p
  142. type(Path), allocatable, intent(inout) :: pathArr(:)
  143. type(Path), allocatable :: tempArr(:)
  144. integer :: i, isize
  145. if(p%IsNull()) return
  146. if(p%Length()<=1) return
  147. call OnPathOpen%RunAll(p%Valves)
  148. if(allocated(pathArr)) then
  149. isize = size(pathArr)
  150. ! check to see if already have a path same as p
  151. do i=1,isize
  152. if(pathArr(i)%First()==p%First() .and. pathArr(i)%Last()==p%Last()) then
  153. ! if there is then
  154. ! check to see if both have exacly a same length
  155. if(pathArr(i)%Length()==p%Length())then
  156. ! now they are the same so ignore adding this one
  157. return
  158. else
  159. !if they have different lengths then choose the shorter one
  160. if(pathArr(i)%Length()>p%Length())pathArr(i) = p
  161. return
  162. endif
  163. endif
  164. end do
  165. !TODO: if p last valve is input source then ignore adding it
  166. !TODO: if p start valve is output source then ignore adding it
  167. ! if p is a new entry then add it to the collections of found paths
  168. allocate(tempArr(isize+1))
  169. do i=1,isize
  170. tempArr(i) = pathArr(i)
  171. end do
  172. tempArr(isize+1) = p
  173. deallocate(pathArr)
  174. call move_alloc(tempArr, pathArr)
  175. else
  176. allocate(pathArr(1))
  177. pathArr(1) = p
  178. end if
  179. endsubroutine
  180. subroutine RemovePath(pathArr, index)
  181. implicit none
  182. integer, intent(in) :: index
  183. type(Path), allocatable, intent(inout) :: pathArr(:)
  184. type(Path), allocatable :: tempArr(:)
  185. integer :: i
  186. logical :: found
  187. if(index <= 0 .or. index > size(pathArr)) return
  188. if(.not.allocated(pathArr))return
  189. allocate(tempArr(size(pathArr)-1))
  190. found = .false.
  191. do i=1, size(pathArr)
  192. if(i==index) then
  193. found = .true.
  194. cycle
  195. end if
  196. if(found) then
  197. tempArr(i-1) = pathArr(i)
  198. !call OnPathClose%RunAll(pathArr(i)%Valves)
  199. else
  200. tempArr(i) = pathArr(i)
  201. endif
  202. end do
  203. deallocate(pathArr)
  204. call move_alloc(tempArr, pathArr)
  205. endsubroutine
  206. subroutine Setup()
  207. implicit none
  208. integer :: i
  209. ! initialize all valves
  210. do i = 1, ValveCount
  211. call Valve(i)%init(i)
  212. end do
  213. ! open source valves
  214. do i = MinSource , MaxSource
  215. Valve(i)%Status = .true.
  216. Valve(i)%ValveType = InputOutput
  217. end do
  218. do i = MinRelation , MaxRelation
  219. Valve(i)%Status = .true.
  220. Valve(i)%ValveType = Relation
  221. end do
  222. ! make adjustments
  223. call Valve(1)%AdjacentTo(91)
  224. call Valve(2)%AdjacentTo(92)
  225. call Valve(2)%AdjacentTo(117)
  226. call Valve(3)%AdjacentTo(93)
  227. call Valve(3)%AdjacentTo(118)
  228. call Valve(4)%AdjacentTo(94)
  229. call Valve(5)%AdjacentTo(95)
  230. call Valve(6)%AdjacentTo(91)
  231. call Valve(6)%AdjacentTo(92)
  232. call Valve(7)%AdjacentTo(92)
  233. call Valve(7)%AdjacentTo(93)
  234. call Valve(8)%AdjacentTo(93)
  235. call Valve(8)%AdjacentTo(94)
  236. call Valve(9)%AdjacentTo(91)
  237. call Valve(9)%AdjacentTo(96)
  238. call Valve(10)%AdjacentTo(94)
  239. call Valve(10)%AdjacentTo(98)
  240. call Valve(11)%AdjacentTo(96)
  241. call Valve(11)%AdjacentTo(97)
  242. call Valve(12)%AdjacentTo(97)
  243. call Valve(12)%AdjacentTo(98)
  244. call Valve(13)%AdjacentTo(96)
  245. call Valve(13)%AdjacentTo(99)
  246. call Valve(14)%AdjacentTo(78)
  247. call Valve(14)%AdjacentTo(97)
  248. !call Valve(14)%AdjacentTo(126)
  249. call Valve(15)%AdjacentTo(98)
  250. call Valve(15)%AdjacentTo(99)
  251. call Valve(16)%AdjacentTo(121)
  252. !call Valve(16)%AdjacentTo()
  253. call Valve(17)%AdjacentTo(122)
  254. !call Valve(17)%AdjacentTo()
  255. call Valve(18)%AdjacentTo(123)
  256. !call Valve(18)%AdjacentTo()
  257. call Valve(19)%AdjacentTo(101)
  258. call Valve(19)%AdjacentTo(102)
  259. call Valve(20)%AdjacentTo(100)
  260. call Valve(21)%AdjacentTo(101)
  261. call Valve(22)%AdjacentTo(102)
  262. call Valve(23)%AdjacentTo(71)
  263. call Valve(24)%AdjacentTo(71)
  264. call Valve(25)%AdjacentTo(108)
  265. call Valve(25)%AdjacentTo(118)
  266. call Valve(26)%AdjacentTo(109)
  267. call Valve(26)%AdjacentTo(117)
  268. call Valve(27)%AdjacentTo(32)
  269. call Valve(27)%AdjacentTo(108)
  270. call Valve(28)%AdjacentTo(33)
  271. call Valve(28)%AdjacentTo(108)
  272. call Valve(29)%AdjacentTo(110)
  273. call Valve(29)%AdjacentTo(113)
  274. call Valve(30)%AdjacentTo(34)
  275. call Valve(30)%AdjacentTo(109)
  276. call Valve(31)%AdjacentTo(35)
  277. call Valve(31)%AdjacentTo(109)
  278. call Valve(32)%AdjacentTo(27)
  279. call Valve(32)%AdjacentTo(61)
  280. call Valve(33)%AdjacentTo(28)
  281. call Valve(33)%AdjacentTo(62)
  282. call Valve(34)%AdjacentTo(30)
  283. call Valve(34)%AdjacentTo(63)
  284. call Valve(35)%AdjacentTo(31)
  285. call Valve(35)%AdjacentTo(64)
  286. call Valve(36)%AdjacentTo(116)
  287. call Valve(37)%AdjacentTo(78)
  288. call Valve(38)%AdjacentTo(71)
  289. call Valve(39)%AdjacentTo(77)
  290. !call Valve(40)%AdjacentTo(105)
  291. call Valve(40)%AdjacentTo(80)
  292. call Valve(41)%AdjacentTo(77)
  293. call Valve(42)%AdjacentTo(71)
  294. call Valve(43)%AdjacentTo(106)
  295. call Valve(44)%AdjacentTo(77)
  296. call Valve(45)%AdjacentTo(71)
  297. call Valve(46)%AdjacentTo(104)
  298. call Valve(47)%AdjacentTo(104)
  299. call Valve(47)%AdjacentTo(117)
  300. call Valve(48)%AdjacentTo(69)
  301. call Valve(48)%AdjacentTo(79)
  302. call Valve(49)%AdjacentTo(104)
  303. call Valve(49)%AdjacentTo(79)
  304. !call Valve(50)%AdjacentTo(48)
  305. call Valve(50)%AdjacentTo(51)
  306. !call Valve(50)%AdjacentTo(54)
  307. call Valve(50)%AdjacentTo(104)
  308. call Valve(51)%AdjacentTo(50)
  309. call Valve(51)%AdjacentTo(52)
  310. call Valve(52)%AdjacentTo(51)
  311. !call Valve(52)%AdjacentTo(127)
  312. call Valve(52)%AdjacentTo(80)
  313. !call Valve(53)%AdjacentTo(103)
  314. !call Valve(53)%AdjacentTo(105)
  315. call Valve(53)%AdjacentTo(80)
  316. !call Valve(54)%AdjacentTo(69)
  317. !call Valve(54)%AdjacentTo(124)
  318. !call Valve(55)%AdjacentTo(103)
  319. !call Valve(55)%AdjacentTo(124)
  320. call Valve(56)%AdjacentTo(128)
  321. call Valve(56)%AdjacentTo(127)
  322. !call Valve(57)%AdjacentTo(14)
  323. !call Valve(57)%AdjacentTo(103)
  324. !call Valve(57)%AdjacentTo(126)
  325. call Valve(58)%AdjacentTo(78)
  326. call Valve(59)%AdjacentTo(78)
  327. call Valve(60)%AdjacentTo(78)
  328. call Valve(61)%AdjacentTo(32)
  329. call Valve(61)%AdjacentTo(115)
  330. call Valve(62)%AdjacentTo(33)
  331. call Valve(62)%AdjacentTo(114)
  332. call Valve(63)%AdjacentTo(112)
  333. call Valve(63)%AdjacentTo(34)
  334. call Valve(64)%AdjacentTo(35)
  335. call Valve(64)%AdjacentTo(111)
  336. call Valve(65)%AdjacentTo(120)
  337. call Valve(66)%AdjacentTo(120)
  338. call Valve(67)%AdjacentTo(73)
  339. call Valve(68)%AdjacentTo(125)
  340. call Valve(68)%AdjacentTo(126)
  341. call Valve(69)%AdjacentTo(48)
  342. call Valve(69)%AdjacentTo(124)
  343. !call Valve(70)%AdjacentTo()
  344. !call Valve(70)%AdjacentTo()
  345. call Valve(71)%AdjacentTo(20)
  346. call Valve(71)%AdjacentTo(44)
  347. call Valve(71)%AdjacentTo(59)
  348. call Valve(72)%AdjacentTo(21)
  349. call Valve(72)%AdjacentTo(23)
  350. call Valve(73)%AdjacentTo(22)
  351. call Valve(74)%AdjacentTo(24)
  352. !call Valve(75)%AdjacentTo()
  353. !call Valve(76)%AdjacentTo()
  354. call Valve(77)%AdjacentTo(43)
  355. call Valve(77)%AdjacentTo(58)
  356. !call Valve(78)%AdjacentTo()
  357. call Valve(79)%AdjacentTo(48)
  358. call Valve(79)%AdjacentTo(49)
  359. call Valve(80)%AdjacentTo(52)
  360. call Valve(80)%AdjacentTo(107)
  361. call Valve(81)%AdjacentTo(53)
  362. call Valve(82)%AdjacentTo(16)
  363. call Valve(83)%AdjacentTo(17)
  364. call Valve(84)%AdjacentTo(18)
  365. !call Valve(85)%AdjacentTo()
  366. !call Valve(86)%AdjacentTo()
  367. !call Valve(87)%AdjacentTo()
  368. !call Valve(88)%AdjacentTo()
  369. !!call Valve(89)%AdjacentTo()
  370. !call Valve(90)%AdjacentTo()
  371. call Valve(91)%AdjacentTo(6)
  372. call Valve(91)%AdjacentTo(9)
  373. call Valve(91)%AdjacentTo(75)
  374. call Valve(92)%AdjacentTo(6)
  375. call Valve(92)%AdjacentTo(7)
  376. call Valve(92)%AdjacentTo(2)
  377. call Valve(93)%AdjacentTo(3)
  378. call Valve(93)%AdjacentTo(7)
  379. call Valve(93)%AdjacentTo(8)
  380. call Valve(94)%AdjacentTo(8)
  381. call Valve(94)%AdjacentTo(10)
  382. call Valve(94)%AdjacentTo(95)
  383. call Valve(95)%AdjacentTo(76)
  384. call Valve(95)%AdjacentTo(94)
  385. call Valve(96)%AdjacentTo(9)
  386. call Valve(96)%AdjacentTo(11)
  387. call Valve(96)%AdjacentTo(13)
  388. call Valve(97)%AdjacentTo(11)
  389. call Valve(97)%AdjacentTo(12)
  390. call Valve(97)%AdjacentTo(14)
  391. call Valve(98)%AdjacentTo(10)
  392. call Valve(98)%AdjacentTo(12)
  393. call Valve(98)%AdjacentTo(15)
  394. call Valve(99)%AdjacentTo(13)
  395. call Valve(99)%AdjacentTo(15)
  396. call Valve(99)%AdjacentTo(125)
  397. !call Valve(100)%AdjacentTo(16)
  398. call Valve(100)%AdjacentTo(82)
  399. call Valve(100)%AdjacentTo(101)
  400. !call Valve(101)%AdjacentTo(17)
  401. call Valve(101)%AdjacentTo(19)
  402. call Valve(101)%AdjacentTo(83)
  403. call Valve(101)%AdjacentTo(100)
  404. !call Valve(102)%AdjacentTo(18)
  405. call Valve(102)%AdjacentTo(19)
  406. call Valve(102)%AdjacentTo(84)
  407. !call Valve(103)%AdjacentTo(53)
  408. !call Valve(103)%AdjacentTo(56)
  409. call Valve(103)%AdjacentTo(124)
  410. !call Valve(103)%AdjacentTo(56)
  411. !call Valve(103)%AdjacentTo(78)
  412. call Valve(104)%AdjacentTo(46)
  413. call Valve(104)%AdjacentTo(47)
  414. call Valve(104)%AdjacentTo(49)
  415. call Valve(104)%AdjacentTo(50)
  416. !call Valve(105)%AdjacentTo(53)
  417. !call Valve(105)%AdjacentTo(107)
  418. !call Valve(105)%AdjacentTo(127)
  419. call Valve(106)%AdjacentTo(40)
  420. call Valve(106)%AdjacentTo(45)
  421. call Valve(107)%AdjacentTo(41)
  422. !call Valve(107)%AdjacentTo(105)
  423. call Valve(107)%AdjacentTo(119)
  424. !call Valve(107)%AdjacentTo(42)
  425. call Valve(108)%AdjacentTo(25)
  426. call Valve(108)%AdjacentTo(27)
  427. call Valve(108)%AdjacentTo(28)
  428. call Valve(108)%AdjacentTo(110)
  429. call Valve(109)%AdjacentTo(26)
  430. call Valve(109)%AdjacentTo(30)
  431. call Valve(109)%AdjacentTo(31)
  432. call Valve(109)%AdjacentTo(110)
  433. call Valve(110)%AdjacentTo(29)
  434. call Valve(110)%AdjacentTo(85)
  435. call Valve(110)%AdjacentTo(108)
  436. call Valve(110)%AdjacentTo(109)
  437. call Valve(111)%AdjacentTo(37)
  438. call Valve(111)%AdjacentTo(64)
  439. call Valve(111)%AdjacentTo(112)
  440. call Valve(112)%AdjacentTo(63)
  441. call Valve(112)%AdjacentTo(111)
  442. call Valve(112)%AdjacentTo(113)
  443. call Valve(113)%AdjacentTo(29)
  444. call Valve(113)%AdjacentTo(112)
  445. call Valve(113)%AdjacentTo(114)
  446. call Valve(114)%AdjacentTo(62)
  447. call Valve(114)%AdjacentTo(113)
  448. call Valve(114)%AdjacentTo(115)
  449. call Valve(115)%AdjacentTo(36)
  450. call Valve(115)%AdjacentTo(61)
  451. call Valve(115)%AdjacentTo(114)
  452. call Valve(116)%AdjacentTo(38)
  453. call Valve(116)%AdjacentTo(39)
  454. call Valve(117)%AdjacentTo(2)
  455. call Valve(117)%AdjacentTo(26)
  456. call Valve(117)%AdjacentTo(47)
  457. call Valve(118)%AdjacentTo(3)
  458. call Valve(118)%AdjacentTo(25)
  459. call Valve(118)%AdjacentTo(46)
  460. call Valve(119)%AdjacentTo(42)
  461. call Valve(119)%AdjacentTo(60)
  462. call Valve(119)%AdjacentTo(107)
  463. call Valve(120)%AdjacentTo(71)
  464. !call Valve(121)%AdjacentTo(16)
  465. call Valve(121)%AdjacentTo(1)
  466. call Valve(121)%AdjacentTo(65)
  467. !call Valve(122)%AdjacentTo(17)
  468. call Valve(122)%AdjacentTo(4)
  469. call Valve(122)%AdjacentTo(66)
  470. !call Valve(123)%AdjacentTo(18)
  471. call Valve(123)%AdjacentTo(5)
  472. call Valve(123)%AdjacentTo(67)
  473. !call Valve(124)%AdjacentTo(54)
  474. !call Valve(124)%AdjacentTo(55)
  475. call Valve(124)%AdjacentTo(69)
  476. call Valve(124)%AdjacentTo(103)
  477. call Valve(125)%AdjacentTo(68)
  478. call Valve(125)%AdjacentTo(99)
  479. ! call Valve(125)%AdjacentTo(126)
  480. call Valve(126)%AdjacentTo(128)
  481. call Valve(126)%AdjacentTo(68)
  482. !call Valve(126)%AdjacentTo(125)
  483. call Valve(127)%AdjacentTo(56)
  484. call Valve(127)%AdjacentTo(78)
  485. !call Valve(127)%AdjacentTo(105)
  486. call Valve(128)%AdjacentTo(56)
  487. call Valve(128)%AdjacentTo(126)
  488. ! initialization
  489. call ChangeValve(60, .true.)
  490. call RemoveIBop()
  491. call ToggleFillupHead(.false.)
  492. call ToggleMudBox(.false.)
  493. call RemoveTopDriveIBop()
  494. call InstallSafetyValve_KellyMode()
  495. call KellyDisconnected()
  496. end subroutine
  497. subroutine KellyConnected()
  498. !use CLog3
  499. implicit none
  500. call Valve(127)%RemoveAdjacent(78)
  501. call Valve(127)%AdjacentTo(103)
  502. call Valve(103)%AdjacentTo(127)
  503. #ifdef deb
  504. print*, 'KellyConnected()'
  505. !call Log_3( 'KellyConnected()')
  506. #endif
  507. IsPathsDirty = .true.
  508. end subroutine
  509. subroutine KellyDisconnected()
  510. !use CLog3
  511. implicit none
  512. call Valve(127)%RemoveAdjacent(103)
  513. call Valve(103)%RemoveAdjacent(127)
  514. call Valve(127)%AdjacentTo(78)
  515. #ifdef deb
  516. print*, 'KellyDisconnected()'
  517. !call Log_3( 'KellyDisconnected()')
  518. #endif
  519. IsPathsDirty = .true.
  520. end subroutine
  521. subroutine InstallSafetyValve_KellyMode()
  522. implicit none
  523. IsSafetyValveInstalled_KellyMode = .true.
  524. call RemoveTopDriveIBop()
  525. ! Remove Safey Valve (54)
  526. call Valve(124)%RemoveAdjacent(54)
  527. call Valve(54)%RemoveAdjacent(124)
  528. call Valve(69)%RemoveAdjacent(54)
  529. call Valve(54)%RemoveAdjacent(69)
  530. ! Remove 126-103 cnn
  531. call Valve(128)%RemoveAdjacent(127)
  532. call Valve(127)%RemoveAdjacent(128)
  533. ! now make cnn
  534. call Valve(124)%AdjacentTo(69)
  535. call Valve(69)%AdjacentTo(124)
  536. call Valve(128)%AdjacentTo(56)
  537. call Valve(56)%AdjacentTo(128)
  538. call Valve(56)%AdjacentTo(127)
  539. call Valve(127)%AdjacentTo(56)
  540. #ifdef deb
  541. print*, 'InstallSafetyValve_KellyMode()'
  542. #endif
  543. IRSafetyValveLed = 1
  544. call OpenSafetyValve_KellyMode()
  545. end subroutine
  546. subroutine RemoveSafetyValve_KellyMode()
  547. implicit none
  548. IsSafetyValveInstalled_KellyMode = .false.
  549. call Valve(128)%RemoveAdjacent(56)
  550. call Valve(56)%RemoveAdjacent(128)
  551. call Valve(127)%RemoveAdjacent(56)
  552. call Valve(56)%RemoveAdjacent(127)
  553. call Valve(127)%AdjacentTo(128)
  554. call Valve(128)%AdjacentTo(127)
  555. IRSafetyValveLed = 0
  556. call CloseSafetyValve_KellyMode()
  557. OpenSafetyValveLed = 0
  558. CloseSafetyValveLed = 0
  559. #ifdef deb
  560. print*, 'RemoveSafetyValve_KellyMode()'
  561. #endif
  562. end subroutine
  563. subroutine OpenSafetyValve_KellyMode()
  564. implicit none
  565. if(.not.IsSafetyValveInstalled_KellyMode) return
  566. OpenSafetyValveLed = 1
  567. CloseSafetyValveLed = 0
  568. SafetyValve = .true.
  569. call ChangeValve(56, SafetyValve)
  570. #ifdef deb
  571. print*, 'OpenSafetyValve_KellyMode()'
  572. #endif
  573. end subroutine
  574. subroutine CloseSafetyValve_KellyMode()
  575. implicit none
  576. if(.not.IsSafetyValveInstalled_KellyMode) return
  577. CloseSafetyValveLed = 1
  578. OpenSafetyValveLed = 0
  579. SafetyValve = .false.
  580. call ChangeValve(56, SafetyValve)
  581. #ifdef deb
  582. print*, 'CloseSafetyValve_KellyMode()'
  583. #endif
  584. end subroutine
  585. subroutine InstallSafetyValve_TripMode()
  586. implicit none
  587. IsSafetyValveInstalled_TripMode = .true.
  588. call Valve(128)%RemoveAdjacent(56)
  589. call Valve(56)%RemoveAdjacent(128)
  590. call Valve(127)%RemoveAdjacent(56)
  591. call Valve(56)%RemoveAdjacent(127)
  592. call Valve(69)%RemoveAdjacent(124)
  593. call Valve(124)%RemoveAdjacent(69)
  594. call Valve(127)%AdjacentTo(128)
  595. call Valve(128)%AdjacentTo(127)
  596. call Valve(124)%AdjacentTo(54)
  597. call Valve(54)%AdjacentTo(124)
  598. call Valve(54)%AdjacentTo(69)
  599. call Valve(69)%AdjacentTo(54)
  600. IRSafetyValveLed = 1
  601. call OpenSafetyValve_TripMode()
  602. #ifdef deb
  603. print*, 'InstallSafetyValve_TripMode()'
  604. #endif
  605. end subroutine
  606. subroutine RemoveSafetyValve_TripMode()
  607. implicit none
  608. IsSafetyValveInstalled_TripMode = .false.
  609. call Valve(124)%RemoveAdjacent(54)
  610. call Valve(54)%RemoveAdjacent(124)
  611. call Valve(54)%RemoveAdjacent(69)
  612. call Valve(69)%RemoveAdjacent(54)
  613. call Valve(124)%AdjacentTo(69)
  614. call Valve(69)%AdjacentTo(124)
  615. IRSafetyValveLed = 0
  616. call CloseSafetyValve_TripMode()
  617. OpenSafetyValveLed = 0
  618. CloseSafetyValveLed = 0
  619. #ifdef deb
  620. print*, 'RemoveSafetyValve_TripMode()'
  621. #endif
  622. end subroutine
  623. subroutine OpenSafetyValve_TripMode()
  624. implicit none
  625. if(.not.IsSafetyValveInstalled_TripMode) return
  626. OpenSafetyValveLed = 1
  627. CloseSafetyValveLed = 0
  628. SafetyValve = .true.
  629. call ChangeValve(54, SafetyValve)
  630. #ifdef deb
  631. print*, 'OpenSafetyValve_TripMode()'
  632. #endif
  633. end subroutine
  634. subroutine CloseSafetyValve_TripMode()
  635. implicit none
  636. if(.not.IsSafetyValveInstalled_TripMode) return
  637. CloseSafetyValveLed = 1
  638. OpenSafetyValveLed = 0
  639. SafetyValve = .false.
  640. call ChangeValve(54, SafetyValve)
  641. #ifdef deb
  642. print*, 'CloseSafetyValve_TripMode()'
  643. #endif
  644. end subroutine
  645. subroutine InstallSafetyValve_TopDrive()
  646. implicit none
  647. IsSafetyValveInstalled_TopDrive = .true.
  648. call Valve(128)%RemoveAdjacent(56)
  649. call Valve(56)%RemoveAdjacent(128)
  650. call Valve(127)%RemoveAdjacent(56)
  651. call Valve(56)%RemoveAdjacent(127)
  652. call Valve(69)%RemoveAdjacent(124)
  653. call Valve(124)%RemoveAdjacent(69)
  654. call Valve(124)%AdjacentTo(54)
  655. call Valve(54)%AdjacentTo(124)
  656. call Valve(54)%AdjacentTo(69)
  657. call Valve(69)%AdjacentTo(54)
  658. IRSafetyValveLed = 1
  659. call OpenSafetyValve_TopDrive()
  660. #ifdef deb
  661. print*, 'InstallSafetyValve_TopDrive()'
  662. #endif
  663. end subroutine
  664. subroutine RemoveSafetyValve_TopDrive()
  665. implicit none
  666. IsSafetyValveInstalled_TopDrive = .false.
  667. call Valve(124)%RemoveAdjacent(54)
  668. call Valve(54)%RemoveAdjacent(124)
  669. call Valve(54)%RemoveAdjacent(69)
  670. call Valve(69)%RemoveAdjacent(54)
  671. call Valve(124)%AdjacentTo(69)
  672. call Valve(69)%AdjacentTo(124)
  673. IRSafetyValveLed = 0
  674. call CloseSafetyValve_TopDrive()
  675. OpenSafetyValveLed = 0
  676. CloseSafetyValveLed = 0
  677. #ifdef deb
  678. print*, 'RemoveSafetyValve_TopDrive()'
  679. #endif
  680. end subroutine
  681. subroutine OpenSafetyValve_TopDrive()
  682. implicit none
  683. if(.not.IsSafetyValveInstalled_TopDrive) return
  684. OpenSafetyValveLed = 1
  685. CloseSafetyValveLed = 0
  686. SafetyValve = .true.
  687. #ifdef deb
  688. print*, 'OpenSafetyValve_TopDrive()'
  689. #endif
  690. call ChangeValve(54, SafetyValve)
  691. end subroutine
  692. subroutine CloseSafetyValve_TopDrive()
  693. implicit none
  694. if(.not.IsSafetyValveInstalled_TopDrive) return
  695. CloseSafetyValveLed = 1
  696. OpenSafetyValveLed = 0
  697. SafetyValve = .false.
  698. #ifdef deb
  699. print*, 'CloseSafetyValve_TopDrive()'
  700. #endif
  701. call ChangeValve(54, SafetyValve)
  702. end subroutine
  703. subroutine InstallIBop()
  704. implicit none
  705. IsIBopInstalled = .true.
  706. call Valve(103)%RemoveAdjacent(124)
  707. call Valve(124)%RemoveAdjacent(103)
  708. call Valve(55)%AdjacentTo(103)
  709. call Valve(55)%AdjacentTo(124)
  710. call Valve(103)%AdjacentTo(55)
  711. call Valve(124)%AdjacentTo(55)
  712. #ifdef deb
  713. print*, 'InstallIBop()'
  714. #endif
  715. IRIBopLed = 1
  716. call OpenIBop()
  717. end subroutine
  718. subroutine RemoveIBop()
  719. implicit none
  720. IsIBopInstalled = .false.
  721. call Valve(55)%RemoveAdjacent(103)
  722. call Valve(55)%RemoveAdjacent(124)
  723. call Valve(103)%RemoveAdjacent(55)
  724. call Valve(124)%RemoveAdjacent(55)
  725. call Valve(103)%AdjacentTo(124)
  726. call Valve(124)%AdjacentTo(103)
  727. #ifdef deb
  728. print*, 'RemoveIBop()'
  729. #endif
  730. IRIBopLed = 0
  731. IBop = .false.
  732. call ChangeValve(55, IBop)
  733. end subroutine
  734. subroutine OpenIBop()
  735. implicit none
  736. if(.not.IsIBopInstalled) return
  737. IBop = .true.
  738. #ifdef deb
  739. print*, 'OpenIBop()'
  740. #endif
  741. call ChangeValve(55, IBop)
  742. end subroutine
  743. subroutine CloseIBop()
  744. implicit none
  745. if(.not.IsIBopInstalled) return
  746. IBop = .false.
  747. #ifdef deb
  748. print*, 'CloseIBop()'
  749. #endif
  750. call ChangeValve(55, IBop)
  751. end subroutine
  752. subroutine InstallKellyCock()
  753. implicit none
  754. IsKellyCockInstalled = .true.
  755. call Valve(125)%RemoveAdjacent(126)
  756. call Valve(126)%RemoveAdjacent(125)
  757. call Valve(125)%AdjacentTo(68)
  758. call Valve(68)%AdjacentTo(125)
  759. call Valve(68)%AdjacentTo(126)
  760. call Valve(126)%AdjacentTo(68)
  761. #ifdef deb
  762. print*, 'InstallKellyCock()'
  763. #endif
  764. call OpenKellyCock()
  765. end subroutine
  766. subroutine RemoveKellyCock()
  767. implicit none
  768. IsKellyCockInstalled = .false.
  769. call Valve(125)%RemoveAdjacent(68)
  770. call Valve(126)%RemoveAdjacent(68)
  771. call Valve(68)%RemoveAdjacent(125)
  772. call Valve(68)%RemoveAdjacent(126)
  773. call Valve(125)%AdjacentTo(126)
  774. call Valve(126)%AdjacentTo(125)
  775. KellyCock = .false.
  776. call ChangeValve(68, KellyCock)
  777. CloseKellyCockLed = 0
  778. OpenKellyCockLed = 0
  779. #ifdef deb
  780. print*, 'RemoveKellyCock()'
  781. #endif
  782. end subroutine
  783. subroutine OpenKellyCock()
  784. implicit none
  785. if(.not.IsKellyCockInstalled) return
  786. OpenKellyCockLed = 1
  787. CloseKellyCockLed = 0
  788. KellyCock = .true.
  789. #ifdef deb
  790. print*, 'OpenKellyCock()'
  791. #endif
  792. call ChangeValve(68, KellyCock)
  793. end subroutine
  794. subroutine CloseKellyCock()
  795. implicit none
  796. if(.not.IsKellyCockInstalled) return
  797. CloseKellyCockLed = 1
  798. OpenKellyCockLed = 0
  799. KellyCock = .false.
  800. #ifdef deb
  801. print*, 'CloseKellyCock()'
  802. #endif
  803. call ChangeValve(68, KellyCock)
  804. end subroutine
  805. subroutine InstallTopDriveIBop()
  806. implicit none
  807. IsTopDriveIBopInstalled = .true.
  808. call Valve(126)%RemoveAdjacent(128)
  809. call Valve(128)%RemoveAdjacent(126)
  810. call Valve(126)%AdjacentTo(70)
  811. call Valve(70)%AdjacentTo(126)
  812. call Valve(128)%AdjacentTo(70)
  813. call Valve(70)%AdjacentTo(128)
  814. #ifdef deb
  815. print*, 'InstallTopDriveIBop()'
  816. #endif
  817. call OpenTopDriveIBop()
  818. end subroutine
  819. subroutine RemoveTopDriveIBop()
  820. implicit none
  821. IsTopDriveIBopInstalled = .false.
  822. call Valve(126)%RemoveAdjacent(70)
  823. call Valve(70)%RemoveAdjacent(126)
  824. call Valve(128)%RemoveAdjacent(70)
  825. call Valve(70)%RemoveAdjacent(128)
  826. call Valve(126)%AdjacentTo(128)
  827. call Valve(128)%AdjacentTo(126)
  828. #ifdef deb
  829. print*, 'RemoveTopDriveIBop()'
  830. #endif
  831. TopDriveIBop = .false.
  832. call ChangeValve(70, TopDriveIBop)
  833. end subroutine
  834. subroutine OpenTopDriveIBop()
  835. implicit none
  836. if(.not.IsTopDriveIBopInstalled) return
  837. TopDriveIBop = .true.
  838. call ChangeValve(70, TopDriveIBop)
  839. #ifdef deb
  840. print*, 'OpenTopDriveIBop()'
  841. #endif
  842. end subroutine
  843. subroutine CloseTopDriveIBop()
  844. implicit none
  845. if(.not.IsTopDriveIBopInstalled) return
  846. TopDriveIBop = .false.
  847. call ChangeValve(70, TopDriveIBop)
  848. #ifdef deb
  849. print*, 'CloseTopDriveIBop()'
  850. #endif
  851. end subroutine
  852. subroutine InstallFloatValve()
  853. implicit none
  854. IsFloatValveInstalled = .true.
  855. call Valve(69)%RemoveAdjacent(79)
  856. call Valve(79)%RemoveAdjacent(69)
  857. call Valve(48)%AdjacentTo(69)
  858. call Valve(48)%AdjacentTo(79)
  859. call Valve(69)%AdjacentTo(48)
  860. call Valve(79)%AdjacentTo(48)
  861. #ifdef deb
  862. print*, 'InstallFloatValve()'
  863. #endif
  864. call OpenFloatValve()
  865. end subroutine
  866. subroutine RemoveFloatValve()
  867. implicit none
  868. IsFloatValveInstalled = .false.
  869. call Valve(48)%RemoveAdjacent(69)
  870. call Valve(48)%RemoveAdjacent(79)
  871. call Valve(69)%RemoveAdjacent(48)
  872. call Valve(79)%RemoveAdjacent(48)
  873. call Valve(69)%AdjacentTo(79)
  874. call Valve(79)%AdjacentTo(69)
  875. #ifdef deb
  876. print*, 'RemoveFloatValve()'
  877. #endif
  878. FloatValve = .false.
  879. call ChangeValve(48, FloatValve)
  880. end subroutine
  881. subroutine OpenFloatValve()
  882. implicit none
  883. if(.not.IsFloatValveInstalled) return
  884. FloatValve = .true.
  885. #ifdef deb
  886. print*, 'OpenFloatValve()'
  887. #endif
  888. call ChangeValve(48, FloatValve)
  889. end subroutine
  890. subroutine CloseFloatValve()
  891. implicit none
  892. if(.not.IsFloatValveInstalled) return
  893. FloatValve = .false.
  894. #ifdef deb
  895. print*, 'CloseFloatValve()'
  896. #endif
  897. call ChangeValve(48, FloatValve)
  898. end subroutine
  899. subroutine ToggleFillupHead(v)
  900. implicit none
  901. logical, intent(in) :: v
  902. if(v) then
  903. call Valve(14)%RemoveAdjacent(78)
  904. call Valve(14)%AdjacentTo(57)
  905. call Valve(57)%AdjacentTo(14)
  906. call Valve(57)%AdjacentTo(103)
  907. call Valve(103)%AdjacentTo(57)
  908. else
  909. call Valve(14)%RemoveAdjacent(57)
  910. call Valve(57)%RemoveAdjacent(14)
  911. call Valve(57)%RemoveAdjacent(103)
  912. call Valve(103)%RemoveAdjacent(57)
  913. call Valve(14)%AdjacentTo(78)
  914. endif
  915. IsPathsDirty = .true.
  916. call ChangeValve(57, .true.)
  917. end subroutine
  918. subroutine ToggleMudBox(v)
  919. implicit none
  920. logical, intent(in) :: v
  921. call ChangeValve(53, v)
  922. end subroutine
  923. subroutine ToggleMiddleRams(v)
  924. implicit none
  925. logical, intent(in) :: v
  926. Valve(50)%Status = v
  927. call ChangeValve(69, v)
  928. end subroutine
  929. subroutine ChangeValve(i, state)
  930. implicit none
  931. integer, intent(in) :: i
  932. logical, intent(in) :: state
  933. if(Valve(i)%Status==state) return
  934. Valve(i)%Status = state
  935. if(i == 41 .or. i == 42) then
  936. if(Valve(41)%Status == .false. .and. Valve(42)%Status == .false.) then
  937. Valve(60)%Status = .true.
  938. else
  939. Valve(60)%Status = .false.
  940. endif
  941. endif
  942. #ifdef deb
  943. print*, 'Valve(', i, ') = ', state
  944. #endif
  945. !call Traverse()
  946. IsPathsDirty = .true.
  947. end subroutine
  948. subroutine DisplayOpenPaths()
  949. implicit none
  950. integer :: i
  951. if(allocated(OpenPaths)) then
  952. do i = 1, size(OpenPaths)
  953. call OpenPaths(i)%Display()
  954. end do
  955. end if
  956. end subroutine
  957. subroutine DisplayOpenPathsWrite()
  958. implicit none
  959. integer :: i
  960. if(allocated(OpenPaths)) then
  961. do i = 1, size(OpenPaths)
  962. call OpenPaths(i)%DisplayWrite()
  963. end do
  964. end if
  965. end subroutine
  966. end module CManifolds