update
[unres.git] / source / unres / src_MD-M / geomout.F
index 47e8c7e..6cb9968 100644 (file)
@@ -80,9 +80,15 @@ cmodel      write (iunit,'(a5,i6)') 'MODEL',1
 
       if (nss.gt.0) then
         do i=1,nss
+         if (dyn_ss) then
           write(iunit,'(a6,i4,1x,a3,i7,4x,a3,i7)') 
-     &         'SSBOND',i,'CYS',ihpb(i)-1-nres,
-     &                    'CYS',jhpb(i)-1-nres
+     &         'SSBOND',i,'CYS',idssb(i)-nnt+1,
+     &                    'CYS',jdssb(i)-nnt+1
+         else
+          write(iunit,'(a6,i4,1x,a3,i7,4x,a3,i7)') 
+     &         'SSBOND',i,'CYS',ihpb(i)-nnt+1-nres,
+     &                    'CYS',jhpb(i)-nnt+1-nres
+         endif
         enddo
       endif
       
@@ -91,7 +97,7 @@ cmodel      write (iunit,'(a5,i6)') 'MODEL',1
       ires=0
       do i=nnt,nct
         iti=itype(i)
-        if (iti.eq.21) then
+        if ((iti.eq.ntyp1).and.((itype(i+1)).eq.ntyp1)) then
           ichain=ichain+1
           ires=0
           write (iunit,'(a)') 'TER'
@@ -99,6 +105,7 @@ cmodel      write (iunit,'(a5,i6)') 'MODEL',1
         ires=ires+1
         iatom=iatom+1
         ica(i)=iatom
+        if (iti.ne.ntyp1) then
         write (iunit,10) iatom,restyp(iti),chainid(ichain),
      &     ires,(c(j,i),j=1,3),vtot(i)
         if (iti.ne.10) then
@@ -106,17 +113,18 @@ cmodel      write (iunit,'(a5,i6)') 'MODEL',1
           write (iunit,20) iatom,restyp(iti),chainid(ichain),
      &      ires,(c(j,nres+i),j=1,3),
      &      vtot(i+nres)
+         endif
         endif
         endif
       enddo
       write (iunit,'(a)') 'TER'
       do i=nnt,nct-1
-        if (itype(i).eq.21) cycle
-        if (itype(i).eq.10 .and. itype(i+1).ne.21) then
+        if (itype(i).eq.ntyp1) cycle
+        if (itype(i).eq.10 .and. itype(i+1).ne.ntyp1) then
           write (iunit,30) ica(i),ica(i+1)
-        else if (itype(i).ne.10 .and. itype(i+1).ne.21) then
+        else if (itype(i).ne.10 .and. itype(i+1).ne.ntyp1) then
           write (iunit,30) ica(i),ica(i+1),ica(i)+1
-        else if (itype(i).ne.10 .and. itype(i+1).eq.21) then
+        else if (itype(i).ne.10 .and. itype(i+1).eq.ntyp1) then
           write (iunit,30) ica(i),ica(i)+1
         endif
       enddo
@@ -124,7 +132,11 @@ cmodel      write (iunit,'(a5,i6)') 'MODEL',1
         write (iunit,30) ica(nct),ica(nct)+1
       endif
       do i=1,nss
+       if (dyn_ss) then
+        write (iunit,30) ica(idssb(i))+1,ica(jdssb(i))+1
+       else
         write (iunit,30) ica(ihpb(i)-nres)+1,ica(jhpb(i)-nres)+1
+       endif
       enddo
       write (iunit,'(a6)') 'ENDMDL'     
   10  FORMAT ('ATOM',I7,'  CA  ',A3,1X,A1,I4,4X,3F8.3,f15.3)
@@ -200,6 +212,7 @@ c------------------------------------------------------------------------
       include 'COMMON.INTERACT'
       include 'COMMON.NAMES'
       include 'COMMON.GEO'
+      include 'COMMON.TORSION'
       write (iout,'(/a)') 'Geometry of the virtual chain.'
       write (iout,'(7a)') '  Res  ','         d','     Theta',
      & '       Phi','       Dsc','     Alpha','      Omega'
