increase array in module - module

I am trying to write a small module/class in Fortran. The idea is very basic:
Create and initialize the object with a dedicated constructor
Add a new element inside of it
I already write Fortran but only subroutine and I will try to use oriented object principle. Currently I have two errors:
the constructor I built does not work (seems to not accept my input arguments)...
the add_bb procedure is not accepted.
MNWE:
module test_mod
implicit none
type :: bb
real :: item
real,allocatable :: vect(:)
end type bb
interface bb
procedure :: new_bb!,add_bb
end interface bb
contains
type(bb) function new_bb(val,nbv)
real, intent(in) :: val
integer, intent(in) :: nbv
integer :: ii
new_bb%item=val
allocate(new_bb%vect(nbv))
print *,nbv
do ii=1,nbv
new_bb%vect(ii)=val
print *,ii
enddo
print *,new_bb%vect
end function new_bb
type(bb) function add_bb(it)
real,intent(in) :: it
integer :: sp
real,allocatable :: tmp(:)
sp=size(add_bb%vect)+1
allocate(tmp(sp))
tmp(1:sp-1) = add_bb%vect(1:sp-1)
call move_alloc(tmp, add_bb%vect)
add_bb%vect(sp)=it
end function add_bb
end module test_mod
program test
use test_mod
implicit none
type(bb) :: cc
cc=bb(10,20)
call cc%add_bb(10)
print *,cc%item
print *,cc%vect
!
end program test

I tried to fix the bugs in your code, but as I worked on it more, I discovered more and more fundamental flaws in your code. Obviously, that implies that you are likely not well familiar with OOP, in particular, in Fortran. Therefore, I recommend you to grab a book, for example, "Modern Fortran Explained" by Metcalf et al. and learn this topic. Meanwhile, here is a revised version of your code that at least works without syntax error:
module test_mod
implicit none
type :: bb_type
real :: item
real, allocatable :: vect(:)
contains
procedure, pass :: add_bb
end type bb_type
interface bb_type
procedure :: construct_bb
end interface bb_type
contains
function construct_bb(val,nbv) result (bb)
real, intent(in) :: val
integer, intent(in) :: nbv
type(bb_type) :: bb
integer :: ii
bb%item=val
allocate(bb%vect(nbv))
print *,nbv
do ii=1,nbv
bb%vect(ii)=val
print *,ii
enddo
print *,bb%vect
end function construct_bb
subroutine add_bb(self,it)
class(bb_type), intent(inout) :: self
real,intent(in) :: it
integer :: sp
real, allocatable :: tmp(:)
sp=size(self%vect)+1
allocate(tmp(sp))
!tmp(1:sp-1) = self%vect(1:sp-1)
!call move_alloc(tmp, self%vect)
!self%vect(sp)=it
end subroutine add_bb
end module test_mod
program test
use test_mod
implicit none
type(bb_type) :: cc, dd
cc=bb_type(10,[20])
call dd%add_bb(10.0)
print *,cc%item
print *,cc%vect
!
end program test

Related

Read(u=UNIT,*) reads just half the file in fortran

