- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
the program below causes an internal error when compiled with Intel Fortran 11.1.065.
As I do not have version 12 available at this moment, I can not check whether the problem
has already been fixed. Therefore I report this just in case it is not.
(I have not tried to shorten it further than this)
Regards,
Arjen
-----
! random_walk.f90 --
! Simulate a random walk in two and three dimensions
!
! Problem gfortran:
! - with both arguments class(..) add_vector_2d and add_vector_3d ambiguous
! - with vector type(...) error on operator(+): class(...) actual arguments
!
module points2d3d
implicit none
type point2d
real :: x, y
contains
procedure :: print => print_2d
procedure :: add_vector => add_vector_2d
procedure :: random => random_vector_2d
procedure :: assign => assign_2d
end type point2d
type, extends(point2d) :: point3d
real :: z
contains
procedure :: print => print_3d
procedure :: add_vector => add_vector_3d
procedure :: random => random_vector_3d
procedure :: assign => assign_3d
end type point3d
contains
subroutine print_2d( point )
class(point2d) :: point
write(*,'(2f10.4)') point%x, point%y
end subroutine print_2d
subroutine print_3d( point )
class(point3d) :: point
write(*,'(3f10.4)') point%x, point%y, point%z
end subroutine print_3d
subroutine random_vector_2d( point )
class(point2d) :: point
call random_number( point%x )
call random_number( point%y )
point%x = 2.0 * point%x - 1.0
point%y = 2.0 * point%y - 1.0
end subroutine random_vector_2d
!
! This routine gets confused for the 2D variant
! - essentially the same interface?
subroutine random_vector_3d( point )
class(point3d) :: point
call point%point2d%random
call random_number( point%z )
point%z = 2.0 * point%z - 1.0
write(*,*) '3D point - ', point%z
end subroutine random_vector_3d
function add_vector_2d( point, vector )
class(point2d), intent(in) :: point, vector
class(point2d), allocatable :: add_vector_2d
if ( allocated(add_vector_2d) ) then
deallocate( add_vector_2d )
endif
allocate( add_vector_2d )
add_vector_2d%x = point%x + vector%x
add_vector_2d%y = point%y + vector%y
write(*,*) '2D called'
end function add_vector_2d
function add_vector_3d( point, vector )
class(point3d), intent(in) :: point
class(point2d), intent(in) :: vector
class(point3d), allocatable :: vector_3d
class(point2d), allocatable :: add_vector_3d
allocate( vector_3d )
select type (vector)
class is (point3d)
call vector_3d%point2d%assign(point%point2d%add_vector(vector%point2d))
write(*,*) 'Vector_3d (after 2d assignment):'
call vector_3d%print
call vector_3d%point2d%print
vector_3d%z = point%z + vector%z
write(*,*) 'Vector:'
call vector%point2d%print
end select
write(*,*) 'Point (2d part):'
call point%point2d%print
write(*,*) 'Vector_3d (2d part):'
call vector_3d%point2d%print
write(*,*) 'Vector_3d:'
call vector_3d%print
call move_alloc( vector_3d, add_vector_3d )
end function add_vector_3d
subroutine assign_2d( left, right )
class(point2d), intent(inout) :: left
class(point2d), intent(in) :: right
write(*,*) '2D assignment'
left%x = right%x
left%y = right%y
end subroutine assign_2d
subroutine assign_3d( left, right )
class(point3d), intent(inout) :: left
class(point2d), intent(in) :: right
write(*,*) '3D assignment'
select type (right)
type is (point3d)
call left%point2d%assign(right%point2d)
left%z = right%z
end select
end subroutine assign_3d
end module points2d3d
program random_walk
use points2d3d ! Both 2D and 3D points available
type(point2d), target :: point_2d, vector_2d
type(point3d), target :: point_3d, vector_3d
!
! A variable of class point2d can point to point_2d but
! also to point_3d
!
class(point2d), pointer :: point, vector
integer :: nsteps = 3 ! Was 10
integer :: i
integer :: trial
real :: deltt = 0.1
! Select what type of point ...
do trial = 1,2
if (trial == 1) then
write(*,*) 'Two-dimensional walk:'
point => point_2d
vector => vector_2d
else
! Now let's take a 3D walk ...
write(*,*) 'Three-dimensional walk:'
point => point_3d
vector => vector_3d
end if
call point%random
do i = 1,nsteps
call vector%random
point = point%add_vector( vector )
!
! ICE also happens with:
!
! call point%assign(point%add_vector( vector ) )
call point%print
enddo
enddo
end program random_walk
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
solved. However, I get a strange result with an improved version (see below):
Two-dimensional walk:
-1.2950 -0.6152
-0.3689 0.0614
-0.6981 0.8920
Three-dimensional walk:
1.3341 -0.1548 -0.3099
1.7361 0.3143 -0.3099
0.8355 1.1307 -0.3099
It turns out that the assignment "point = point+ vector" is using the 2D version of the assignment
procedure, not the 3D one as I expected. Is this correct behaviour?
Regards,
Arjen
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Arjen
----
! random_walk.f90 --
! Simulate a random walk in two and three dimensions
!
module points2d3d
implicit none
type point2d
real :: x, y
contains
procedure :: print => print_2d
procedure :: add_vector => add_vector_2d
procedure :: random => random_vector_2d
procedure :: assign => assign_2d
generic, public :: operator(+) => add_vector
generic, public :: assignment(=) => assign
end type point2d
type, extends(point2d) :: point3d
real :: z
contains
procedure :: print => print_3d
procedure :: add_vector => add_vector_3d
procedure :: random => random_vector_3d
procedure :: assign => assign_3d
end type point3d
contains
subroutine print_2d( point )
class(point2d) :: point
write(*,'(2f10.4)') point%x, point%y
end subroutine print_2d
subroutine print_3d( point )
class(point3d) :: point
write(*,'(3f10.4)') point%x, point%y, point%z
end subroutine print_3d
subroutine random_vector_2d( point )
class(point2d) :: point
call random_number( point%x )
call random_number( point%y )
point%x = 2.0 * point%x - 1.0
point%y = 2.0 * point%y - 1.0
end subroutine random_vector_2d
!
! This routine gets confused for the 2D variant
! - essentially the same interface?
subroutine random_vector_3d( point )
class(point3d) :: point
call point%point2d%random
call random_number( point%z )
point%z = 2.0 * point%z - 1.0
end subroutine random_vector_3d
function add_vector_2d( point, vector )
class(point2d), intent(in) :: point, vector
class(point2d), allocatable :: add_vector_2d
if ( allocated(add_vector_2d) ) then
deallocate( add_vector_2d )
endif
allocate( add_vector_2d )
add_vector_2d%x = point%x + vector%x
add_vector_2d%y = point%y + vector%y
end function add_vector_2d
function add_vector_3d( point, vector )
class(point3d), intent(in) :: point
class(point2d), intent(in) :: vector
class(point3d), allocatable :: vector_3d
class(point2d), allocatable :: add_vector_3d
allocate( vector_3d )
select type (vector)
class is (point3d)
vector_3d%point2d = point%point2d + vector%point2d
vector_3d%z = point%z + vector%z
end select
call move_alloc( vector_3d, add_vector_3d )
end function add_vector_3d
subroutine assign_2d( left, right )
class(point2d), intent(inout) :: left
class(point2d), intent(in) :: right
left%x = right%x
left%y = right%y
end subroutine assign_2d
subroutine assign_3d( left, right )
class(point3d), intent(inout) :: left
class(point2d), intent(in) :: right
select type (right)
type is (point3d)
left%point2d = right%point2d
left%z = right%z
end select
end subroutine assign_3d
end module points2d3d
program random_walk
use points2d3d ! Both 2D and 3D points available
type(point2d), target :: point_2d, vector_2d
type(point3d), target :: point_3d, vector_3d
!
! A variable of class point2d can point to point_2d but
! also to point_3d
!
class(point2d), pointer :: point, vector
integer :: nsteps = 3 ! Was 10
integer :: i
integer :: trial
real :: deltt = 0.1
! Select what type of point ...
do trial = 1,2
if (trial == 1) then
write(*,*) 'Two-dimensional walk:'
point => point_2d
vector => vector_2d
else
! Now let's take a 3D walk ...
write(*,*) 'Three-dimensional walk:'
point => point_3d
vector => vector_3d
end if
call point%random
do i = 1,nsteps
call vector%random
point = point + vector
call point%print
enddo
enddo
end program random_walk
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I compiled your problem (first entry of the thread) with XE 2011 update 3 (package 175). The compiler complained on the line near the end of the prgram that was:
point = point%add_vector(vector)
It produced error #8304: In an intrinsic assignment, variable shall not be polymorphic. [POINT].
Does this help you?
Robert
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Robert,
well, Intel Fortran 11 complains about that too, but then produces an internal error. With the explicit call
that was commented out, it does not complain but still produces an internal error. I understand the reason for the complaint, but I could not check that the internal error was taken care of.
As I reported later, with Intel Fortran 12 things do work, but give some odd-looking results.
Thanks anyway for looking into it.
Regards,
Arjen

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page