Use variable name for argument-derived bounds of local arrays - arrays

With fortran, I am running in situations where I have multiple local variables whose size is derived from input parameters in a somewhat verbose manner, e.g.
program pbounds
contains
subroutine sbounds(x)
integer,intent(in) :: x(:,:)
integer y1(size(x,1)/3,size(x,2)/2)
integer y2(size(x,1)/3,size(x,2)/2)
integer y3(size(x,1)/3,size(x,2)/2)
! ... do some stuff
end subroutine sbounds
end program pbounds
This seems overly verbose as I keep repeating the size expression. Additionally, when a change is needed – e.g. when it turns out that I need a y4 and change size(x,1)/3 to size(x,1)/4 – for real-world code that doesn't look quite as neat, it is easy to miss one of the previous variables.
In my real code, other examples include declarations with sizes coming from verbose, repetitive composite type fields, such as
type(sometype), intent(in) :: obj
real :: arr1(obj%subfield%nmax, obj%subfield%nmax, obj%subfield%xmax, 3, 3)
real :: arr2(obj%subfield%nmax, obj%subfield%xmax)
...
Is it possible to define a name for the size expressions, without resorting to preprocessor macros or allocatable arrays?
The things I have tried
With allocatable variables, we can use a local variable
as name for the size expressions, but we split the declaration
of the local arrays over two lines each.
program pboundsx
contains
subroutine sboundsx(x)
integer,intent(in) :: x(:,:)
integer,allocatable :: y1(:,:),y2(:,:),y3(:,:)
integer s(2)
s = [ size(x,1)/3, size(x,2)/2 ]
allocate(y1(s(1),s(2)))
allocate(y2(s(1),s(2)))
allocate(y3(s(1),s(2)))
! ... do some stuff
end subroutine sboundsx
end program pboundsx
With preprocessor macros we can give the size expression a name,
but at the cost of adding multiple preprocessor lines, that
disturb the indentation pattern among other things.
program pboundsm
contains
subroutine sboundsm(x)
integer,intent(in) :: x(:,:)
#define s1 (size(x,1)/3)
#define s2 (size(x,2)/2)
integer y1(s1,s2)
integer y2(s1,s2)
integer y3(s1,s2)
#undef s1
#undef s2
! ... do some stuff
end subroutine sboundsm
end program pboundsm
With a second subroutine we can make the sizes an explicit
parameter, but this is probably the most verbose and obscure
solution; even more so considering that in real-world code 'x'
isn't the only parameter.
program pboundss
contains
subroutine sboundss(x)
integer, intent(in) :: x(:,:)
call sboundss2(x,size(x,1)/3,size(x,2)/2)
end subroutine sboundss
subroutine sboundss2(x,s1,s2)
integer, intent(in) :: x(:,:), s1, s2
integer y1(s1,s2), y2(s1,s2), y3(s1,s2)
end subroutine sboundss2
! ... do stuff
end program pboundss
If it was allowed to mix declarations and initialization, the solution would be simple – but it is not:
program pboundsv
contains
subroutine sboundsv(x)
integer,intent(in) :: x(:,:)
integer s1 = size(x,1)/3, s2 = size(x,2)/3 ! INVALID DECLARATION
integer y1(s1,s2), y2(s1,s2), y3(s1,s2)
! ... do stuff
end subroutine sboundsv
end program pboundsv

If the compiler allows (*), it may be an option to include the subroutine body entirely into a block (= a new scope) and mix declarations and assignment:
program pboundsv
contains
subroutine sboundsv(x)
integer,intent(in) :: x(:,:)
integer s1, s2
s1 = size(x,1)/3 ; s2 = size(x,2)/3
block
integer y1(s1,s2), y2(s1,s2), y3(s1,s2)
! ... do stuff
endblock
endsubroutine
end program
(*) But, this is Fortran >95, and Oracle studio fortran 12.5 still cannot compile it (very sadly)... (gfortran and ifort seem OK).