so I'm trying to make a Fortran subroutine that reads a matrix (or a tensor I guess) of size 125x125x125 from a file that I create in another subroutine, but for some reason it doesn't work. I have successfully done it using almost the same program but for a different size of matrix (70x200x70) and for some reason when I change the size of the arrays and a couple of other things to fit the new data, the program reads just half the data file and throws an error that says At line 133 of file Busqueda.f90 (unit = 2, file = 'test2.txt') Fortran runtime error: End of file. So my working code is:
Subroutine DataSorting(datasort,indexsort,datosden,datostemp)
use globals
implicit None
real*8, dimension(70,200,70) :: datosdentemp
real*8, dimension(70,200,70), intent(out) :: datostemp, datosden
real*8, dimension(980000), intent(out) :: datasort
integer,dimension(3,980000),intent(out) :: indexsort
integer, dimension(3) :: Result
integer :: i
rewind(2)
read(2,*) datosden
datosdentemp = datosden
rewind(3)
read(3,*) datostemp
do i = 1, 10
Result = MAXLOC(datosdentemp)
datasort(i) = datosden(Result(1),Result(2),Result(3))
indexsort(1,i) = Result(1)
indexsort(2,i) = Result(2)
indexsort(3,i) = Result(3)
datosdentemp(Result(1),Result(2),Result(3)) = 0
end do
End Subroutine DataSorting
And the code that dont work is:
Subroutine DataSorting(datasort,indexsort,datosden,datostemp)
use globals
implicit None
real*8, dimension(125,125,125) :: datosdentemp
real*8, dimension(125,125,125), intent(out) :: datostemp, datosden
real*8, dimension(1953125), intent(out) :: datasort
integer,dimension(3,1953125),intent(out) :: indexsort
integer, dimension(3) :: Result
integer :: i
rewind(2)
read(2,*) datosden
datosdentemp = datosden
rewind(3)
read(3,*) datostemp
do i = 1, 10
Result = MAXLOC(datosdentemp)
datasort(i) = datosden(Result(1),Result(2),Result(3))
indexsort(1,i) = Result(1)
indexsort(2,i) = Result(2)
indexsort(3,i) = Result(3)
datosdentemp(Result(1),Result(2),Result(3)) = 0
end do
End Subroutine DataSorting
The files from where I'm reading the data just have the data arranged in 125 columns and 15625 rows in the case of the non-working program, and in 70 columns and 14000 rows for the working one, and the files are just that, I mean they are really structured that way in both cases. I was using scratch files for the files 2 and 3, and change them to '.txt' files to see if there was a problem with the input file, but no. Then I build a new file and did the reading with a do-loop, to see if that was the problem, but no, but at least that helped me to realize that the code was reading exactly half of 15625, but i don't know why this is happening, I'm new to fortran, my thesis advisor told me to do this code in Fortran 'cause the amount of data that have to handle will make my Julia code way to slow, so honestly any help will be much appreciated.

Fortran READ into derived type not working with gfortran (Fortran runtime error: End of file)

I have a derived type in Fortran and I need to read values from a text file into that type. My problem is that my code is working fine with the Intel Fortran compiler as well as the NAG Fortran compiler, but GFortran exits with an error. The minimal working example is below.
Module my_mod
Type T
Real :: a
End Type T
Interface Read (Formatted)
Module Procedure read_T
End Interface
Contains
Subroutine read_T(var, unit, iotype, v_list, iostat, iomsg)
Class (T), Intent (Inout) :: var
Integer, Intent (In) :: unit
Character (*), Intent (In) :: iotype
Integer, Intent (In) :: v_list(:)
Integer, Intent (Out) :: iostat
Character (*), Intent (Inout) :: iomsg
Read (unit, *, iostat=iostat, iomsg=iomsg) var%a
End Subroutine
End Module my_mod
Program main
Use my_mod
Implicit None
Type(T) :: x
Type(T) :: y
Open(unit=20, file='data.txt', action='read')
Read(20, *) x ! Here GFortran fails because it somehow reaches EOF
Write(*, *) x
Read(20, *) y
Write(*, *) y
End Program main
with the data.txt file:
1.0
2.0
With GFortran I get the error
At line 30 of file test.f90 (unit = 20, file = 'data.txt')
Fortran runtime error: End of file
Error termination. Backtrace:
#0 0x7f27a76fef2f in finalize_transfer
at ../.././libgfortran/io/transfer.c:4175
#1 0x400aca in ???
#2 0x400b86 in ???
#3 0x7f27a69a8504 in ???
#4 0x4007e8 in ???
#5 0xffffffffffffffff in ???
One thing that works is to replace the Read statements as follows
Read(20, fmt='(DT)', advance='no') x ! Works with all compilers :)
Write(*, *) x
Read(20, fmt='(DT)', advance='no') y ! Works with all compilers :)
Write(*, *) y
So my question .. is it possible to get the same behaviour in GFortran without fmt='(DT)', advance='no'?
And who has the correct behavior? GFortran or Intel Fortran and NAG Fortran?
Thanks for any help,
Simon

