首页 > 解决方案 > 复数矩阵类的 Fortran 运算符赋值(=)

问题描述

如何为复数矩阵类编写赋值运算符。我知道复杂是fortran的标准。对于 zcomplex_type 工作正常。我可以将复数的实部分配给实型,但在 zmatrix_type 中不起作用。我必须在子程序 zmatrix_realmatrix_assign 中创建实数矩阵。

错误

mat1=tab
Error: Incompatible ranks 0 and 2 in assignment at (1)
module zmatrix_module
implicit none
type, public :: zcomplex_type

    real :: realis
    real :: imaginalis

end type zcomplex_type

type, public :: zmatrix_type
    type(zcomplex_type), dimension(:,:), allocatable, public :: zmatrix_data
end type zmatrix_type

    public :: zmatrix_allocate
    public :: zmatrix_free
    public :: zmatrix_set
    public :: zmatrix_print
    public :: assignment(=)
    
interface assignment(=)
procedure zcomplex_re_assign
procedure re_zcomplex_assign
procedure zmatrix_realmatrix_assign
end interface 
    
contains

subroutine zcomplex_re_assign(zcomplex1,real2)
type(zcomplex_type), intent(out) :: zcomplex1
real, intent(in) :: real2
        zcomplex1%realis =real2
        zcomplex1%imaginalis =0.0
end subroutine zcomplex_re_assign

subroutine re_zcomplex_assign(real2,zcomplex1)
real, intent(out) :: real2
type(zcomplex_type), intent(in) :: zcomplex1
        real2=zcomplex1%realis 
end subroutine re_zcomplex_assign

subroutine zmatrix_realmatrix_assign(zmatrix1,realmatrix2)
type(zmatrix_type), intent(out) :: zmatrix1
real,  intent(in) :: realmatrix2

    zmatrix1%zmatrix_data%realis=realmatrix2
    zmatrix1%zmatrix_data%imaginalis=0
end subroutine zmatrix_realmatrix_assign

subroutine zmatrix_allocate(zarray,rows)
    type(zmatrix_type), intent(out) :: zarray
    integer, intent(in) :: rows
    allocate(zarray%zmatrix_data(1:rows, 1:rows))
end subroutine zmatrix_allocate

subroutine zmatrix_free(zarray)
    type(zmatrix_type), intent(inout) :: zarray
    deallocate(zarray%zmatrix_data)
end subroutine zmatrix_free

subroutine zmatrix_set(zarray, rows, re_values, im_values)
    type(zmatrix_type), intent(inout) :: zarray
    integer, intent(in) :: rows
    real, intent(in) :: re_values, im_values
    integer :: i,j
    do i=1, rows
        do j=1, rows
            zarray%zmatrix_data(i,j)%realis = re_values
            zarray%zmatrix_data(i,j)%imaginalis = im_values
        enddo
    enddo
end subroutine zmatrix_set

subroutine zmatrix_print(array,rows)
    type(zmatrix_type), intent(in) :: array
    integer, intent(in) :: rows
    integer i,j
    
    do i=1, rows
        write(*,*) (array%zmatrix_data(i,j), j=1, rows)
    enddo
    write(*,*)
end subroutine zmatrix_print

end module zmatrix_module

Program main
use zmatrix_module
implicit none
type(zmatrix_type) :: mat1
real :: tab(3,3)
call zmatrix_allocate(mat1,3)
tab=3
mat1=tab
print *, mat1

call zmatrix_free(mat1)

End Program main ```

标签: fortranassignment-operator

解决方案


您创建了一个重载赋值运算符zmatrix_realmatrix_assign,它将 real量值作为输入并输出 a zmatrix_type

我的猜测是您可能想要zmatrix_realmatrix_assign执行以下操作:

  1. 让它接受一个二维实数组real, intent(in) :: realmatrix2(:,:)
  2. zmatrix1%zmatrix_data相应地分配
  3. 像以前一样设置实/图像部分
  subroutine zmatrix_realmatrix_assign(this, rmat)
    type(zmatrix_type), intent(out) :: this
    real,               intent(in)  :: rmat(:,:)

    allocate (this%zmatrix_data(size(rmat, dim=1), size(rmat, dim=2)))
    this%zmatrix_data%realis     = rmat
    this%zmatrix_data%imaginalis = 0
  end subroutine

赋值过程显式分配数据结构this%zmatrix_data,因此程序中的 allocate 调用是不必要的

call zmatrix_allocate(mat1,3)

您仍然可以zmatrix_allocate通过更改分配过程中的意图来使用该过程,但它容易出错(这就是我添加分配测试的原因)

  subroutine zmatrix_realmatrix_assign(this, rmat)
    type(zmatrix_type), intent(inout) :: this
    real,               intent(in)    :: rmat(:,:)

    if (.not. allocated(this%zmatrix_data)         ) error stop 'did not call allocate beforehand'
    if (any(shape(this%zmatrix_data) /= shape(rmat)) error stop 'wrong allocation of zmatrix_data'
    this%zmatrix_data%realis     = rmat
    this%zmatrix_data%imaginalis = 0
  end subroutine

推荐阅读