Iteratively Reading Integers with Leading Spaces

Hello Everyone,

I am attempting to read a .vtk type data file that was generated, partially, with the code below:

do k=1,npts3
do j=1,npts2
do i = 1,npts1
write(93,fmt=‘(256(g6.4))’) array1(i,j,k)
write(101,fmt=‘(256(g6.4))’) array1(i,j,k)
end do
end do
enddo

array1 is integer type

I am trying to read the .vtk file with this below:

do k = 1,tnpts3
do j = 1,tnpts2
do i = 1,tnpts1
read(232,*) array2(i,j,k)
enddo
enddo
enddo

array2 is integer type
This always produces a “Fortran runtime error: Bad integer for item1 in list input”
I have also tried with ‘(I6)’ as the fmt indicator to a similar error.
I have also tried with ‘(A5,I1)’ since I know the integer is a single digit and the width of this would be 6 (5 leading spaces) based on the original format.
It properly reads the data if i just write either format outside of the nested loops.
Anyone have insight on how this could be done iteratively? I would really like to access this data outside of a software that reads the file.
Thanks!

I just rewrote the file, removing spaces, which fixed my issue, but if anyone has insight into why this was an issue in the first place or if there are some less computationally-intense workarounds (the file is ~39M lines and I want to do this for 100s of files).

I suggest you look at the generated data. The format for your read statement is permissive, so it is likely that the format for your write statement is inappropriate and outputs “******” or similar for some elements.

If, as you say, array1 is an integer then you would be better with
write(93,fmt=‘((I6))’) array1(i,j,k)
to write a single integer at a time.

Try that. If it gets you closer we can tune the output to better suit your needs.

If that doesn’t work then you need to find the line(s) in the data file that fail. If you can’t find it in an editor, start by echoing each read to stdout by adding the following after the read
write(*,*) i, j, k, a(i,j,k)
or - added points for style - adding an err= argument to the read statement and handle the error(s).

Also, why is there a multiplier 256 in the write formats? You are only writing a single element at a time. It is valid, but it is misleading.

Here’s a section of the integer data:
"
0
0
0"
And some formerly double precision data:
"
2.94
38.58
5.25"

It seems to be just the combination of the leading spaces and the nested iteration (or perhaps just iteration in general) that prevents it from properly taking in the data. It is able to read the " 0" as an integer. When I just do “read(232,*) array2(i,j,k)” or similarly with “(I6)” as the format outside of the iteration, it works. Both within the iteration fail.

Honestly, I’m not sure why the 256 is there. I inherited this code from someone else and it accomplishes simulations that take up to 10 days, which is why I’m more inclined to just work with the data I have, rather than changing the output of the original code. I do agree with you that it could be improved.

Imagine the data looks like that, but with a set width of 6 including spaces.

OK. The simulation takes days. The data file is only 39M. The I/O time isn’t that important (yet). Lets find the problem by reading each line of data into a string, then read from the string and trap and report errors using IOSTAT https://www.intel.com/content/www/us/en/docs/fortran-compiler/developer-guide-reference/2023-1/i-o-status-specifier-iostat.html

This may be a start. At least it compiles. For simplicity (laziness) I am reading from stdin and reporting to stdout.

  implicit none
  character(len=16) :: buffer  ! to suit line length
  integer, parameter :: ni=2, nj=3, nk=5
  integer i, j, k, status
  integer a(ni,nj,nk)

  do k = 1, size(a,dim=3)
    do j = 1, size(a,dim=2)
      do i = 1, size(a,dim=1)
        read(*,fmt='(a)') buffer
        read(buffer,fmt='(I6)',iostat=status) a(i,j,k)
        if (status/=0) then ! catch I/O error
          write(*,*) 'Error ', i, j, k, status, buffer
          a(i,j,k) = 0 ! or an appropriate invalid value
        end if
      end do
    end do
  end do

  end

Edit: Fix typo. Don’t say the code compiles, then change a variable name “for clarity”

Edit2: The code above would not have addressed an error due to reading past the end of file. We should have check the status of the read into the buffer.

I’m not sure if this is helpful, but the iostat value varies (22039, 22077, 21868, etc.) each time I compile and run the script, but it is consistent for a single run and it throws up an error for every single data read.

Here’s my code:

module global
  implicit none

  integer :: i,j,k, tnpts1,tnpts2,tnpts3, nsysmx
  integer, allocatable :: grain(:,:,:), slip(:,:,:)
  double precision, allocatable :: rss(:,:,:,:) 
  character(len=50) :: prosa

endmodule global

!-----------------------------------------------------------------------------------------------------------------------

program vtkanalyze
  use global
  implicit none

  ! determining max slip systems
  open(unit = 121, file = 'SlipBand_good.f90', status = 'old')
  do i = 1,77
    read(121,*)
  enddo

  read(121,'(A55,I2)') prosa, nsysmx
  close(unit = 121)

  call read_vtk(93,210)



endprogram vtkanalyze

!-----------------------------------------------------------------------------------------------------------------------

subroutine read_vtk(out_type,step)
  use global
  implicit none

  integer :: out_type, step, status
  character(len = 50) :: vtk_filename, step_c

  write(step_c,*) step
  step_c =adjustl(step_c)

  ! setting proper filename and step
  if (out_type == 93) write(vtk_filename,*) 'SlipBand_rss1' // trim(step_c) // '.vtk'

  ! reading commmon vtk elements (header, grain, slip)
  open(unit = 232, file = adjustl(vtk_filename), status = 'old')
  do i = 1,4
    read(232,*)
  enddo

  read(232,*) prosa, tnpts1,tnpts2,tnpts3

  do i = 6,10
    read(232,*)
  enddo

    ! allocating arrays
  allocate(grain(tnpts1,tnpts2,tnpts3) , slip(tnpts1,tnpts2,tnpts3))

  if (out_type == 93) allocate(rss(nsysmx,tnpts1,tnpts2,tnpts3))

  do k = 1,tnpts1
    do j = 1,tnpts2
      do i = 1,tnpts3
        read(232,*) grain(i,j,k)
        if (status /= 0) then
          write(*,*) 'Error', i,j,k, status
        endif
      enddo
    enddo
  enddo

  write(*,*) grain(tnpts1,tnpts2,tnpts3)

  close(232)
  deallocate(grain,slip)
  if (out_type == 93) deallocate(rss)

endsubroutine read_vtk

There is an error with line

It should be
read(232,*,iostat=status) grain(i,j,k)
As you have it, status is unassigned.

This isn’t quite what I had in mind, but it may be sufficient. It you need more clues then reading each line into a character variable and then read the data from the buffer. Then you can report the actual data that fails.

1 Like

Oh you are amazing! This is very good to know for future troubleshooting. Turns out, for some reason, the dimensions (tnpts1,tnpts2,tnpts3) within the file are not correct (they should be -1 what they are), so that was pushing me into a region where I was reading a character as an integer.

Got it working and thank you so much!

Excellent.

You can defend against end of file errors using a couple of options to READ:

  1. iostat=status option, then test for status < 0 (some sort of end of file) which I prefer
  2. end= which diverts to a label, then abort with a message.

Work out how long we spent tracking down this issue next time you are writing or modifying I/O routines. This type of bug has bitten me many times, but I have also been saved repeatedly by a few lines of defensive programming. Unfortunately Fortran exception handling is … primitive, but that isn’t an excuse to do nothing.

Edit: Reword slightly.

1 Like