- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I am trying to see if I want to do a project using object oriented feature of Fortran 2003 so I wrote a simple little test to check out the compiler but ran into the following error
ifort -free t4.F90
: catastrophic error: **Internal compiler error: segmentation violation signal raised** Please report this error along with the circumstances in which it occurred in a Software Problem Report. Note: File and line given may not be explicit cause of this error.
The same thing works fine using the IBM xlf2003 compiler. Can someone tell me why the compiler crashes ?
Thanks,
butette
!------- t4.F90 ------
module foo_mod
implicit none
private
public :: init,zero,print
type, public :: foo
private
integer n
real, allocatable :: u(:)
! Intel compiler did not like the save statement here either
! IBM xlf2003 did not have any problem with it
! real, save, allocatable :: u(:)
contains
procedure :: init
procedure :: zero
procedure :: print
end type foo
contains
subroutine init(this,u1,n1)
class(foo) :: this
real, intent(in) :: u1(n1)
integer, intent(in) :: n1
if (.not.allocated(this%u)) then
print *, '---allocating'
allocate(this%u(n1))
endif
this%u = u1
this%n = n1
end subroutine init
subroutine zero(this)
class(foo) :: this
if (.not.allocated(this%u)) print *, ' in zero, not allocated'
this%u = 0.
! this%u(1:this%n) = 0.
end subroutine zero
subroutine print(this)
class(foo) :: this
if (.not.allocated(this%u)) print *, ' in print, not allocated'
print *, this%u
end subroutine print
end module foo_mod
program test
use foo_mod
type(foo) :: a
real, allocatable :: b(:)
allocate(b(3))
b=9999
call a%init(b,3)
call a%print()
call a%zero()
call a%print()
end
ifort -free t4.F90
: catastrophic error: **Internal compiler error: segmentation violation signal raised** Please report this error along with the circumstances in which it occurred in a Software Problem Report. Note: File and line given may not be explicit cause of this error.
The same thing works fine using the IBM xlf2003 compiler. Can someone tell me why the compiler crashes ?
Thanks,
butette
!------- t4.F90 ------
module foo_mod
implicit none
private
public :: init,zero,print
type, public :: foo
private
integer n
real, allocatable :: u(:)
! Intel compiler did not like the save statement here either
! IBM xlf2003 did not have any problem with it
! real, save, allocatable :: u(:)
contains
procedure :: init
procedure :: zero
procedure :: print
end type foo
contains
subroutine init(this,u1,n1)
class(foo) :: this
real, intent(in) :: u1(n1)
integer, intent(in) :: n1
if (.not.allocated(this%u)) then
print *, '---allocating'
allocate(this%u(n1))
endif
this%u = u1
this%n = n1
end subroutine init
subroutine zero(this)
class(foo) :: this
if (.not.allocated(this%u)) print *, ' in zero, not allocated'
this%u = 0.
! this%u(1:this%n) = 0.
end subroutine zero
subroutine print(this)
class(foo) :: this
if (.not.allocated(this%u)) print *, ' in print, not allocated'
print *, this%u
end subroutine print
end module foo_mod
program test
use foo_mod
type(foo) :: a
real, allocatable :: b(:)
allocate(b(3))
b=9999
call a%init(b,3)
call a%print()
call a%zero()
call a%print()
end
Link Copied
6 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
First, it is incorrect to use SAVE in a derived type component declaration. This is a bug in the IBM compiler if it accepts this, as SAVE is not among the list of attributes allowable in a component-attr-spec (F2003 R441).
When I get back to the office on Monday I'll try your program with our development stream - I know we've fixed a lot of issues with type-bound procedures recently. I can reproduce the failure in the released compiler - thanks.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
This is strange. If you rename the procedure "print" to "xprint", it works! I have reported this as issue DPD200149208.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Quoting - Steve Lionel (Intel)
This is strange. If you rename the procedure "print" to "xprint", it works! I have reported this as issue DPD200149208.
Is the compiler having a hard time distinguishing the name of a function attached to a type from the intrinsic print statement. If that's the case it may explain some of the simple error I am seenig from a slightly modified variants of the same code. See below
!------ foo.F90
module foo_mod
implicit none
private
public :: zero,xprint
type, public :: Foo
private
integer n
real, allocatable :: u(:)
contains
procedure :: zero
procedure :: xprint
final :: delete
end type Foo
interface Foo
module procedure newFoo
end interface Foo
contains
subroutine delete(this)
type(Foo) :: this
if (allocated(this%u)) deallocate(this%u)
this%n = 0
write(*,*) "hello"
end subroutine delete
type(foo) function newFoo(u) result(this)
real, intent(in) :: u(:)
integer :: n
n = size(u)
if (.not.allocated(this%u)) then
print *, '---allocating'
allocate(this%u(n))
endif
this%u = u
this%n = n
end function newFoo
subroutine zero(this)
class(foo) :: this
if (.not.allocated(this%u)) then
print *, ' in zero, not allocated'
else
this%u = 0.
endif
end subroutine zero
subroutine xprint(this)
class(foo) :: this
if (.not.allocated(this%u)) then
print *, ' in print, not allocated'
else
print *, this%u
endif
end subroutine xprint
end module foo_mod
program test
use foo_mod
type(foo) :: a
real, allocatable :: b(:)
allocate(b(3))
b=9999
!call a%init(b)
a = Foo(b)
call a%xprint()
call a%zero()
call a%xprint()
end
When compiling it with 11.064 compiler I get
ifort -free foo.F90
foo.F90(14): error #5082: Syntax error, found '::' when expecting one of: ( % : . = =>
final :: delete
------------^
foo.F90(18): error #5082: Syntax error, found IDENTIFIER 'NEWFOO' when expecting one of:
module procedure newFoo
----------------------^
foo.F90(19): error #6546: A required END statement for the interface-body is missing.
end interface Foo
---^
foo.F90(7): error #6406: Conflicting attributes or multiple declaration of name. [FOO]
type, public :: Foo
-------------------^
foo.F90(8): error #7811: Error with derived type symbol whose definition contains a PRIVATE statement.
private
^
: catastrophic error: **Internal compiler error: segmentation violation signal raised** Please report this error along with the circumstances in which it occurred in a Software Problem Report. Note: File and line given may not be explicit cause of this error.
compilation aborted for foo.F90 (code 3).
-----------------------
If the compiler can't compile simple stuff like this, I am beginning to wonder if anybody is really doing any object oriented programming with Fortran 2003 using Intel compiler at all.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Intel Fortran does not yet support FINAL::. Other than that, this is similar to the first example. I don't think it's simply a confusion with the PRINT statement, but I don't really know.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Quoting - Steve Lionel (Intel)
Intel Fortran does not yet support FINAL::. Other than that, this is similar to the first example. I don't think it's simply a confusion with the PRINT statement, but I don't really know.
Even if I comment out the FNIAL statement, and already made the change from print to xprint, I would still get all the other error messages. I have a feeling that I will have to back off from trying to use F2003 object oriented as a design goal.
Thanks.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
We also do not yet support a generic interface whose name is the same as a derived type.

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