[Wien] compilation problems in the new pes module

Pavel Ondračka pavel.ondracka at email.cz
Tue Jul 10 12:57:34 CEST 2018


Thanks for the fixes, the code compiles now. I've prepared a patch so
that other users don't have to patch by hand, and also for Gavin if he
continues the great work of collecting fixes in his repo. Copy to the
SRC_pes folder and apply with patch -p1 < pes-patch.txt
Best regards
Pavel


On Tue, 2018-07-10 at 08:33 +0200, Peter Blaha wrote:
> Thanks for the report. See inlined comments.
> 
> PS: Unfortunately, when I looked into the code, I saw it is in
> terrible 
> shape. It mixes real*4 up to real*16 variables randomly and has a
> couple 
> of unclear things in it (for instance just before calling spline....
> 
> Peter Blaha
> 
> > I'm interested in the new pes module. Unfortunately, the
> > compilation of
> > the module faces some problems with gfortran, specifically:
> > 
> > -------------
> > 
> > pes.f:114:19:
> > 
> >           read (*,'(I)') database
> >                     1
> > Error: Nonnegative width required in format string at (1)
> > pes.f:146:21:
> > 
> >             read (*,'(i)') scheme
> >                       1
> > Error: Nonnegative width required in format string at (1)
> > 
> > - This is nonstandard behavior, looking at the expected values it
> > should be probably I1 in both cases
> 
> 
> Yes I1 is fine.
> 
> > ------------
> > 
> > pes.f:235:39:
> > 
> >              500 format(A,A16,2x,A16,2x,<7>(A16,2x))
> >                                         1
> > Error: Unexpected element ‘<’ in format string at (1)
> > pes.f:239:42:
> > 
> >               600 format(f16.8,2x,e16.8,2x,<7>(e16.8,2x))
> >                                            1
> > Error: Unexpected element ‘<’ in format string at (1)
> > ind_p.f:39:26:
> > 
> >                 100 format(<15>A1)
> >                            1
> > Error: Unexpected element ‘<’ in format string at (1)
> > optimize_charge.f:239:21:
> > 
> >           1013 FORMAT(<3>A15)
> >                       1
> > Error: Unexpected element ‘<’ in format string at (1)
> > 
> >   - Another nonstandard ifort specific stuff. Since the value is
> > constant the brackets are not needed anyway.
> 
> Yes, the "<" and ">" characters should simply be removed.
> 
> 
> > 
> > ------------
> > 
> > pes.f:266:22:
> > 
> >         800 format(4x,I)
> >                        1
> > Error: Non-negative width required in format string at (1)
> > optimize_charge.f:64:25:
> > 
> >        1001 FORMAT(3x,A1,I)
> 
> This should be I3
> 
> 
> >                           1
> > Error: Nonnegative width required in format string at (1)
> > read_dos.f:41:21:
> > 
> >       301 FORMAT (7x,I)
> 
> This should be I5
> 
> >                       1
> > Error: Nonnegative width required in format string at (1)
> > read_dos.f:44:45:
> > 
> >        400 format(4x,f10.5,10x,i3,10x,i8,20x,f)
> 
> should be f10.5
> 
> >                                               1
> > Error: Nonnegative width required in format string at (1)
> > 
> > - No idea here about the required width, but needs to be set too.
> > 
> > ------------
> > 
> > pes.f:279:26:
> > 
> >        if((ERROR.eq.0).AND.(STR.eq.'#')) then
> 
> Yes, of course this should be STTR instead of STR
> 
> >                            1
> > Error: Operands of comparison operator ‘.eq.’ at (1) are
> > INTEGER(4)/CHARACTER(1)
> > 
> > -It looks like the STR is undefined, probably a typo (did author
> > want
> > STTR in the comparison)?
> > 
> > ------------
> > 
> > read_dos.f:51:36:
> > 
> >                     600 format(f10.5,<n_clmn>f14.8)
> 
> Should simply be: 600 format(f10.5,7f14.8)
> 
> >                                      1
> > Error: Unexpected element ‘<’ in format string at (1)
> > Find_p.f:46:25:
> > 
> >                200 format(<j-1>A1)
> 
> It should be 15A1
> 
> >                           1
> > Error: Unexpected element ‘<’ in format string at (1)
> > Find_p.f:50:25:
> > 
> >                300 format(<m-j>A1)
> 
> Also here: 15A1
> 
> >                           1
> > Error: Unexpected element ‘<’ in format string at (1)
> > 
> > - Can be rewritten with combination of internal output and string
> > formats.
> > 
> > for example:
> > write(Anumber,200)(temp(l),l=1,k-1)
> > 200 format(<j-1>A1)
> > 
> > should be equivalent to
> > 
> > character(len=10) :: frmt
> > write(frmt,'("(",I0,"A1)")') j-1
> > write(Anumber,frmt)(temp(l),l=1,k-1)
> > 
> > ------------
> > 
> > optimize_charge.f:103:9:
> > 
> >         IF(PCHECK(j).EQ. .FALSE.)THEN
> >           1
> > Error: Logicals at (1) must be compared with .eqv. instead of .eq.
> > optimize_charge.f:329:12:
> > 
> >           IF (CHECK.EQ..FALSE.) THEN
> >              1
> > Error: Logicals at (1) must be compared with .eqv. instead of .eq.
> > read_database2.f:68:5:
> > 
> >    if (data_exist.eq..false.)then
> >       1
> > Error: Logicals at (1) must be compared with .eqv. instead of .eq.
> > 
> > - Use .eqv. as suggested.
> 
> Yes, in all these cases it should be   .eqv.
> 
> > 
> > -------------
> > 
> > SPLINE.f:15:14:
> > 
> >      call  setup(p0, p1, p2, p3,
> > delta_x,X,F,N,strt,stp,J,interpolation)
> >                1
> > Error: Explicit interface required for ‘setup’ at (1): allocatable
> > argument
> 
> edit SPLINE.f and remove p0-p3 from the arguments of subroutine
> setup 
> and remove the intent(out) definition for these variables:
> 
> ...
>     call  setup(delta_x,X,F,N,strt,stp,J,interpolation)
> 
> END SUBROUTINE SPLINE
> 
> subroutine setup(delta_x,tempx,tempy,n,strt,stp,J,interpolation)
> ...
> !    real(dp),dimension(:),allocatable, intent(out) :: p0, p1, p2, p3
> ! 
> spline coefficients
>      real(dp),dimension(:),allocatable :: p0, p1, p2, p3 ! spline 
> coefficients
> ...
> 
> > 
> > - No idea here :-(
> > 
> > -------------
> > 
> > read_int.f:18:25:
> > 
> >                read(22,100),ndos
> 
> 
> remove comma before ndos
> 
> >                           1
> > Warning: Legacy Extension: Comma before i/o item list at (1)
> > 
> > Find_p.f:66:65:
> > 
> >                             write(output_names(output_counter),500)
> > ,aname(m),composition(m,n),m
> 
> Remove comma before aname
> 
> >                                                                   1
> > Warning: Legacy Extension: Comma before i/o item list at (1)
> > 
> > - Some unrelated harmless easy to fix warnings.
> > -------------
> > 
> > Most of the fixes are probably obvious except the missing length
> > for
> > the read formats, where the proper fix requires some knowledge
> > about
> > the input structuring and also the "Explicit interface required"
> > stuff.
> > 
> > Best regards
> > Pavel
> > 
> > _______________________________________________
> > Wien mailing list
> > Wien at zeus.theochem.tuwien.ac.at
> > http://zeus.theochem.tuwien.ac.at/mailman/listinfo/wien
> > SEARCH the MAILING-LIST at:  http://www.mail-archive.com/wien@zeus.
> > theochem.tuwien.ac.at/index.html
> > 
> 
> 
-------------- next part --------------
diff -Naur SRC_pes/Find_p.f SRC_pes/Find_p.f
--- SRC_pes/Find_p.f	2018-06-07 12:27:06.325829000 +0200
+++ SRC_pes/Find_p.f	2018-07-10 12:26:12.371017112 +0200
@@ -36,18 +36,18 @@
 
                   
               read(dosname(i),100) (temp(j),j=1,15)
-              100 format(<15>A1)
+              100 format(15A1)
 
       do j=1,15
 
         if (temp(j).eq.':') then
            k=j
             write(Anumber,200)(temp(l),l=1,k-1)
-             200 format(<j-1>A1)
+             200 format(15A1)
                Anumber=adjustl(Anumber)
                m=len_trim(dosname(i))
               write(POname,300)(temp(l),l=j+1,m)
-             300 format(<m-j>A1)
+             300 format(15A1)
            POname=adjustl(POname)
 
              do m=1,nat 
@@ -62,7 +62,7 @@
                             do o=1,trow
                               output_dos(o,output_counter)=dosdata(o,i)*mult(m)
                             end do
-                          write(output_names(output_counter),500) ,aname(m),composition(m,n),m
+                          write(output_names(output_counter),500) aname(m),composition(m,n),m
                           500 format(A2,A2,I3)
                        end if
                      end do
diff -Naur SRC_pes/optimize_charge.f SRC_pes/optimize_charge.f
--- SRC_pes/optimize_charge.f	2018-06-07 12:27:07.137832000 +0200
+++ SRC_pes/optimize_charge.f	2018-07-10 12:12:21.182584889 +0200
@@ -61,7 +61,7 @@
    
   DO j=1,output_counter
      READ (output_names(j),1001) pname(j),atomnum(j)
-     1001 FORMAT(3x,A1,I)
+     1001 FORMAT(3x,A1,I3)
      WRITE (oname(j),1002)atomnum(j),':',pname(j)
      1002 FORMAT (I3,A1,A1)
      oname(j) = TRIM (oname(j))
@@ -100,7 +100,7 @@
 
   DO j=1,output_counter
      nametemp1=output_names(j)
-      IF(PCHECK(j).EQ. .FALSE.)THEN
+      IF(PCHECK(j).EQV. .FALSE.)THEN
         recon_counter             = recon_counter+1
         q_temp(recon_counter)     = qsphere(j,1)
         recon_name(recon_counter) = output_names(j)
@@ -236,7 +236,7 @@
 
 ! Replace the WIEN2k generated charge inside the atomic spheres with the optimized values          
         WRITE(*,1013)'Partial Orbital', 'Case.outputst','Optimized'
-        1013 FORMAT(<3>A15)
+        1013 FORMAT(3A15)
 
          DO j = 1, output_counter        
           WRITE(*,1014) output_names(j), qsphere(j,1), min_temp(j)
@@ -326,7 +326,7 @@
        ! CLOSE(999)
     
         IF (ierr.EQ.3.OR.ierr.EQ.4) THEN 
-        IF (CHECK.EQ..FALSE.) THEN
+        IF (CHECK.EQV..FALSE.) THEN
            PRINT *, 'Change the constraints values for q_sphere to ±0.99?','(y/n)'
            READ (*,'(a)') answer
            IF(answer .NE.'n'.AND.answer.NE.'N') THEN
diff -Naur SRC_pes/pes.f SRC_pes/pes.f
--- SRC_pes/pes.f	2018-06-07 12:27:06.933831000 +0200
+++ SRC_pes/pes.f	2018-07-10 12:08:52.597391001 +0200
@@ -111,7 +111,7 @@
      
      database=0
      do while ((database.NE.3).AND.(database.NE.2).AND.(database.NE.1))
-        read (*,'(I)') database
+        read (*,'(I1)') database
         if(database.eq.0) database=1
      end do
      print *,'________________'
@@ -143,7 +143,7 @@
           Print *,'  5   LDAD'
          scheme=0
          do while ((scheme.NE.1).AND.(scheme.NE.2) .AND.(scheme.NE.3) .AND.(scheme.NE.4).AND.(scheme.NE.5))
-          read (*,'(i)') scheme
+          read (*,'(i1)') scheme
           if(scheme.eq.0) scheme=1
           calc_info=info(scheme+1)
         end do
@@ -232,11 +232,11 @@
            460 format (A,2x,A17,f16.10,A2)
          if(k.eq.0) then
            write ((30+k),500)'#',output_names(0),output_names(output_counter+1),(output_names(j),j=str,stp)
-           500 format(A,A16,2x,A16,2x,<7>(A16,2x))                 
+           500 format(A,A16,2x,A16,2x,7(A16,2x))                 
            do i=1,trow
            write (30+k,600)output_dos(i,0),output_dos(i,output_counter+1),(output_dos(i,j),j=str,stp)
            !600 format(f16.8,2x,<7>(f16.8,2x),f16.8)
-            600 format(f16.8,2x,e16.8,2x,<7>(e16.8,2x))
+            600 format(f16.8,2x,e16.8,2x,7(e16.8,2x))
            end do
          else
            write ((30+k),500)'#',output_names(0),(output_names(j),j=str,stp)
@@ -263,7 +263,7 @@
    700 format (A15,2x,A16,18x,A16,2x,A4,2x,A16)
      do j=1,output_counter 
       read(output_names(j),800)temp
-      800 format(4x,I)
+      800 format(4x,I3)
       write (7,900) output_names(j),cross_section(j),stat(j),qsphere(j,1),mult(temp),cross_section(j)*mult(temp)/qsphere(j,1)
       900 format(A4,13x,D16.8,2x,A14,2x,D16.8,2x,I3,2x,D16.8)
      end do    
@@ -276,7 +276,7 @@
    do i=8,39
     INQUIRE(UNIT=i, SIZE=file_size)
     READ(UNIT=i,FMT='(A)',IOSTAT=ERROR) STTR 
-     if((ERROR.eq.0).AND.(STR.eq.'#')) then  
+     if((ERROR.eq.0).AND.(STTR.eq.'#')) then  
       goto 1000
      end if            
          if((ERROR.ne.0).AND.(STTR.ne.'#')) then 
diff -Naur SRC_pes/read_database2.f SRC_pes/read_database2.f
--- SRC_pes/read_database2.f	2018-06-07 12:27:06.685830000 +0200
+++ SRC_pes/read_database2.f	2018-07-10 12:12:44.894720611 +0200
@@ -65,7 +65,7 @@
 !! close (4)
  rewind 4
 
- if (data_exist.eq..false.)then
+ if (data_exist.eqv..false.)then
     print *, 'No data on this configuration:', ' ', output_names(J);
     print *, 'Value 0.0 has been assigneed to the ceoss section'
     cross_section(J)= 0.0
diff -Naur SRC_pes/read_dos.f SRC_pes/read_dos.f
--- SRC_pes/read_dos.f	2018-06-07 12:27:06.561829000 +0200
+++ SRC_pes/read_dos.f	2018-07-10 12:14:42.591389057 +0200
@@ -38,17 +38,17 @@
        100 REWIND(7+round)
 
     read(7+round,301,  end=300)BAND
-    301 FORMAT (7x,I)
+    301 FORMAT (7x,I5)
     read(7+round,400,end=300) EF,n_clmn,n_row,GB
     !400 format(24x,i3,10x,i5)
-     400 format(4x,f10.5,10x,i3,10x,i8,20x,f)
+     400 format(4x,f10.5,10x,i3,10x,i8,20x,f10.5)
     300 if (n_clmn.eq.0)then
            print *,'Data reading stoped, corrupted case DOS file.'
            else
            read(7+round,*,end=500) (temp(j),j=-1,n_clmn)                  
            500 do i=1,n_row
                   read (7+round,600,end=700)(dosdata(i,j),j=start,n_clmn+start)
-                  600 format(f10.5,<n_clmn>f14.8)
+                  600 format(f10.5,7f14.8)
                   700 do j=start,n_clmn+start
                     if ( dosdata(i,j).ne.dosdata(i,j)) then
                     print *, 'Error in reading case DOS file'
diff -Naur SRC_pes/read_int.f SRC_pes/read_int.f
--- SRC_pes/read_int.f	2018-06-07 12:27:06.477829000 +0200
+++ SRC_pes/read_int.f	2018-07-10 12:26:30.060112499 +0200
@@ -15,7 +15,7 @@
         if (lexist) then
            read(22,*)
             read(22,*)
-             read(22,100),ndos
+             read(22,100) ndos
               100 format(I5)
              !  print *,'Number of DOS columns in CASE.int :',ndos
                 else 
diff -Naur SRC_pes/SPLINE.f SRC_pes/SPLINE.f
--- SRC_pes/SPLINE.f	2018-06-07 12:27:06.177828000 +0200
+++ SRC_pes/SPLINE.f	2018-07-10 12:25:34.977815472 +0200
@@ -12,11 +12,11 @@
    REAL *8                                :: delta_x
    REAL *8, DIMENSION(1:9)                :: p0, p1, p2, p3
 
-   call  setup(p0, p1, p2, p3, delta_x,X,F,N,strt,stp,J,interpolation)
+   call  setup(delta_x,X,F,N,strt,stp,J,interpolation)
 
 END SUBROUTINE SPLINE
 
-subroutine setup(p0, p1, p2, p3, delta_x,tempx,tempy,n,strt,stp,J,interpolation)
+subroutine setup(delta_x,tempx,tempy,n,strt,stp,J,interpolation)
     
     USE main  ,ONLY :excitation_energy,output_names
     USE find_orbital,only : cross_section
@@ -28,7 +28,7 @@
     integer ,intent(in)                 :: n,strt,stp,J
     real*16  ,dimension(1000),intent(in):: tempx,tempy  ! given points
     real(dp),intent(in)                 :: delta_x
-    real(dp),dimension(:),allocatable, intent(out) :: p0, p1, p2, p3 ! spline coefficients
+    real(dp),dimension(:),allocatable   :: p0, p1, p2, p3 ! spline coefficients
     ! local
     integer                             :: i
     real(dp), dimension(:),allocatable  :: m


More information about the Wien mailing list