在我的代码中,我使用的是可分配的派生数据类型(例如,类型数据),其中存储了多维可分配的数组(x和y)。在同一模块中,我还定义了例程以分配/取消分配整个对象,赋值运算符(=)以及其他重载运算符(*)和(+)。现在,我在主程序中分配data1(类型为data)以及data1%x和data1%y,对其进行初始化,并使用重载运算符执行简单的操作(假设对data1的所有元素进行了简单的乘法运算) %x和data1%y的常数)。这是编译和复制我刚才描述的代码的最小代码:
program minimal
USE dimensions
USE typedef
IMPLICIT NONE
integer :: i, k
type(data), dimension(:), allocatable :: data1, data2
call alloc ( data1 )
call alloc ( data2 )
do k = 1 , ndat
data1(k)%x = real(k)
data1(k)%y = -real(k)
data2(k)%x = 0.
data2(k)%y = 0.
enddo
do i = 1, 10
data2 = data2 + 2.*data1
enddo
do k = 1, ndat
print*, k, maxval(data2(k)%x), maxval(data2(k)%y)
enddo
call dealloc ( data1 )
call dealloc ( data2 )
end program
和模块:
module dimensions
integer :: ndat=2
integer :: m1=10, m2=50
integer :: n1=10, n2=50
end module dimensions
module typedef
USE dimensions
type :: data
real, dimension(:,:), allocatable :: x
real, dimension(:,:), allocatable :: y
end type data
interface alloc
module procedure alloc_data
end interface alloc
interface dealloc
module procedure dealloc_data
end interface dealloc
interface assignment (=)
module procedure data_to_data
end interface
interface operator (*)
module procedure const_times_data
end interface
interface operator (+)
module procedure data_plus_data
end interface
CONTAINS
subroutine alloc_data (data1)
type(data), dimension(:), allocatable, intent(inout) :: data1
integer :: i
allocate ( data1(1:ndat) )
do i = 1, ndat
allocate ( data1(i)%x(m1:m2,n1:n2) )
allocate ( data1(i)%y(m1:m2,n1:n2) )
enddo
end subroutine alloc_data
subroutine dealloc_data (data1)
type(data), dimension(:), allocatable, intent(inout) :: data1
integer :: i
do i = 1, ndat
deallocate ( data1(i)%x )
deallocate ( data1(i)%y )
enddo
deallocate ( data1 )
end subroutine dealloc_data
subroutine data_to_data (data2,data1)
type(data), dimension(:), intent(in) :: data1
type(data), dimension(1:ndat), intent(out) :: data2
integer :: i
do i = 1, ndat
data2(i)%x = data1(i)%x
data2(i)%y = data1(i)%y
enddo
end subroutine data_to_data
function const_times_data (c,data1) result(data2)
type(data), dimension(:), intent(in) :: data1
real, intent(in) :: c
type(data), dimension(1:ndat) :: data2
integer :: i
do i = 1, ndat
data2(i)%x = c*data1(i)%x
data2(i)%y = c*data1(i)%y
enddo
end function const_times_data
function data_plus_data (data1,data2) result(data3)
type(data), dimension(:), intent(in) :: data1, data2
type(data), dimension(1:ndat) :: data3
integer :: i
do i = 1, ndat
data3(i)%x = data1(i)%x + data2(i)%x
data3(i)%y = data1(i)%y + data2(i)%y
enddo
end function data_plus_data
end module typedef
使用ifort 17.0(我们机器上的推荐版本)和-O0选项进行调试编译代码不会返回任何问题。但是,使用优化级别-O2或-O3会产生分段错误。我已经用ifort 18.0尝试了相同的过程,但结果相同,而ifort 19.0似乎可以工作。
我也用这个最小的代码玩了一点,发现例如,如果数据结构“数据”包含单个元素x,或者它本身不是可分配的数组,则它可以与优化的ifort 17一起使用。
问题很简单:ifort编译器的早期版本是否存在问题,或者我做错了什么?现在,我发现了一个非常简单的解决方法(其中包括重新定义运算符(*)以处理单个数据元素,即function data_times_data
中没有任何循环),但是我想知道一种干净的方法在充分利用重载运算符功能的同时,重写上面的代码以避免当前问题。
非常感谢。
答案 0 :(得分:2)
我可以使用ifort 18.0确认段错误。由于某些原因,当重载+
或*
运算符时,编译器不希望将哑元参数作为数组。我建议保持参数标量不变,而使函数elemental
代替:
module dimensions
integer :: ndat=2
integer :: m1=10, m2=50
integer :: n1=10, n2=50
end module dimensions
module typedef
USE dimensions
type :: data
real, dimension(:,:), allocatable :: x
real, dimension(:,:), allocatable :: y
end type data
interface alloc
module procedure alloc_data
end interface alloc
interface dealloc
module procedure dealloc_data
end interface dealloc
interface assignment (=)
module procedure data_to_data
end interface
interface operator (*)
module procedure const_times_data
end interface
interface operator (+)
module procedure data_plus_data
end interface
CONTAINS
subroutine alloc_data (data1)
type(data), dimension(:), allocatable, intent(inout) :: data1
integer :: i
allocate ( data1(1:ndat) )
do i = 1, ndat
allocate ( data1(i)%x(m1:m2,n1:n2) )
allocate ( data1(i)%y(m1:m2,n1:n2) )
enddo
end subroutine alloc_data
subroutine dealloc_data (data1)
type(data), dimension(:), allocatable, intent(inout) :: data1
integer :: i
do i = 1, ndat
deallocate ( data1(i)%x )
deallocate ( data1(i)%y )
enddo
deallocate ( data1 )
end subroutine dealloc_data
elemental subroutine data_to_data (data2,data1)
type(data), intent(in) :: data1
type(data), intent(out) :: data2
integer :: i
data2%x = data1%x
data2%y = data1%y
end subroutine data_to_data
elemental function const_times_data (c,data1) result(data2)
type(data), intent(in) :: data1
real, intent(in) :: c
type(data) :: data2
integer :: i
data2%x = c*data1%x
data2%y = c*data1%y
end function const_times_data
elemental function data_plus_data (data1,data2) result(data3)
type(data), intent(in) :: data1, data2
type(data) :: data3
integer :: i
data3%x = data1%x + data2%x
data3%y = data1%y + data2%y
end function data_plus_data
end module typedef
我认为使用elemental
还是比将维度硬编码到函数中更好的样式,尽管考虑到Fortran标准,我无法立即找到任何直接禁止您尝试做的事情。