迭代器模式
正文:https://refactoringguru.cn/design-patterns/iterator
Go代码:https://refactoringguru.cn/design-patterns/iterator/go/example
module iterator_module
use, intrinsic :: iso_fortran_env, only: int8
implicit none
private
public :: user_type, user_collection_type, user_iterator_type, iterator_type
!> Abstract types
!> Collection
type, abstract :: collection_type
contains
procedure(collection_type_create_iterator), deferred :: create_iterator
end type collection_type
!> Iterator
type, abstract :: iterator_type
contains
procedure(iterator_t_has_next), deferred :: has_next
procedure(iterator_t_get_next), deferred :: get_next
end type iterator_type
!> User
type user_type
character(:), allocatable :: name
integer(int8) :: age
end type user_type
abstract interface
function collection_type_create_iterator(self) result(iterator)
import iterator_type, collection_type
!> TODO:
class(collection_type), intent(in) :: self
class(iterator_type), allocatable :: iterator
end function collection_type_create_iterator
logical function iterator_t_has_next(self)
import iterator_type
class(iterator_type), intent(in) :: self
end function iterator_t_has_next
type(user_type) function iterator_t_get_next(self)
import user_type, iterator_type
class(iterator_type), intent(inout) :: self
end function iterator_t_get_next
end interface
!> Specific types
!> User collection
type, extends(collection_type) :: user_collection_type
type(user_type), allocatable :: users(:)
contains
procedure :: create_iterator => user_collection_t_create_iterator
end type user_collection_type
!> User iterator
type, extends(iterator_type) :: user_iterator_type
integer :: index
type(user_type), allocatable :: users(:)
contains
procedure :: has_next => user_iterator_t_has_next
procedure :: get_next => user_iterator_t_get_next
end type user_iterator_type
contains
function user_collection_t_create_iterator(self) result(iterator)
class(user_collection_type), intent(in) :: self
class(iterator_type), allocatable :: iterator
! TODO:
iterator = user_iterator_type(index=0, users=self%users)
end function user_collection_t_create_iterator
logical function user_iterator_t_has_next(self) result(has)
class(user_iterator_type), intent(in) :: self
has = merge(.true., .false., self%index < size(self%users))
end function user_iterator_t_has_next
type(user_type) function user_iterator_t_get_next(self) result(user)
class(user_iterator_type), intent(inout) :: self
self%index = self%index + 1
user = self%users(self%index)
end function user_iterator_t_get_next
end module iterator_module
program iterator_main
use, intrinsic :: iso_fortran_env, only: int8
use iterator_module, only: user_type, user_collection_type, user_iterator_type, iterator_type
type(user_type) :: user1, user2, user
type(user_collection_type) :: user_collection
! TODO:
class(iterator_type), allocatable :: iterator
user1 = user_type(name="A", age=30_int8)
user2 = user_type(name="B", age=20_int8)
user_collection = user_collection_type(users=[user1, user2])
!> Specific iterator
allocate (user_iterator_type :: iterator)
iterator = user_collection%create_iterator()
do while (iterator%has_next())
user = iterator%get_next()
print "(3A,I3)", "User is ", user%name, ", age is ", user%age
end do
deallocate (iterator)
end program iterator_main
!> Results shall be:
! User is A, age is 30
! User is B, age is 20