Fixed eello5, eello6, eturn6, and shortrange RESPA
[unres.git] / source / unres / src_MD-M / parmread.F
index ae4d710..23fe7df 100644 (file)
@@ -58,7 +58,7 @@ C Assign virtual-bond length
       vblinv2=vblinv*vblinv
 c
 c Read the virtual-bond parameters, masses, and moments of inertia
-c and Stokes' radii of the peptide group and side chains
+c and Stokes radii of the peptide group and side chains
 c
 #ifdef CRYST_BOND
       read (ibond,*) vbldp0,vbldpdum,akp,mp,ip,pstok
@@ -99,13 +99,30 @@ c
      &        vbldsc0(j,i),aksc(j,i),abond0(j,i)
           enddo
         enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 C reading lipid parameters
-       read(iliptranpar,*) pepliptran
+       read(iliptranpar,*,end=120,err=120) pepliptran
        do i=1,ntyp
-       read(iliptranpar,*) liptranene(i)
+       read(iliptranpar,*,end=120,err=120) liptranene(i)
        enddo
        close(iliptranpar)
+       if (lprint) then
+         write (iout,*) "Lipid transfer parameters"
+         write (iout,'(a5,f10.5)') "pept",pepliptran
+         do i=1,ntyp
+           write (iout,'(a5,f10.5)') restyp(i),liptranene(i)
+         enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
+       endif
 #ifdef CRYST_THETA
 C
 C Read the parameters of the probability distribution/energy expression 
@@ -182,6 +199,7 @@ C
           write (iout,'(a3,i4,2x,5(1pe14.5))') restyp(i),i,theta0(i),
      &       sig0(i),(gthet(j,i),j=1,3)
         enddo
+        call flush(iout)
        else
        write (iout,'(a)') 
      &    'Parameters of the virtual-bond valence angles:'
@@ -210,6 +228,11 @@ C
           write (iout,'(a3,1h&,2x,5(f8.3,1h&))') restyp(i),theta0(i),
      &       100*sig0(i),gthet(1,i)*0.1D0,gthet(2,i),gthet(3,i)*10.0D0
        enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
       endif
 #else 
@@ -395,9 +418,13 @@ C
           enddo
         enddo
       enddo
-      call flush(iout)
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
-      write (2,*) "Start reading THETA_PDB",ithep_pdb
+      write (iout,*) "Start reading THETA_PDB",ithep_pdb
       do i=1,ntyp
 c      write (2,*) 'i=',i
         read (ithep_pdb,*,err=111,end=111)
@@ -442,7 +469,7 @@ c      write (2,*) 'i=',i
          gthet(j,i)=gthet(j,-i)
        enddo
       enddo
-      write (2,*) "End reading THETA_PDB"
+      write (iout,*) "End reading THETA_PDB"
       close (ithep_pdb)
 #endif
       close(ithep)
@@ -530,6 +557,11 @@ C BSC is amplitude of Gaussian
             endif
          endif
         enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 #else
 C 
@@ -550,7 +582,7 @@ C
 C Read the parameters of the probability distribution/energy expression
 C of the side chains.
 C
-      write (2,*) "Start reading ROTAM_PDB"
+      write (iout,*) "Start reading ROTAM_PDB"
       do i=1,ntyp
         read (irotam_pdb,'(3x,i3,f8.3)',end=112,err=112) nlob(i),dsc(i)
         if (i.eq.10) then
@@ -589,7 +621,12 @@ C
         endif
       enddo
       close (irotam_pdb)
-      write (2,*) "End reading ROTAM_PDB"
+c      write (iout,*) "End reading ROTAM_PDB"
+c#ifdef AIX
+c      call flush_(iout)
+c#else
+c      call flush(iout)
+c#endif
 #endif
       close(irotam)
 
@@ -617,6 +654,11 @@ C
            write (iout,'(6x,6f10.5)') (v2(k,i,j),k=1,nterm_old)
           enddo
         enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 #else
 C
@@ -659,8 +701,16 @@ c      &v2(k,-i,-j,iblock),v2(k,i,j,iblock)
       enddo
       enddo
       close (itorp)
+c      write (iout,*) "End reading torsional parameters"
+c#ifdef AIX
+c      call flush_(iout)
+c#else
+c      call flush(iout)
+c#endif
       if (lprint) then
         write (iout,'(/a/)') 'Torsional constants:'
+        do iblock=1,2
+        write (iout,*) "IBLOCK",iblock
         do i=1,ntortyp
           do j=1,ntortyp
             write (iout,*) 'ityp',i,' jtyp',j