Fortran Mismatch in components of derived type

I am currently developing a software in Fortran. It has been already a couple of times I've encountered the error below. Previously I just managed to undo those changes and rewrite the code again as I was not able to understand the issue.
Obviously, the issue came back again. So I am wondering why it happens. What am I doing in the code thats triggering it.
The compiler used is gfortran-9. I also tried to compile in gfortran-10 (ubuntu 20.04) with the hope it was a compiler bug already solved :/. The error shown is the same but with different elements.
This part of the software consists in a library (modules starting with SIO_...) which is using another one (modules starting with SHR_...).
Project structure:
soulio (library folder)
src
tests/unit
soulshared (external library)
The file triggering the error at compilation times is soulio/tests/unit/ncSpatialFile.F90. It has the following imports:
module ncSpatialFile_test
use netcdf
use SHR_file_mod, only: removeIfExists
use SHR_testSuite_mod, only: testSuite
use SHR_datetime_mod, only: datetime, timedelta, clock
use SIO_ncSpatialFile_mod, only: ncSpatialFile_abs <- gfortran-9 complains about this line
...
Imports from soulio/src/ncSpatialFile_abs.F90
module SIO_ncSpatialFile_abs
! use netcdf
use SHR_datetime_mod, only: clock, datetime, timedelta
use SHR_strings_mod, only: string
use SHR_precision_mod, only: sp
use SHR_array_mod, only: initArrayRange
use SHR_error_mod, only: raiseError
use SIO_ncfile_mod, only: ncfile
use SIO_ncDimensions_mod, only: ncDimensions
use SIO_ncVariables_mod, only: ncVariables
use SIO_grid_mod, only: grid
use SIO_parallel_mod, only: mpiContext_type
use SIO_ncSlimSpatialDims_mod, only: ncSlimSpatialDims
use SIO_ncFullSpatialDims_mod, only: ncFullSpatialDims
use SIO_ncSpatialDims_abs, only: ncSpatialDims
use SIO_ncParams_mod, only: NC_TIME_DIM_NAME, NC_SPATIAL_DIM_NAME!, SIO_NC_GLOBAL_ATTR
use SIO_ncOtherDim_mod, only: ncOtherDim
use SIO_ncTimeDim_mod, only: ncTimeDim
use SIO_ncVar_mod, only: ncVar
use SIO_ncDim_mod, only: ncDim, ncDimHolder
use SIO_ncTime_mod, only: ncTime
use SIO_ncDimensionsRequest_mod, only: ncDimensionsRequest
use SIO_ncVariableBounds_mod, only: ncVariableBounds
use SIO_ncAttributes_mod, only: ncAttributes
... (too many imports?)
type, abstract :: ncSpatialFile_abs
! netcdf file interface
class(ncfile), allocatable :: ncfile
! time series
class(clock), allocatable :: ncClock
soulio/soulshared/src/datetime_mod.F90
module SHR_datetime_mod
use iso_fortran_env, only: real32, real64
use iso_c_binding, only: c_char, c_int, c_null_char
use SHR_error_mod, only: raiseError
implicit none
private
public :: datetime, timedelta, clock, calendar
...
Error in gfortran-10:
soulio/tests/unit/ncSpatialFile_test.F90:20:7:
20 | use SIO_ncSpatialFile_mod, only: ncSpatialFile_abs
| 1
Fatal Error: Mismatch in components of derived type ‘__vtype_shr_datetime_mod_Calendar’ from ‘shr_datetime_mod’ at (1): expecting ‘calendar_assign’, but got ‘getdaysinmonth’
compilation terminated.
make[2]: *** [tests/unit/CMakeFiles/soulio_test.dir/build.make:232: tests/unit/CMakeFiles/soulio_test.dir/ncSpatialFile_test.F90.o] Error 1
make[1]: *** [CMakeFiles/Makefile2:260: tests/unit/CMakeFiles/soulio_test.dir/all] Error 2
Error in gfortran-9:
soulio/tests/unit/ncSpatialFile_test.F90:20:6:
20 | use SIO_ncSpatialFile_mod, only: ncSpatialFile_abs
| 1
Fatal Error: Mismatch in components of derived type ‘__vtype_shr_datetime_mod_Clock’ from ‘shr_datetime_mod’ at (1): expecting ‘currenttickintervals’, but got ‘clock_assign’
compilation terminated.
make[2]: *** [tests/unit/CMakeFiles/soulio_test.dir/build.make:232: tests/unit/CMakeFiles/soulio_test.dir/ncSpatialFile_test.F90.o] Error 1
The error came up after modifing ncSpatialFile_test but not datetime.
I find the error confusing. Any ideas about what the compiler is trying to say? Any other advice in how to dig further?
Edit:
Datetime_mod file is taken from https://github.com/wavebitscientific/datetime-fortran. There are a few modifications but its the same structure.
clock declaration:
type :: clock
type(datetime) :: startTime
type(datetime) :: stopTime
type(datetime) :: currentTime
type(datetime) :: prevTime !> currentTime - 1 timestep
type(datetime) :: nextTime !> currentTime + 1 timestep
type(timedelta) :: tickInterval
logical :: alarm = .false.
logical :: started = .false.
logical :: stopped = .false.
logical :: nullified = .false. !< it is considered not defined
contains
procedure :: getStartTime
procedure :: getStopTime
procedure :: reset
procedure :: tick
procedure :: toString => toString_clock
procedure :: isStopped
procedure :: isNull
! true when the condition is satisfied for the current time step
procedure :: isBeginYear, isEndYear
procedure :: isBeginMonth, isEndMonth
procedure :: isBeginDay, isEndDay
procedure :: isBeginClock, isEndClock
procedure :: getTickIntervals
procedure :: totalTickIntervals
procedure :: currentTickIntervals
!
procedure, private :: clock_assign
procedure, private, pass(from) :: clock_assign_tickInterval
generic :: assignment(=) => clock_assign, clock_assign_tickInterval
procedure :: findEquivalentCurrentTime
procedure :: getCalendarType => getCalendarType_clock
procedure, private :: equiv_clock
generic :: operator(==) => equiv_clock
procedure :: isInAbsoluteBounds
end type clock
As suggested by #veryreverie in the comments section, it was a problem of cache.
The cmake project places its mod files into tree project/lib. Those files are not removed when I clean the build folder. Because of this, some inconsistencies were happening.

