Silverfrost Forums

Welcome to our forums

compiler error

22 Jul 2010 11:27 #6671

Hi, I get a compiler error with silverfrost/FTN95, which I do not see in Lahey fortran (Windows XP X64, service pack 2).

The error is 'error 304 - Non-writable expression in READ statement' The code in question is below it is the first read statement that appears to be causing a problem.

All help gratefully received. I don't know what to do next. I can find no helpful description of this error message to give me a clue what is going wrong.

best regards... Iain

SUBROUTINE read_wavecar(wave) TYPE(wave_obj) :: wave

open(unit=12,file='WAVECAR',status='old',form='unformatted')

! Read in from WAVECAR:
! the number of k-points
! the number of bands
! the energy maximum
! the cell dimensions
! the type of VASP code

read(12) nkpt,nband,emax,((A(i,j),i=1,3),j=1,3)

!????????????????????????????????????????????????????????
!      write(19,*) 
!      write(19,*) 'nkpt  =',nkpt
!      write(19,*) 'nband =',nband
!      write(19,*) 'emax  =',emax
!      write(19,*) 'A='
!      write(19,'(3X,3(1X,f8.3))') (A(i,1),i=1,3)
!      write(19,'(3X,3(1X,f8.3))') (A(i,2),i=1,3)
!      write(19,'(3X,3(1X,f8.3))') (A(i,3),i=1,3)
!????????????????????????????????????????????????????????

read(12) code
DO ikpt=1, nkpt

  ! Read in from WAVECAR:
  ! the number of pw wave fns
  ! the k-point
  
  read(12) npw, kpt(1:3)

  !????????????????????????????????????????????????????????
  ! write(19,*)
  ! write(19,'('k-point #',I3,':  (',3f7.4,')    npw=',I6)') 
  !		& ikpt, (kpt(i),i=1,3),npw 
  ! write(19,*) 'kpt =',kpt
  ! write(19,*) 'npw =',npw
  ! write(19,*) '  band       energy        weight'
  !
  !????????????????????????????????????????????????????????

  ALLOCATE(coef(npw))
  ALLOCATE(ac(npw,200))
  ic = 1 
  DO iband = 1, nband
        
    ! Read in from WAVECAR:
    ! the energy (eval)
    ! the occupation (fweight)

    read(12) eval, fweight, (coef(i),i=1,npw)

    !????????????????????????????????????????????????????????
    ! write(19,'(5X,I3,5X,f8.4,5x,f8.4)') iband, dreal(eval), fweight
    !????????????????????????????????????????????????????????

    ! Create matrix (ac):
    ! row: coefficients for plane waves
    ! column: coeff of 1st plane wave for bands interested in 

! IF(iband >= nbandmin.and.iband.le.nbandmax) then DO i = 1,npw ac(i,ic) = coef(i) ENDDO ic = ic+1 ! end if

  ENDDO
  DEALLOCATE(coef)
ENDDO
close(unit=12)
23 Jul 2010 7:51 #6675

I have had a quick look at this but I cannot see any immediate problems.

You may need to provide more information. The context is presumably a module that provides TYPEs and declarations.

Try posting the context but with the program cut down to a minimum that shows the problem.

23 Jul 2010 3:50 #6679

Hi, I atempted to include the whole module in this reply (not my code, so I'm not comfortable cutting it down), but although I can see it in Preview, it disappears once the message is posted. I'm guessing a line limit, but I cannot find instructions on this, or on how to attach a file. I have uploaded the responsible code to:

http://www.utoronto.ca/jpolanyi/Iain/wavecar_mod.f90

FTN95 reports two errors 'error 246 - The END statement cannot be used to end an internal SUBROUTINE, use END SUBROUTINE instead' (that's pretty clear, no problem about doing that). and 'error 304 - Non-writable expression in READ statement' applying to the first read. That's too cryptic for me. In the documentation I cannot find a list of errors and less cryptic meanings. Does such a one exist?

These errors are not picked up in Lahey fortran or Intel fortran (X64).

All help most gratefully received. I'd really like to be able to run this code. Thank you for your time and help, I truly appreciate it.

best regards... Iain

29 Jul 2010 4:34 (Edited: 22 Feb 2011 10:56) #6709

The Salford/Silverfrost compiler does not know how to process subprogram dummy arguments with the allocatable attribute, which are not legal in Fortran 95 without the TR 15581 extensions.

Had you passed the allocatable arrays individually, instead of their being squirreled away within a derived type, the compiler would have given you an appropriate message. But, since 'wave_obj' has components that are allocatable, the compiler is confused.

29 Jul 2010 6:14 #6710

😄 Thank you very much for your help. Not my code, but I guess the author enjoys squirreling things away.

Best regards and many thanks ... Iain

14 Aug 2010 10:05 #6777

I didn't mean to be critical of defining and using structured variables. The error messages that a compiler emits can be incomprehensible when it has been given code in a language version that it does not know about, but the user expects it to be able to compile.

9 Feb 2011 11:03 #7732

I thought I would never see this error, as I still write in Fortran 77 style, and thought it was a fancy modern sort of thing that was causing your message. However, I saw it yesterday. It came inside a loop where I was asking:

READ(27,*) (A(I), B(I), I=1,Number_of_Things)

First of all I checked Number_Of_Things was spelled correctly. Of course, the error was failing to dimension both A and B!

FTN95 error messages are usually very understandable. I had to puzzle out what this one meant, and that took longer than fixing the underlying problem. Mostly they tell you what is wrong in 'Fortran programmer' language, so you can immediately tell what you have to do to fix it. The 'Non-writable ...' etc message is telling you how the compiler sees it.

Did you ever fix your problem?

Eddie

Please login to reply.