我有一个派生类型,其指针指向第二个派生类型的数组
TYPE vertex
REAL :: x, y, z
END TYPE
TYPE path
TYPE(vertex), DIMENSION(:), POINTER :: vertices => NULL()
END TYPE
目的是使顶点数组可调整大小,以便可以将任意数量的顶点添加到数组中。我已创建代码将顶点附加到该指针。
SUBROUTINE path_append_vertex(this, x, y, z)
IMPLICIT NONE
!-------------------------------------------------------------------------------
! Variable declarations.
!-------------------------------------------------------------------------------
TYPE(path), INTENT(inout) :: this
REAL, INTENT(in) :: x, y, z
!-------------------------------------------------------------------------------
! Local Variable declarations.
!-------------------------------------------------------------------------------
INTEGER :: status
TYPE(vertex), DIMENSION(:), ALLOCATABLE :: vertices
!-------------------------------------------------------------------------------
! Start of executable code
!-------------------------------------------------------------------------------
IF (ASSOCIATED(this%vertices)) THEN
! Create a temporary array the same size as current number of vertices. Copy the
! contents of the old array to the new array then delete the old array.
ALLOCATE(vertices(SIZE(this%vertices)), STAT = status)
CALL check_status(status)
vertices = this%vertices
DEALLOCATE(this%vertices)
! Create a new array with one extra element. Copy the contents of the temporary
! array to the new one the delete the temporary array.
ALLOCATE(this%vertices(SIZE(vertices) + 1), STAT = status)
CALL check_status(status)
this%vertices(1:SIZE(vertices)) = vertices
DEALLOCATE(vertices)
this%vertices(SIZE(this%vertices))%x = x
this%vertices(SIZE(this%vertices))%y = y
this%vertices(SIZE(this%vertices))%z = z
ELSE
ALLOCATE(this%vertices(1), STAT = status)
CALL check_status(status)
this%vertices(1)%x = x
this%vertices(1)%y = y
this%vertices(1)%z = z
ENDIF
END SUBROUTINE
我创建了一些路径对象。
TYPE ipch_desc
...
TYPE(path) :: chordPath
END TYPE
SUBROUTINE ipch_desc_construct(this, ...)
...
TYPE (ipch_desc), INTENT(inout) :: this
...
! Must NULL out the vertices array or else it will point to the last
! integration_path created in memory. Not sure why these are defaulting
! to NULL
this%chordPath%vertices => NULL()
CALL path_append_vertex(this%chordPath, xcart_i(1), xcart_i(2), xcart_i(3))
CALL path_append_vertex(this%chordPath, xcart_f(1), xcart_f(2), xcart_f(3))
! Check the value of the path vertices.
write(*,*) this%chordPath%vertices
END SUBROUTINE
一切都很好,我得到每个顶点的正确值。例如,对于创建的三个路径对象,我得到了
-0.33808113528699218 1.0467574437103653 0.10713720000000000 -0.16057879084545851 0.49717960298733294 0.10713720000000000
-0.33322243268266594 1.0483142707971911 1.42240000000000010E-003 -0.14945358419461796 0.47017940500485894 1.42240000000000010E-003
-0.33656460666251325 1.0472460386853264 -0.10629900000000000 -0.15821659220752302 0.49230280357365630 -0.10629900000000000
在代码中使用这些路径对象后,
SUBROUTINE ipch_mc_model_compute(a_ipch, ...)
...
TYPE (ipch_desc), INTENT (inout) :: a_ipch
...
! Check the value of the path vertices again.
write(*,*) a_ipch%chordPath%vertices
...
END SUBROUTINE
只有前N-1值保持正确。对于我上面创建的相同值,
-0.33808113528699218 1.0467574437103653 0.10713720000000000 -0.16057879084545851 0.49717960298733294 0.10713720000000000
-0.33322243268266594 1.0483142707971911 1.42240000000000010E-003 -0.14945358419461796 0.47017940500485894 1.42240000000000010E-003
0.15094203233057696 6.94277920927416864E-310 -0.10629900000000000 1.63041663127611360E-322 3.01884064661153912E-003 6.94277920927179713E-310
无论我创建的path
个对象的数量如何,Nth总是以错误的值结束。可能导致这种情况的原因是什么?
答案 0 :(得分:1)
您的代码似乎正确无误。你可以简化一下。为什么派生类型PATH包含单个变量?您可以直接调整VERTEX类型的数组,而无需使用此附加类型。另外,我认为没有理由使用指针;可分配的就足够了。 Fortran 2003提供了MOVE_ALLOC,它也可以提供简化(如果在您使用的编译器中可用)(请参阅Insert a value changing shape in allocated vector fortran)。
module vertex_stuff
TYPE vertex
REAL :: x, y, z
END TYPE
contains
SUBROUTINE path_append_vertex(this, x, y, z)
IMPLICIT NONE
!-------------------------------------------------------------------------------
! Variable declarations.
!-------------------------------------------------------------------------------
TYPE(vertex), dimension (:), allocatable, INTENT(inout) :: this
REAL, INTENT(in) :: x, y, z
!-------------------------------------------------------------------------------
! Local Variable declarations.
!-------------------------------------------------------------------------------
TYPE(vertex), DIMENSION(:), ALLOCATABLE :: tmp_vertices
!-------------------------------------------------------------------------------
! Start of executable code
!-------------------------------------------------------------------------------
IF (allocated(this)) THEN
! Create a temporary array the same size as current number of vertices. Copy the
! contents of the old array to the new array then delete the old array.
ALLOCATE(tmp_vertices(SIZE(this)))
tmp_vertices = this
DEALLOCATE(this)
! Create a new array with one extra element. Copy the contents of the temporary
! array to the new one the delete the temporary array.
ALLOCATE(this(SIZE(tmp_vertices) + 1))
this(1:SIZE(tmp_vertices)) = tmp_vertices
DEALLOCATE(tmp_vertices)
this(SIZE(this))%x = x
this(SIZE(this))%y = y
this(SIZE(this))%z = z
ELSE
ALLOCATE(this(1))
this(1)%x = x
this(1)%y = y
this(1)%z = z
ENDIF
END SUBROUTINE
SUBROUTINE output_vertices (this)
IMPLICIT NONE
TYPE(vertex), dimension (:), INTENT(in) :: this
integer :: i
write (*, '(// "Current vertices:" )' )
do i=1, size(this)
write (*, '( 3F5.2 )' ) this (i) % x, this (i) % y, this (i) % z
end do
end SUBROUTINE output_vertices
end module vertex_stuff
program vertices
use vertex_stuff
implicit none
TYPE (vertex), dimension (:), allocatable :: this
call path_append_vertex(this, 1.0, 1.1, 1.2)
call output_vertices (this)
call path_append_vertex(this, 2.0, 2.1, 2.2)
call output_vertices (this)
call path_append_vertex(this, 3.0, 3.1, 3.2)
call output_vertices (this)
call path_append_vertex(this, 4.0, 4.1, 4.2)
call output_vertices (this)
call path_append_vertex(this, 5.0, 5.1, 5.2)
call output_vertices (this)
end program vertices
答案 1 :(得分:0)
我弄清楚问题出在哪里。 ipch_desc
对象被构造为temp,然后分配给数组中的元素。
ipch_desc_arr(icount_chords) = ipch_desc_temp
我将需要删除此临时或过载默认的赋值运算符来修复它。