A partial solution - while specification statements cannot depend on the value of a local variable(**), they can depend on previous specifications for other local variables. For example:
subroutine sbounds(x)
integer,intent(in) :: x(:,:)
integer y1(size(x,1)/3,size(x,2)/2)
integer y2(size(y1,1),size(y1,2))
integer y3(size(y1,1),size(y1,2))
! ... do some stuff
end subroutine sbounds
...
type(sometype), intent(in) :: obj
real :: arr1(obj%subfield%nmax, obj%subfield%nmax, obj%subfield%xmax, 3, 3)
real :: arr2(size(arr1,1), size(arr1,3))
In some cases this can make the logical structure of your declarations clearer - "the extent of this dimension of this variable is the same as the extent of this dimension of that variable", which might be a more relevant message to a reader of the code than the specific expression that calculates the extent.
** Note that it is various restrictions on specification and constant expressions that is the real issue with your last block of code. You can quite happily mix declarations with initializations and other declarations in Fortran (they are just specification statements), what you cannot do is mix specification statements with executable statements (block constructs and the like aside). Specification expressions cannot depend on the value of a local variable, in part because it otherwise becomes difficult to ensure a deterministic ordering, while constant expressions cannot depend on the value of any variable, because constant expressions are supposed to be constant (and able to be evaluated at compile time).

Related

Fortran: How do I optimize the input data so that I can use it globally but don't need to copy it

I am currently writing a Fortran subroutine that processes a (possibly large) data array. I am using multiple subroutines from multiple modules and would like to have the input data array, as well as the output data array as global variables so that I can read / write them in every subroutine. However I would like to refrain from copying the data arrays unnecessarily, because I fear it would slow down the whole program (as said before, the data arrays are potentially very big, ~10.000x5 entries or so).
At the moment, I use a variable module which contains global variables for all subroutines. I read the input and output arrays into my subroutine and then copy the input values onto the global array, perform the calculations and then copy the global output array onto the output array I have within my subroutine. The code for the subroutine looks as follows:
subroutine flexible_clustering(data_array_in, limits_in, results_array_out)
use globalVariables_mod
use clusterCreation_mod
use clusterEvaluation_mod
implicit none
real*8, dimension(:,:) :: data_array_in
real*8, dimension(:) :: limits_in
real*8, dimension(:,:) :: results_array_out
! determine dimensions
data_entries_number = size(data_array_in(:,1))
data_input_dimension = size(data_array_in(1,:))
data_output_dimension = size(results_array_out(1,:))
! allocate and fill arrays
call allocate_global_variable_arrays()
data_array = data_array_in
limits = limits_in
! clustering
call cluster_creation()
call cluster_evaluation()
results_array_out = results_array
call reset_global_variables()
end subroutine flexible_clustering
The global variables used here are defined as follows in globalVariables_mod (with appropriate allocate / deallocate subroutines):
integer :: data_entries_number = 0, data_input_dimension = 0, data_output_dimension = 0
integer :: total_cluster_number = 0
real*8, allocatable, dimension(:) :: limits
real*8, allocatable, dimension(:,:) :: data_array
real*8, allocatable, dimension(:,:) :: results_array
Summed up, I take data_array_in, limits_in and results_array_out and copy them to data_array, limits and results_array to make them global variables in all subroutines.
Is there a way to omit this copying? Maybe using pointers? Can I optimize this another way?
Thanks in advance!

Adding to an array of characters in Fortran