using Fortran Module from external files

I would like to call subroutines contained in a module. the module is saved in a separate file with my_mod.f95 filename.
module calc_mean
! this module contains two subroutines
implicit none
public :: calc_sum
public :: mean
contains
subroutine calc_sum(x,n,s)
! this subroutine calculates sum of elements of a vector
! x the vector
! n size of the vector
! s sum of elements of x
integer, intent(in):: n
real, intent(in):: x(n)
integer :: i
real, intent(out):: s
s=0
do i=1,n
s=s+x(i)
end do
end subroutine calc_sum
!
!
!
subroutine mean(x,n,xav)
! this subroutine calculates the mean of a vector
! x the vector
! n size of the vector
! xav mean of x
integer, intent(in):: n
real, intent(in):: x(n)
real, intent(out):: xav
real :: s
!
!
call calc_sum(x,n,s)
xav=s/n
end subroutine mean
end module calc_mean
I have the main program saved in a different file with 'my_program.f95'
program find_mean
! this program calculates mean of a vector
use calc_mean
implicit none
! read the vector from a file
integer, parameter ::n=200
integer :: un, ierror
character (len=25):: filename
real :: x(n), xav
un=30
filename='randn.txt'
!
OPEN (UNIT=un, FILE=filename, STATUS='OLD', ACTION='READ', IOSTAT=ierror)
read(un,*) x !
!
call mean(x,n,xav)
write (*,100) xav
100 format ('mean of x is', f15.8)
end program find_mean
when I compile the main program with geany, I got the following error message. Please, help me!
**
/usr/bin/ld: /tmp/cctnlPMO.o: in function MAIN__': my_program.f08:(.text+0x1e1): undefined reference to __calc_mean_MOD_mean'
collect2: error: ld returned 1 exit status
**
When I save both the main program and the module to the same file and run it, everything is fine.

