pdbread-mult
[unres.git] / source / unres / src-HCD-5D / parmread.F
index aad982a..721d05b 100644 (file)
@@ -7,7 +7,7 @@ C Important! Energy-term weights ARE NOT read here; they are read from the
 C main input file instead, because NO defaults have yet been set for these
 C parameters.
 C
-      implicit real*8 (a-h,o-z)
+      implicit none
       include 'DIMENSIONS'
 #ifdef MPI
       include "mpif.h"
@@ -25,6 +25,20 @@ C
       include 'COMMON.NAMES'
       include 'COMMON.SBRIDGE'
       include 'COMMON.MD'
+#ifdef FIVEDIAG
+       include 'COMMON.LAGRANGE.5diag'
+#else
+       include 'COMMON.LAGRANGE'
+#endif
+#ifdef LANG0
+#ifdef FIVEDIAG
+      include 'COMMON.LANGEVIN.lang0.5diag'
+#else
+      include 'COMMON.LANGEVIN.lang0'
+#endif
+#else
+      include 'COMMON.LANGEVIN'
+#endif
       include 'COMMON.SETUP'
       include 'COMMON.CONTROL'
       include 'COMMON.SHIELD'
@@ -32,11 +46,17 @@ C
       character*1 onelett(4) /"G","A","P","D"/
       character*1 toronelet(-2:2) /"p","a","G","A","P"/
       logical lprint,LaTeX
-      dimension blower(3,3,maxlob)
+      double precision blower(3,3,maxlob)
       character*3 string
-C      dimension b(13)
       character*3 lancuch,ucase
       character*1000 weightcard
+      character*4 res1
+      integer i,ii,j,jj,k,kk,l,ll,lll,llll,m,mm,n,iblock,junk,ijunk,
+     & nkcctyp,maxinter
+      double precision akl,v0ij,si,rri,epsij,v0ijsccor,epsijlip,rjunk,
+     & sigt2sq,sigt1sq,sigii1,sigii2,ratsig1,ratsig2,rsum_max,r_augm,
+     & rrij,sigeps
+      double precision dwa16
 C
 C For printing parameters after they are read set the following in the UNRES
 C C-shell script:
@@ -49,6 +69,7 @@ C setenv LATEX YES
 C
       call getenv_loc("PRINT_PARM",lancuch)
       lprint = (ucase(lancuch).eq."YES" .or. ucase(lancuch).eq."Y")
+     & .and. (me.eq.king.or..not.out1file) .and. fg_rank.eq.0
       call getenv_loc("LATEX",lancuch)
       LaTeX = (ucase(lancuch).eq."YES" .or. ucase(lancuch).eq."Y")
 C
@@ -101,6 +122,7 @@ c
      &        vbldsc0(j,i),aksc(j,i),abond0(j,i)
           enddo
         enddo
+        call flush(iout)
       endif
 C reading lipid parameters
       if (lprint) then
@@ -112,6 +134,13 @@ C reading lipid parameters
        read(iliptranpar,*) liptranene(i)
        enddo
        close(iliptranpar)
+       if (lprint) then
+         write (iout,'(/a)') "Water-lipid transfer parameters"
+         write (iout,'(a3,3x,f10.5)') 'p',pepliptran
+         do i=1,ntyp
+           write (iout,'(a3,3x,f10.5)') restyp(i),liptranene(i)
+         enddo
+       endif
 #ifdef CRYST_THETA
 C
 C Read the parameters of the probability distribution/energy expression 
@@ -433,6 +462,7 @@ C here will be the apropriate recalibrating for D-aminoacid
 c      write (2,*) "Start reading THETA_PDB",ithep_pdb
       do i=1,ntyp
 c      write (2,*) 'i=',i
+      call flush(iout)
         read (ithep_pdb,*,err=111,end=111)
      &     a0thet(i),(athet(j,i,1,1),j=1,2),
      &    (bthet(j,i,1,1),j=1,2)
@@ -653,6 +683,12 @@ c      write (iout,*) "itype2loc",(itype2loc(i),i=1,ntyp1)
 c      write (iout,*) "nloctyp",nloctyp,
 c     &  " iloctyp",(iloctyp(i),i=0,nloctyp)
 #ifdef NEWCORR
+      bnew1=0.0d0
+      bnew2=0.0d0
+      ccnew=0.0d0
+      ddnew=0.0d0
+      eenew=0.0d0
+      e0new=0.0d0
       do i=0,nloctyp-1
 c             write (iout,*) "NEWCORR",i
         read (ifourier,*,end=115,err=115)
@@ -734,7 +770,8 @@ c          ddnew(ii,2,i)=ddnew(ii,2,i)/2
       enddo
       if (lprint) then
         write (iout,'(a)') "Coefficients of the multibody terms"
-        do i=-nloctyp+1,nloctyp-1
+c        do i=-nloctyp+1,nloctyp-1
+        do i=-nloctyp,nloctyp
           write (iout,*) "Type: ",onelet(iloctyp(i))
           write (iout,*) "Coefficients of the expansion of B1"
           do j=1,2
@@ -981,8 +1018,8 @@ c        Dtilde(2,2,i)=0.0d0
         EEold(2,2,-i)=-b(10,i)+b(11,i)
         EEold(2,1,-i)=-b(12,i)+b(13,i)
         EEold(1,2,-i)=-b(12,i)-b(13,i)
