Fortran array input

↘锁芯ラ 提交于 2021-02-11 05:11:34

问题


I haven't done any Fortran programming for year and it seems I'm rather rusty now. So, I won't provide you with all my failed attempts but will humbly ask you to help me with the following. I've got the following "input" file

1 5 e 4  
A b & 1  
c Z ; b  
y } " N  
t r ' +  

It can have more columns and/or rows. I would now like to assign each of these ASCII characters to arrays x(i,j) so that I can process them further after ICHAR conversions. In this example i=1,4, j=1,5, but it can be any No depending on the input file. The simplest example

PROGRAM Example
integer :: i, j
CHARACTER, ALLOCATABLE, DIMENSION(:,:) :: A
READ *, A
ALLOCATE (A(i,j))
PRINT *, A
END PROGRAM Example

compiles (Example.f95) but

cat input | ./Example.f95

does not give any output. I would greatly appreciate an advice on how to import the afore-mentioned strings into the program as x(i,j) terms of an array.


回答1:


In Fortran, it's always best to know in advance how big your arrays need to be. I understand that in your case you can't know.

Assuming that your input is at least formatted correctly (i.e. the columns match up and have only a single space in between them), I've created a code that should in theory be able to read them in an arbitrary shape. (Not quite arbitrary, it assumes that there are fewer than 511 columns.)

It uses two ways:

  • It simply reads the first line in at once (1024 characters, hence the 511 limit on columns) then calculates from the length the number of columns
  • It then allocates an array with a guessed number of rows, and once it notices that the guess was too small, it creates a new allocation with double the number of rows. It then uses the move_alloc command to swap the allocations.

To find when it should end reading the values, it simply checks whether the read returns the IOSTAT_END error code.

Here's the code:

program read_input

    use iso_fortran_env, only: IOSTAT_END
    implicit none
    character, dimension(:,:), allocatable :: A, A_tmp
    character(len=1024) :: line  ! Assumes that there are never more than 500 or so columns
    integer :: i, ncol, nrow, nrow_guess
    integer :: ios
    character :: iom

    ! First, read the first line, to see how many columns there are
    read(*, '(A)', iostat=ios, iomsg=iom) line
    call iocheck('read first line', ios, iom)

    ncol = (len_trim(line) + 1) / 2

    ! Let's first allocate memory for two rows, we can make it more later.
    nrow_guess = 2
    allocate(A(ncol, nrow_guess))

    ! Instead of standard input, we're reading from the line we read before.
    read(line, '(*(A1,X))', iostat=ios, iomsg=iom) A(:, 1)
    call iocheck('read first line into vals', ios, iom)

    ! Now loop over all the rows
    nrow = 1
    read_loop: do

        if (nrow >= nrow_guess) then    ! We have guessed too small.
                                        ! This is a bit convoluted, but the best
                                        ! way to increase the array shape.
            nrow_guess = nrow_guess * 2
            allocate(A_tmp(ncol, nrow_guess))
            A_tmp(:, 1:nrow_guess/2) = A(:,:)
            call move_alloc(A_tmp, A)
        end if

        read(*, '(*(A1,X))', iostat = ios, iomsg=iom) A(:, nrow+1)
        if (ios == IOSTAT_END) exit read_loop   ! We're done reading.
        call iocheck('read line into vals', ios, iom)
        nrow = nrow + 1

    end do read_loop

    ! The last guess was probably too large,
    ! let's move it to an array of the correct size.
    if (nrow < nrow_guess) then
        allocate(A_tmp(ncol, nrow))
        A_tmp(:,:) = A(:, 1:nrow)
        call move_alloc(A_tmp, A)
    end if

    ! To show we have all values, print them out.
    do i = 1, nrow
        print '(*(X,A))', A(:, i)
    end do

contains

    ! This is a subroutine to check for IO Errors
    subroutine iocheck(op, ios, iom)
        character(len=*), intent(in) :: op, iom
        integer, intent(in) :: ios
        if (ios == 0) return
        print *, "IO ERROR"
        print *, "Operation: ", op
        print *, "Message: ", iom
    end subroutine iocheck
end program read_input

Edited to add

I had trouble with the special characters in your example input file, otherwise I'd just have made a read(*, *) A(:, nrow) -- but that messed the special characters up. That's why I chose the explicit (*(A1, X)) format. Of course that messes up when your characters don't start at the first position in the line.




回答2:


You need to read the first line and determine how characters there in the line. Then read the entire file to determine the number of lines. Allocate the 2D array to hold characters. Then read the file and parse each line into the 2D array. There are more elegant ways of doing this, but here you go

  program foo

  implicit none

  character(len=:), allocatable :: s
  character, allocatable :: a(:,:)
  integer fd, i, j, n, nr, nc
  !
  ! Open file for reading
  !
  open(newunit=fd, file='tmp.dat', status='old', err=9)
  !
  ! Determine number of characters in a row.  Assumes all rows
  ! are of the same length.
  !
  n = 128
1 if (allocated(s)) then
     deallocate(s)
     n = 2 * n
  end if
  allocate(character(len=n) :: s)
  read(fd,'(A)') s
  if (len_trim(s) == 128) goto 1
  s = adjustl(s)
  n = len_trim(s)
  deallocate(s)
  !
  ! Allocate a string of the correct length.
  ! 
  allocate(character(len=n) :: s)
  !
  ! Count the number of rows
  !
  rewind(fd)
  nr = 0
  do
     read(fd,*,end=2)
     nr = nr + 1
  end do
  !
  ! Read file and store individual characters in a(:,:)
  !
2 rewind(fd)
  nc = n / 2 + 1
  allocate(a(nr,nc))
  do i = 1, nr
     read(fd,'(A)') s
     do j = 1, nc
        a(i,j) = s(2*j-1:2*j-1)
     end do
  end do
  close(fd)
  write(s,'(I0)') nc
  s = '('  // trim(s) // '(A,1X))'
  do i = 1, nr
     write(*,s) a(i,:)
  end do
  stop
9 write(*,'(A)') 'Error: cannot open tmp.dat'
  end program foo

Apparently, GOTO is verbotem, here. Here's an elegant solution.

  program foo

  implicit none

  character, allocatable :: s(:), a(:,:)
  integer fd, i, j, n, nr, nc

  ! Open file for reading
  open(newunit=fd, file='tmp.dat', status='old', access='stream', err=9)

  inquire(fd, size = n) ! Determine file size.
  allocate(s(n))        ! Allocate space
  read(fd) s            ! Read the entire file

  close(fd)

  nr = count(ichar(s) == 10)             ! Number of rows
  nc = (count(ichar(s) /= 32) - nr) / nr ! Number of columns 

  a = reshape(pack(s, ichar(s) /= 32 .and. ichar(s) /= 10), [nc,nr])
  a = transpose(a)

  do i = 1, nr
     do j = 1, nc
        write(*,'(A,1X)',advance='no') a(i,j)
     end do
     write(*,*)
  end do
  stop
9 write(*,'(A)') 'Error: cannot open tmp.dat'
  end program foo


来源:https://stackoverflow.com/questions/62163213/fortran-array-input

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!