- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
SUBROUTINE chk_shell_fib( stp_prg, findtbar )
USE mod_unit_numbers
USE mod_FE_Element_types, &
ONLY : el_giveNodeGnum, &
nod_rst_cord, &
min_elem_nodes, &
nat_nod_ord, &
element
! non relevant stuf left out
USE mod_shape_fun_ex, &
ONLY : p_shape_der
IMPLICIT NONE
!
INTRINSIC :: ALL, SUM, SIZE, MODULO, ALLOCATED, &
ABS, ACOS, PRESENT
!
LOGICAL(LGL), INTENT(OUT) :: stp_prg
LOGICAL(LGL), INTENT(IN), OPTIONAL :: findtbar
!
REAL(DP), ALLOCATABLE :: r_points(:), &
s_points(:), &
dpN_dpr_(:,:)
(I have "bolded" relevant objects): "element" is an array of derived types "FE_Element", p_shape_der is a FUNCTION returning a two dimensional array. The function result is NOT allocatable and DOES NOT HAVE TO BE to "work" with the Fortran 2003 requirement of re-allocation of allocatable arrays.
within this subroutine there is a call thus
CALL nod_rst_cord( element(iel), pak=.TRUE., rpts=r_points, spts=s_points )
DO k = 1, numelnod
fib_np(:,k) = unitvec( fib_np(:,k) )
dpN_dpr_ = p_shape_der( element(iel), r = r_points(k), s = s_points(k) )
r_points and s_points are already allocated before that call to p_shape_der, and the above four lines are nested in a loop over "iel".
Now, "element" is a derived type with an (already allocated) allocatable component named element(iel)%node_gnum(:), and in p_shape_der the RESULT is an AUTOMATIC (this is ALLOWED per Fortran 95) with shape (rank and extent) of (element(iel)%node_gnum(:), dim23). Here's part of p_shape_der
FUNCTION p_shape_der( elementd, r, s, t ) RESULT(dpN_dpr_)
!
USE mod_FE_Element_types, &
ONLY : FE_Element
USE mod_global_model_data, &
ONLY : dim23
!
IMPLICIT NONE
!
INTRINSIC :: SIZE, TRIM, ADJUSTL, PACK
!
TYPE(FE_Element), INTENT(IN) :: elementd
REAL(DP), INTENT(IN) :: r
REAL(DP), INTENT(IN), OPTIONAL :: s, t
REAL(DP) :: dpN_dpr_( 1:SIZE(elementd%node_gnum), 1:dim23 )
so you see the actual argument element(iel) (of type "FE_Element") has dummy argument "elementd". As I wrote above, this is LEGAL Fortran 95 to have a function result as an automatically shaped array. Also, as I wrote above, elementd%node_gnum(:) IS allocated (debugging showed this), so this is perfectly legal Fortran 95 (+ legal F2003 for the re-allocation of allocatable arrays) usage through and through. So the dimensioning of dpN_dpr_ has available ONLY knowns (dim23 is known and has value 2 or 3).
So, this is exactly the usage Intel now promulgates as being implemented when in fact it is not fully/correctly implemented. When I run the exe I get the error message:
"forrtl: severe (408): fort: (8): Attempt to fetch from allocatable variable DPN_DPR_ when it is not allocated." The traceback goes on to point out the (final) offending line which points to (in the source code)
dpN_dpr_ = p_shape_der( element(iel), r = r_points(k), s = s_points(k) )
So you can see anyway all this business about a function result being automatic does not matter since the error reported in the traceback read the allocatable array was not allocated when the call to p_shape_der was executed. When does Intel plan on correctly implementing what that have publicly announced as being implemented?
-Brian
Addendum:
I communicated this to others and one reply was automatic objects are deallocated once the function returns, implying the same for a function result. Nothing could be farther from the truth. WHY would the Fortran 95 standard allow function results, which are arrays, NOT to be automatic (dynamically sized while NOT being allocatable)? That's crazy, and I find all kinds of snippets in Metcalf and Reid and other references where they do create functions, the result of which is an automatic array and NOT an allocatable array result.
Also, to prove to myself IVF indeed allows function results to be automatic arrays, and the result array is not dealloca ted until AFTER the assignment is made, I recoded the above call to p_shape_der thus:
CALL nod_rst_cord( element(iel), pak=.TRUE., rpts=r_points, spts=s_points )
IF ( ALLOCATED( dpN_dpr_) ) DEALLOCATE ( dpN_dpr_ )
ALLOCATE ( dpN_dpr_(SIZE(element(iel)%node_gnum), dim23) )
DO k = 1, numelnod
fib_np(:,k) = unitvec( fib_np(:,k) )
dpN_dpr_(:,:) = p_shape_der( element(iel), r = r_points(k), s = s_points(k) )
you can see I allocated dpN_dpr to be the same size as the automatic result of p_shape_der and lo' and behold the app executed and debugging showed correct results for the array dpN_dpr, which means IVF DOES understand function results are allowed to be automatic arrays and IN FACT the resulting array is NOT gotten rid of until AFTER the assignment, NOT on exit of the function. That's GOOD news for IVF (and their users!), and also reinforces my posit /assume:realloc_lhs is not implemented correclty.
-Brian
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for the note. I'll take a look at this - it is entirely possible that we're not doing the right thing in this case.
As for automatic and allocatable function results - you are correct that the result is still "available" until the statement is complete. This is actually quite a pain for the compiler and we've put in a lot of work to make sure it works as intended.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
-Brian
- 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
This is amusing. First of all, /assume:realloc_lhs is indeed working properly. What is NOT working is /check:pointer which incorrectly triggers an error in this case. If you remove that option you should find, as I did, that the reallocation works as documented. We'll fix this.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Wow. Could I have somehow seen that for myself while debugging?
Another question: one of those builds was "release", so I did not think /check:pointer was on. Is that the case?
Observation: last night, on a 32 bit machine, I debug built same solution, and instead of traceback indicating non-allocated array was being referenced, the traceback read the #2 array index was being referenced as 1 which exceeded the upper bound of -1. Now, in all cases, while stepping through, MS debugger always reported the array in question as being not defined.
Anyway, I suppose the different tracebacks have something to do with the target as well as the host on which the build is executed.
Now, how do I, in "release" configuration, ensure /check:pointer is not turned on? I'll check myself by looking at the Intel/MSVS generated command line, but I don't recall seeing it there in both debug and release.
I'll report back (later tonight hopefully).
And THANKS for looking into this.
-Brian
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It was clear to me from the message that /check:pointer was on, as that's the only thing that would generate a message like that. This is not a default option in either debug or release configurations. If you don't see it in the list of options on the "Command Line" property page, check your ifort.cfg file in the compiler BIN folder to see if you (or someone else) added it there.
In the process of creating a "reproducer", I naturally see if I can do a command-line build because that's so much simpler for the developers and testers. I was astonished when JUST using /assume:realloc_lhs did not reproduce the problem.
However... now that I am thinking again - I first reproduced this on a MacBook I was using and I didn't use /check:pointer, so.. Weird. I'll have to play with this some more.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Yeah, after posting and then going back (on my laptop, which was not the machine on which this problem behavior originally appeared) I slapped my forehead and realized my last post must have been ... at least frustrating.
Setting the record straight:
I did have /check:pointer when built on x64 host for Intel 64 target (the original post was based on subsequent exe behavior).
I had /check:bounds for the IA-32 host for IA-32 target builds when I posted subscript #2 error.
So, I just finished with going back and "doing it" a bit more methodically.
Debug: Where I had "everything" turned off (both /check:pointer AND /check:bounds off) I got an "access violation" and windows asked me if I wanted to send an error report (I did the first time it happened). Where I had only /check:pointer I got same thing as originally (attempt to access unallocated allocatable). Where I had only /check:bounds on, I got the attempt to access subscript #2 as 1 when upper bound for that subscript is -1 (which is erroneous as you can see for the declaration of result in funciton p_shape_der). So, those are the three behaviors I'm getting in debug when IA-32 host builds for IA-32 target. I also get the same behaviors for release.
I have not tried IA-32 host building for Intel 64, neither debug nor release. Nor have I tried x64 host building for IA-32 target.
But as it stands now, I'm getting errors reported, not in build but ,in run-time, all cases of course use /assume:realloc_lhs added in "command line" for compiler.
Yes, I should use the command line more, it's cleaner. Some people I know say "to mouse is to be a Boy".
When I get back to my x64 machine I'll check out the rest of the story.
-Brian
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
There's nothing wrong with using the IDE - I prefer it in general. But for reporting bugs to development, there is a strong preference for getting things as simple as possible which means, ideally, a single source file and a command line.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve,
I'll draw up as simple a test case as I can while retaining the structure implied by the source code (modules, derived types, functions, etc essentially involved). I'll first make a test case all in one exe to see if noted behavior manifests. If it doesn't then I'll (be really worried) make a test case where there is an exe and one dll (same current form as the app I'm developing).
I'll submit report some time over the weekend and let Premier Support know you requested to be assigned.
Thanks Much Steve.
-Brian
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I've provided source code, complete MSVS 2005 Pro Fortran Solution (two projects, one exe and one dll), and my environment in three separate uploads to IPS.
A few notes:
All the below results included the switch /assume:realloc_lhs
With both /check:pointer and /check:bounds => attempt to access unallocated allocatable
With /check:pointer only => attempt to access unallocated allocatable
With /check:bounds only => subscript #2 referenced as 1 when upper bound is -1
Neither /check:pointer nor /check:bounds => access violation (unhandled exception) but debug traceback points to same source code line as error with /check:pointer.
This occurs for the following hosts/targets:
Intel 64 => Intel 64
IA32 => IA32
Intel 64 => IA32
I have not checked IA32 host build for Intel 64 target.
This occurs for both debug and release configurations.
-Brian
- 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