命令模式

正文:https://refactoringguru.cn/design-patterns/command

Go代码:https://refactoringguru.cn/design-patterns/command/go/example

!> Reference: https://refactoring.guru/design-patterns/command/go/example
module command_pattern

    implicit none
    private

    public :: tv_type, on_command_type, off_command_type, button_type

    !> Abstract classes

    type, abstract :: command_type
    contains
        procedure(execute_procedure), deferred :: execute
    end type command_type

    type, abstract :: device_type
    contains
        procedure(on_procedure), deferred :: on
        procedure(off_procedure), deferred :: off
    end type device_type

    abstract interface
        subroutine execute_procedure(self)
            import command_type
            class(command_type), intent(inout) :: self
        end subroutine execute_procedure
        subroutine on_procedure(self)
            import device_type
            class(device_type), intent(inout) :: self
        end subroutine on_procedure
        subroutine off_procedure(self)
            import device_type
            class(device_type), intent(inout) :: self
        end subroutine off_procedure
    end interface

    !> Specific Objects

    type, extends(command_type) :: on_command_type
        class(device_type), pointer :: d
    contains
        procedure :: execute => on_command_type_execute
    end type on_command_type

    type, extends(command_type) :: off_command_type
        class(device_type), pointer :: d
    contains
        procedure :: execute => off_command_type_execute
    end type off_command_type

    type, extends(device_type) :: tv_type
        logical :: is_running
    contains
        procedure :: on => tv_type_on
        procedure :: off => tv_type_off
    end type tv_type

    type :: button_type
        class(command_type), pointer :: c
    contains
        procedure :: press
    end type button_type

contains

    subroutine press(self)
        class(button_type), intent(inout) :: self
        call self%c%execute()
    end subroutine press

    subroutine on_command_type_execute(self)
        class(on_command_type), intent(inout) :: self
        call self%d%on()
    end subroutine on_command_type_execute

    subroutine off_command_type_execute(self)
        class(off_command_type), intent(inout) :: self
        call self%d%off()
    end subroutine off_command_type_execute

    subroutine tv_type_on(self)
        class(tv_type), intent(inout) :: self
        self%is_running = .true.
        print *, "Turning tv on. ✔️"
    end subroutine tv_type_on

    subroutine tv_type_off(self)
        class(tv_type), intent(inout) :: self
        self%is_running = .false.
        print *, "Turning tv off. ❌"
    end subroutine tv_type_off

end module command_pattern
!> Reference: https://refactoring.guru/design-patterns/command/go/example
program test_command

    use command_pattern, only: tv_type, on_command_type, off_command_type, button_type
    type(tv_type) :: t
    type(on_command_type) :: on_c
    type(off_command_type) :: off_c

    type(button_type) :: on_b
    type(button_type) :: off_b

    !> Linking
    allocate (on_c%d, source=t)
    allocate (off_c%d, source=t)

    allocate (on_b%c, source=on_c)
    allocate (off_b%c, source=off_c)

    !> Operating
    call on_b%press()
    call off_b%press()

    !> Free memory.
    deallocate (on_c%d)
    deallocate (off_c%d)
    deallocate (on_b%c)
    deallocate (off_b%c)

end program test_command

!> Results shall be:

!  Turning tv on. ✔️
!  Turning tv off. ❌