Can fortran infer shape of array passed to subroutine? - fortran

I read that Fortran (unlike C) knows the size of arrays, and can infer it when I pass the array into function (subroutine). But I cannot make it work.
Minimum example:
program.f90
program test_arrayPass
! === variables
integer :: n
real, dimension (:,:),allocatable :: data
! === Body
n = 3
allocate(data(n,n))
write (*,*) "DEBUG test_arrayPass : shape(data) ", shape(data)
call writeToArray( data )
end
writeToArray.f90
subroutine writeToArray( data )
real , dimension(:,:), intent(out) :: data ! none of these works
!real , dimension(:,:), intent(in) :: data ! none of these works
!real , dimension(*,*), intent(in) :: data ! none of these works
write (*,*) "DEBUG writeToArray : shape(data) ", shape(data)
end
Makefile
FC := /usr/bin/gfortran
FCFLAGS = -g -Og -c -fdefault-real-8 -fbacktrace -fno-align-commons -fbounds-check
FLFLAGS =
SRCS = $(patsubst %.f90, %.o, $(wildcard *.f90))
PROGRAM = program
all: $(PROGRAM)
$(PROGRAM): $(SRCS)
$(FC) $(FLFLAGS) -o $# $^
%.o: %.f90
$(FC) $(FCFLAGS) -o $# $<
clean:
rm -f *.o *.mod
Result
with dimension(:,:) it does not know corret size inside writeToArray()
DEBUG test_arrayPass : shape(data) 3 3
DEBUG writeToArray : shape(data) 1 0
with dimension(*,*) it produces error
5 | real , dimension(*,*), intent(in) :: data
| 1
Error: Non-PARAMETER symbol ‘data’ at (1) cannot be implied-shape

