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 

Issue with 64 bit compiler

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



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Wed May 03, 2023 4:42 pm    Post subject: Issue with 64 bit compiler Reply with quote

The following code demonstrates a failure of the X64 compiler where the definition of an allocatable derived type (which itself contains an allocatable element) is present.

The fault occurs in the subroutine initial. After XMIN is allocated, the content of A from the module FIT is copied over to XMIN. This copy fails and the contents of XMIN are incorrect as can be seen by running the code complied with both WIN32 and X64 and comparing the printed terminal output.

If one of the two lines indicated are commented out, the code runs correctly with both WIN32 and X64, i.e. the presence of an allocatable derived type with an allocable element is removed. In the much larger code, all the unallocated arrays were actually allocated, but adding the copy operation caused all the numerical results to go awry.

Note that the presence of the protected attribute on variable A in module FIT has no impact on this – but is one of the reasons for the required copy.

Code:
module fit
implicit none
integer, parameter, private :: dp=kind(1.d0)
integer, parameter :: n = 2
real(dp), protected :: a(1:n) = [-1.d0,2.d0]
end module fit

module casper_mod
use fit
implicit none
integer, parameter :: dp = kind(1.d0)

type mytype
  integer(2), allocatable :: intVal(:)  ! Comment out this line
  real(dp)                :: fit
end type mytype

real(dp), allocatable :: xmin(:)
type(mytype), allocatable :: pop(:)     ! Comment out this line
integer :: probSize
 
  contains
  subroutine casper
    probSize = n
    call initial
  end subroutine casper

  subroutine initial
      allocate(xmin(1:probSize))
      xmin = a              !Copy from minx to xmin fails
      print*, xmin          !Does not return -1.0, 2.0 when compiled with X64
  end subroutine initial
end module Casper_mod

program t
use Casper_mod
implicit none
  call casper
end program t
Back to top
View user's profile Send private message Visit poster's website
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Wed May 03, 2023 5:58 pm    Post subject: Reply with quote

Here is a better (shorter) demonstration. It appears that the subroutine INITIAL cannot see the correct value of A.
Code:
module fit
implicit none
integer, parameter :: dp=kind(1.d0)
  real(dp), protected :: a(1:2) = [-1.d0,2.d0]
end module fit

module casper
use fit
implicit none
 
type mytype
  integer, allocatable :: intVal(:)  ! Comment out this line
  real(dp)                :: fit
end type mytype

type(mytype), allocatable :: pop(:)     ! Comment out this line
 
  contains
 
  subroutine initial
      print*, a   !Print A in FIT as seen by INITIAL, Should return -1.0, 2.0
  end subroutine initial
 
end module Casper

program t
use Casper
implicit none
  call initial
end program t
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


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

PostPosted: Wed May 03, 2023 7:07 pm    Post subject: Reply with quote

Ken

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



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Tue May 09, 2023 12:39 am    Post subject: Reply with quote

Paul,

Can you take a look at this one when you have time. It's similar in the sense that the executable produced by 32 bit compiler does what is expected, while the 64 bit executable has an issue.

The program has a subroutine to reverse the contents of a vector. When compiled with the 32 bit compiler the program runs as expected. When compiled and run with the 64 bit compiler the program generates a runtime error at line 22 “Nonconformant arrays”.

Note that the dimension of the array in the calling program is (11:14), which becomes (1:4) in the subroutine. The same behaviour is observed if the dimension in the calling program is changed to (1:4).

Each of the three alternative ways of reversing the array which are commented out, do not have any issues complied with X64 when used instead of line 22. With the 64 bit compiler UBOUND and LBOUND both return kind=3, SIZE returns kind=4, but the observed behaviour does not appear to relate to this, so I am at a loss of see a reason for the observed behaviour with the 64 bit compiler.

Note that if the same construction is used, not in a subroutine, but in the main program as in the second example program the executable produced by the 64 bit compiler runs as expected.

Code:
program main
implicit none
 
real:: v(11:14) = [1,2,3,4]

print*, 'ubound(v)', ubound(v)
print*, 'lbound(v)', lbound(v)
print*, 'size(v)  ', size(v)
print*, 'Original matrix', v
call reverse(v)
print*, 'Reversed matrix', v

contains

  subroutine reverse(a)
  real, intent(inout) :: a(:)
  print'(/A)', 'Beginning reverse'
  print*, 'ubound(a)', ubound(a), kind(ubound(a))
  print*, 'lbound(a)', lbound(a), kind(lbound(a))
  print*, 'size(a)  ', size(a),   kind(size(a))
 
    a = a(ubound(a,dim=1):lbound(a,dim=1):-1) !X64 "Nonconformant arrays"

  !!!  a = a(ubound(a,dim=1):1:-1)            !X64 OK with these three alternatives.
  !!!  a = a(size(a):1:-1)
  !!!  a = a(size(a):lbound(a,dim=1):-1)

  print'(A/)', 'Completed reverse'
  end subroutine reverse
