How to use the value of an allocatable argument? - fortran

I have the following code and I would like to save the value of idx to use afterwards.
program use_value_allocatable
implicit none
integer :: i, ii
integer, dimension(3) :: array_save
character(1), dimension(3) :: array_char_ref = (/'a','b','c'/), array_char_1 = (/'c','a','b'/)
integer, allocatable :: idx(:)
array_save = 0
do i = 1, 3
idx = pack([(ii,ii=1,3)], array_char_ref == array_char_1(i) )
print*, 'i=', i, ', idx=', idx, ', array_save(i) =', array_save(i)
!!$ array_save(i) = idx
deallocate(idx)
end do
end program use_value_allocatable
Having array_save(i) = idx in the code leads to an error as follows:
Error: Incompatible ranks 0 and 1 in assignment at (1)
So, I can conclude that I cannot use the value of an allocatable variable (here idx). How I can circumvent this problem?
P.S.: in this example I assume that idx will always be an integer of dimension 1

As you say, "idx will always be an integer of dimension 1", so you just need
array_save(i) = idx(1)
i.e. you need to store the first (and only) element of idx in array_save(i), rather than the whole array.
A side note: you do not need the line deallocate(idx). idx will be implicitly re-allocated by the line idx = ..., and will be automatically deallocated when it drops out of scope.

Related

Calling Fortran code from julia, accessing array dynamically allocated in fortran

