Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Rhinorhino on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Char argument

Status
Not open for further replies.

IamMcCoder

Programmer
Joined
Jun 11, 2010
Messages
6
Location
US
I could use some help fixing this error. Thanks in advance.
Code:
 In file aacgm_init.f:65

         fname(i:i) = char(filename(i))                                 
                          1
Error: 'i' argument of 'char' intrinsic at (1) must be INTEGER

My code:
Code:
     SUBROUTINE aacgm_init( filename, ascii_flag)
      IMPLICIT NONE
      logical*1 filename(80), ascii_flag
      INTEGER I_NUM_TERMS, I_NUM_AXES, I_NUM_LEVEL, I_NUM_FLAG
      PARAMETER (I_NUM_TERMS = 121)
      PARAMETER (I_NUM_AXES  =   3)
      PARAMETER (I_NUM_LEVEL =   5)
      PARAMETER (I_NUM_FLAG  =   2)

      integer fnum/71/,i,t,a,l,f
      double precision D_COEF(I_NUM_TERMS, I_NUM_AXES, I_NUM_LEVEL,
     $     I_NUM_FLAG)
      character*80 fname

      common / SPH_HARM_MODEL /D_COEF

      do i=1,80
         fname(i:i) = char(filename(i))
         enddo
      if (.NOT. ascii_flag) then
         open(UNIT=fnum,FORM='unformatted', STATUS='old',FILE=fname
         read(fnum)((((d_coef(t,a,l,f),t=1,I_NUM_TERMS),a=1,I_NUM_A
     $        l=1,I_NUM_LEVEL),f=1,I_NUM_FLAG)
      else
         open(UNIT=fnum,FORM='formatted',STATUS='old',FILE=fname)  
         read(fnum,*)((((d_coef(t,a,l,f),t=1,I_NUM_TERMS),
     $        a=1,I_NUM_AXES),l=1,I_NUM_LEVEL),f=1,I_NUM_FLAG)
         endif
      close(fnum)
      return
      end
 
It is in your declaration and conversion loop
Code:
      logical*1 filename(80), ascii_flag
      character*80 fname

It should be
Code:
     character*1 filename(80)
     logical ascii_flag
     character*80 fname

...
     do i = 1, 80
         fname(i:i) = filename(i)
     end do
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top