end program main


Code:
program main
implicit none
real:: v(11:14) = [1,2,3,4]
print*, 'Original matrix', v
v = v(ubound(v,dim=1):lbound(v,dim=1):-1)
print*, 'Reversed matrix', v
end program main
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


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

PostPosted: Tue May 09, 2023 6:32 am    Post subject: Reply with quote

Ken

Thank you for the feedback. I have made a note that this needs to be investigated.
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: Tue May 09, 2023 6:52 am    Post subject: Reply with quote

Ken

This last issue relates only to /64 and /CHECK and is very likely something that needs fixing at our end. For the moment you could add /INHIBIT_CHECK 19.
Back to top
View user's profile Send private message AIM Address
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Tue May 09, 2023 8:24 am    Post subject: Reply with quote

Paul, Ooops, I had /ZEROISE /UNDEF set in Plato under “Extra FTN95 command line options”. With this removed x64 in release mode now runs OK, x64 /Check fails - as you have described.
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


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

PostPosted: Tue May 30, 2023 7:40 am    Post subject: Reply with quote

This issue has now been fixed for the next release of FTN95.
Back to top
View user's profile Send private message AIM Address
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Sat Jun 03, 2023 1:33 pm    Post subject: Reply with quote

Hi Ken,

I find your examples interesting, but I wonder about the benefits.
Are you finding a practical use of "PROTECTED" ?
Does it provide benefits over PARAMETER ?
I must admit, I don't find a need or like PRIVATE in modules.

I would be interested in where you find an advantage of these options.

John
Back to top
View user's profile Send private message
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Sun Jun 04, 2023 2:34 pm    Post subject: Reply with quote

Hi John,

Thanks for your feedback.

Well 15 years ago I was definitely a Fortran 77 programmer, but over time I have seen myself using the features of Fortran 95 and later standards.

Using modules (and avoiding COMMON) was probably the first big change, and now I tend to group data and procedures for operating on that data within the same module, and the PROTECTED attribute is a natural extension to have with this approach.

There is negligible difference whether a module variable has the PARAMETER or PROTECTED attribute, the end result is the same, the variable cannot be changed by the procedure that USEs the module.

For look up tables, which I tend to use extensively ( perhaps based on some empirical equation f(x,y,z) ), a fixed size array can have the PARAMETER attribute, and so long as the empirical equation is not too complex, the table can be generated at compile time by an implied DO LOOP.

If the equation is too complex to be directly be initialised at compile time, requiring a call to a specific initialisation routine, the PARAMETER attribute cannot be applied. Similarly if the variables x, y, z change, or the SIZE of the look up table requires to be changed at run time again the PARAMETER attribute cannot be applied. This is where the PROTECTED and possibly the PRIVATE attribute comes into play.

When more than one programmer is working on the code i.e. responsible for different modules, programmer A can PROTECT the variables in Module 1 that he does not programmer B’s Module 2 that USEs Module 1 to change. If the variables have to change during run time, they can only be changed by a routine within Module 1, so the change is controlled by programmer 1 rather than 2.

When I was asked to extend the functionality of a module I had written for a client a few years ago (which manipulated statistical data for lightning strikes [log normal distributions] and provided parameters for modelling lightning stroke currents in EMT programs), I took the opportunity to PROTECT the module variables (using Ifort at the time). This exposed an error in my client’s own code, as it was inadvertently changing a variable which was now PROTECTED. The resulting error in the output was fortunately small and on the conservative side, and would probably not have been picked up otherwise.

Since that time I have tended to make extensive use of PRIVATE and PROTECTED in such modules, even in cases where there is only one programmer i.e. myself, to avoid such errors – which do occur from time to time. I’m often in a hurry trying to plot some parametric curves – for which I guess others would use excel or similar. So I think there is a benefit to using PROTECTED.

Sometimes when I look at some of the more recent features of the language, I think that replicates existing functionality, but then think no that’s better as it introduces more clarity to the code e.g. z%re = a is much clearer than z = cmplx(a,aimag(z))

I guess it’s all down to programming style/preference which evolves with time. The first code I wrote 10 years ago using FTN95 looks completely different to today’s code! We all learn new tricks as we read posts here and elsewhere.

Ken
Back to top
View user's profile Send private message Visit poster's website
PaulLaidler
Site Admin


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

PostPosted: Mon Dec 04, 2023 8:56 am    Post subject: Reply with quote

Ken

The failure demonstrated in your post of 3 May has now been fixed for the next release of FTN95 (after v9.0).
Back to top
View user's profile Send private message AIM Address
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