Listing code not working

The objective is to print lines that do not drop of the page.

program test
character(200) :: stringin
character,dimension(200) :: strgout
integer :: single_character
stringin = 'the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze.'
do i = 1, len(stringin), 1
single_character = iachar(stringin(i:i))
strgout(i) = achar(single_character)
print *,strgout(i)
!
! I now need code to collate the characters back into an output string
! and to print it after a string length of 40 has been achieved
! and to skip to the next line after the output string has passed
! a length of 40 and encounters a space, so as to not skip in the
! middle of a word. Thank you.
!
!
end do

end program

Your code does not loop over lines, it is looping over characters within a single line.

The do loop is always going to loop over the 200 characters of stringin, so when the value of i gets to 41, the if statement will be tripped thereafter.

The syntax of the if test is not correct. In order to nest if statements in fortran, you must use separate statements.

if ( i > 40 ) then
   if ( strgout == achar(32) ) print *, 'a space with i>40 has occurred'
endif

You can compare characters in fortran directly, you do not need to convert them to integer values first.

If you want to know the length of a string after ignoring the trailing spaces, then the intrinsic function len_trim() can be used.

Ron, I will try and redo/rethink the test code, using what you suggest. Thank you so far. Patrick.[

Some other fortran intrinsic functions that you might find useful for your application are index(), scan(), and verify().

The objective is to list strings 40 characters wide.

The skip back up isn’t working. Please suggest the way to do this

program test
character(200) :: strIn
integer::single_character
      
strIn= 'the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze. '

    do i = 1, len(strIn), 1
    single_character = ichar(strIn(i:i))
    write(*,*) achar(single_character)
    if (i < 40) print *, achar(43)!skip back up

  end do
end program

Try this. It counts and prints a trailing space, which may not be what you want. See the first line of the output, which is broken as ‘his \nbanana.’

EDIT: It should be possible to modify the logic and eliminate the final write. I will leave that as an exercise.

EDIT^2: Fix an off-by-one error in the call to index function. Obvious if n=1. s/left+n/left+n-1/

program prog01
  character(len=200) :: stringin
  stringin = 'the kat kissed the dog and ate his banana. '//&
       'The banana was too big for its mouth so it had to sneeze.'
  call print_string(stringin,40)
  write(*,*)
  call print_string(stringin,50)
contains

  ! Write string to stdout with maximum line length n
  ! Break lines at spaces, if there is a <space> in next n characters.
  subroutine print_string(string,n)
    character(len=*), intent(in) :: string
    integer, intent(in) :: n
    
    integer left  ! leftmost unprocessed character
    integer last  ! last non-<space> character in string
    integer nout  ! number of character to print on this line

    left = 1
    last = len_trim(string)
    
    do while (left+n.le.last)
      nout = index(string(left:left+n-1),substring=' ',back=.true.)
      if (nout==0) nout=n ! print n characters if no <space> found
      write(*,"(a)") string(left:left+nout-1)
      left = left + nout
    end do
    if (left<=last) write(*,"(a)") string(left:last)
  end subroutine print_string

end program prog01

Output for n=40 and n=50 is

the kat kissed the dog and ate his
banana. The banana was too big for its
mouth so it had to sneeze.

the kat kissed the dog and ate his banana. The
banana was too big for its mouth so it had to
sneeze.
1 Like

David, I am very impressed by your code. You are obviously at the end of the Fortran Knowledge Route, whereas I have just learnt how to spell the word “Fortran”. So I will need to study your code first. Ï will also convert the relative positioning of my code, to absolute positioning, using my locateXY command, to deal with the unsolved one-up problem that my code has: in order to compare the two approaches, and to learn from that. So please allow me some time before getting back to you. Thank you very much so far.

1 Like

Patrick. Feel free to ask away. The code is pretty simple once you understand the Fortran intrinsics.

I should have mentioned:

  1. len_trim and index are Fortran string intrinsic functions
  2. My code doesn’t copy or modify the input string. It just manipulates indexes to substrings and reasonable compilers shouldn’t generate temporary copies.
  3. I think corner cases are handled correctly, including all-blank strings, no-blank strings and zero-length strings.

Here is a version of the subroutine with a single write statement, but a more complex test.

  subroutine print_string(string,n)
    character(len=*), intent(in) :: string
    integer, intent(in) :: n
    
    integer left  ! leftmost unprocessed character
    integer last  ! last non-blank character in string
    integer nout  ! number of characters to print on this line

    if ( n <= 0 ) return
    left = 1
    last = len_trim(string)
    
    do while (left.le.last)
      if ( left+n > last ) then
         nout = last - left + 1
      else
        nout = index(string(left:left+n-1),substring=' ',back=.true.)
        if (nout==0) nout=n ! print n characters if no blank found
      end if
      write(*,"(a)") string(left:left+nout-1)
      left = left + nout
    end do
  end subroutine print_string

EDIT: minor clarification.

David, the easy thing for me to do would be simply to copy your code - which I might be ending up doing anyway, however, then I won’t learn by doing, If I post a new attempt, would you please comment how I should display the second string after the previous has been successfully executed (marked *).? I presume the do loop marked * would need to be placed in another do loop. That I am not succeeding in doing,

subroutine show
character(200)::strin
integer::e=0
integer::crt=1
integer::start=1
strin = "the kat kissed the dog and ate his banana. The banana was too big for its mouth so it had to sneeze."

    !*
    do  while (crt<100)
    crt=crt+1
    if(strin(crt:crt)==" ") e = crt
    if(crt>70)print *,strin(start:e)  
    if(crt>70)exit    
    end do 
    !*
end subroutine show

No. No. No. No. The whole point of a subroutine is that you can use it again - both within this program and in other programs.

Let’s put the subroutine in a module and in a separate file. This is just the subroutine surrounded by “module print_string_m” / “end module”.

Multiple files and modules may be overkill here, but it is essential for larger projects.

File: print_string.f90 - nothing special about the name

module print_string_m
  implicit none
contains
  ! Write string to stdout with maximum line length n
  ! Break lines at spaces, if there is a <space> in next n characters.
  subroutine print_string(string,n)
    character(len=*), intent(in) :: string
    integer, intent(in) :: n
    
    integer left  ! leftmost unprocessed character
    integer last  ! last non-<space> character in string
    integer nout  ! number of character to print on this line

    left = 1
    last = len_trim(string)
    
    do while (left+n.le.last)
      nout = index(string(left:left+n-1),substring=' ',back=.true.)
      if (nout==0) nout=n ! print n characters if no <space> found
      write(*,"(a)") string(left:left+nout-1)
      left = left + nout
    end do
    if (left<=last) write(*,"(a)") string(left:last)
  end subroutine print_string
end module

Now put the calling code in a separate file and “use” the module.

File: prog04.f90

program prog04
  use print_string_m
  implicit none
  character(len=200) :: stringin
  character(len=50) ::  string2
  stringin = 'the kat kissed the dog and ate his banana. '//&
       'The banana was too big for its mouth so it had to sneeze.'
  string2 = 'The quick, brown fox jumped over the lazy dog'
  call print_string(stringin,40)
  write(*,*)
  call print_string(string2,10)
  write(*,*)
  call print_string('... and we can print a literal string, too',12)
end

I compiled this with the commands

gfortran -Wall -fcheck=all -c print_string.f90
gfortran -Wall -fcheck=all -o prog04.exe prog04.f90 print_string.o

It generates

the kat kissed the dog and ate his
banana. The banana was too big for its
mouth so it had to sneeze.

The
quick,
brown fox
jumped
over the
lazy dog

... and we
can print a
literal
string, too

David, I gave up trying to get my trial code to work and inserted your code into the application than I am attempting to make. Could you please make your output lines respect a margin of four spaces on the left hand side on the screen? I am using your second version. By the way, the lines to be printed are retrieved from a file. So the code will need to be able to deal with the subsequent lines retrieved from the file .

Change the format string in the write statement to:

write(*,"(4x,a)") string(left:last)

Fortran FORMAT is little language itself. There are entire book chapters on it.

  • 4x is four spaces
  • a is a complete character variable - the length the write statement argument

David, thank you very much for helping me. Patrick.

As I showed, the subroutine can deal with subsequent lines. You could try something like the following fragment

program main
  .
  .
  character(len=256) :: line ! sufficiently large input buffer
  integer stat ! IO status
  .
  .
  do  ! read a line at a time from stdin and display using print_string
    ! use fmt="(a)" as free format input can interpet commas and quotes
    read(*,"(a)",iostat=stat) line
    if ( stat /= 0 ) exit  ! stat < 0 == EOF.  stat > 0 == I/O error
    call print_string(line,40)
  end do
  .
  .
end

David, I have not done reading/writing files in FTN before. Something like so?
It doesn’t do anything. Sorry.

open(1,file=“data.txt”,action = “read”,iostat=stat)
do while(stat /=0)
read(1,“(a)”)string
call print_string(string,80)
end do

close(1)

Patrick,

You are only getting a status for the OPEN statement, and stat /=0 is a failure for the open statement. If the open succeeds then stat=0 and the do loop won’t be executed.

You need a iostat=stat on the READ statement to detect EOF or errors on the read. The test needs to be between the read and the call to print_string(). The DO / END DO loop with the test to exit - as I did above - is the simplest way.

open(1,file="data.txt",action = "read")
do 
  read(1,"(a)",iostat=stat) string
  if ( stat /= 0 ) exit
  call print_string(string,80)
end do
close(1)

Edit: The variable associated with the IOSTAT specifier in I/O statements is assigned only when the statement is executed. open(…, IOSTAT=stat) returns information about the file open, read(…,IOSTAT=stat) returns information about reading the current record, etc.

Edit^2: Remove duplicate comma in read statement of code.

David. I was excited to see the data appear on the display for the first time, thanks to your patient help. (The data are things one wants to look up easily. The bits and pieces of data - that I call labels - are delimited by an asterisk, the key is on the first line after the asterisk. Simple but effective.). Thank you for all your effective help. I only need to insert key selection now. I have transferred your remarks to my notes (my sort of FTN manual for future reference). Patrick.

Glad to help.

David, if the source text consists of paragraphs, separated by a blank line, your beautiful code (no 2) does not skip a line. Could you possibly please apply an amendment? I do not trust myself to tinker with it. Patrick.