seakeeping_collection_vector.f90 Source File


Contents


Source Code

!> Vector ๆณ›ๅž‹ๅ‘้‡ (้€š็”จไฝ†ๆ•ˆ็Ž‡็จไฝŽ)
module seakeeping_collection_vector

    implicit none

    private
    public :: vector

    !> ่Š‚็‚น
    type node
        private
        class(*), allocatable :: item  !! ๆณ›ๅž‹ๆ•ฐๆฎ
    end type node

    !> Vector ๆณ›ๅž‹ๅ‘้‡
    type vector
        private
        integer, public :: len = 0  !! ๆœ‰ๆ•ˆๅ‘้‡้•ฟๅบฆ
        type(node), allocatable :: items(:)  !! ๆณ›ๅž‹ๆ•ฐ็ป„
    contains
        procedure :: init
        procedure :: push, pop
        procedure :: get, set
        procedure :: clear
        procedure, private :: extend
    end type vector

contains

    !> ๅˆๅง‹ๅŒ–ๅ‘้‡
    pure subroutine init(self)
        class(vector), intent(inout) :: self

        self%len = 0
        if (.not. allocated(self%items)) allocate (self%items(256))

    end subroutine init

    !> ๅ‘้‡ๆ‰ฉๅฎน
    pure subroutine extend(self)
        class(vector), intent(inout) :: self
        type(node), allocatable :: tmp(:)
        intrinsic :: size

        allocate (tmp(size(self%items)))
        self%items = [self%items, tmp]

    end subroutine extend

    !> ๅ‘้‡ๅŽ‹ๅ…ฅ
    pure subroutine push(self, item)
        class(vector), intent(inout) :: self
        class(*), intent(in) :: item
        intrinsic :: size

        if (self%len == size(self%items)) call self%extend()
        self%len = self%len + 1
        allocate (self%items(self%len)%item, source=item)

    end subroutine push

    !> ๅ‘้‡ๅผนๅ‡บ
    subroutine pop(self, item)
        class(vector), intent(inout) :: self
        class(*), intent(out), optional, allocatable :: item

        if (self%len == 0) return
        if (present(item)) then
            call move_alloc(self%items(self%len)%item, item)
        else
            deallocate (self%items(self%len)%item)
        end if
        self%len = self%len - 1

    end subroutine pop

    !> ๅ‘้‡่Žทๅ–
    subroutine get(self, index, item)
        class(vector), intent(in) :: self
        integer, intent(in) :: index
        class(*), intent(out), allocatable :: item

        if (index < 1 .or. index > self%len) return
        allocate (item, source=self%items(index)%item)

    end subroutine get

    !> ๅ‘้‡่ฎพ็ฝฎ
    pure subroutine set(self, index, item)
        class(vector), intent(inout) :: self
        integer, intent(in) :: index
        class(*), intent(in) :: item

        if (index < 1 .or. index > self%len) return
        allocate (self%items(index)%item, source=item)

    end subroutine set

    !> ๅ‘้‡ๆธ…็ฉบ
    pure subroutine clear(self)
        class(vector), intent(inout) :: self

        deallocate (self%items)
        self%len = 0

    end subroutine clear

end module seakeeping_collection_vector