How can I set an array to the contents of a file?

I have a .txt file and I want to set an array to the contents of it. The file is full of integers, and the size of it is about 1000 elements (when translated into the array). The elements are split by a comma, nothing else. How can I set an array to the file’s contents if the amount of elements was unknown. I am using fortran 90.

https://fortranwiki.org/fortran/show/getvals

shows how to do that specific task (file with unknown number of integers) near the bottom. If the file has the same number of values on each line it gets easier; there are also several modules that work with fpm(1) that can do this and a lot more complicated parsing, even allowing expressions. Showing the file would be helpful, as if it follows certain formatting rules and you know some upper bounds that are reasonable (such as the a fore-mentioned “around 1000 values)” this can just be a simple READ with some checks on the status values returned.

When you say you are using “f90”, does that mean you are not allowed to use anything past the Fortran 90 standard (which that example) does? Or do you just mean “not using FORTRAN”?

Also, with the caveat that there have been arguments about whether this is standard or not, it
can be as simple as

program testit
integer :: lun
integer,allocatable :: ivals(:)
   if(allocated(ivals))deallocate(ivals)
   allocate(ivals(0))
   open(file='sample.txt',newunit=lun)
   do
      read(lun,'(i256)',advance='no',iostat=ios)i
      if(is_iostat_eor(ios).or.ios.eq.0)then
         ivals=[ivals,i]
      else
         exit
      endif
   enddo
   write(*,*)'size=',size(ivals),'ivals=',ivals
end program testit

which works with gfortran, ifort, and nvfortran.

Depends on what compiler you are using and whether this is a quick throw-away you just need to get done.

Thank you, is there anywhere to read up on the parameters of read and write functions. I couldn’t find anything.

The file looks like this

2,3,5,1,5,6,12,1002,2,31000,3,10293, 

and this continues on for 1000 numbers. Your other solution worked, but if it isn’t efficient what is a better way of doing it?

Those are more than efficient enough for a small file. I would not worry about efficiency until you were looking at multiple megabytes. There are long lists of fortran resources on the Fortran Wiki, as well as at fortran-lang.org; as well as the vendor documentation. IBM, NVidia, Intel, Cray, NAG, … all have Fortran resources. I can’t think of one that specifically addresses I/O any better than those, but perhaps someone else has a favorite. There is everything from standard formatted READ and WRITE to NAMELIST and binary files, direct access, asynchronous, special formats like HDF5, JSON, TOML, and so on; but I think for just general READ and WRITE descriptions the IBM documentation is probably best; and there is always the Fortran standard but it is describing the standard, not really providing much user-level information.

The way I solved this for large files is to add the data to the end of a linked-list then at the end convert the list to an array. I found that constant reallocation was a severe performance penalty although of course doing it this way means that at some point there are effectively 2n of data rather than just n.

Fortran reallocation is really ineffective if done one-by-one (see this topic) because it allocates new memory, copies the data and deallocates the old chunk. So it pretty much uses 2n as @simong said even w/o any linked lists.

It can be, however, made much, much more effectively by reallocating the memory in bigger chunks. See the snippet below.

code
program testit
  implicit none
  integer, parameter :: chunk=1024
  integer :: i, lun, ios, cursize, npoints=0, temp(chunk)=0
  integer,allocatable :: ivals(:)
  if(allocated(ivals))deallocate(ivals)
  allocate(ivals(chunk))
  cursize = chunk
  open(file='sample.txt',newunit=lun)
  do
    read(lun,'(i256)',advance='no',iostat=ios) i
    if(is_iostat_eor(ios).or.ios.eq.0)then
      npoints = npoints+1
      if (npoints > cursize) then
        ivals=[ivals,temp]
        cursize = cursize + chunk
      endif
      ivals(npoints) = i
    else
      exit
    endif
  enddo
  if (npoints < cursize) then
    ivals = [ivals(1:npoints)]
  endif
  write(*,*)'size=',size(ivals)
end program testit

The difference is huge. I tried the @urbanjost version on my 6 years old macbook pro (2,8 GHz Quad-Core Intel Core i7) and a sample file containing just below 200,000 random integers (1.1 MB). It takes 14 seconds to read them. The above code takes 0.1 sec.

2 Likes