Fortran can indeed assume (not infer) the shape or size of a dummy argument.
Assuming shape and size are two different things, with different requirements. With the dummy argument (intent doesn't matter)
real , dimension(:,:), intent(out) :: data
you are assuming its shape (by using : in the declaration). The problem you are seeing with this attempt is that you do not provide an explicit interface in your main program. This is such a common mistake that has been covered many times here that I won't expand more: searching for "explicit interface" will provide lots of ideas.
Instead, I'll talk about your other attempt:
real , dimension(*,*), intent(in) :: data
This isn't assuming the argument's shape, and neither is it assuming its size. An assumed size dummy argument would look like
real , dimension(*), intent(in) :: data
or
real , dimension(3,*), intent(in) :: data
In an assumed size array you can only have "unknown" extent in one of the ranks, and that must be the final one. However, the syntax for an implied-shape array is as you have, but only named constants (and not dummy arguments) may be implied-shape. Your compiler is complaining about this error, not thinking you are trying to talk about an assumed-size dummy array.
Assumed-size array arguments don't require such an explicit interface, but to make this work you'll need to assume just one dimension. (You can make associate a rank-2 array with a rank-1 assumed-size dummy argument if you don't want to guess one of the extents in the subroutine.)
But unless you have a really good reason you want to use an assumed-shape (:,:) array with an explicit interface. (If you have a good reason to use an implicit interface, you need to think very hard about whether you should be doing what you are doing.)
Finally, with an assumed-size array, you can't inquire of the shape of the array (using shape), its size (size) or its upper bounds (ubound). For size and upper bound you can ask about these properties of the initial extents, just not the final. You can use an assumed-size array, but you'll need some other source of information about its shape.

Minimal working example:
program test_arrayPass
! === variables
integer :: n
real, dimension (:,:),allocatable :: data
! === Body
n = 3
allocate(data(n,n))
write (*,*) "DEBUG test_arrayPass : shape(data) ", shape(data)
call writeToArray( data )
contains
subroutine writeToArray( data )
! === variables
real , dimension(:,:), intent(out) :: data
integer :: n, m, k
! === Body
write (*,*) "DEBUG writeToArray : shape(data) ", shape(data)
n = size(data,1)
m = size(data,2)
data = reshape( [(real(k), k=1,n*m)], [n,m] )
end subroutine
end program
The problem with your code is that the subroutine writeToArray is declared outside the scope of the program. You either contain it within the program, or you put in a module.

Related

array operation in fortran

I am writing a code with a lot of 2D arrays and manipulation of them. I would like the code to be as concise as possible, for that I would like to use as many 'implicit' operation on array as possible but I don't really know how to write them for 2D arrays.
For axample:
DO J=1,N
DO I=1,M
A(I,J)=B(J)*A(I,J)
ENDDO
ENDDO
become easily:
DO J=1,N
A(:,J)=B(J)*A(:,J)
ENDDO
Is there a way to reduce also the loop J?
Thanks
For brevity and clarity, you could wrap these operations in a derived type. I wrote a minimal example which is not so concise because I need to initialise the objects, but once this initialisation is done, manipulating your arrays becomes very concise and elegant.
I stored in arrays_module.f90 a derived type arrays2d_T which can hold the array coefficients, plus useful information (number of rows and columns). This type contains procedures for initialisation, and the operation you are trying to perform.
module arrays_module
implicit none
integer, parameter :: dp = kind(0.d0) !double precision definition
type :: arrays2d_T
real(kind=dp), allocatable :: dat(:,:)
integer :: nRow, nCol
contains
procedure :: kindOfMultiply => array_kindOfMuliply_vec
procedure :: init => initialize_with_an_allocatable
end type
contains
subroutine initialize_with_an_allocatable(self, source_dat, nRow, nCol)
class(arrays2d_t), intent(inOut) :: self
real(kind=dp), allocatable, intent(in) :: source_dat(:,:)
integer, intent(in) :: nRow, nCol
allocate (self%dat(nRow, nCol), source=source_dat)
self%nRow = nRow
self%nCol = nCol
end subroutine
subroutine array_kindOfMuliply_vec(self, vec)
class(arrays2d_t), intent(inOut) :: self
real(kind=dp), allocatable, intent(in) :: vec(:)
integer :: iRow, jCol
do jCol = 1, self%nCol
do iRow = 1, self%nRow
self%dat(iRow, jCol) = vec(jCol)*self%dat(iRow, jCol)
end do
end do
end subroutine
end module arrays_module
Then, in main.f90, I check the behaviour of this multiplication on a simple example:
program main
use arrays_module
implicit none
type(arrays2d_T) :: A
real(kind=dp), allocatable :: B(:)
! auxilliary variables that are only useful for initialization
real(kind=dp), allocatable :: Aux_array(:,:)
integer :: M = 3
integer :: N = 2
! initialise the 2d array
allocate(Aux_array(M,N))
Aux_array(:,1) = [2._dp, -1.4_dp, 0.3_dp]
Aux_array(:,2) = [4._dp, -3.4_dp, 2.3_dp]
call A%init(aux_array, M, N)
! initialise vector
allocate (B(N))
B = [0.3_dp, -2._dp]
! compute the product
call A%kindOfMultiply(B)
print *, A%dat(:,1)
print *, A%dat(:,2)
end program main
Compilation can be as simple as gfortran -c arrays_module.f90 && gfortran -c main.f90 && gfortran -o main.out main.o arrays_module.o
Once this object-oriented machinery exists, call A%kindOfMultiply(B) is much clearer than a FORALL approach (and much less error prone).
No one has mentioned do concurrent construct here, which has the potential to automatically parallelize and speed up your code,
do concurrent(j=1:n); A(:,j)=B(j)*A(:,j); end do
A one-line solution can be achieved by using FORALL:
FORALL(J=1:N) A(:,J) = B(J)*A(:,J)
Note that FORALL is deprecated in the most recent versions of the standard, but as far as I know, that is the only way you can perform that operation as a single line of code.

Data transfer element cannot have ALLOCATABLE components in gfortran

I am compiling a code in Fortran. If I use a recent version of Intel Fortran it compiles. However, I need to compile the same code with gfortran (I have gcc version 6.3.0 (GCC)).
At these two lines of the code
read(F%Unit) FileSettings%TCosmoTheoryParams
Write(F%Unit) CosmoSettings%TCosmoTheoryParams
I get the error `
Error: Data transfer element at (1) cannot have ALLOCATABLE components unless it is processed by a defined input/output procedure`
How to modify the code, keeping the compiler gcc?
The full compiler error, within the 'make' compilation
mpif90 -cpp -O3 -ffast-math -ffree-line-length-none -fopenmp -fmax-errors=4 -march=native -DMPI -DEFTCOSMOMC -I../EFTCAMB/ReleaseEFTMPI -JReleaseEFTMPI -IReleaseEFTMPI/ -c CosmoTheory.f90 -o ReleaseEFTMPI/CosmoTheory.o
CosmoTheory.f90:253:52:
read(F%Unit) FileSettings%TCosmoTheoryParams
1
Error: Data transfer element at (1) cannot have ALLOCATABLE components unless it is processed by a defined input/output procedure
CosmoTheory.f90:183:54:
Write(F%Unit) CosmoSettings%TCosmoTheoryParams
1
Error: Data transfer element at (1) cannot have ALLOCATABLE components unless it is processed by a defined input/output procedure
And the snippet of code where these lines are from:
subroutine TCosmoTheoryPredictions_ReadTheory(this, F, first)
Class(TCosmoTheoryPredictions) this
class(TFileStream) :: F
logical, intent(in) :: first
type(TCosmoTheorySettings), save :: FileSettings
!JD 02/14 new variables for handling new pk arrays
integer :: num_k, num_z
real(mcp), allocatable :: temp(:,:)
real(mcp), allocatable :: k(:), z(:)
real(mcp), allocatable :: cl(:)
real(mcp), allocatable :: valArray(:)
integer i,j
if (first) then
read(F%Unit) FileSettings%TCosmoTheoryParams
if (FileSettings%use_LSS) call F%ReadSizedArray(FileSettings%power_redshifts)
if (FileSettings%use_CMB) call F%ReadSizedArray(FileSettings%cl_lmax)
call F%ReadSizedArray(FileSettings%ArraySizes) !not used
end if
subroutine TCosmoTheoryPredictions_WriteTheory(this, F, first)
Class(TCosmoTheoryPredictions) this
class(TFileStream) :: F
logical, intent(in) :: first
integer ArraySizes(1)
real(mcp) :: valArray(6)
integer i,j
if (first .and. new_chains) then
Write(F%Unit) CosmoSettings%TCosmoTheoryParams
if (CosmoSettings%use_LSS) call F%WriteSizedArray(CosmoSettings%power_redshifts)
if (CosmoSettings%use_CMB) call F%WriteSizedArray(CosmoSettings%cl_lmax)
ArraySizes(1)=size(valArray)
call F%WriteSizedArray(ArraySizes)
end if
Definition of TCosmoTheorySettings:
Type, extends(TCosmoTheoryParams):: TCosmoTheorySettings
!Just add the allocatable components
integer, allocatable :: cl_lmax(:,:)
integer, allocatable :: ArraySizes(:)
!e.g. lmax_cl(1,1) is lmax for TT; zero if CL is not used; order is T, E, B, Phi
real(mcp), dimension(:), allocatable :: power_redshifts
contains
procedure, private :: Initialize_PKSettings
procedure, private :: Initialize_CMBSettings
procedure :: InitForLikelihoods => TCosmoTheorySettings_InitForLikelihoods
procedure :: ReadParams => TCosmoTheorySettings_ReadParams
end type TCosmoTheorySettings
Type TCosmoTheoryParams contains only ordinary non-allocatable and non-pointer data components and no procedures

What does "array cannot have a deferred shape" mean in fortran?

I have a simple fortran function that computes the Kronecker product:
function kron(A, B)
implicit none
real, intent(in) :: A(:, :), B(:, :)
integer :: i, j, ma, na, mb, nb
real, dimension(:, :) :: kron
ma = ubound(A, 1)
na = ubound(A, 2)
mb = ubound(b, 1)
nb = ubound(b, 2)
forall(i=1:ma, j=1:na)
kron(mb*(i-1)+1:mb*i, nb*(j-1)+1:nb*j) = A(i,j)*B
end forall
end function kron
It's inside a module, but when I compile it with gfortran -static -ffree-form -std=f2003 -Wall, I get these errors:
function kron(A, B)
1
Error: Array 'kron' at (1) cannot have a deferred shape
Is this error occurring because you're supposed to know the size of the array to be returned beforehand?
That is exactly what the error is telling you: kron must have an explicit shape. If you do not want to pass the array sizes beforehand, you'd have to define kron as
real, dimension(lbound(a,dim=1):ubound(a,dim=1),&
lbound(a,dim=2):ubound(a,dim=2)) :: kron
Using this particular explicit declaration above does compile for me on gfortran 4.6.3.
A deferred-shape array that has the ALLOCATABLE attribute is referred to as an allocatable array. Its bounds and shape are determined when storage is allocated for it by an ALLOCATE statement.
try this
real, intent(in), allocatable, dimension(:, :: A(:, :), B(:, :)
You just need to define the allocatable array as allocatable, i.e replace the kron definition with;
real, allocatable, dimension(:,:) :: kron
This also compiles fine in 4.6.3 and is defined at:
https://docs.roguewave.com/codedynamics/2017.0/html/index.html#page/TotalViewLH/totalviewlhug-examining-data.09.10.html
Hopefully this should save you some effort, especially considering there is no need to define a lower bound here!

Smart way to pass arguments in Fortran 90

I am a Fortran novice. I am trying to write a subroutine that will take in four arguments from the main program, and then outputs to the main program an array that involves the four arguments that were originally passed in. What is a good/smart way to do this?
For example, in my test program below, I create four real variables (a, b, c, and d) in the main program. Then I pass these real variables to a subroutine called mysub. I would like mysub to be able to take in a, b, c, and d, use them to populate a 2-by-2 array called o, and then send o to the main program for displaying (and possible modification) there. So, I tried the following:
SUBROUTINE mysub(w,x,y,z)
IMPLICIT NONE
REAL, INTENT(IN) :: w, x, y, z
REAL, DIMENSION(:,:), ALLOCATABLE, INTENT(OUT) :: o
ALLOCATE(o(2,2))
o(1,1)=w
o(1,2)=x
o(2,1)=y
o(2,2)=z
END SUBROUTINE mysub
END MODULE testsubs
PROGRAM test
USE testsubs
IMPLICIT NONE
REAL :: a=1.1, b=2.2, c=3.3, d=4.4
CALL mysub(a, b, c, d)
PRINT *, o(1,1), o(1,2)
PRINT *, o(2,1), o(2,2)
END PROGRAM test
But, I get the following error:
test.f90:10.53:
REAL, DIMENSION(:,:), ALLOCATABLE, INTENT(OUT) :: o
1
Error: Symbol at (1) is not a DUMMY variable
I interpret this as, the compiler doesn't know what o is, because o is not in the list of arguments in the subroutine header: SUBROUTINE mysub(w,x,y,z). So I probably need to include o in that header. So, I next try the following (where I have denoted changes or additions using !...):
SUBROUTINE mysub(w,x,y,z,o) !...
IMPLICIT NONE
REAL, INTENT(IN) :: w, x, y, z
REAL, DIMENSION(:,:), ALLOCATABLE, INTENT(OUT) :: o
ALLOCATE(o(2,2))
o(1,1)=w
o(1,2)=x
o(2,1)=y
o(2,2)=z
END SUBROUTINE mysub
END MODULE testsubs
PROGRAM test
USE testsubs
IMPLICIT NONE
REAL :: a=1.1, b=2.2, c=3.3, d=4.4
REAL, DIMENSION(:,:), ALLOCATABLE :: o !...
CALL mysub(a, b, c, d, o) !...
PRINT *, o(1,1), o(1,2)
PRINT *, o(2,1), o(2,2)
DEALLOCATE(o) !...
END PROGRAM test
This seems to work fine, and I get the correct output:
1.1000000 2.2000000
3.3000000 4.4000001
But, my question is, is this a good way to do this? In this working example, I'm declaring the array o both in the subroutine and in the main program. This seems potentially confusing, because I think that this means that I need to take care that either the subroutine or the main program allocates o (but not both, I think, in order to avoid error messages). Is there a smarter way to do this--to send an array from a subroutine to the main program? Thank you for your time.
Your solution, making "o" an intent(out) argument is just fine. Without "o" being an argument there was no connection between the variable "o" in the subroutine and the variable "o" in the main program, and therefore there was no declaration or allocation of the one in the main program. Yet another solution (besides the one provided by #ja72) would be to alter your method: make "o" an intent(inout) argument of the subroutine and allocate it in the main program. Possible advantage: the allocate and deallocate are closer together in the code and paired. Possible disadvantage: depending on the the program logic and design, the array dimensions might be best known to the subroutine.
P.S. If you allocate the array in the main program, and don't actually use allocatable properties of the array in the subroutine (i.e., you don't allocate or deallocate it), then you don't have to declare it with the allocatable attribute in the subroutine -- a useful simplification. In which case "intent (out)" might be appropriate. But if you allocate the array in the main program and wish to pass that status to a subroutine, then the argument status can't be "intent (out)". "intent (out)" automatically deallocates the argument upon entry to the procedure.
If you want to return an array you can a) add it to the arguments with INTENT(OUT) like your example #2 with allocation within the sub, or b) create a function and allocate the array externally:
FUNCTION myfun(w,x,y,z,n,m)
IMPLICIT NONE
INTEGER, INTENT(IN) :: n,m
REAL, DIMENSION(n,m) :: myfun
REAL, INTENT(IN) :: w,x,y,z
myfun(1,1)=w
myfun(1,2)=x
myfun(2,1)=y
myfun(2,2)=z
END FUNCTION
END MODULE testsubs
PROGRAM test
USE testsubs
IMPLICIT NONE
REAL :: a=1.1, b=2.2, c=3.3, d=4.4
REAL, DIMENSION(:,:), ALLOCATABLE :: o !...
ALLOCATE(o(2,2))
o = myfun(a,b,c,d,2,2)
PRINT *, o(1,1), o(1,2)
PRINT *, o(2,1), o(2,2)
DEALLOCATE(o) !...
END PROGRAM test
Actually I think your solution is cleaner.
It is not clear from your question if you know in advance the size of the array or not, but if you do, it is usually a good practice to allocate and deallocate the array in the same place, or even better is to leave the compiler allocate memory when possible.
How I would do:
if the size is known at compile time:
Declare your array in the main program, use intent(out) in a subroutine.
if the size is known only at runtime:
Allocate in the main program, use intent(out) in a subroutine and deallocate in the main program.
Functions are best suited for small outputs, since the outputs needs to be copied.

changing array dimensions in fortran

There are basically two ways to pass arrays to a subroutine in Fortran 90/95:
PROGRAM ARRAY
INTEGER, ALLOCATABLE :: A(:,:)
INTEGER :: N
ALLOCATE(A(N,N))
CALL ARRAY_EXPLICIT(A,N)
! or
CALL ARRAY_ASSUMED(A)
END PROGRAM ARRAY
SUBROUTINE ARRAY_EXPLICIT(A,N)
INTEGER :: N
INTEGER :: A(N,N)
! bla bla
END SUBROUTINE ARRAY_EXPLICIT
SUBROUTINE ARRAY_ASSUMED(A)
INTEGER, ALLOCATABLE :: A(:,:)
N=SIZE(A,1)
! bla bla
END SUBROUTINE ARRAY_ASSUMED
where you need an explicit interface for the second, usually through the use of a module.
From FORTRAN77, I'm used to the first alternative, and I read this is also the most efficient if you pass the whole array.
The nice thing with the explicit shape is that I can also call a subroutine and treat the array as a vector instead of a matrix:
SUBROUTINE ARRAY_EXPLICIT(A,N)
INTEGER :: N
INTEGER :: A(N**2)
! bla bla
END SUBROUTINE ARRAY_EXPLICIT
I wondered if there is a nice way to do that kind of thing using the second, assumed shape interface, without copying it.
See the RESHAPE intrinsic, e.g.
http://gcc.gnu.org/onlinedocs/gfortran/RESHAPE.html
Alternatively, if you want to avoid the copy (in some cases an optimizing compiler might be able to do a reshape without copying, e.g. if the RHS array is not used afterwards, but I wouldn't count on it), as of Fortran 2003 you can assign pointers to targets of different rank, using bounds remapping. E.g. something like
program ptrtest
real, pointer :: a(:)
real, pointer :: b(:,:)
integer :: n = 10
allocate(a(n**2))
a = 42
b (1:n, 1:n) => a
end program ptrtest
I was looking to do the same thing and came across this discussion. None of the solutions suited my purposes, but I found that there is a way to reshape an array without copying the data using iso_c_binding if you are using the fortran 2003 standard which current fortran 90/95 compilers tend to support. I know the discussion is old, but I figured I would add what I came up with for the benefit of others with this question.
The key is to use the function C_LOC to convert an array to an array pointer, and then use C_F_POINTER to convert this back into a fortran array pointer with the desired shape. One challenge with using C_LOC is that C_LOC only works for array that have a directly specified shape. This is because arrays in fortran with an incomplete size specification (i.e., that use a : for some dimension) include an array descriptor along with the array data. C_LOC does not give you the memory location of the array data, but the location of the descriptor. So an allocatable array or a pointer array don't work with C_LOC (unless you want the location of the compiler specific array descriptor data structure). The solution is to create a subroutine or function that receives the array as an array of fixed size (the size really doesn't matter). This causes the array variable in the function (or subroutine) to point to the location of the array data rather than the location of the array descriptor. You then use C_LOC to get a pointer to the array data location and C_F_POINTER to convert this pointer back into an array with the desired shape. The desired shape must be passed into this function to be used with C_F_POINTER. Below is an example:
program arrayresize
implicit none
integer, allocatable :: array1(:)
integer, pointer :: array2(:,:)
! allocate and initialize array1
allocate(array1(6))
array1 = (/1,2,3,4,5,6/)
! This starts out initialized to 2
print *, 'array1(2) = ', array1(2)
! Point array2 to same data as array1. The shape of array2
! is passed in as an array of intergers because C_F_POINTER
! uses and array of intergers as a SIZE parameter.
array2 => getArray(array1, (/2,3/))
! Change the value at array2(2,1) (same as array1(2))
array2(2,1) = 5
! Show that data in array1(2) was modified by changing
! array2(2,1)
print *, 'array(2,1) = array1(2) = ', array1(2)
contains
function getArray(array, shape_) result(aptr)
use iso_c_binding, only: C_LOC, C_F_POINTER
! Pass in the array as an array of fixed size so that there
! is no array descriptor associated with it. This means we
! can get a pointer to the location of the data using C_LOC
integer, target :: array(1)
integer :: shape_(:)
integer, pointer :: aptr(:,:)
! Use C_LOC to get the start location of the array data, and
! use C_F_POINTER to turn this into a fortran pointer (aptr).
! Note that we need to specify the shape of the pointer using an
! integer array.
call C_F_POINTER(C_LOC(array), aptr, shape_)
end function
end program
#janneb has already answered re RESHAPE. RESHAPE is a function -- usually used in an assignment statement so there will be a copy operation. Perhaps it can be done without copying using pointers. Unless the array is huge, it is probably better to use RESHAPE.
I'm skeptical that the explicit shape array is more efficient than the assumed shape, in terms of runtime. My inclination is to use the features of the Fortran >=90 language and use assumed shape declarations ... that way you don't have to bother passing the dimensions.
EDIT:
I tested the sample program of #janneb with ifort 11, gfortran 4.5 and gfortran 4.6. Of these three, it only works in gfortran 4.6. Interestingly, to go the other direction and connect a 1-D array to an existing 2-D array requires another new feature of Fortran 2008, the "contiguous" attribute -- at least according to gfortran 4.6.0 20110318. Without this attribute in the declaration, there is a compile time error.
program test_ptrs
implicit none
integer :: i, j
real, dimension (:,:), pointer, contiguous :: array_twod
real, dimension (:), pointer :: array_oned
allocate ( array_twod (2,2) )
do i=1,2
do j=1,2
array_twod (i,j) = i*j
end do
end do
array_oned (1:4) => array_twod
write (*, *) array_oned
stop
end program test_ptrs
You can use assumed-size arrays, but it can mean multiple layers of wrapper
routines:
program test
implicit none
integer :: test_array(10,2)
test_array(:,1) = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
test_array(:,2) = (/11, 12, 13, 14, 15, 16, 17, 18, 19, 20/)
write(*,*) "Original array:"
call print_a(test_array)
write(*,*) "Reshaped array:"
call print_reshaped(test_array, size(test_array))
contains
subroutine print_reshaped(a, n)
integer, intent(in) :: a(*)
integer, intent(in) :: n
call print_two_dim(a, 2, n/2)
end subroutine
subroutine print_two_dim(a, n1, n2)
integer, intent(in) :: a(1:n1,1:*)
integer, intent(in) :: n1, n2
call print_a(a(1:n1,1:n2))
end subroutine
subroutine print_a(a)
integer, intent(in) :: a(:,:)
integer :: i
write(*,*) "shape:", shape(a)
do i = 1, size(a(1,:))
write(*,*) a(:,i)
end do
end subroutine
end program test
I am using ifort 14.0.3 and 2D to 1D conversion, I could use an allocatable array for 2D array and a pointer array for 1D:
integer,allocatable,target :: A(:,:)
integer,pointer :: AP(:)
allocate(A(3,N))
AP(1:3*N) => A
As #M.S.B mentioned, in case both A and AP have the pointer attribute, I had to use contiguous attribute for A to guarantee the consistency of the conversion.
Gfortran is a bit paranoid with interfaces. It not only wants to know the type, kind, rank and number of arguments, but also the shape, the target attribute and the intent (although I agree with the intent part). I encountered a similar problem.
With gfortran, there are three different dimension definition:
1. Fixed
2. Variable
3. Assumed-size
With ifort, categories 1 and 2 are considered the same, so you can do just define any dimension size as 0 in the interface and it works.
program test
implicit none
integer, dimension(:), allocatable :: ownlist
interface
subroutine blueprint(sz,arr)
integer, intent(in) :: sz
integer, dimension(0), intent(in) :: arr
! This zero means that the size does not matter,
! as long as it is a one-dimensional integer array.
end subroutine blueprint
end interface
procedure(blueprint), pointer :: ptr
allocate(ownlist(3))
ownlist = (/3,4,5/)
ptr => rout1
call ptr(3,ownlist)
deallocate(ownlist)
allocate(ownlist(0:10))
ownlist = (/3,4,5,6,7,8,9,0,1,2,3/)
ptr => rout2
call ptr(3,ownlist)
deallocate(ownlist)
contains
! This one has a dimension size as input.
subroutine rout1(sz,arr)
implicit none
integer, intent(in) :: sz
integer, dimension(sz), intent(in) :: arr
write(*,*) arr
write(*,*) arr(1)
end subroutine rout1
! This one has a fixed dimension size.
subroutine rout2(sz,arr)
implicit none
integer, intent(in) :: sz
integer, dimension(0:10), intent(in) :: arr
write(*,*) "Ignored integer: ",sz
write(*,*) arr
write(*,*) arr(1)
end subroutine rout2
end program test
Gfortran complains about the interface. Changing the 0 into 'sz' solves the problem four 'rout1', but not for 'rout2'.
However, you can fool gfortran around and say dimension(0:10+0*sz) instead of dimension(0:10) and gfortran compiles and gives the same
result as ifort.
This is a stupid trick and it relies on the existence of the integer 'sz' that may not be there. Another program:
program difficult_test
implicit none
integer, dimension(:), allocatable :: ownlist
interface
subroutine blueprint(arr)
integer, dimension(0), intent(in) :: arr
end subroutine blueprint
end interface
procedure(blueprint), pointer :: ptr
allocate(ownlist(3))
ownlist = (/3,4,5/)
ptr => rout1
call ptr(ownlist)
deallocate(ownlist)
allocate(ownlist(0:10))
ownlist = (/3,4,5,6,7,8,9,0,1,2,3/)
ptr => rout2
call ptr(ownlist)
deallocate(ownlist)
contains
subroutine rout1(arr)
implicit none
integer, dimension(3), intent(in) :: arr
write(*,*) arr
write(*,*) arr(1)
end subroutine rout1
subroutine rout2(arr)
implicit none
integer, dimension(0:10), intent(in) :: arr
write(*,*) arr
write(*,*) arr(1)
end subroutine rout2
end program difficult_test
This works under ifort for the same reasons as the previous example, but gfortran complains about the interface. I do not know how I can fix it.
The only thing I want to tell gfortran is 'I do not know the dimension size yet, but we will fix it.'. But this needs a spare integer arguemnt (or something else that we can turn into an integer) to fool gfortran around.