Binary Read/Write of Data Types with Allocatable Components in Fortran90+

What is the best way to save a binary snapshot of the variable save which is made out of sample data type below?
program save_it
type core
integer, dimension(8) :: indx
end type core
type sample
integer :: a
real*8, dimension(:), allocatable :: b
type(core), dimension(:), allocatable :: c
end type sample
! here it comes
type(sample) :: save
! here we allocate all componenets of variable "save"
!.
!.
! Now, how to write/read variable "save" to/from external file?
end program save_it
There is pretty straight binary input/output streaming in C++ but I don't know how to do it in Fortran 90+.
If by Fortran90+ you mean you are happy with Fortran 2003, then there is the option of user-defined derived type IO. This allows you to wrap the extra bookkeeping required for the allocation in the write statement. I'll put example code at the bottom.
If you don't want to use this feature, which is possibly because you don't have a compiler which supports it (I've tested with ifort 14), then you can mimic the bookkeeping easily enough.
The crucial part is just sending out and reading back in the sizes and allocating the variables before the read.
The code:
module types
type core
integer, dimension(8) :: indx
end type core
type sample
integer :: a
real*8, dimension(:), allocatable :: b
type(core), dimension(:), allocatable :: c
contains
procedure write_sample
procedure read_sample
generic :: write(unformatted) => write_sample
generic :: read(unformatted) => read_sample
end type sample
contains
! Unformatted writing for the sample derived type
subroutine write_sample(dtv, unit, iostat, iomsg)
class(sample), intent(in) :: dtv
integer, intent(in) :: unit
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
integer i
! Write a record giving sizes for the allocation
write(unit, iostat=iostat, iomsg=iomsg) SIZE(dtv%b), SIZE(dtv%c)
write(unit, iostat=iostat, iomsg=iomsg) dtv%a, dtv%b, &
(dtv%c(i)%indx, i=1,SIZE(dtv%c))
end subroutine write_sample
! Unformatted reading for the sample derived type
subroutine read_sample(dtv, unit, iostat, iomsg)
class(sample), intent(inout) :: dtv
integer, intent(in) :: unit
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
integer i
integer sizeb, sizec
! We first have a record telling us the sizes of components
read(unit, iostat=iostat, iomsg=iomsg) sizeb, sizec
! So we do the allocation
allocate(dtv%b(sizeb), dtv%c(sizec))
! And then finally the reading.
read(unit, iostat=iostat, iomsg=iomsg) dtv%a, dtv%b, &
(dtv%c(i)%indx, i=1,SIZE(dtv%c))
end subroutine read_sample
end module types
program save_it
use types
implicit none
integer i, unit_in, unit_out
! here it comes
type(sample) :: save
type(sample) :: save_test
! Define some values - using ifort don't forget to set the compile flag
save%a = 14
save%b = [(i*1., i=1, 10)]
save%c = [core([(i, i=1,8)]), core([(i, i=11, 18)])]
! Write out the derived type
open(newunit=unit_out, file='serial', form='unformatted', &
status='replace', action='write')
write(unit_out) save
close(unit_out)
! Read in the derived type to a new one
open(newunit=unit_in, file='serial', form='unformatted', &
status='old', action='read')
read(unit_in) save_test
close(unit_in)
! Test, if we want to be certain
end program save_it
There's certainly a lot of work to be done on making it robust.