How to iterate over character strings with numbers, words and blancks in Fortran90?

随声附和 提交于 2021-02-17 06:00:07

问题


Description of the file: The STL file consists of

solid <solid_name>
   facet normal n1 n2 n3 (the triangles normal vector)
      outerloop         (one of the markers I want to read)
      v1          x1 y1 z1
      v2          x2 y2 z2       (three vertex of the triangle/facet)    
      v3          x3 y3 z3
      endloop
   end facet
endsolid

The idea is to read the information in each line. First, I'm trying !to read the first line:solid

program Leitura
        !use, intrinsic :: trim
        implicit none
        integer ilo, ierror, ihi, ios, iunit, num_text, len_blanck, 
        len_word,        
        len_text, i
        character(len=80) :: filename
        character(len=:), dimension(:), allocatable :: text, lenc
        character(len=:), dimension(:), allocatable :: word
        character(len=:), dimension(:), allocatable :: blanck
        len_blanck=1
        len_word=11
        len_text=256
        allocate(character(len=len_blanck) :: blanck(1))
        allocate(character(len=len_word) :: word(1))
        allocate(character(len=len_text) :: text(1))
        allocate(character(len=len_text) :: lenc(1))
        blanck= " "
        ierror = 0
        iunit=10
        filename="Esfera.stl"

        !Opening the STL file
        open(unit=iunit, file=filename, status='old', access='stream',    form='unformatted')


        !  If NUM_TEXT is zero, then initialize TEXT.
        !
        if ( num_text <= 0 ) then
            num_text = 0
            text = blanck
        end if
        !
        !  If TEXT is blank, try to read a new line from the file.
        if ( ios /= 0 ) then
            ierror = 1
            word = blanck
            text = blanck
            return
        end if

        num_text = num_text + 1
        !Reading the first line of information- should be solid name, aka,             !       !the name of the solid
        read ( iunit, '(a)', iostat = ios ) text
        do i=1,len(text)
            if ( text(i)==blanck ) then
                word = blanck
                return
            end if
        end do

       !
       !  Extract the next word from TEXT into WORD and return.
       !
        lenc = len_trim ( text )
       !
       !  Find ILO, the index of the first nonblank in TEXT.
       !
       ilo = 1

       do while ( text(ilo:ilo) == blanck )
           ilo = ilo + 1
       end do
      !
      !  Find IHI, the index of the last consecutive nonblank after the one
              ! at ILO.
      !
      ihi = ilo

      do while ( ihi+1 <= lenc )
          if ( text(ihi+1:ihi+1) == blanck ) then
              exit
          end if
          ihi = ihi + 1
      end do
    !
    !  Set WORD.
    !
      word = text(ilo:ihi)
    !
    !  Slide TEXT to the left.
    !
      if ( ihi+1 <= lenc ) then
          text = text(ihi+1:)
      else
          text = ' '
      end if

      return
end program Leitura

回答1:


I don't have the time to write a complete answer but the following fragments should get you started towards a working code.

First off, I think you're going in the wrong direction by trying to parse the STL file as you read it. The STL file format is fairly clean with little, in practice, variation between one example and the next. It's not like some file formats with a thousand different types of line and little clue what's coming next. We'll start by assuming that the input file is well structured. And we'll start with a code that has almost no error processing at all because:

  • almost none should be needed;
  • including it would serve to bury the important parts of this answer into lots of ifs and elses; and
  • unless you are planning to write code to repair broken STL files, the only error processing necessary is to report failure to read the solid from the file.

We will start, of course, with some data structures, specifically one for the solid and one for the facets. Like this:

  TYPE facet
     REAL, DIMENSION(3) :: normal
     REAL, DIMENSION(3,3) :: vertices
  END TYPE facet

  TYPE solid
     CHARACTER(len=64) :: label
     TYPE(facet), DIMENSION(:), ALLOCATABLE :: facets
  END TYPE solid

  TYPE(solid) :: model

I'll wrap the code to read the file into a function, and use it like this:

  model = read_solid('filename.stl')

Now, to the meat of it, the function definition

FUNCTION read_solid(fn) RESULT(mdl)
  ! Read solid from file fn
  CHARACTER(*), INTENT(in) :: fn
  TYPE(solid) :: mdl
  ! Local variables
  INTEGER :: nu
  INTEGER :: ix, jx, num_facets
  CHARACTER(len=132) :: line
  CHARACTER(len=8) :: word1, word2
  ! Executables
  num_facets = 0
  OPEN(newunit=nu, file=fn, status='old')

Read the file, count the number of facets, allocate space for them, then rewind

ios = 0
! Now find out how many facets there are in the file
DO WHILE (ios==0)
   READ(nu,'(a132)',iostat=ios) line
   ! Count the facets in the file
   line = ADJUSTL(line)
   IF (line(1:5)=='facet') num_facets = num_facets+1
END DO

ALLOCATE(mdl%facets(num_facets))
REWIND(nu)

Read the file again from the beginning, get the solid on this pass:

ios = 0
! Ignore any leading blank lines
sol: DO WHILE (ios==0)
   READ(nu,'(a132)',iostat=ios) line
   ! If the line is empty, get the next one
   IF (LEN_TRIM(line)==0) CYCLE sol

Trim any leading spaces from the line using adjustl

   line = ADJUSTL(line)
   IF (line(1:5)=='solid') THEN
      ! We've already read the line from the file, now use an
   internal read
      READ(line,*) word1, mdl%label
      EXIT sol
      ELSE ! The line didn't start with 'solid'
         ! Do something
   END IF
END DO sol

The variables word1 and word2 are used to 'catch' strings we're not really interested in, their contents are ignored. The next block reads the facets.

fct: DO ix = 1, num_facets
   DO WHILE (ios==0)
      READ(nu,'(a132)',iostat=ios) line
      IF (LEN_TRIM(line)==0) CYCLE fct ! ignore any blank lines
      line = ADJUSTL(line)
      IF (line(1:5)=='facet') THEN
         READ(line,*) word1, word2, mdl%facets(ix)%normal
         READ(nu,*) aline ! this should be 'outer loop' and we ignore it
         DO jx = 1, 3
            READ(nu,*) word1, mdl%facets(ix)%vertices(jx,:)
         END DO
      ELSE ! The line didn't start with 'facet'
         ! Do something
      END IF
   END DO
END DO fct

CLOSE(nu)

! If anything has gone wrong reading the file, return an empty solid.
IF (ios/=0) DEALLOCATE(mdl%facets)

END FUNCTION read_solid

The main difference between my approach and OP's is that I rely on list-directed input to take care of finding fields in lines, and in reading strings, reals, etc, properly. If the STL file is clean this is a sensible approach, if you're working with dirty STL files, fix them at source.

And, finally, this doesn't actually answer OP's question(s) about how to read strings character-by-character and interpret them. Nor does it fix any of the errors manifest in the code OP posted.



来源:https://stackoverflow.com/questions/57738862/how-to-iterate-over-character-strings-with-numbers-words-and-blancks-in-fortran

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