- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Link Copied
- 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
By polymorphic allocation I mean something like this:
[fortran]function alloc(x) implicit none class(object), intent(in) :: x class(object), allocatable :: obj allocate (obj, source=x) end alloc[/fortran]
With 11.1.054 I get the following compilation error for such constructs:
error #5415: Feature not yet implemented: SOURCE=polymorphic_expression
- 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
Hi,
I encountered similar problem. In my case CLASS object can be ALLOCATE (i.e. no syntax error), but runtime error occurs.
Here is the output and code.
Yamajun
draw circle 10.00000 10.00000 6.000000
draw circle 40.00000 12.00000 10.00000
location = 20.00000 10.00000
location = 60.00000 2.000000
draw rectangle 20.00000 10.00000 35.00000 10.00000
draw rectangle 60.00000 2.000000 15.00000 8.000000
forrtl: severe (157): Program Exception - access violation
Image PC Routine Line Source
test2.exe 00401DE2 _MAIN__ 80 test2.f90
test2.exe 004A9DD3 Unknown Unknown Unknown
test2.exe 0044E0D3 Unknown Unknown Unknown
test2.exe 0044DE9D Unknown Unknown Unknown
kernel32.dll 7D4F7D42 Unknown Unknown Unknown
[fortran]MODULE m_shape IMPLICIT NONE TYPE :: t_shape REAL :: x = 0.0 , y = 0.0 CONTAINS PROCEDURE :: location END TYPE t_shape CONTAINS SUBROUTINE location(this) CLASS (t_shape), INTENT(IN) :: this PRINT *, 'location = ', this%x, this%y RETURN END SUBROUTINE location END MODULE m_shape !=================================================== MODULE m_test USE m_shape IMPLICIT NONE ! TYPE, EXTENDS(t_shape) :: t_circle REAL :: r = 0.0 CONTAINS PROCEDURE :: draw => draw_circle END TYPE t_circle ! TYPE, EXTENDS(t_shape) :: t_rectangle REAL :: dx = 0.0, dy = 0.0 CONTAINS PROCEDURE :: draw => draw_rectangle END TYPE t_rectangle ! CONTAINS SUBROUTINE draw_circle(this) CLASS (t_circle), INTENT(IN) :: this PRINT *, 'draw circle ', this%x, this%y, this%r RETURN END SUBROUTINE draw_circle SUBROUTINE draw_rectangle(this) CLASS (t_rectangle), INTENT(IN) :: this PRINT *, 'draw rectangle ', this%x, this%y, this%dx, this%dy RETURN END SUBROUTINE draw_rectangle END MODULE m_test !======================================== PROGRAM test USE m_test IMPLICIT NONE TYPE (t_circle ), ALLOCATABLE :: c(:) TYPE (t_rectangle), ALLOCATABLE :: r1, r2 CLASS (t_shape) , ALLOCATABLE :: s1, s2 ALLOCATE( c(2) ) c(1) = t_circle(10.0, 10.0, 6.0) c(2) = t_circle(40.0, 12.0, 10.0) ALLOCATE( r1, SOURCE = t_rectangle(20.0, 10.0, 35.0, 10.0) ) ALLOCATE( r2, SOURCE = t_rectangle(60.0, 2.0, 15.0, 8.0) ) CALL c(1)%draw() CALL c(2)%draw() CALL r1%location() CALL r2%location() CALL r1%draw() CALL r2%draw() DEALLOCATE( c, r1, r2 ) ALLOCATE( s1, SOURCE = t_rectangle(20.0, 10.0, 35.0, 10.0) ) ! Crash here ALLOCATE( s2, SOURCE = t_rectangle(60.0, 2.0, 15.0, 8.0) ) CALL s1%location() CALL s2%location() STOP END PROGRAM test [/fortran]
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yamajun,
This is a compiler bug that will be fixed in a future update. As a workaround, set the project properties Fortran > Diagnostics > Generate Interface Blocks and Check Routine Interfaces to No.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve,
Thanks! Now it runs fine! I thought I've tried those options after reading your reply in some other thread, but maybe I made some silly mistake.
There is, however, another problem with TYPE, ABSTRACT. I encounter syntax error#8212.
Here is a sample code.
Yamajun
[fortran]MODULE m_shape IMPLICIT NONE ! TYPE, ABSTRACT :: t_shape CONTAINS PROCEDURE (p_draw), DEFERRED :: draw END TYPE t_shape ! ABSTRACT INTERFACE SUBROUTINE p_draw(this) IMPORT :: t_shape CLASS (t_shape), INTENT(IN) :: this END SUBROUTINE p_draw END INTERFACE ! END MODULE m_shape !=================================================== MODULE m_test USE m_shape IMPLICIT NONE TYPE, EXTENDS(t_shape) :: t_circle REAL :: x, y REAL :: r CONTAINS PROCEDURE :: draw => draw_circle END TYPE t_circle CONTAINS SUBROUTINE draw_circle(this) CLASS (t_circle), INTENT(IN) :: this PRINT *, 'Darw circle ', this%x, this%y, this%r RETURN END SUBROUTINE draw_circle END MODULE m_test !======================================== PROGRAM test USE m_test IMPLICIT NONE TYPE (t_circle) :: c1 TYPE (t_circle) :: c2 c1 = t_circle(10.0, 5.0, 6.0) !error #8212: Omitted field is not initialized. Field initialization missing:ALLOCATE( c2, SOURCE = t_circle(10.0, 5.0, 3.0) ) !error #8212: STOP END PROGRAM test[/fortran]
- 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
[bash]module demo_module implicit none type, public, abstract :: parent_type character(12) :: name integer :: codeNumber end type parent_type
contains subroutine someMethod(object) implicit none class (parent_type), intent(in) :: object class (parent_type), allocatable :: copy allocate(copy,source=object) ! error #5415: Feature not yet implemented: SOURCE=polymorphic_expression end subroutine someMethod end module demo_module [/bash]
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
ALLOCATE(source=polymorhic) won't be in the initial release of the next major version of the compiler, which is planned for November. It might be provided in a subsequent update, or perhaps even a subsequent major version.
If parent_type were not abstract, typed allocation might be a workaround, for example,
ALLOCATE(something_derived_from_parent_type :: copy)
Patrick Kennedy
Intel Developer Support
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content

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