I'm trying to write a class procedure that adds a new character to an array of characters, but keep stumbling across "different character length in array constructor" errors (compiling with GFortran), even when the characters lengths are, as far as I can see, the same.
Here's my function:
subroutine addToArray(this, newElement)
class(MyClass), intent(inout) :: this
character(len=*), intent(in) :: newElement
character(len=256) :: tempElement
character(len=256), dimension(:), allocatable :: temp
tempElement = newElement ! Needed otherwise newElement is of the wrong size
allocate(temp(size(this%charArray)+1) ! Make the char array bigger by 1
temp = [this%charArray, tempElement]
call move_alloc(from=temp, to=this%charArray)
end subroutine
This results in the error Fortran runtime error: Different CHARACTER lengths (538976288/256) in array constructor. However, if I print len(this%charArray) or len(tempElement), they are both 256 characters long. So where is the 538976288 coming from?
I'm typically calling this procedure using something like myObject%addToArray('hello'). this%charArray is declared in the type definition as character(len=256), dimension(:), allocatable :: charArray, and allocated using allocate(this%charArray(0)).
It appears it is an error which I reported to GCC more than a year ago https://gcc.gnu.org/bugzilla/show_bug.cgi?id=70231
The workaround is to compile with optimizations at least -O1.
If it is not the same error, an exact reproduction case is needed including the compilation flags and all relevant details.

How to declare an array variable and its size mid-routine in Fortran

I would like to create an array with a dimension based on the number of elements meeting a certain condition in another array. This would require that I initialize an array mid-routine, which Fortran won't let me do.
Is there a way around that?
Example routine:
subroutine example(some_array)
real some_array(50) ! passed array of known dimension
element_count = 0
do i=1,50
if (some_array.gt.0) then
element_count = element_count+1
endif
enddo
real new_array(element_count) ! new array with length based on conditional statement
endsubroutine example
Your question isn't about initializing an array, which involves setting its values.
However, there is a way to do what you want. You even have a choice, depending on how general it's to be.
I'm assuming that the element_count means to have a some_array(i) in that loop.
You can make new_array allocatable:
subroutine example(some_array)
real some_array(50)
real, allocatable :: new_array(:)
allocate(new_array(COUNT(some_array.gt.0)))
end subroutine
Or have it as an automatic object:
subroutine example(some_array)
real some_array(50)
real new_array(COUNT(some_array.gt.0))
end subroutine
This latter works only when your condition is "simple". Further, automatic objects cannot be used in the scope of modules or main programs. The allocatable case is much more general, such as when you want to use the full loop rather than the count intrinsic, or want the variable not as a procedure local variable.
In both of these cases you meet the requirement of having all the declarations before executable statements.
Since Fortran 2008 the block construct allows automatic objects even after executable statements and in the main program:
program example
implicit none
real some_array(50)
some_array = ...
block
real new_array(COUNT(some_array.gt.0))
end block
end program example
Try this
real, dimension(50) :: some_array
real, dimension(:), allocatable :: other_array
integer :: status
...
allocate(other_array(count(some_array>0)),stat=status)
at the end of this sequence of statements other_array will have the one element for each element of some_array greater than 0, there is no need to write a loop to count the non-zero elements of some_array.
Following #AlexanderVogt's advice, do check the status of the allocate statement.
You can use allocatable arrays for this task:
subroutine example(some_array)
real :: some_array(50)
real,allocatable :: new_array(:)
integer :: i, element_count, status
element_count = 0
do i=lbound(some_array,1),ubound(some_array,1)
if ( some_array(i) > 0 ) then
element_count = element_count + 1
endif
enddo
allocate( new_array(element_count), stat=status )
if ( status /= 0 ) stop 'cannot allocate memory'
! set values of new_array
end subroutine
You need to use an allocatable array (see this article for more on it). This would change your routine to
subroutine example(input_array,output_array)
real,intent(in) :: input_array(50) ! passed array of known dimension
real, intent(out), allocatable :: output_array(:)
integer :: element_count, i
element_count = 0
do i=1,50
if (some_array.gt.0) element_count = element_count+1
enddo
allocate(output_array(element_count))
end subroutine
Note that the intents may not be necessary, but are probably good practice. If you don't want to call a second array, it is possible to create a reallocate subroutine; though this would require the array to already be declared as allocatable.

C-Fortran character string interoperability

Good day. Sorry for maybe not so understandable definition of my problem and maybe some inaccuracies - I'm just starting to try myself in programming. Still, I'll try my best to explain everything plain.
I have mathematical DLL written in Fortran.
For example, there is a function. This function is used to parse name of log file into the dll to watch for the calculations.
integer function initLog(
* int_parameter,
* char_parameter,
* char_parameter_length,
* )
*bind(C, name = "initLog");
use, intrinsic :: ISO_C_BINDING;
!DEC$ATTRIBUTES DLLEXPORT::initLog
integer(C_INT), value :: parameter;
character(C_CHAR), intent(in) :: char_parameter(char_parameter_length);
integer(C_INT), value :: char_parameter_length;
...
some_other_variable = char_parameter(1:1)(1:char_parameter_length);
end function;
Usually I use MATLAB to work with the dll and, thus, have to use .mex files to call my functions directly from MATLAB. Inside the .mex file I have some interface code written in C that provides the interface between MATLAB and dll. For example, C interface for the function mentioned is:
int doSmth(const int int_parameter,
const char* char_parameter,
const int char_parameter_length,);
And then I use loadLibrary and GetProcAddress to get the function. And this works fine.
However, now I need to create .exe test file in Fortran which would use my dll. So, I have to link my dll to exe by linking it to an import .lib library. Another option for this executable is to take the name of the log file via command line as parameter. So, first I tried to pass the logfile filename just from within the exe file, like this:
program test
use dll_name;
use ifport;
implicit none;
...
integer :: log_init_status;
...
log_init_status = init_log(2, 'logfile.log', len('logfile.log'));
...
end program
This works fine in release, but returns a "severe (664): Out of range: substring ending position '11' is greater than string length '1'" mistake in debug. But at first I didn't find this bug and kept on writing the code. This is what I've got now:
program test
use dll_name;
use ifport;
use ISO_C_BINDING;
implicit none;
...
character*255 :: log_flag_char;
integer(C_INT) :: log_flag;
character*255 :: filename;
character(C_CHAR) :: log_filename;
integer(C_INT) :: log_filename_length;
....
call getarg(5, log_flag_char);
read(log_flag_char, *) log_flag;
call getarg(6, log_filename);
log_filename_length = len(log_filename);
log_init_status = analyticsLogInit(log_flag, log_filename, log_filename_length);
...
end program
This worked fine, but took only 1 first character of the log_filename ("C:\abcd\logfile.log" is transformed into "C"). If I change
character(C_CHAR) :: log_filename;
to
character(C_CHAR) :: log_filename(255);
, I get 2 problems: first, I have the length of my log_filename equal to 255 (can be fixed by trim though), and second - and the main - I again get "severe (664): Out of range: substring ending position '255' is greater than string length '1'".
If I change
log_init_status = analyticsLogInit(log_flag, log_filename,
log_filename_length);
to
log_init_status = analyticsLogInit(log_flag, C_LOC(log_filename),
log_filename_length);
, I get the error about the dummy argument type differ than the actual one.
I myself have a feeling that the 664 error shown comes from this line in dll:
some_other_variable = char_parameter(1:1)(1:char_parameter_length);
. I should write in my exe something like
character*255 :: log_filename;
and not
character :: log_filename(255);
But how can I parse it with (C_CHAR) used?
I realise that all this is quite messy and that it all comes from the leak of understanding, but this is my almost first serious experience in programming.
I only glanced over your question, but one thing to take note of is the way a character variable or named constant is declared. You can provide two type parameters: length and kind. If you don't use the corresponding keyword in the declaration, the first parameter specifies the length, and the second (if present) specifies the kind.
So if you want to declare a character variable of length 255 and kind C_CHAR, you can do so in any of the following ways:
character(len=255, kind=C_CHAR) :: log_filename
character(255, kind=C_CHAR) :: log_filename
character(255, C_CHAR) :: log_filename
character(kind=C_CHAR, len=255) :: log_filename
character(kind=C_CHAR) :: log_filename*255
The following syntax on the other hand (which is the one you used), declares a character variable of length C_CHAR, whatever value that may be.
character(C_CHAR) :: log_filename
Oh, and the next syntax declares an array of 255 elements, each element being a character variable of length C_CHAR.
character(C_CHAR) :: log_filename(255)
So the conclusion is, that one should take some time to study the peculiarities of declaring character entities in fortran.

keeping array limits in fortran during subroutine call

I have the following program
module test
contains
subroutine foo()
integer, allocatable :: a(:)
allocate(a(-5:5))
call bar(a)
print *, a
end subroutine
subroutine bar(a)
integer, intent(out) :: a(:)
a = 0
a(-4) = 3 ! here
a(2) = 3
end subroutine
end module
program x
use test
call foo()
end program
In the line marked with "here" I am doing something wrong. The fact is that when I receive the array a (in the caller allocated from -5 to +5), the callee uses conventional numbering (1 to n), meaning that assigning -4 I am doing an out of boundary assignment. How can I instruct the compiler that, within the bar routine, the numbering of the a array must be the same as in the caller ?
The type of dummy argument that you are are using in the subroutine, with the dimension specified with a colon, is called "assumed shape". This name is the clue -- Fortran passes only the shape and not the lower and upper bounds. The lower bound is assumed to be one unless you override it as shown in the answer by kemiisto. If the lower bound is not fixed, you can pass an argument to use as the lower bound.
Later addition: a code example if the lower dimension isn't known at compile time:
subroutine example (low, array)
integer, intent (in) :: low
real, dimension (low:), intent (out) :: array
There are two common options:
As kemisto wrote, you pass a second argument. This was common in F77-style code. You can not use the LBOUND trick! It has to be passed as an integer.
You declare the argument to be a pointer, which includes the entire array descriptor. Then the bounds of the array in the subroutine are the same as in the calling scope. Of course you may lose on optimization this way.
How can I instruct the compiler that, within the bar routine, the numbering of the a array must be the same as in the caller ?
Not sure but according to the standard you can specify the lower bound for an assumed-shape array.
subroutine bar(a)
integer, intent(out) :: a(-5:)

Resources