Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Character

Rasa_N_
Beginner
1,457 Views

Hi,

I wrote small program to read and write a character. But it gives error messages.

program check1

    CHARACTER str*(*) 
    read *, str
    print *, str
   
 end program check1

When i ran this program, it gave following error.

Error    2    Compilation Aborted (code 1)    J:\Personal Works\Fortran\CHECK\check1\check1\check1.f90    1    
Error    1     error #6832: This passed length character name has been used in an invalid context.   [STR]    

 

I could not find any error in the source code. Anyone can explain what is wrong with this code.

Thanks

0 Kudos
19 Replies
Les_Neilson
Valued Contributor II
1,457 Views

You need to tell the compiler how long STR is.

For example character :: str(len=80)

Les

0 Kudos
Rasa_N_
Beginner
1,457 Views

What if, length of string is unknown how to define the character?

0 Kudos
Anthony_Richards
New Contributor I
1,457 Views

If you add the declaration

CHARACTER :: STR(LEN=80)

you are telling the compiler to assign 80 bytes of memory as a buffer to receive your character string(s). As long as the strings you are reading in have a length less than or equal to the declared length, then after your READ *, STR, the character string will be left justified in memory, starting from the address of the first byte in STR. The remaining characters will be blanks. If the string is longer than the length of the memory buffer assigned to STR, your stored string will be a truncated version of the string you are reading from.

You will have a problem determining the length of the string that you have read in if it actually contains blanks, or if it actually has trailing blanks. Windows gets around that problem by always terminating its strings with the CHAR(0) character (sometimes two of them) which can be searched for using the INDEX intrinsic function to determine its position in the buffer and hence the length of the string.

0 Kudos
JVanB
Valued Contributor II
1,457 Views

Fortran doesn't directly allow you to perform an input of unknown length, but it's possible to write out a function that does this using deferred length character variables.

module m
   implicit none
   contains
      function getline(iunit)
         character(:), allocatable :: getline
         integer, intent(in) :: iunit
         integer, parameter :: N = 10
         character(N) buffer
         integer sizeread
         getline = ''
         do
            read(iunit,'(a)',advance='no',eor=10,size=sizeread) buffer
            getline = getline // buffer
         end do
         10 continue
         getline = getline // buffer(1:sizeread)
      end function getline
end module m

program p
   use m
   use, intrinsic :: iso_fortran_env, only: input_unit
   implicit none
   character(:), allocatable :: line
   line = getline(input_unit)
   print*, line
end program p

I don't know how foolproof the above is, but it worked for a simple testing.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,457 Views

Great example.

A change I would recommend though is to create a threadprivate SAVE allocatable array inside the function. Use that, expanding as necessary, in the do read loop. Then pass the temp(1:sizeread) out directly to getline. (test code)

module m
   implicit none
   contains
      function getline(iunit)
        use omp_lib
        character(:), allocatable :: getline
        integer, intent(in) :: iunit
        integer, parameter :: N = 20
        character(N), SAVE :: buffer
        integer sizeread
        character(:), SAVE, allocatable :: privateLine
 !$omp threadprivate (privateLine, buffer)
        write(buffer, *) 'x', omp_get_thread_num(), 'x'
      privateLine = ''
      
        do
            call sleepqq(1000)
           ! read(iunit,'(a)',advance='no',eor=10,size=sizeread) privateLine
           privateLine = privateLine // buffer
           print *,  privateLine
        end do
        10 continue
        getline = privateLine(1:sizeread)
      end function getline
end module m
  
  x           5x
  x           4x
  x           1x
  x           0x
  x           6x
  x           2x
  x           5x      x           5x
  x           1x      x           1x
  x           7x
  x           4x      x           4x
  x           6x      x           6x
  x           5x      x           5x      x           5x
  x           1x      x           1x      x           1x
  x           7x      x           7x

This will reduce the number of allocations and possibly reduce potential memory fragmentation issues.

Jim Dempsey

0 Kudos
dboggs
New Contributor I
1,457 Views

I think this is really quite simple. Here's the way I do it:

      CHARACTER(1)   :: ch
      CHARACTER(:), ALLOCATABLE  :: string
      ...
      OPEN (1, FILE = 'InputFile1.txt')
      string = '' ! initialize to null
      DO
         READ (1, '(A)', ADVANCE = 'NO', EOR = 100) ch
         string = string // ch
      END DO