I need to call some fortran code that dynamically allocates arrays similar to this basic example. (unlike this example in the code I'm working with the size of the array is not known at the beginning of the function)
subroutine getIdentity(n,I)
integer, intent(in) :: n
integer, allocatable,dimension(:,:), intent(out) :: I
integer :: j,k
write(*,*) "creating " ,n, "x", n, "identity matrix"
allocate(I(n,n))
do j=1,n
do k=1,n
if(k==j) then
I(j,k) = 1
else
I(j,k) = 0
end if
end do
end do
end subroutine getIdentity
When I call this with this julia code:
I = zeros(Int32,1,1)
n = Ref{Int32}(3)
ccall((:__myModule_MOD_getidentity,"./test.so"), Cvoid ,
(Ref{Int32},Ref{Int32}), n,I)
println(I)
When I look at I in julia it is just garbage, not the Identity matrix I would expect. What would be the correct way to do this?

Big integer factorial function in Fortran, as efficient as python or Haskell

Here's my factorial function in Fortran.
module facmod
implicit none
contains
function factorial (n) result (fac)
use FMZM
integer, intent(in) :: n
integer :: i
type(IM) :: fac
fac = 1
if(n==0) then
fac = 1
elseif(n==1) then
fac = 1
elseif(n==2) then
fac = 2
elseif(n < 0) then
write(*,*) 'Error in factorial N=', n
stop 1
else
do i = 1, n
fac = fac * i
enddo
endif
end function factorial
end module facmod
program main
use FMZM
use facmod, only: factorial
implicit none
type(IM) :: res
integer :: n, lenr
character (len=:), allocatable :: str
character(len=1024) :: fmat
print*,'enter the value of n'
read*, n
res = factorial(n)
lenr = log10(TO_FM(res))+2
allocate(character(len=lenr) :: str)
write (fmat, "(A5,I0)") "i", lenr
call im_form(fmat, res, str)
print*, trim( adjustl(str))
end program main
I compile using FMZM:
gfortran -std=f2008 fac.F90 fmlib.a -o fac
echo -e "1000" | .fac computes easy. However, if I give this echo -e "3600" | .fac, I already get an error on my machine:
Error in FM. More than 200000 type (FM), (ZM), (IM) numbers
have been defined. Variable SIZE_OF_START in file
FMSAVE.f95 defines this value.
Possible causes of this error and remedies:
(1) Make sure all subroutines (also functions that do not
return type FM, ZM, or IM function values) have
CALL FM_ENTER_USER_ROUTINE
at the start and
CALL FM_EXIT_USER_ROUTINE
at the end and before any other return, and all
functions returning an FM, ZM, or IM function value have
CALL FM_ENTER_USER_FUNCTION(F)
at the start and
CALL FM_EXIT_USER_FUNCTION(F)
at the end and before any other return, where the actual
function name replaces F above.
Otherwise that routine could be leaking memory, and
worse, could get wrong results because of deleting some
FM, ZM, or IM temporary variables too soon.
(2) Make sure all subroutines and functions declare any
local type FM, ZM, or IM variables as saved. Otherwise
some compilers create new instances of those variables
with each call, leaking memory.
For example:
SUBROUTINE SUB(A,B,C,X,Y,RESULT)
TYPE (FM) :: A,B,C,X,Y,RESULT,ERR,TOL,H
Here A,B,C,X,Y,RESULT are the input variables and
ERR,TOL,H are local variables. The fix is:
SUBROUTINE SUB(A,B,C,X,Y,RESULT)
TYPE (FM) :: A,B,C,X,Y,RESULT
TYPE (FM), SAVE :: ERR,TOL,H
(3) Since = assignments for multiple precision variables are
the trigger for cleaning up temporary multiple precision
variables, a loop with subroutine calls that has no =
assignments can run out of space to store temporaries.
For example:
DO J = 1, N
CALL SUB(A,B,C,TO_FM(0),TO_FM(1),RESULT)
ENDDO
Most compilers will create two temporary variables with
each call, to hold the TO_FM values.
One fix is to put an assignment into the loop:
DO J = 1, N
ZERO = TO_FM(0)
CALL SUB(A,B,C,ZERO,TO_FM(1),RESULT)
ENDDO
(4) If a routine uses allocatable type FM, ZM, or IM arrays
and allocates and deallocates with each call, then after
many calls this limit on number of variables could be
exceeded, since new FM variable index numbers are
generated for each call to the routine.
A fix for this is to call FM_DEALLOCATE before actually
deallocating each array, so those index numbers can be
re-used. For example:
DEALLOCATE(T)
becomes:
CALL FM_DEALLOCATE(T)
DEALLOCATE(T)
(5) If none of this helps, try running this program again
after increasing the value of SIZE_OF_START and
re-compiling.
What optimizations or Fortran idioms am I missing that is hurting my performance so much?
For example, in python, I can factorial numbers much larger than 3500:
>>> import math
>>> math.factorial(100000)
Or in Haskell:
Prelude> product [1..100000]
Both these compute, not exactly quickly, but without error.
How can I improve my algorithm or better use existing libraries to improve performance of large integer factorials in Fortran? Is there a more appropriate big integer library than FMZM?
Try this. Apart from minor cosmetic changes, I just followed the recommendations of the error message in your question:
added calls to FM_ENTER_USER_FUNCTION and FM_EXIT_USER_FUNCTION,
added an assignment inside the loop (without this ii = to_im(i), it still fails, but I'm not sure why, as there is already an assignment with fac = fac * i, and accordind to the doc the assignment triggers cleaning up temporaries),
renamed factorial in main program as there is already a function with this name in FMZM.
Tested with ifort and n=100000.
module fac_mod
implicit none
contains
function factorial(n) result(fac)
use FMZM
integer, intent(in) :: n
integer :: i
type(IM) :: fac
type(IM), save :: ii
call FM_ENTER_USER_FUNCTION(fac)
fac = to_im(1)
if (n < 0) then
write (*, *) "Error in factorial N=", n
stop 1
else if (n > 1) then
do i = 1, n
ii = to_im(i)
fac = fac * ii
end do
end if
call FM_EXIT_USER_FUNCTION(fac)
end function factorial
end module fac_mod
program main
use FMZM
use fac_mod, only: f=>factorial
implicit none
type(IM) :: res
integer :: n, lenr
character(:), allocatable :: str
character(1024) :: fmat
print *, "enter the value of n"
read *, n
res = f(n)
lenr = 2 + log10(TO_FM(res))
allocate (character(lenr) :: str)
write (fmat, "(A5,I0)") "i", lenr
call im_form(fmat, res, str)
print *, trim(adjustl(str))
end program main

What in my ALLOCATE is causing my integer overflow?

I have a set of code in which I declare the size of all my variables. However, I want to change them so some of the variables are allocatable.
This is (what I believe) to be the relevant code of the original.
parameter (m=10**5,nchar=2000,ncols=110)
character (LEN=*), PARAMETER :: FORM = "(A)"
character(LEN=nchar),DIMENSION(m) :: data
* determine the length of the data
nlines = 0
do i = 1,m
read(12,*,end=10)
nlines = nlines+1
end do
nlines = nlines+1
* read in the data
10 REWIND(unit = 12)
do i = 1,nlines
read(12,FORM) data(i)
end do
This is the form I would like.
parameter (m=10**5,nchar=2000,ncols=110)
character (LEN=*), PARAMETER :: FORM = "(A)"
character(LEN=:),DIMENSION(:),allocatable :: data
integer j
character(LEN=100000) :: temp
* determine the length of the data
nlines = 0
j = 0
do while (ios == 0)
read(12,FORM,end=10,iostat=ios) temp
if (LEN(TRIM(temp)) .gt. j) THEN
j = LEN(TRIM(temp))
end if
nlines = nlines+1
end do
nlines = nlines+1
10 REWIND(unit = 12)
ALLOCATE (character(LEN=j) :: data(nlines))
* read in the data
do i = 1,nlines
read(12,FORM) data(i)
end do
Problematically, this causes an integer overflow error. "Fortran runtime error: Integer overflow when calculating the amount of memory to allocate". I find this very perplexing as the 'nlines' and 'j' values I obtain from my test dataset are only 10 and 110 respectively.
I have found that if I don't allocate the character length (i.e. keep it a constant), this works.
I am using gfortran, version 4.8.0.
What is wrong with my code/method?

Invalid chacter in name fortran 90

This is probably something really simple but I'm getting the error when compiling my little Fortran program. (The file is .f90) Is this something to do with fixed versus free line length? That seems to be all I could glean from a google search.
Here's the program:
program array
integer :: k, n, i, j, h, f, AllocateStatus
real*8, dimension(:, :, :), allocatable :: a
character, parameter :: "fname"
k = 5
n = 5
h = 1
allocate(a(n,k,h), stat = AllocateStatus)
if (AllocateStatus /= 0) stop "*** Not enough memory ***"
a(1,:,:) = 5
a(2,:,:) = 6
call writeArray(7,a,"testOutput")
deallocate(a)
end program array
subroutine writeArray(f,array,fname)
implicit none
integer :: f, i, j, k, n
character, parameter :: "fname"
real*8, dimension(:, :, :), allocatable :: array
open(unit = f, file="fname")
do, i=1,n
do, j=1,k
write(7,"(F5.2)") array(i,j,:)
if (j==k) write(7,"(A1)") "X"
enddo
enddo
!write(7,"(I5)") size(a)
close(f)
end subroutine writeArray
And the errors:
test.f90:4.29:
character, parameter :: "fname"
1
Error: Invalid character in name at (1)
test.f90:24.26:
character, parameter :: "fname"
1
Error: Invalid character in name at (1)
test.f90:21.35:
subroutine writeArray(f,array,fname)
1
Error: Symbol 'fname' at (1) has no IMPLICIT type
You cannot use quotation marks to denote an initialization. In your subroutine, you should have
CHARACTER(LEN=*) :: fname
in place of what you have there. You probably do not need the PARAMETER statement with the character declaration. The initialization of fname does not appear to be needed in the main program.
Another pair of things I noted in your code: (1) you don't need to declare array and ALLOCATABLE and (2) you ought to start file UNITs at values >= 10 because the single-digit numbers are occasionally associated with (reserved for?) standard out.
Another suggestion is that you should either put your writeArray subroutine in its own MODULE and USE it, or write the program as
PROGRAM Main
...
CONTAINS
SUBROUTINE writeArray
...
END SUBROUTINE
END PROGRAM
With either method, you will catch inconsistencies in the arguments. Not only that, you will also be able to use the variables n and k without issue.
I totally agree with #kyle. So in heeding those suggestions I would also declare the intent of the variables to the subroutine writeArray. Thus the program would be along the lines of:
program array
integer :: k, n, h, AllocateStatus
double precision, dimension(:, :, :), allocatable :: a
character(len=1024) :: fname
fname = "testOutput"
k = 5
n = 5
h = 1
allocate(a(n,k,h), stat = AllocateStatus)
if (AllocateStatus /= 0) stop "*** Not enough memory ***"
a(1,:,:) = 5
a(2,:,:) = 6
call writeArray(7,a,fname)
deallocate(a)
contains
subroutine writeArray(f,array,fname)
implicit none
integer, intent(in) :: f
integer :: i, j, k
character(len=*), intent(in) :: fname
double precision, dimension(:, :, :), intent(in) :: array
open(unit = f, file=fname)
i = size(array, 1)
k = size(array, 2)
do, i=1,n
do, j=1,k
write(7,"(F5.2)") array(i,j,:)..
if (j==k) write(7,"(A1)") "X"
enddo
enddo
!write(7,"(I5)") size(a)
close(f)
end subroutine writeArray
end program array
Also I don't like using real*8, I tend to either declare it as either real(kind=8) or double precision.
Lastly, depending on the compiler you use (and hence it's flags), Try to always be as pedantic and chatty as possible. For gfortran I typically use the options -Wall -pedantic when compiling.
Additional comments:
You definitely don't want parameter in the declaration of fname -- that designates that the "variable" is constant, which is inconsistent with a dummy argument.
You could declare the arguments as:
integer, intent (in) :: f
character (len=*), intent (in) :: fname
real*8, dimension(:, :, :), intent (in) :: array
The reason that you don't need to declare array as allocatable in the subroutine is that you don't change its allocation in the subroutine. You can obtain the values of n and k with the size intrinsic and so don't need to pass them as arguments.

how to write wrapper for 'allocate'

I am trying to write a wrapper for 'allocate' function, i.e. function which receives an array and dimensions, allocates memory and returns allocated array. The most important thing is that the function must work with arrays of different rank. But I have to explicitly state rank of array in function interface, and in this case code only compiles if I pass arrays of certain rank as a parameter. For example, this code does not compile:
module memory_allocator
contains
subroutine memory(array, length)
implicit none
real(8), allocatable, intent(out), dimension(:) :: array
integer, intent(in) :: length
integer :: ierr
print *, "memory: before: ", allocated(array)
allocate(array(length), stat=ierr)
if (ierr /= 0) then
print *, "error allocating memory: ierr=", ierr
end if
print *, "memory: after: ", allocated(array)
end subroutine memory
subroutine freem(array)
implicit none
real(8), allocatable, dimension(:) :: array
print *, "freem: before: ", allocated(array)
deallocate(array)
print *, "freem: after: ", allocated(array)
end subroutine freem
end module memory_allocator
program alloc
use memory_allocator
implicit none
integer, parameter :: n = 3
real(8), allocatable, dimension(:,:,:) :: foo
integer :: i, j, k
print *, "main: before memory: ", allocated(foo)
call memory(foo, n*n*n)
print *, "main: after memory: ", allocated(foo)
do i = 1,n
do j = 1,n
do k = 1, n
foo(i, j, k) = real(i*j*k)
end do
end do
end do
print *, foo
print *, "main: before freem: ", allocated(foo)
call freem(foo)
print *, "main: after freem: ", allocated(foo)
end program alloc
Compilation error:
gfortran -o alloc alloc.f90 -std=f2003
alloc.f90:46.14:
call memory(foo, n*n*n)
1
Error: Rank mismatch in argument 'array' at (1) (1 and 3)
alloc.f90:60.13:
call freem(foo)
1
Error: Rank mismatch in argument 'array' at (1) (1 and 3)
Is there any way of implementing such wrapper?..
Thanks!
This can be done via a generic interface block. You have to create procedures for each rank that you want to handle, e.g., memory_1d, memory_2d, ... memory_4d. (Obviously a lot of cut & pasting.) Then you write a generic interface block that gives all of these procedures the alternative name memory as a generic procedure name. When you call memory, the compiler distinguishes which memory_Xd should be called based on the rank of the argument. The same for your freem functions.
This is how intrinsic functions such as sin have long worked -- you can call sin with a real arguments of various previsions, or with a complex argument, and the compiler figures out with actual sin function to call. In really old FORTRAN you had to use different names for the different sin functions. Now modern Fortran you can setup the same thing with your own routines.
Edit: adding a code example demonstrating the method & syntax:
module double_array_mod
implicit none
interface double_array
module procedure double_vector
module procedure double_array_2D
end interface double_array
private ! hides items not listed on public statement
public :: double_array
contains
subroutine double_vector (vector)
integer, dimension (:), intent (inout) :: vector
vector = 2 * vector
end subroutine double_vector
subroutine double_array_2D (array)
integer, dimension (:,:), intent (inout) :: array
array = 2 * array
end subroutine double_array_2D
end module double_array_mod
program demo_user_generic
use double_array_mod
implicit none
integer, dimension (2) :: A = [1, 2]
integer, dimension (2,2) :: B = reshape ( [11, 12, 13, 14], [2,2] )
integer :: i
write (*, '( / "vector before:", / 2(2X, I3) )' ) A
call double_array (A)
write (*, '( / "vector after:", / 2(2X, I3) )' ) A
write (*, '( / "2D array before:" )' )
do i=1, 2
write (*, '( 2(2X, I3) )' ) B (i, :)
end do
call double_array (B)
write (*, '( / "2D array after:" )' )
do i=1, 2
write (*, '( 2(2X, I3) )' ) B (i, :)
end do
stop
end program demo_user_generic
subroutine memory(array, length) has as it first dummy parameter 1-dimensional array (real(8), allocatable, intent(out), dimension(:) :: array).
Calling this subroutine from your main program with 3-dimensional array foo (real(8), allocatable, dimension(:,:,:) :: foo) is error obviously. And this is what compiler actually said.
If you really need such subroutines write one pair memory/freem subroutines for each array of different dimension - one subroutines pair for 1-dimensional array, another for 2-dimensional array, etc.
By the way, memory subroutines will be different in general because in order to allocate n-dimensional array you need to pass n extents to above-mentioned subroutine.