wham in lipid still diff
[unres.git] / source / wham / src-M / parmread.F
index b2b64d5..914c090 100644 (file)
@@ -78,7 +78,7 @@ c
       wvdwpp=ww(16)
       wbond=ww(18)
       wsccor=ww(19)
-
+      wliptran=ww(22)
       endif
 
       call card_concat(controlcard,.false.)
@@ -150,7 +150,7 @@ c Read the virtual-bond parameters, masses, and moments of inertia
 c and Stokes' radii of the peptide group and side chains
 c
 #ifdef CRYST_BOND
-      read (ibond,*) vbldp0,akp
+      read (ibond,*) vbldp0,vbldpdum,akp
       do i=1,ntyp
         nbondterm(i)=1
         read (ibond,*) vbldsc0(1,i),aksc(1,i)
@@ -162,7 +162,7 @@ c
         endif
       enddo
 #else
-      read (ibond,*) ijunk,vbldp0,akp,rjunk
+      read (ibond,*) ijunk,vbldp0,vbldpdum,akp,rjunk
       do i=1,ntyp
         read (ibond,*) nbondterm(i),(vbldsc0(j,i),aksc(j,i),abond0(j,i),
      &   j=1,nbondterm(i))
@@ -188,6 +188,11 @@ c
           enddo
         enddo
       endif
+       read(iliptranpar,*) pepliptran
+       do i=1,ntyp
+       read(iliptranpar,*) liptranene(i)
+       enddo
+       close(iliptranpar)
 #ifdef CRYST_THETA
 C
 C Read the parameters of the probability distribution/energy expression 
@@ -295,6 +300,7 @@ C
 C Read the parameters of Utheta determined from ab initio surfaces
 C Kozlowska et al., J. Phys.: Condens. Matter 19 (2007) 285203
 C
+c      write (iout,*) "tu dochodze"
       read (ithep,*) nthetyp,ntheterm,ntheterm2,
      &  ntheterm3,nsingle,ndouble
       nntheterm=max0(ntheterm,ntheterm2,ntheterm3)
@@ -302,6 +308,7 @@ C
       do i=-ntyp1,-1
         ithetyp(i)=-ithetyp(-i)
       enddo
+c      write (iout,*) "tu dochodze"
       do iblock=1,2
       do i=-maxthetyp,maxthetyp
         do j=-maxthetyp,maxthetyp
@@ -420,14 +427,14 @@ C
               write (iout,'(//a,10x,a)') " l","a[l]"
               write (iout,'(i2,1pe15.5)') 0,aa0thet(i,j,k,iblock)
               write (iout,'(i2,1pe15.5)')
-     &           (l,aathet(l,i,j,k),l=1,ntheterm)
+     &           (l,aathet(l,i,j,k,iblock),l=1,ntheterm)
             do l=1,ntheterm2
               write (iout,'(//2h m,4(9x,a,3h[m,i1,1h]))')
      &          "b",l,"c",l,"d",l,"e",l
               do m=1,nsingle
                 write (iout,'(i2,4(1pe15.5))') m,
-     &          bbthet(m,l,i,j,k),ccthet(m,l,i,j,k,iblock),
-     &          ddthet(m,l,i,j,k),eethet(m,l,i,j,k,iblock)
+     &          bbthet(m,l,i,j,k,iblock),ccthet(m,l,i,j,k,iblock),
+     &          ddthet(m,l,i,j,k,iblock),eethet(m,l,i,j,k,iblock)
               enddo
             enddo
             do l=1,ntheterm3
@@ -980,8 +987,10 @@ C
         bpp (i,j)=-2.0D0*epp(i,j)*rri
         ael6(i,j)=elpp6(i,j)*4.2D0**6
         ael3(i,j)=elpp3(i,j)*4.2D0**3
+        lprint=.true.
         if (lprint) write(iout,'(2i3,4(1pe15.4))')i,j,app(i,j),bpp(i,j),
      &                    ael6(i,j),ael3(i,j)
+         lprint=.false.
         enddo
       enddo
 C
@@ -1022,13 +1031,24 @@ C----------------------- LJK potential --------------------------------
       endif
       goto 50
 C---------------------- GB or BP potential -----------------------------
-   30 read (isidep,*)((eps(i,j),j=i,ntyp),i=1,ntyp),
-     &  (sigma0(i),i=1,ntyp),(sigii(i),i=1,ntyp),(chip0(i),i=1,ntyp),
-     &  (alp(i),i=1,ntyp)
+   30 do i=1,ntyp
+       read (isidep,*)(eps(i,j),j=i,ntyp)
+      enddo
+      read (isidep,*)(sigma0(i),i=1,ntyp)
+      read (isidep,*)(sigii(i),i=1,ntyp)
+      read (isidep,*)(chip(i),i=1,ntyp)
+      read (isidep,*)(alp(i),i=1,ntyp)
+      do i=1,ntyp
+       read (isidep,*)(epslip(i,j),j=i,ntyp)
+C       print *,"WARNING!!"
+C       do j=1,ntyp
+C       epslip(i,j)=epslip(i,j)+0.05d0
+C       enddo
+      enddo
 C For the GB potential convert sigma'**2 into chi'
       if (ipot.eq.4) then
        do i=1,ntyp
-         chip(i)=(chip0(i)-1.0D0)/(chip0(i)+1.0D0)
+         chip(i)=(chip(i)-1.0D0)/(chip(i)+1.0D0)
         enddo
       endif
       if (lprint) then
@@ -1063,6 +1083,7 @@ C Calculate the "working" parameters of SC interactions.
       do i=2,ntyp
         do j=1,i-1
          eps(i,j)=eps(j,i)
+          epslip(i,j)=epslip(j,i)
         enddo
       enddo
       do i=1,ntyp
@@ -1080,6 +1101,7 @@ C Calculate the "working" parameters of SC interactions.
       do i=1,ntyp
        do j=i,ntyp
          epsij=eps(i,j)
+          epsijlip=epslip(i,j)
          if (ipot.eq.1 .or. ipot.eq.3 .or. ipot.eq.4) then
            rrij=sigma(i,j)
           else
@@ -1091,10 +1113,16 @@ C Calculate the "working" parameters of SC interactions.
          epsij=eps(i,j)
          sigeps=dsign(1.0D0,epsij)
          epsij=dabs(epsij)
-         aa(i,j)=epsij*rrij*rrij
-         bb(i,j)=-sigeps*epsij*rrij
-         aa(j,i)=aa(i,j)
-         bb(j,i)=bb(i,j)
+         aa_aq(i,j)=epsij*rrij*rrij
+         bb_aq(i,j)=-sigeps*epsij*rrij
+         aa_aq(j,i)=aa_aq(i,j)
+         bb_aq(j,i)=bb_aq(i,j)
+          sigeps=dsign(1.0D0,epsijlip)
+          epsijlip=dabs(epsijlip)
+          aa_lip(i,j)=epsijlip*rrij*rrij
+          bb_lip(i,j)=-sigeps*epsijlip*rrij
+          aa_lip(j,i)=aa_lip(i,j)
+          bb_lip(j,i)=bb_lip(i,j)
          if (ipot.gt.2) then
            sigt1sq=sigma0(i)**2
            sigt2sq=sigma0(j)**2