debugging 5Dia
[unres4.git] / source / unres / io.f90
index 05f3585..a6bda64 100644 (file)
       call reada(weightcard,'WTURN6',wturn6,1.0D0)
       call reada(weightcard,'WSCCOR',wsccor,1.0D0)
       call reada(weightcard,'WSTRAIN',wstrain,1.0D0)
-      call reada(weightcard,'WVDWPP_NUCL',wvdwpp_nucl,1.0D0)
-      call reada(weightcard,'WELPP',welpp,1.0d0)
-      call reada(weightcard,'WVDWPSB',wvdwpsb,1.0d0)
-      call reada(weightcard,'WELPSB',welpsb,1.0D0)
-      call reada(weightcard,'WVDWSB',wvdwsb,1.0d0)
-      call reada(weightcard,'WELSB',welsb,1.0D0)
-      call reada(weightcard,'WBOND_NUCL',wbond_nucl,1.0D0)
-      call reada(weightcard,'WANG_NUCL',wang_nucl,1.0D0)
-      call reada(weightcard,'WSBLOC',wsbloc,1.0D0)
-      call reada(weightcard,'WTOR_NUCL',wtor_nucl,1.0D0)
-      call reada(weightcard,'WTORD_NUCL',wtor_d_nucl,1.0D0)
-      call reada(weightcard,'WCORR_NUCL',wcorr_nucl,1.0D0)
-      call reada(weightcard,'WCORR3_NUCL',wcorr3_nucl,1.0D0)
+      call reada(weightcard,'WVDWPP_NUCL',wvdwpp_nucl,0.0D0)
+      call reada(weightcard,'WELPP',welpp,0.0d0)
+      call reada(weightcard,'WVDWPSB',wvdwpsb,0.0d0)
+      call reada(weightcard,'WELPSB',welpsb,0.0D0)
+      call reada(weightcard,'WVDWSB',wvdwsb,0.0d0)
+      call reada(weightcard,'WELSB',welsb,0.0D0)
+      call reada(weightcard,'WBOND_NUCL',wbond_nucl,0.0D0)
+      call reada(weightcard,'WANG_NUCL',wang_nucl,0.0D0)
+      call reada(weightcard,'WSBLOC',wsbloc,0.0D0)
+      call reada(weightcard,'WTOR_NUCL',wtor_nucl,0.0D0)
+      call reada(weightcard,'WTORD_NUCL',wtor_d_nucl,0.0D0)
+      call reada(weightcard,'WCORR_NUCL',wcorr_nucl,0.0D0)
+      call reada(weightcard,'WCORR3_NUCL',wcorr3_nucl,0.0D0)
       call reada(weightcard,'WBOND',wbond,1.0D0)
       call reada(weightcard,'WTOR',wtor,1.0D0)
       call reada(weightcard,'WTORD',wtor_d,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)
-      call reada(weightcard,'WSCBASE',wscbase,1.0D0)
+      call reada(weightcard,'WSCBASE',wscbase,0.0D0)
       if (index(weightcard,'SOFT').gt.0) ipot=6
-      call reada(weightcard,'WBOND_NUCL',wbond_nucl,1.0D0)
+      call reada(weightcard,'WBOND_NUCL',wbond_nucl,0.0D0)
       call reada(weightcard,'WCATCAT',wcatcat,0.0d0)
       call reada(weightcard,'WCATPROT',wcatprot,0.0d0)
       call reada(weightcard,'WPEPBASE',wpepbase,1.0d0)
-      call reada(weightcard,'WSCPHO',wscpho,1.0d0)
-      call reada(weightcard,'WPEPPHO',wpeppho,1.0d0)
+      call reada(weightcard,'WSCPHO',wscpho,0.0d0)
+      call reada(weightcard,'WPEPPHO',wpeppho,0.0d0)
 
 ! 12/1/95 Added weight for the multi-body term WCORR
       call reada(weightcard,'WCORRH',wcorr,1.0D0)
       if (ndih_constr.gt.0) then
         allocate(idih_constr(ndih_constr),idih_nconstr(ndih_constr)) !(maxdih_constr)
         allocate(phi0(ndih_constr),drange(ndih_constr)) !(maxdih_constr)
+        allocate(ftors(ndih_constr)) !(maxdih_constr)
         
-        read (inp,*) ftors
-        read (inp,*) (idih_constr(i),phi0(i),drange(i),i=1,ndih_constr)
+!        read (inp,*) ftors
+        read (inp,*) (idih_constr(i),phi0(i),drange(i),ftors(i), &
+        i=1,ndih_constr)
         if(me.eq.king.or..not.out1file)then
          write (iout,*) &
          'There are',ndih_constr,' constraints on phi angles.'
          do i=1,ndih_constr
-          write (iout,'(i5,2f8.3)') idih_constr(i),phi0(i),drange(i)
+          write (iout,'(i5,3f8.3)') idih_constr(i),phi0(i),drange(i), &
+          ftors(i)
          enddo
         endif
         do i=1,ndih_constr
           phi0(i)=deg2rad*phi0(i)
           drange(i)=deg2rad*drange(i)
         enddo
-        if(me.eq.king.or..not.out1file) &
-         write (iout,*) 'FTORS',ftors
+!        if(me.eq.king.or..not.out1file) &
+!         write (iout,*) 'FTORS',ftors
         do i=1,ndih_constr
           ii = idih_constr(i)
           phibound(1,ii) = phi0(i)-drange(i)
           omeg(i)=-120d0*deg2rad
           if (itype(i,1).le.0) omeg(i)=-omeg(i)
          enddo
+         call chainbuild
         else
           if(me.eq.king.or..not.out1file) &
            write (iout,'(a)') 'Random-generated initial geometry.'