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.
 
 
 
 
 
 

137 lines
4.2 KiB

  1. module CArrangement
  2. implicit none
  3. public
  4. integer, parameter :: Normal = 0
  5. integer, parameter :: Relation = 1
  6. integer, parameter :: Input = 2
  7. integer, parameter :: Output = 3
  8. integer, parameter :: InputOutput = 4
  9. type, public :: Arrangement
  10. integer, allocatable :: Adjacent(:) !adjacent valves that is connected to this valve
  11. logical :: Status !valve status ... open/close ... true/false
  12. integer :: ValveType ! Normal/Input/Output/InputOutput
  13. integer :: Number
  14. logical :: IsTraversed
  15. contains
  16. procedure :: Init => Init
  17. procedure :: IsConnectedTo => IsConnectedTo
  18. procedure :: IsSource => IsSource
  19. procedure :: Length => Length
  20. procedure :: AdjacentTo => AdjacentTo
  21. procedure :: RemoveAdjacent => RemoveAdjacent
  22. end type Arrangement
  23. contains
  24. subroutine Init(this, value)
  25. implicit none
  26. class(Arrangement), intent(inout) :: this
  27. integer, intent(in) :: value
  28. if(allocated(this%Adjacent)) deallocate(this%Adjacent)
  29. this%Status = .false.
  30. this%IsTraversed = .false.
  31. this%ValveType = Normal
  32. this%Number = value
  33. end subroutine
  34. integer function Length(this)
  35. implicit none
  36. class(Arrangement), intent(in) :: this
  37. if(allocated(this%Adjacent)) then
  38. Length = size(this%Adjacent)
  39. return
  40. end if
  41. Length = 0
  42. end function
  43. subroutine AdjacentTo(this, value)
  44. implicit none
  45. class(Arrangement), intent(inout) :: this
  46. integer, intent(in) :: value
  47. integer, allocatable :: tempArr(:)
  48. integer :: i, isize
  49. if(allocated(this%Adjacent)) then
  50. isize = size(this%Adjacent)
  51. ! check to see if already AdjacentTo that valve#
  52. do i=1,isize
  53. if(this%Adjacent(i)==value) return
  54. end do
  55. ! if value is a new entry then add it to the collection
  56. allocate(tempArr(isize+1))
  57. do i=1,isize
  58. tempArr(i) = this%Adjacent(i)
  59. end do
  60. tempArr(isize+1) = value
  61. deallocate(this%Adjacent)
  62. call move_alloc(tempArr, this%Adjacent)
  63. else
  64. allocate(this%Adjacent(1))
  65. this%Adjacent(1) = value
  66. end if
  67. end subroutine
  68. logical function IsConnectedTo(this, value)
  69. implicit none
  70. class(Arrangement), intent(in) :: this
  71. integer, intent(in) :: value
  72. if(.not.allocated(this%Adjacent)) then
  73. IsConnectedTo = .false.
  74. return
  75. endif
  76. IsConnectedTo = any(this%Adjacent == value)
  77. return
  78. end function
  79. logical function IsSource(this)
  80. implicit none
  81. class(Arrangement), intent(in) :: this
  82. IsSource = this%ValveType > Relation
  83. end function
  84. subroutine RemoveAdjacent(this, value)
  85. implicit none
  86. class(Arrangement), intent(inout) :: this
  87. integer, intent(in) :: value
  88. integer, allocatable :: tempArr(:)
  89. integer :: i, index, isize
  90. logical :: found
  91. if(.not.allocated(this%Adjacent))return
  92. index = -1
  93. do i=1, size(this%Adjacent)
  94. if(this%Adjacent(i)==value) then
  95. index = i
  96. exit
  97. end if
  98. end do
  99. if(index <= 0 .or. index > size(this%Adjacent)) return
  100. allocate(tempArr(size(this%Adjacent)-1))
  101. found = .false.
  102. do i=1, size(this%Adjacent)
  103. if(i==index) then
  104. found = .true.
  105. cycle
  106. end if
  107. if(found) then
  108. tempArr(i-1) = this%Adjacent(i)
  109. else
  110. tempArr(i) = this%Adjacent(i)
  111. endif
  112. end do
  113. deallocate(this%Adjacent)
  114. call move_alloc(tempArr, this%Adjacent)
  115. end subroutine
  116. end module CArrangement