责任链模式

正文:https://refactoringguru.cn/design-patterns/chain-of-responsibility

Go代码:https://refactoringguru.cn/design-patterns/chain-of-responsibility/go/example

示例

本例子模拟医院的看病缴费的责任链。

病人需要进行的大致步骤是:

  1. 进院,注册信息
  2. 医生检查
  3. 药房给药
  4. 病人缴费,出院
!> CoR: Hospital departments
module hospital_CoR

    implicit none
    private

    public :: patient_type, department_type, reception_type, doctor_type, medical_type, cashier_type

    type patient_type
        character(:), allocatable :: name
        logical :: registration_done
        logical :: doctor_check_up_done
        logical :: medicine_done
        logical :: payment_done
    end type patient_type

    type, abstract :: department_type
    contains
        procedure(execute_procedure), deferred :: execute
        procedure(set_next_procedure), deferred :: set_next
    end type department_type

    abstract interface
        subroutine execute_procedure(self, p)
            import department_type, patient_type
            class(department_type), intent(inout) :: self
            type(patient_type), intent(inout) :: p
        end subroutine execute_procedure
        subroutine set_next_procedure(self, next)
            import department_type
            class(department_type), intent(inout) :: self
            class(department_type), intent(inout) :: next
        end subroutine set_next_procedure
    end interface

    type, extends(department_type) :: reception_type
        class(department_type), pointer :: next
    contains
        procedure :: execute => reception_type_execute
        procedure :: set_next => reception_type_set_next
    end type reception_type

    type, extends(department_type) :: doctor_type
        class(department_type), pointer :: next
    contains
        procedure :: execute => doctor_type_execute
        procedure :: set_next => doctor_type_set_next
    end type doctor_type

    type, extends(department_type) :: medical_type
        class(department_type), pointer :: next
    contains
        procedure :: execute => medicine_type_execute
        procedure :: set_next => medicine_type_set_next
    end type medical_type

    type, extends(department_type) :: cashier_type
        class(department_type), pointer :: next
    contains
        procedure :: execute => cashier_type_execute
        procedure :: set_next => cashier_type_set_next
    end type cashier_type

contains

    subroutine reception_type_execute(self, p)
        class(reception_type), intent(inout) :: self
        type(patient_type), intent(inout) :: p

        if (p%registration_done) then
            print *, "Patient registration already done.✔️"
            call self%next%execute(p)
            return
        end if

        print *, "Reception registering patient."
        p%registration_done = .true.
        call self%next%execute(p)

    end subroutine reception_type_execute

    subroutine reception_type_set_next(self, next)
        class(reception_type), intent(inout) :: self
        class(department_type), intent(inout) :: next

        allocate (self%next, source=next)

    end subroutine reception_type_set_next

    subroutine doctor_type_execute(self, p)
        class(doctor_type), intent(inout) :: self
        type(patient_type), intent(inout) :: p

        if (p%doctor_check_up_done) then
            print *, "Doctor checkup already done.✔️"
            call self%next%execute(p)
            return
        end if

        print *, "Doctor checking patient."
        p%doctor_check_up_done = .true.
        call self%next%execute(p)

    end subroutine doctor_type_execute

    subroutine doctor_type_set_next(self, next)
        class(doctor_type), intent(inout) :: self
        class(department_type), intent(inout) :: next

        allocate (self%next, source=next)

    end subroutine doctor_type_set_next

    subroutine medicine_type_execute(self, p)
        class(medical_type), intent(inout) :: self
        type(patient_type), intent(inout) :: p

        if (p%medicine_done) then
            print *, "Medicine already given to patient.✔️"
            call self%next%execute(p)
            return
        end if

        print *, "Medical giving medicine to patient."
        p%medicine_done = .true.
        call self%next%execute(p)

    end subroutine medicine_type_execute

    subroutine medicine_type_set_next(self, next)
        class(medical_type), intent(inout) :: self
        class(department_type), intent(inout) :: next

        allocate (self%next, source=next)

    end subroutine medicine_type_set_next

    subroutine cashier_type_execute(self, p)
        class(cashier_type), intent(inout) :: self
        type(patient_type), intent(inout) :: p

        if (p%payment_done) then
            print *, "Payment Done.✔️"
            return
        end if

        print *, "Cashier getting money from patient."
        p%payment_done = .true.

    end subroutine cashier_type_execute

    subroutine cashier_type_set_next(self, next)
        class(cashier_type), intent(inout) :: self
        class(department_type), intent(inout) :: next

        allocate (self%next, source=next)

    end subroutine cashier_type_set_next

end module hospital_CoR

!> CoR: Patient visiting hospital
program CoR_main

    use hospital_CoR

    type(cashier_type) :: c
    type(medical_type) :: m
    type(doctor_type) :: d
    type(reception_type) :: r

    type(patient_type) :: p1, p2

    !> Set next for departments
    call m%set_next(c)
    call d%set_next(m)
    call r%set_next(d)

    p1 = patient_type("abc", .true., .true., .true., .true.)
    !> Patient visiting
    print *, "> Patient `"//p1%name//"` : "
    call r%execute(p1)

    p2 = patient_type("def", .true., .false., .false., .false.)
    !> Patient visiting
    print *, "> Patient `"//p2%name//"` : "
    call r%execute(p2)

    !> Optional statements
    deallocate (m%next)
    deallocate (d%next)
    deallocate (r%next)

end program CoR_main

!> Results shall be:

!  > Patient `abc` :
!  Patient registration already done.✔️
!  Doctor checkup already done.✔️
!  Medicine already given to patient.✔️
!  Payment Done.✔️
!  > Patient `def` :
!  Patient registration already done.✔️
!  Doctor checking patient.
!  Medical giving medicine to patient.
!  Cashier getting money from patient.

评价

责任链很像流水线,上一节点处理完进入下一节点。

可以应用于科学计算的文件输入检查过程。