I have a routine which accepts two variables, one is type(*) the other character(*).
If I pass character variables to both arguments, the length of the variable passed to the type(*) arguments determines the length of the variable of the character(*) argument.
E. g. if I do call sub("a", "123") then sub only receives “1” at the second argument, even if I never use the first argument. If the first argument is very long, the second also gets filled with junk.
Example code:
implicit none
character(100) :: not_used
call sub(not_used, "123")
contains
subroutine sub(useless_var, print_this)
type(*), intent(in) :: useless_var
character(*), intent(in) :: print_this
print *, "should be 123: '", print_this, "'"
end subroutine sub
end
I think that for making that sub interafce as general as possible, you need to make two slight changes:
use class(*) instead of type(*) (hoping that you don’t actually use that variable in the procedure, but then why to even pass it in the first place… so I fear you actually do use it).
make the useless var assumed rank, in order to work with both scalar/array entries.
This worked with gfortran trunk, ifort/ifx latest.
program main
implicit none
character(len = *), parameter :: not_used = 'A very long, long, long, long string'
character(len = 1), parameter :: not_used_chArray(115) = 'A very long, long, long, long string, but as an array'
call sub(not_used, "123")
call sub(not_used_chArray, "123")
contains
subroutine sub(useless_var, print_this)
class(*), intent(in) :: useless_var(..)
character(*), intent(in) :: print_this
print *, "should be 123: '", print_this, "' "
end subroutine sub
end
I tested using type(*), and ifort/ifx actually give the expected output. Don’t know at this point if it is a gfortran bug there. Might need to wait someone else’s answer for that.
For whatever it’s worth, I think your code conforms and Intel Fortran works as expected with it. You may want to post a support request with GCC Bugzilla.
Thank you very much, I didn’t know this flag. Looks very useful!
However, I don’t really understand its output. Could you give me a hint, please?
For reference, I put the output into this collapsible section:
I can confirm that Intel compiles this correctly.
I wanted to open a bug, but the bug reporting website looks a bit scary to me, and it recommends using a secondary e-mail (because of spam etc.) which I currently don’t have. So I may get to it later.
Thanks for this very interesting introduction to the GFortran tree dump. It’s cool to see the hidden arguments. I have heard about them here and there, and now here they are!
Note that the argument to sub must be allocatable or optional then in your example. As written the call to is_unallocated should always return .true., as it is always present, but you may get a segfault if the actual argument to sub isn’t allocated. I.e. it should be
subroutine sub(useless_var, print_this)
type(*), intent(in), optional :: useless_var(..)
character(*), intent(in) :: print_this
print *, "should be 123: '", print_this, "'"
print *, "useless_var is unallocated", is_unallocated(useless_var)
end subroutine sub
Note that type(*) is fine in this case if you don’t intend to use its value.
Do you mean that it is against the standard to pass an unallocated variable as an actual argument to a dummy argument that is neither allocatable nor optional? I think I understand what you mean, but it worked in GFortran. Maybe it’s undefined behaviour?
Since many people have asked why would you need such a function, here’s what I do:
I’ve written a program that stores all arguments of a subroutine in a netCDF file. Since some arguments are deeply nested derived types, I automated the process by parsing the source code and generating function calls to my netCDF library. For each Fortran data type within the derived types, I generate the necessary variable definition (including its dimensions) and storage of each variable. (In some cases, there are over 100 individual variables). Sometimes, a derived type is passed to a subroutine where some members are not allocated because they aren’t used in the subroutine. My plan is to skip all unallocated variables, because the parser that generates the function calls has no way of knowing whether an allocatable variable is allocated or not.
Correct. If it worked with gfortran I would say it was coincidental, and that turning on certain run-time checking may have flagged it. Sounds like an interesting use case though.
Unless you have a function which accepts both allocatable and not allocatable variables. You cannot call allocated on a variable which isn’t allocatable.
‘array’ argument of ‘allocated’ intrinsic at (1) must be ALLOCATABLE
I’m referring to your explanation here and particularly with, “a derived type is passed to a subroutine where some members are not allocated because they aren’t used in the subroutine.” and with functions such as is_allocated in conjunction with procedures such as your sub above.
My point is you’re after a certain edifice with netCDF and your aspects such as is_allocated with a sub that takes unlimited polymorphic are unclear; is_allocated does not make sense. Perhaps you relook what you are after from this perspective, you may find a way to work with ALLOCATED intrinsic.
Perhaps I haven’t made it clear enough what the situation is.
I have a large Chemistry Transport Model (CTM) which consists of many subroutines. I want to work on a subroutine without having to run the whole model (which takes hours even on 500+ CPU cores).
For example, I have a target routine like this:
subroutine target(a, b, c)
integer :: a
real :: b
type(t1) :: c
end subroutine
I parse the relevant types of the code with a Python script, which generates another subroutine store_target_netcdf with exactly the same arguments. But within this subroutine, each argument is written to a netCDF file.
So there is one interface that simply accepts variables of any type and rank, and under the hood distinguishes between type and rank to define the correct netCDF variable and call the correct netCDF library functions.
In the CTM, all I have to do is change the call from target to store_target_netcdf and the next model run will generate a loadable checkpoint anywhere I want.
But when there are variables which aren’t allocated, trying to store them results obviously in segfaults.
It would appear you are after a specific form of serialization around your need with Fortran subprograms.
You may want to consider some specific binary format or a literal string or some such that helps you with, “variables which aren’t allocated.”
That is, pick some idea(s) for your specific case from what others have done with object-oriented languages and serialization toward netCDF, etc. in order to handle objects that are not instantiated.