forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

One untyped variable causes access violation in compiler

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support
View previous topic :: View next topic  
Author Message
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Thu Jul 16, 2020 1:03 pm    Post subject: One untyped variable causes access violation in compiler Reply with quote

The following test code causes FTN95 8.63 to abort with an access violation, with or without /64. The code has IMPLICIT NONE, and is missing a type declaration for the variable NSTATN.

Minor changes to the code cause the compiler to revert to normal behavior, with an error message for the undeclared variable.

Code:
      subroutine subx(nl, nu, sa33, sb33, v, nomega)
      implicit none
      real vwe2
      integer , intent(in) :: nl, nu, nomega
      real , intent(in) :: v
      real , intent(in) :: sa33(25,nomega), sb33(25,nomega)
      integer :: i   !, nstatn
      complex :: pitacc
      real , dimension(25) :: stemp
!-----------------------------------------------
      nstatn = 5        ! variable type not declared
      vwe2 = 1.5
      pitacc = 1.7
      do i = nl, nu
         stemp(1:nstatn) = -(sa33(1:nstatn, i)*(1.3-pitacc) + &
            3.2-vwe2*sb33(1:nstatn, i) * pitacc+v*sa33(1:nstatn, i)*3.2)
      end do
      print *,stemp(5)
      return
      end subroutine subx
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Thu Jul 16, 2020 2:46 pm    Post subject: Reply with quote

mecej4

Thank you for the feedback. I have made a note of this.
Back to top
View user's profile Send private message AIM Address
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Fri Jul 17, 2020 9:32 am    Post subject: Reply with quote

mecej4

I have a potential fix for this bug. Do you have a test case that I can use to check the outcome?
Back to top
View user's profile Send private message AIM Address
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Fri Jul 17, 2020 10:10 am    Post subject: Reply with quote

Paul,

Here is a link to a zip containing two source files. It was by pruning these sources that I obtained the short test file in the initial report.

https://www.dropbox.com/s/wo6taralxbptmvy/lrao.7z?dl=0

The file modules.f90 needs to be compiled first to generate the *.mod files needed by lrao.f90.

You will see an access violation if you then attempt to compile lrao.f90.

Code:
0049c351 the_base_type(<ptr>structÄtype_definition) [+0035]
 00436085 base_tree_type(structÄtree_ptr) [+0030]
 00504d4a process_tree2(<ref>structÄtree_ptr,structÄtree_context) [+1439]
 00509faa flatten_plus(structÄtree_ptr,enumÄlogical,enumÄlogical)#56 [+01bf]
 00504d4a process_tree2(<ref>structÄtree_ptr,structÄtree_context) [+1439] [recur=  8]
 0043a446 process_tree_completely(<ref>structÄtree_ptr) [+015a]
 00418615 end_function(int) [+0a7c]
 0041a4d0 parse_end_statement(<ptr>char,int,<ref>int) [+0c0d
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Fri Jul 17, 2020 11:42 am    Post subject: Reply with quote

mecej4

Thanks. I can see the access violation and I have a potential fix for it. The fix does not break our test suite but I don't know if the result of the computation will be correct.

Do you have test data and a simple main program that calls the subroutine lrao?
Back to top
View user's profile Send private message AIM Address
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Fri Jul 17, 2020 11:56 am    Post subject: Reply with quote

Unfortunately, the subroutine LRAO is part of a package with over 150 subroutines, and I have not yet been able to get the package to output reproducible results. I do not have a complete reference set of results, either.

One of the bad features of this package is that it has dozens of large COMMON blocks, and uses EQUIVALENCEd variables of different types to write (and later read back) entire block contents to scratch files. This feature does not allow FTN95's /undef to be used.
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Fri Jul 17, 2020 1:15 pm    Post subject: Reply with quote

Thanks. I will go with my potential fix which I know works with the current test suite.
Back to top
View user's profile Send private message AIM Address
mecej4



Joined: 31 Oct 2006
Posts: 1885

PostPosted: Fri Jul 17, 2020 2:47 pm    Post subject: Reply with quote

There were two source files in the package that FTN95 could not compile, one of which is LRAO.f90. Fortunately, I have now found a work-around: replace a couple of WHERE constructs with DO loops.
Back to top
View user's profile Send private message
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Wed Jul 22, 2020 6:39 am    Post subject: Reply with quote

I get the following adaptation to fail with FTN95 8.62.0

I find that even when declaring INTEGER nstatn, I stll get an ICE.
Changing pitacc to REAL or replacing 1:nstatn with do j = 1,nstatn both remove the ICE.
Code:
      subroutine subx(nl, nu, sa33, sb33, v, nomega)
      implicit none
      integer , intent(in) :: nl, nu, nomega
      real , intent(in) :: v
      real , intent(in) :: sa33(25,nomega), sb33(25,nomega)
!
      integer :: i, nstatn,j
      real    :: vwe2
      complex :: pitacc
!     real    :: pitacc
      real , dimension(25) :: stemp
!-----------------------------------------------
      nstatn = 5        ! variable type not declared
      vwe2 = 1.5
      pitacc = 1.7
      do i = nl, nu
!
!        stemp(1:nstatn) = -(sa33(1:nstatn, i)*(1.3-pitacc) + &
!           3.2-vwe2*sb33(1:nstatn, i) * pitacc+v*sa33(1:nstatn, i)*3.2)
!
         stemp(1:nstatn) = - ( sa33(1:nstatn, i) * (1.3-pitacc)  &
                             + 3.2                               &
                             - sb33(1:nstatn, i) * vwe2*pitacc   &
                             + sa33(1:nstatn, i) * 3.2*v            )
!
        do j = 1,nstatn
         stemp(j       ) = - ( sa33(j       , i) * (1.3-pitacc)  &
                             + 3.2                               &
                             - sb33(j       , i) * vwe2*pitacc   &
                             + sa33(j       , i) * 3.2*v            )
        end do
!
      end do
      print *,stemp(5)
      return
      end subroutine subx

Perhaps another example of complex * real error
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> Support All times are GMT + 1 Hour
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group