原型模式
正文:https://refactoringguru.cn/design-patterns/prototype
Go代码:https://refactoringguru.cn/design-patterns/prototype/go/example
module prototype_module
implicit none
private
public :: file_type, folder_type, inode_type
type, abstract :: inode_type
contains
procedure(inode_type_print), deferred :: print
procedure(inode_type_clone), deferred :: clone
end type inode_type
type, extends(inode_type) :: file_type
character(:), allocatable :: name
contains
procedure :: print => file_type_print
procedure :: clone => file_type_clone
end type file_type
!> Wrapper (Important)
type node_type
class(inode_type), pointer :: inode
end type node_type
type, extends(inode_type) :: folder_type
type(node_type), allocatable :: children(:)
character(:), allocatable :: name
contains
procedure :: print => folder_type_print
procedure :: clone => folder_type_clone
end type folder_type
abstract interface
subroutine inode_type_print(self, indentation)
import inode_type
class(inode_type), intent(inout) :: self
character(*), intent(in) :: indentation
end subroutine inode_type_print
function inode_type_clone(self) result(inode)
import inode_type
class(inode_type), intent(inout) :: self
class(inode_type), allocatable :: inode
end function inode_type_clone
end interface
contains
subroutine file_type_print(self, indentation)
class(file_type), intent(inout) :: self
character(*), intent(in) :: indentation
print *, indentation//self%name
end subroutine file_type_print
function file_type_clone(self) result(inode)
class(file_type), intent(inout) :: self
class(inode_type), allocatable :: inode
allocate (file_type :: inode)
inode = file_type(name=self%name//"_clone")
end function file_type_clone
! - - - - - - - - -
subroutine folder_type_print(self, indentation)
class(folder_type), intent(inout) :: self
character(*), intent(in) :: indentation
integer :: i
print *, indentation//self%name
if (size(self%children) == 0) return
do i = 1, size(self%children)
call self%children(i)%inode%print(indentation//indentation)
end do
end subroutine folder_type_print
!> There may be incorrect usage here, but I have no choice but to do so.
!> Fortran's compilation check is stricter, and I am indeed bypassing it.
function folder_type_clone(self) result(inode)
class(folder_type), intent(inout) :: self
class(inode_type), allocatable :: inode
type(folder_type), allocatable :: tmp_folder
integer :: i
allocate (tmp_folder, source=self)
tmp_folder%name = tmp_folder%name//"_clone"
if (size(self%children) > 0) then
do i = 1, size(tmp_folder%children)
associate (node => tmp_folder%children(i)%inode)
inode = node%clone()
allocate (tmp_folder%children(i)%inode, source=inode)
end associate
end do
end if
call move_alloc(tmp_folder, inode)
end function folder_type_clone
end module prototype_module
program prototype_main
use prototype_module, only: file_type, folder_type, inode_type
implicit none
type(file_type), target :: file1, file2, file3
type(folder_type), target :: folder1
type(folder_type) :: folder2
class(inode_type), allocatable :: clone_folder
file1%name = "file1"
file2%name = "file2"
file3%name = "file3"
folder1%name = "folder1"
allocate (folder1%children(1))
folder1%children(1)%inode => file1
folder2%name = "folder2"
allocate (folder2%children(3))
folder2%children(1)%inode => folder1
folder2%children(2)%inode => file2
folder2%children(3)%inode => file3
print *, "Printing hierarchy for Folder2"
call folder2%print(" ")
clone_folder = folder2%clone()
print *, "Printing hierarchy for clone Folder"
call clone_folder%print(" ")
end program prototype_main
!> Results shall be:
! Printing hierarchy for Folder2
! folder2
! folder1
! file1
! file2
! file3
! Printing hierarchy for clone Folder
! folder2_clone
! folder1_clone
! file1_clone
! file2_clone
! file3_clone