@@ -676,6 +726,12 @@ c      &v2(k,-i,-j,iblock),v2(k,i,j,iblock)
             enddo
           enddo
         enddo
+        enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 
 C
@@ -773,6 +829,11 @@ C Martix of D parameters for two dimesional fourier series
         enddo
       enddo
       enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 #endif
 C Read of Side-chain backbone correlation parameters
@@ -780,6 +841,12 @@ C Modified 11 May 2012 by Adasko
 CCC
 C
       read (isccor,*,end=119,err=119) nsccortyp
+c      write (iout,*) "Reading sccor parameters",nsccortyp
+c#ifdef AIX
+c      call flush_(iout)
+c#else
+c      call flush(iout)
+c#endif
 #ifdef SCCORPDB
       read (isccor,*,end=119,err=119) (isccortyp(i),i=1,ntyp)
       do i=-ntyp,-1
@@ -882,15 +949,23 @@ cc maxinter is maximum interaction sites
             v0ijsccor=v0ijsccor+vlor1sccor(k,i,j)/
      &(1+vlor3sccor(k,i,j)**2)
           enddo
-          v0sccor(i,j,iblock)=v0ijsccor
+          v0sccor(l,i,j)=v0ijsccor
         enddo
       enddo
       enddo
       close (isccor)
 
 #endif      
+c      write (iout,*) "sccor parameters read"
+c#ifdef AIX
+c      call flush_(iout)
+c#else
+c      call flush(iout)
+c#endif
       if (lprint) then
-        write (iout,'(/a/)') 'Torsional constants:'
+        write (iout,'(/a/)') 'SC-torsional constants:'
+        do l=1,maxinter
+        write (iout,*) "Torsional type",l
         do i=1,nsccortyp
           do j=1,nsccortyp
             write (iout,*) 'ityp',i,' jtyp',j
@@ -905,6 +980,12 @@ cc maxinter is maximum interaction sites
             enddo
           enddo
         enddo
+        enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 
 C
@@ -1047,6 +1128,11 @@ c      lprint=.true.
           write (iout,'(2f10.5)') EEold(j,1,i),EEold(j,2,i)
         enddo
       enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 c      lprint=.false.
 
@@ -1077,6 +1163,11 @@ c        lprint=.true.
 c        lprint=.false.
         enddo
       enddo
+#ifdef AIX
+        if (lprint) call flush_(iout)
+#else
+        if (lprint) call flush(iout)
+#endif
 C
 C Read side-chain interaction parameters.
 C
@@ -1251,6 +1342,11 @@ c           augm(i,j)=0.5D0**(2*expon)*aa(i,j)
          endif
         enddo
       enddo
+#ifdef AIX
+        if (lprint) call flush_(iout)
+#else
+        if (lprint) call flush(iout)
+#endif
 #ifdef OLDSCP
 C
 C Define the SC-p interaction constants (hard-coded; old style)
@@ -1297,6 +1393,11 @@ c      lprint=.true.
           write (iout,'(4f8.3,4e12.4)') eps_scp(i,1),rscp(i,1),
      &     eps_scp(i,2),rscp(i,2),aad(i,1),bad(i,1),aad(i,2),bad(i,2)
         enddo
+#ifdef AIX
+        call flush_(iout)
+#else
+        call flush(iout)
+#endif
       endif
 c      lprint=.false.
 #endif
@@ -1357,25 +1458,82 @@ C      buff_shield=1.0d0
 C      endif
       return
   111 write (iout,*) "Error reading bending energy parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   112 write (iout,*) "Error reading rotamer energy parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   113 write (iout,*) "Error reading torsional energy parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   114 write (iout,*) "Error reading double torsional energy parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   115 write (iout,*) 
      &  "Error reading cumulant (multibody energy) parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   116 write (iout,*) "Error reading electrostatic energy parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
  1161 write (iout,*) "Error reading electrostatic energy parameters.Lip"
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   117 write (iout,*) "Error reading side chain interaction parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   118 write (iout,*) "Error reading SCp interaction parameters."
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
       goto 999
   119 write (iout,*) "Error reading SCCOR parameters"
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
+      goto 999
+  120 write (iout,*) "Error reading lipid parameters"
+#ifdef AIX
+      call flush_(iout)
+#else
+      call flush(iout)
+#endif
   999 continue
 #ifdef MPI
       call MPI_Finalize(Ierror)