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)