# 1 "/home/admin/SimulationCore2/CSharp/Equipments/MudPathFinding/CPath.f90" module CPath use CLog5 implicit none public type, public :: Path integer, allocatable :: Valves(:) logical :: IsClosed contains procedure :: Display => Display procedure :: DisplayWrite => DisplayWrite procedure :: First => First procedure :: Last => Last procedure :: Length => Length procedure :: Get => Get procedure :: Add => Add procedure :: Remove => Remove procedure :: Purge => Purge procedure :: Copy => Copy procedure :: MakeNull => MakeNull procedure :: IsNull => IsNull procedure :: Equal => Equal procedure :: Find => Find end type Path contains subroutine DisplayWrite(this) implicit none class(Path), intent(in) :: this character(len=512) :: temp integer :: i if(allocated(this%valves)) then write(temp, '(a1,i0,a3,i0,a4,9999(g0))') '(', this%First(), '<=>', this%Last(), ') : ', (this%Valves(i), ", ",i=1,size(this%Valves)) write(*,*) temp end if end subroutine subroutine Display(this) implicit none class(Path), intent(in) :: this character(len=512) :: temp integer :: i if(allocated(this%valves)) then write(temp, '(a1,i0,a3,i0,a4,9999(g0))') '(', this%First(), '<=>', this%Last(), ') : ', (this%Valves(i), ", ",i=1,size(this%Valves)) call Log_5(temp) end if end subroutine integer function First(this) implicit none class(Path), intent(in) :: this if(allocated(this%Valves) .and. size(this%Valves) > 0) then First = this%Valves(1) return end if First = 0 end function integer function Last(this) implicit none class(Path), intent(in) :: this if(allocated(this%Valves) .and. size(this%Valves) > 0) then Last = this%Valves(size(this%Valves)) return end if Last = 0 end function integer function Length(this) implicit none class(Path), intent(in) :: this if(allocated(this%Valves)) then Length = size(this%Valves) return end if Length = 0 end function integer function Get(this, index) implicit none class(Path), intent(in) :: this integer, intent(in) :: index if(allocated(this%Valves)) then if(index < 1 .or. index > size(this%Valves)) then Get = -1 return endif Get = this%Valves(index) return end if get = -1 end function subroutine Add(this, value) implicit none class(Path), intent(inout) :: this integer, allocatable :: tempArr(:) integer, intent(in) :: value integer :: i, isize if(allocated(this%Valves)) then isize = size(this%Valves) allocate(tempArr(isize+1)) do i=1,isize tempArr(i) = this%Valves(i) end do tempArr(isize+1) = value deallocate(this%Valves) call move_alloc(tempArr, this%Valves) else allocate(this%Valves(1)) this%Valves(1) = value end if end subroutine subroutine Remove(this, index) implicit none class(Path), intent(inout) :: this integer, intent(in) :: index integer, allocatable :: tempArr(:) integer :: i logical :: found if(index <= 0 .or. index > size(this%Valves)) return if(.not.allocated(this%Valves))return allocate(tempArr(size(this%Valves)-1)) found = .false. do i=1, size(this%Valves) if(i==index) then found = .true. cycle end if if(found) then tempArr(i-1) = this%Valves(i) else tempArr(i) = this%Valves(i) endif end do deallocate(this%valves) call move_alloc(tempArr, this%valves) end subroutine subroutine Purge(this, min, max) implicit none class(Path), intent(inout) :: this integer, intent(in) :: min integer, intent(in) :: max integer :: i i = 1 do ! if(this%Valves(i) >= min .and. this%Valves(i) <= max) then call this%Remove(i) else i = i + 1 endif if(i > this%Length()) exit enddo end subroutine subroutine Copy(this, from) implicit none class(Path), intent(inout) :: this class(Path), intent(in) :: from if(allocated(from%Valves)) then if(allocated(this%Valves)) deallocate(this%Valves) allocate(this%Valves(size(from%Valves))) this%Valves(:) = from%Valves(:) end if end subroutine subroutine MakeNull(this) implicit none class(Path), intent(inout) :: this if(allocated(this%Valves)) deallocate(this%Valves) end subroutine logical function IsNull(this) implicit none class(Path), intent(in) :: this IsNull = .not.allocated(this%Valves) return end function logical function Equal(this, otherPath) implicit none class(Path), intent(inout) :: this class(Path), intent(in) :: otherPath integer :: i, sizeThis, sizeOtherPath sizeThis = size(this%Valves) sizeOtherPath = size(otherPath%Valves) if(sizeThis /= sizeOtherPath) then Equal = .false. return end if do i = 1, sizeThis if(this%Valves(i) /= otherPath%Valves(i)) then Equal = .false. return end if end do Equal = .true. return end function logical function Find(this, value) implicit none class(Path), intent(in) :: this integer, intent(in) :: value if(allocated(this%Valves)) then Find = any(this%Valves == value) return end if Find = .false. end function end module CPath