@@ -224,7 +237,7 @@ c---------------------------------------------------------------------------
       include 'COMMON.GEO'
       include 'COMMON.SBRIDGE'
 c     print '(a,i5)',intname,igeom
-#if defined(AIX) || defined(PGI)
+#if defined(AIX) || defined(PGI) || defined(CRAY)
       open (igeom,file=intname,position='append')
 #else
       open (igeom,file=intname,access='append')
@@ -272,14 +285,19 @@ c----------------------------------------------------------------
       include 'COMMON.DISTFIT'
       include 'COMMON.MD'
       double precision time
-#if defined(AIX) || defined(PGI)
+#if defined(AIX) || defined(PGI) || defined(CRAY)
       open(icart,file=cartname,position="append")
 #else
       open(icart,file=cartname,access="append")
 #endif
       write (icart,'(e15.8,2e15.5,f12.5,$)') time,potE,uconst,t_bath
-      write (icart,'(i4,$)')
+      if (dyn_ss) then
+       write (icart,'(i4,$)')
+     &   nss,(idssb(j)+nres,jdssb(j)+nres,j=1,nss)       
+      else
+       write (icart,'(i4,$)')
      &   nss,(ihpb(j),jhpb(j),j=1,nss)
+       endif
        write (icart,'(i4,20f7.4)') nfrag+npair+3*nfrag_back,
      & (qfrag(i),i=1,nfrag),(qpair(i),i=1,npair),
      & (utheta(i),ugamma(i),uscdiff(i),i=1,nfrag_back)
@@ -321,8 +339,13 @@ c-----------------------------------------------------------------
       call xdrffloat_(ixdrf, real(t_bath), iret)
       call xdrfint_(ixdrf, nss, iret) 
       do j=1,nss
+       if (dyn_ss) then
+        call xdrfint_(ixdrf, idssb(j)+nres, iret)
+        call xdrfint_(ixdrf, jdssb(j)+nres, iret)
+       else
         call xdrfint_(ixdrf, ihpb(j), iret)
         call xdrfint_(ixdrf, jhpb(j), iret)
+       endif
       enddo
       call xdrfint_(ixdrf, nfrag+npair+3*nfrag_back, iret)
       do i=1,nfrag
@@ -338,6 +361,9 @@ c-----------------------------------------------------------------
       enddo
 #else
       call xdrfopen(ixdrf,cartname, "a", iret)
+      write (iout,*) "Writing conformation: time",time," potE",potE,
+     & " uconst",uconst," uconst_back",uconst_back," t_bath",t_bath,
+     & " nss",nss
       call xdrffloat(ixdrf, real(time), iret)
       call xdrffloat(ixdrf, real(potE), iret)
       call xdrffloat(ixdrf, real(uconst), iret)
@@ -345,8 +371,13 @@ c-----------------------------------------------------------------
       call xdrffloat(ixdrf, real(t_bath), iret)
       call xdrfint(ixdrf, nss, iret) 
       do j=1,nss
+       if (dyn_ss) then
+        call xdrfint(ixdrf, idssb(j)+nres, iret)
+        call xdrfint(ixdrf, jdssb(j)+nres, iret)
+       else
         call xdrfint(ixdrf, ihpb(j), iret)
         call xdrfint(ixdrf, jhpb(j), iret)
+       endif
       enddo
       call xdrfint(ixdrf, nfrag+npair+3*nfrag_back, iret)
       do i=1,nfrag
@@ -397,6 +428,7 @@ c-----------------------------------------------------------------
       include 'COMMON.SBRIDGE'
       include 'COMMON.DISTFIT'
       include 'COMMON.MD'
+      include 'COMMON.REMD'
       include 'COMMON.SETUP'
       integer itime
       double precision energia(0:n_ene)
@@ -411,12 +443,52 @@ c-----------------------------------------------------------------
        open(istat,file=statname,position="append")
       endif
 #else