-c        write(iout,*) "TU DOCHODZE"
-c        print *,"JESTEM"
+        write(iout,*) "TU DOCHODZE"
+        print *,"JESTEM"
 c        ee(1,1,i)=1.0d0
 c        ee(2,2,i)=1.0d0
 c        ee(2,1,i)=0.0d0
@@ -1425,7 +1462,7 @@ cc maxinter is maximum interaction sites
 
 #endif      
       if (lprint) then
-        write (iout,'(/a/)') 'Torsional constants:'
+        write (iout,'(/a/)') 'SCCor torsional constants:'
         do l=1,maxinter
         do i=1,nsccortyp
           do j=1,nsccortyp
@@ -1442,6 +1479,7 @@ cc maxinter is maximum interaction sites
           enddo
         enddo
         enddo
+        call flush(iout)
       endif
 
 C 
@@ -1871,7 +1909,7 @@ C Important! Energy-term weights ARE NOT read here; they are read from the
 C main input file instead, because NO defaults have yet been set for these
 C parameters.
 C
-      implicit real*8 (a-h,o-z)
+      implicit none
       include 'DIMENSIONS'
 #ifdef MPI
       include "mpif.h"
@@ -1893,6 +1931,8 @@ C
       include 'COMMON.CONTROL'
       include 'COMMON.SHIELD'
       character*1000 weightcard
+      integer i,j
+      double precision scalscp,wlong
 c
 c READ energy-term weights
 c
@@ -1922,6 +1962,7 @@ c
       call reada(weightcard,'WDFAB',wdfa_beta,0.0d0)
       call reada(weightcard,'SCAL14',scal14,0.4D0)
       call reada(weightcard,'SCALSCP',scalscp,1.0d0)
+      call reada(weightcard,'LIPSCALE',lipscale,1.0D0)
       call reada(weightcard,'CUTOFF',cutoff_corr,7.0d0)
       call reada(weightcard,'DELT_CORR',delt_corr,0.5d0)
       call reada(weightcard,'TEMP0',temp0,300.0d0)
@@ -2007,8 +2048,15 @@ C 12/1/95 Added weight for the multi-body term WCORR
       call rescale_weights(t_bath)
       if(me.eq.king.or..not.out1file)
      & write (iout,22) wsc,wscp,welec,wvdwpp,wbond,wang,wscloc,wtor,
-     &  wtor_d,wstrain,wel_loc,wcorr,wcorr5,wcorr6,wsccor,wturn3,
-     &  wturn4,wturn6
+     &  wtor_d,wstrain,wel_loc,
+#ifdef FOURBODY
+     &  wcorr,wcorr5,wcorr6,
+#endif
+     &  wsccor,wturn3,
+#ifdef FOURBODY
+     &  wturn4, 
+#endif
+     &  wturn6
    22 format (/'Energy-term weights (scaled):'//
      & 'WSCC=   ',f10.6,' (SC-SC)'/
      & 'WSCP=   ',f10.6,' (SC-p)'/
@@ -2021,13 +2069,18 @@ C 12/1/95 Added weight for the multi-body term WCORR
      & 'WTORD=  ',f10.6,' (double torsional)'/
      & 'WSTRAIN=',f10.6,' (SS bridges & dist. cnstr.)'/
      & 'WEL_LOC=',f10.6,' (multi-body 3-rd order)'/
+#ifdef FOURBODY
      & 'WCORR4= ',f10.6,' (multi-body 4th order)'/
      & 'WCORR5= ',f10.6,' (multi-body 5th order)'/
      & 'WCORR6= ',f10.6,' (multi-body 6th order)'/
-     & 'WSCCOR= ',f10.6,' (back-scloc correlatkion)'/
+#endif
+     & 'WSCCOR= ',f10.6,' (back-scloc correlation)'/
      & 'WTURN3= ',f10.6,' (turns, 3rd order)'/
      & 'WTURN4= ',f10.6,' (turns, 4th order)'/
-     & 'WTURN6= ',f10.6,' (turns, 6th order)')
+#ifdef FOURBODY
+     & 'WTURN6= ',f10.6,' (turns, 6th order)'
+#endif
+     & )
       if(me.eq.king.or..not.out1file)
      & write (iout,*) "Reference temperature for weights calculation:",
      &  temp0
@@ -2055,11 +2108,12 @@ C 12/1/95 Added weight for the multi-body term WCORR
       do i=1,maxres
         dyn_ss_mask(i)=.false.
       enddo
-      do i=1,maxres-1
-        do j=i+1,maxres
+      do i=1,max_cyst-1
+        do j=i+1,max_cyst
           dyn_ssbond_ij(i,j)=1.0d300
         enddo
       enddo
+      call flush(iout)
       call reada(weightcard,"HT",Ht,0.0D0)
       if (dyn_ss) then
         ss_depth=ebr/wsc-0.25*eps(1,1)
@@ -2090,7 +2144,7 @@ C 12/1/95 Added weight for the multi-body term WCORR
        write (iout,*) "BTRISS=", btriss
        write (iout,*) "CTRISS=", ctriss
        write (iout,*) "DTRISS=", dtriss
-       print *,'indpdb=',indpdb,' pdbref=',pdbref
+c       print *,'indpdb=',indpdb,' pdbref=',pdbref
       endif
       return
       end