added NEWCORR5D
[unres4.git] / source / unres / io_config.F90
index 9b036aa..4d1d103 100644 (file)
           dsc_inv(i)=1.0D0/dsc(i)
         endif
       enddo
+!      ip(1)=0.0001d0
+!      isc(:,1)=0.0001d0
 #endif
       read (ibond_nucl,*) vbldp0_nucl,akp_nucl,mp(2),ip(2),pstok(2)
       do i=1,ntyp_molec(2)
          enddo  
        endif
       enddo
+#ifdef SC_END
+      allocate(nterm_scend(2,ntyp))
+      allocate(arotam_end(0:6,2,ntyp))
+      nterm_scend=0
+      arotam_end=0.0d0
+      read (irotam_end,*) ijunk
+!c      write (iout,*) "ijunk",ijunk
+      do i=1,ntyp
+        if (i.eq.10) cycle
+        do j=1,2
+          read (irotam_end,'(a)')
+          read (irotam_end,*) nterm_scend(j,i)
+!c          write (iout,*) "i",i," j",j," nterm",nterm_scend(j,i)
+          do k=0,nterm_scend(j,i)
+            read (irotam_end,*) ijunk,arotam_end(k,j,i)
+!c            write (iout,*) "k",k," arotam",arotam_end(k,j,i)
+          enddo
+        enddo
+      enddo
+!c      lprint=.true.
+      if (lprint) then
+        write (iout,'(a)') &
+         "Parameters of the local potentials of sidechain ends"
+        do i=1,ntyp
+          write (iout,'(5x,9x,2hp-,a3,6x,9x,a3,2h-p)')&
+          restyp(i,1),restyp(i,1)
+          do j=0,max0(nterm_scend(1,i),nterm_scend(2,i))
+            write (iout,'(i5,2f20.10)') &
+             j,arotam_end(j,1,i),arotam_end(j,2,i)
+          enddo
+        enddo
+      endif
+!c      lprint=.false.
+#endif
+
 !---------reading nucleic acid parameters for rotamers-------------------
       allocate(sc_parmin_nucl(9,ntyp_molec(2)))      !(maxsccoef,ntyp)
       do i=1,ntyp_molec(2)
         sigiso2(i,j)=sigiso2(j,i)
 !        print *,"ATU",sigma(j,i),sigma(i,j),i,j
         nstate(i,j) = nstate(j,i)
-        dtail(1,i,j) = dtail(1,j,i)
-        dtail(2,i,j) = dtail(2,j,i)
+        dtail(1,i,j) = dtail(2,j,i)
+        dtail(2,i,j) = dtail(1,j,i)
         DO k = 1, 4
          alphasur(k,i,j) = alphasur(k,j,i)
          wstate(k,i,j) = wstate(k,j,i)
       cou=1
         write (iout,*) "symetr", symetr
       do i=1,nres
-      lll=lll+1
+       lll=lll+1
 !      write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
-      if (i.gt.1) then
-      if ((itype(i-1,1).eq.ntyp1).and.(i.gt.2)) then
-      chain_length=lll-1
-      kkk=kkk+1
+!      if (i.gt.1) then
+!      if ((itype(i-1,1).eq.ntyp1).and.(i.gt.2)) then
+!      chain_length=lll-1
+!      kkk=kkk+1
 !       write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
-      lll=1
-      endif
-      endif
+!      lll=1
+!      endif
+!      endif
         do j=1,3
           cref(j,i,cou)=c(j,i)
           cref(j,i+nres,cou)=c(j,i+nres)
           endif
          enddo
       enddo
-      write (iout,*) chain_length
-      if (chain_length.eq.0) chain_length=nres
-      do j=1,3
-      chain_rep(j,chain_length,symetr)=chain_rep(j,chain_length,1)
-      chain_rep(j,chain_length+nres,symetr) &
-      =chain_rep(j,chain_length+nres,1)
-      enddo
 ! diagnostic
 !       write (iout,*) "spraw lancuchy",chain_length,symetr
 !       do i=1,4
       dc(j,0)=c(j,1)
       enddo
 
-      if (symetr.gt.1) then
-       call permut(symetr)
-       nperm=1
-       do i=1,symetr
-       nperm=nperm*i
-       enddo
-       do i=1,nperm
-       write(iout,*) (tabperm(i,kkk),kkk=1,4)
-       enddo
-       do i=1,nperm
-        cou=0
-        do kkk=1,symetr
-         icha=tabperm(i,kkk)
-         write (iout,*) i,icha
-         do lll=1,chain_length
-          cou=cou+1
-           if (cou.le.nres) then
-           do j=1,3
-            kupa=mod(lll,chain_length)
-            iprzes=(kkk-1)*chain_length+lll
-            if (kupa.eq.0) kupa=chain_length
-            write (iout,*) "kupa", kupa
-            cref(j,iprzes,i)=chain_rep(j,kupa,icha)
-            cref(j,iprzes+nres,i)=chain_rep(j,kupa+nres,icha)
-          enddo
-          endif
-         enddo
-        enddo
-       enddo
-       endif
+!      if (symetr.gt.1) then
+!       call permut(symetr)
+!       nperm=1
+!       do i=1,symetr
+!       nperm=nperm*i
+!       enddo
+!      do i=1,nperm
+!      write(iout,*) (tabperm(i,kkk),kkk=1,4)
+!      enddo
+!      do i=1,nperm
+!       cou=0
+!       do kkk=1,symetr
+!        icha=tabperm(i,kkk)
+!        write (iout,*) i,icha
+!        do lll=1,chain_length
+!         cou=cou+1
+!          if (cou.le.nres) then
+!          do j=1,3
+!           kupa=mod(lll,chain_length)
+!           iprzes=(kkk-1)*chain_length+lll
+!           if (kupa.eq.0) kupa=chain_length
+!           write (iout,*) "kupa", kupa
+!           cref(j,iprzes,i)=chain_rep(j,kupa,icha)
+!           cref(j,iprzes+nres,i)=chain_rep(j,kupa+nres,icha)
+!         enddo
+!         endif
+!        enddo
+!       enddo
+!      enddo
+!      endif
 !-koniec robienia kopii
 ! diag
       do kkk=1,nperm
 !      print *,"Processor",myrank," opened file ITHEP" 
       call getenv_loc('ROTPAR',rotname)
       open (irotam,file=rotname,status='old',action='read')
+#ifdef SC_END
+      call getenv_loc('ROTPAR_END',rotname_end)
+      open (irotam_end,file=rotname_end,status='old',action='read')
+#endif
 !      print *,"Processor",myrank," opened file IROTAM" 
       call getenv_loc('TORPAR',torname)
       open (itorp,file=torname,status='old',action='read')
       open (ithep,file=thetname,status='old')
       call getenv_loc('ROTPAR',rotname)
       open (irotam,file=rotname,status='old')
+#ifdef SC_END
+      call getenv_loc('ROTPAR_END',rotname_end)
+      open (irotam_end,file=rotname_end,status='old')
+#endif
       call getenv_loc('TORPAR',torname)
       open (itorp,file=torname,status='old')
       call getenv_loc('TORDPAR',tordname)
       open (ithep,file=thetname,status='old',action='read')
       call getenv_loc('ROTPAR',rotname)
       open (irotam,file=rotname,status='old',action='read')
+#ifdef SC_END
+      call getenv_loc('ROTPAR_END',rotname_end)
+      open (irotam_end,file=rotname_end,status='old',action='read')
+#endif
       call getenv_loc('TORPAR',torname)
       open (itorp,file=torname,status='old',action='read')
       call getenv_loc('TORDPAR',tordname)