-#ifdef PGI
+#if defined(PGI) || defined(CRAY)
       open(istat,file=statname,position="append")
 #else
       open(istat,file=statname,access="append")
 #endif
 #endif
+       if (AFMlog.gt.0) then
+       if (refstr) then
+         call rms_nac_nnc(rms,frac,frac_nn,co,.false.)
+          write (line1,'(i10,f15.2,3f12.3,f7.2,2f6.3,4f12.3,i5,$)')
+     &          itime,totT,EK,potE,totE,
+     &          rms,frac,frac_nn,kinetic_T,t_bath,gyrate(),
+     &          potEcomp(23),me
+          format1="a133"
+         else
+C          print *,'A CHUJ',potEcomp(23)
+          write (line1,'(i10,f15.2,7f12.3,i5,$)')
+     &           itime,totT,EK,potE,totE,
+     &           kinetic_T,t_bath,gyrate(),
+     &           potEcomp(23),me
+          format1="a114"
+        endif
+       else if (selfguide.gt.0) then
+       distance=0.0
+       do j=1,3
+       distance=distance+(c(j,afmend)-c(j,afmbeg))**2
+       enddo
+       distance=dsqrt(distance)
+       if (refstr) then
+         call rms_nac_nnc(rms,frac,frac_nn,co,.false.)
+          write (line1,'(i10,f15.2,3f12.3,f7.2,2f6.3,f12.3,f10.1,2f8.2,
+     &    f9.3,i5,$)')
+     &          itime,totT,EK,potE,totE,
+     &          rms,frac,frac_nn,kinetic_T,t_bath,gyrate(),
+     &          distance,potEcomp(23),me
+          format1="a133"
+C          print *,"CHUJOWO"
+         else
+C          print *,'A CHUJ',potEcomp(23)
+          write (line1,'(i10,f15.2,8f12.3,i5,$)')
+     &           itime,totT,EK,potE,totE,
+     &           kinetic_T,t_bath,gyrate(),
+     &           distance,potEcomp(23),me
+          format1="a114"
+        endif
+       else
        if (refstr) then
          call rms_nac_nnc(rms,frac,frac_nn,co,.false.)
           write (line1,'(i10,f15.2,3f12.3,f7.2,4f6.3,3f12.3,i5,$)')
@@ -429,17 +501,33 @@ c-----------------------------------------------------------------
      &           amax,kinetic_T,t_bath,gyrate(),me
           format1="a114"
         endif
+        endif
         if(usampl.and.totT.gt.eq_time) then
+           if (loc_qlike) then
+           write(line2,'(i5,2f9.4,300f7.4)') iset,uconst,uconst_back,
+     &      (qfrag(ii1),ii1=1,nfrag),(qpair(ii2),ii2=1,npair),
+     &      (utheta(i),ugamma(i),uscdiff(i),i=1,nfrag_back),
+     &      ((qloc(j,i),j=1,3),i=1,nfrag_back)
+           write(format2,'(a1,i3.3)') "a",23+7*nfrag+7*npair
+     &             +42*nfrag_back
+           else
            write(line2,'(i5,2f9.4,300f7.4)') iset,uconst,uconst_back,
      &      (qfrag(ii1),ii1=1,nfrag),(qpair(ii2),ii2=1,npair),
      &      (utheta(i),ugamma(i),uscdiff(i),i=1,nfrag_back)
            write(format2,'(a1,i3.3)') "a",23+7*nfrag+7*npair
      &             +21*nfrag_back
+           endif
         else
            format2="a001"
            line2=' '
         endif
         if (print_compon) then
+          if(itime.eq.0) then
+           write(format,'(a1,a4,a1,a4,a10)') "(",format1,",",format2,
+     &                                                     ",20a12)"
+           write (istat,format) "#","",
+     &      (ename(print_order(i)),i=1,nprint_ene)
+          endif
           write(format,'(a1,a4,a1,a4,a10)') "(",format1,",",format2,
      &                                                     ",20f12.3)"
           write (istat,format) line1,line2,