100   CONTINUE 

This solution assumes that the string is terminated by a carriage return in the input file (or typed from the keyboard), i.e. one record per line (which makes EOR = 100 a sufficient DO exit. But it is easily modified for other cases. And if you are averse to statement labels (100) that is easily changed too, but it is more concise this way.

0 Kudos
JVanB
Valued Contributor II
1,457 Views

This last post reminds me that my method was O(N) in terms of number of allocations required. It's not too much of a stretch to make it O(log(N)).

module m
   implicit none
   contains
      function getline(iunit)
         character(:), allocatable :: getline
         integer, intent(in) :: iunit
         integer N
         integer sizeread
         N = 10
         getline = ''
         read_loop: do
            block
               character(N) buffer
               read(iunit,'(a)',advance='no',eor=10,size=sizeread) buffer
               getline = getline // buffer
               N = 2*N
               cycle read_loop
               10 continue
               getline = getline // buffer(1:sizeread)
               exit read_loop
            end block
         end do read_loop
      end function getline
end module m

program p
   use m
   use, intrinsic :: iso_fortran_env, only: input_unit
   implicit none
   character(:), allocatable :: line
   line = getline(input_unit)
   print*, line
end program p

Again, this sample has only survived a minimal testing.

0 Kudos
JVanB
Valued Contributor II
1,457 Views

Mmmf... I found a test my function failed. First we write an input file:

open(7,file='InputFile1.txt',status='replace',access='stream')
do i = 1,10**6
   write(7) achar(mod(i-1,10)+48),'XOXOXOXOX'
end do
write(7) achar(13),achar(10)
close(7)
end

Then a version of the logarithmic program that tries to read the input file:

module m
   implicit none
   contains
      function getline(iunit)
         character(:), allocatable :: getline
         integer, intent(in) :: iunit
         integer N
         integer sizeread
         N = 10
         getline = ''
         read_loop: do
            block
               character(N) buffer
               read(iunit,'(a)',advance='no',eor=10,size=sizeread) buffer
               getline = getline // buffer
               N = 2*N
               cycle read_loop
               10 continue
               getline = getline // buffer(1:sizeread)
               exit read_loop
            end block
         end do read_loop
      end function getline
end module m

program p
   use m
   implicit none
   character(:), allocatable :: line
   integer iunit
   open(newunit=iunit,file='InputFile1.txt',status='old')
   line = getline(iunit)
   print '(i0)', len(line)
   print '(a)', line(1:10)
   print '(a)', line(max(1,len(line)-9):len(line))
end program p

Now, if the loop in the writing program only goes up to 10**5, we get output:

1000000
0XOXOXOXOX
9XOXOXOXOX

But at 10**6 as posted above, gfortran crashes at runtime. Perhaps that's just a bug: does it work with ifort?

0 Kudos
IanH
Honored Contributor II
1,457 Views

The 15 beta (required because of the use of BLOCK from F2008) dies with an ice.

If the processor puts automatic variables on the stack, then your longer test line is likely to exhaust the default stack allocation on Windows.  If the processor doesn't put automatic variables on the stack (and hence does an "allocation" under the covers), then the total number of allocations carried out may still be larger for small line lengths.  I guess if it was critical you'd have to measure to confirm.

0 Kudos
JVanB
Valued Contributor II
1,457 Views

You're right about that stack stuff. When I changed my compile line to

C:\>gfortran bench.f90 -obench -Wl,--stack,500000000

it was able to process the line of length 1e8 created when the writing program loops up to 10**7, so indeed it's not a gfortran bug.

 

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,457 Views

IanH and I were having an off line discussion. This is what I've come up with:

module m
   implicit none
   contains
      function getline(iunit)
        use omp_lib
        character(:), allocatable :: getline
        integer, intent(in) :: iunit
        integer, parameter :: N = 10   
        character(N), SAVE :: bufferExpandBy
        integer sizeread
        character(:), SAVE, allocatable :: privateLine
!$omp threadprivate (privateLine)
        if(.not. allocated(privateLine)) privateLine = bufferExpandBy
!DIR$ IF DEFINED (REGULAR_CODE) 
        do
           read(iunit,'(a)',advance='no',eor=10,size=sizeread) privateLine
           ! here when record .gt. privateLine
           privateLine = privateLine // bufferExpandBy
        end do
10      continue
        ! now read with advancing
        read(iunit,'(a)',) privateLine 
!DIR$ ELSE
        ! TEST CODE
        ! simulate read of .gt. size of private line
        sizeread = sizeof(privateline)
        ! here when record .gt. privateLine
        privateLine = privateLine // bufferExpandBy
        ! put thread specific data into reallocated private line (starting at the pre-expanded position)
        write(privateLine(sizeread:), "('x',i1,'=',i3,'x')") iunit, omp_get_thread_num()
        ! "post read" new size
        sizeread = sizeof(privateline)
!DIR$ ENDIF
        getline = privateLine(1:sizeread)
      end function getline
    end module m
    
program test
    use m
    implicit none

    ! Variables
    character(:), allocatable :: myline
!$omp parallel private(myline)
    myline = getline(1)
    write(6,*) 1, myline, sizeof(myline)
    myline = getline(2)
    write(6,*) 2, myline, sizeof(myline)
    myline = getline(3)
    write(6,*) 3, myline, sizeof(myline)
    myline = getline(4)
    write(6,*) 4, myline, sizeof(myline)
    flush(6)
!$omp end parallel
end program test

Note the above is test code, real code would not have the test code printouts and would use the conditional code that is conditionalized out. Also the N and size of bufferExpandBy would be something reasonable: 128, 256, 512, 1024, ...

Output:

           1          x1=  3x              20
           1          x1=  5x              20
           1          x1=  4x              20
           1          x1=  6x              20
           1          x1=  7x              20
           1          x1=  1x              20
           1          x1=  0x              20
           2          x1=  3x   x2=  3x              30
           1          x1=  2x              20
           2          x1=  5x   x2=  5x              30
           2          x1=  4x   x2=  4x              30
           2          x1=  6x   x2=  6x              30
           2          x1=  7x   x2=  7x              30
           2          x1=  1x   x2=  1x              30
           2          x1=  0x   x2=  0x              30
           3          x1=  3x   x2=  3x   x3=  3x              40
           2          x1=  2x   x2=  2x              30
           3          x1=  5x   x2=  5x   x3=  5x              40
           3          x1=  4x   x2=  4x   x3=  4x              40
           3          x1=  6x   x2=  6x   x3=  6x              40
           3          x1=  7x   x2=  7x   x3=  7x              40
           3          x1=  1x   x2=  1x   x3=  1x              40
           3          x1=  0x   x2=  0x   x3=  0x              40
           4          x1=  3x   x2=  3x   x3=  3x   x4=  3x              50
           3          x1=  2x   x2=  2x   x3=  2x              40
           4          x1=  5x   x2=  5x   x3=  5x   x4=  5x              50
           4          x1=  4x   x2=  4x   x3=  4x   x4=  4x              50
           4          x1=  6x   x2=  6x   x3=  6x   x4=  6x              50
           4          x1=  7x   x2=  7x   x3=  7x   x4=  7x              50
           4          x1=  1x   x2=  1x   x3=  1x   x4=  1x              50
           4          x1=  0x   x2=  0x   x3=  0x   x4=  0x              50
           4          x1=  2x   x2=  2x   x3=  2x   x4=  2x              50

Jim Dempsey

0 Kudos
dboggs
New Contributor I
1,457 Views

Where do we get from the simple bare-bones 10-line code of #7 to the 40-line code of #12? I realize this is not an apples-apples comparison, that one is a snippet while the other is a robust "permanent" module, etc. And, I realize that the simple one is heavy on allocations while the other is efficient.

But I think some more discussion of this is in order. #7 is exceedingly easy to inject in any code, and in most cases the less allocation efficiency is probably unnoticeable--after all, are people reading 100-character strings or 10,000 character strings? And how significant is the time required to allocate 1-charcter chunks, vs. the time required to process multi-character chunks anyway? I would really like some idea of this. #7 is so simple that all one needs is the basic concept then bang it is memorized and easily reproduced when needed. Contrast this with the details of the other methods and you get some idea of why Fortran has the reputation of being difficult to implement basic things that are nearly automatic in other languages.

So, a rundown of features in the other solutions that make them worthwhile would be beneficial to those of us who crave simplicity.

0 Kudos
JVanB
Valued Contributor II
1,457 Views

I wanted to try a little benchmarking here, so a post that seems to request benchmarking is welcome. First, I modified the writing program so that it created records of length 10**[1,2,3,4,5,6,7,8] bytes.

program P
   implicit none
   integer i, j
   character(20) filename
   do j = 0,7
      write(filename,'(a,i0,a)') 'InputFile',j+1,'.txt'
      open(7,file=filename,status='replace',access='stream')
      do i = 1,10**j
         write(7) achar(mod(i-1,10)+48),'XOXOXOXOX'
      end do
      write(7) achar(13),achar(10)
      close(7)
   end do
end program P

Next, I modified the test program for the logarithmic algorithm so that it read all the files and printed out an approximation of time to process each one.

module m
   implicit none
   contains
      function getline(iunit)
         character(:), allocatable :: getline
         integer, intent(in) :: iunit
         integer N
         integer sizeread
         N = 10
         getline = ''
         read_loop: do
            block
               character(N) buffer
               read(iunit,'(a)',advance='no',eor=10,size=sizeread) buffer
               getline = getline // buffer
               N = 2*N
               cycle read_loop
               10 continue
               getline = getline // buffer(1:sizeread)
               exit read_loop
            end block
         end do read_loop
      end function getline
end module m

program p
   use m
   implicit none
   character(:), allocatable :: line
   integer iunit
   integer j
   character(20) filename
   integer values(8,2)
   double precision time
   do j = 1,8
      write(filename,'(a,i0,a)') 'InputFile',j,'.txt'
      open(newunit=iunit,file=filename,status='old')
      print '(/a,i0)', 'Testing logarithmic algorithm for len = 10**',j
      call date_and_time(values=values(:,1))
      line = getline(iunit)
      print '(i0)', len(line)
      print '(a)', line(1:min(10,len(line)))
      print '(a)', line(max(1,len(line)-9):len(line))
      call date_and_time(values=values(:,2))
      time = modulo(values(5,2)-values(5,1),24)
      time = time*60+(values(6,2)-values(6,1))
      time = time*60+(values(7,2)-values(7,1))
      time = time+1.0d-3*(values(8,2)-values(8,1))
      print '(a,f0.3)', 'Elapsed time = ',time
      close(iunit)
   end do
end program p

Results:

Testing logarithmic algorithm for len = 10**1
10
0XOXOXOXOX
0XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**2
100
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**3
1000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**4
10000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**5
100000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**6
1000000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**7
10000000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .046

Testing logarithmic algorithm for len = 10**8
100000000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .500

Then I changed the test program so that it tested the linear algorithm.

program p
   implicit none
   character ch
   character(:), allocatable :: line
   integer iunit
   integer j
   character(20) filename
   integer values(8,2)
   double precision time
   do j = 1,8
      write(filename,'(a,i0,a)') 'InputFile',j,'.txt'
      open(newunit=iunit,file=filename,status='old')
      print '(/a,i0)', 'Testing linear algorithm for len = 10**',j
      call date_and_time(values=values(:,1))
      line = ''
      do
         read(iunit,'(a)',advance='no',eor=100) ch
         line = line//ch
      end do
      100 continue
      print '(i0)', len(line)
      print '(a)', line(1:min(10,len(line)))
      print '(a)', line(max(1,len(line)-9):len(line))
      call date_and_time(values=values(:,2))
      time = modulo(values(5,2)-values(5,1),24)
      time = time*60+(values(6,2)-values(6,1))
      time = time*60+(values(7,2)-values(7,1))
      time = time+1.0d-3*(values(8,2)-values(8,1))
      print '(a,f0.3)', 'Elapsed time = ',time
      close(iunit)
   end do
end program p

Results:

Testing linear algorithm for len = 10**1
10
0XOXOXOXOX
0XOXOXOXOX
Elapsed time = .000

Testing linear algorithm for len = 10**2
100
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing linear algorithm for len = 10**3
1000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing linear algorithm for len = 10**4
10000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .016

Testing linear algorithm for len = 10**5
100000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .406

Testing linear algorithm for len = 10**6
1000000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = 96.079

Testing linear algorithm for len = 10**7
^C

I stopped the test at this point because it was just too slow. Although the latter algorithm is linear in allocations, each allocation implies one or two copies of the data already read (O(N)) unless the Fortran processor is clever enough to detect this idiom. Thus, O(N) in allocations can mean O(N**2) in operations, and for sufficiently large data the difference between O(N**2) and O(N*log(N)) may become apparent.

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,457 Views

If you know you have a record of 10**8 bytes you should use an internal record size of at least 10**8 bytes. And consider expanding by 10**6 bytes.

Also, make your line SAVE such that it only grows. (if used in parallel region, then make it threadprivate too).

Jim Dempsey

 

0 Kudos
Steven_L_Intel1
Employee
1,457 Views

I filed issue DPD200358648 for the ICE that RepeatOffender noted in post #14.

0 Kudos
JVanB
Valued Contributor II
1,457 Views

Thanks for filing the ICE, Steve. I've got a workaround that does essentially what the BLOCK construct did but uses pre-f2008 syntax.

module m
   implicit none
   contains
      function getline(iunit)
         character(:), allocatable :: getline
         integer, intent(in) :: iunit
         integer N
         integer sizeread
         N = 10
         getline = ''
         read_loop: do
            call block(*10)
         end do read_loop
         10 continue
         contains
            subroutine block(*)
               character(N) buffer
               read(iunit,'(a)',advance='no',eor=10,size=sizeread) buffer
               getline = getline // buffer
               N = 2*N
               return
               10 continue
               getline = getline // buffer(1:sizeread)
               return 1
            end subroutine block
      end function getline
end module m

program p
   use m
   implicit none
   character(:), allocatable :: line
   integer iunit
   integer j
   character(20) filename
   integer values(8,2)
   double precision time
   do j = 1,8
      write(filename,'(a,i0,a)') 'InputFile',j,'.txt'
      open(newunit=iunit,file=filename,status='old')
      print '(/a,i0)', 'Testing logarithmic algorithm for len = 10**',j
      call date_and_time(values=values(:,1))
      line = getline(iunit)
      print '(i0)', len(line)
      print '(a)', line(1:min(10,len(line)))
      print '(a)', line(max(1,len(line)-9):len(line))
      call date_and_time(values=values(:,2))
      time = modulo(values(5,2)-values(5,1),24)
      time = time*60+(values(6,2)-values(6,1))
      time = time*60+(values(7,2)-values(7,1))
      time = time+1.0d-3*(values(8,2)-values(8,1))
      print '(a,f0.3)', 'Elapsed time = ',time
      close(iunit)
   end do
end program p

Now users can compare performance of the linear and logarithmic algorithms with ifort. Here is the output I get with gfortran:

Testing logarithmic algorithm for len = 10**1
10
0XOXOXOXOX
0XOXOXOXOX
Elapsed time = .020

Testing logarithmic algorithm for len = 10**2
100
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**3
1000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .000

Testing logarithmic algorithm for len = 10**4
10000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .011

Testing logarithmic algorithm for len = 10**5
100000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .010

Testing logarithmic algorithm for len = 10**6
1000000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .040

Testing logarithmic algorithm for len = 10**7
10000000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .120

Testing logarithmic algorithm for len = 10**8
100000000
0XOXOXOXOX
9XOXOXOXOX
Elapsed time = .720

 

0 Kudos
Steven_L_Intel1
Employee
1,457 Views

FWIW, it's come up for discussion in the standards committee a couple of times that it "would have been nice" if you could name a deferred-length allocatable character variable in a READ and get it to automatically reallocate to the needed size,. But this didn't make the cut for the next standard, which has a rather limited scope. Perhaps the one after that.

0 Kudos
John_Campbell
New Contributor II
1,457 Views

It use to be the case that you could declare a character array in blank common, read the string with stream input, find the length and go from there. Not knowing how big a data set could be is a general problem that has always existed. I don't think this latest discussion shows much of a change.

John

0 Kudos
Steven_L_Intel1
Employee
1,457 Views

The BLOCK error has been fixed for an update later this year (not in the initial 15.0 release.)

0 Kudos
Reply