Merge branch 'UCGM' of mmka.chem.univ.gda.pl:unres4 into UCGM
authorAdam Sieradzan <adasko@piasek4.chem.univ.gda.pl>
Mon, 30 Apr 2018 07:49:32 +0000 (09:49 +0200)
committerAdam Sieradzan <adasko@piasek4.chem.univ.gda.pl>
Mon, 30 Apr 2018 07:49:32 +0000 (09:49 +0200)
1  2 
source/unres/io_config.f90

        write (iout,'(3(a,f10.2))') 'v1ss:',v1ss,' v2ss:',v2ss,&
          ' v3ss:',v3ss
        endif
 +      if (shield_mode.gt.0) then
 +      pi=4.0D0*datan(1.0D0)
 +!C VSolvSphere the volume of solving sphere
 +      print *,pi,"pi"
 +!C rpp(1,1) is the energy r0 for peptide group contact and will be used for it 
 +!C there will be no distinction between proline peptide group and normal peptide
 +!C group in case of shielding parameters
 +      VSolvSphere=4.0/3.0*pi*(4.50d0)**3
 +      VSolvSphere_div=VSolvSphere-4.0/3.0*pi*(4.50/2.0)**3
 +      write (iout,*) VSolvSphere,VSolvSphere_div
 +!C long axis of side chain 
 +      do i=1,ntyp
 +      long_r_sidechain(i)=vbldsc0(1,i)
 +!      if (scelemode.eq.0) then
 +      short_r_sidechain(i)=sigma(i,i)/sqrt(2.0)
 +      if (short_r_sidechain(i).eq.0.0) short_r_sidechain(i)=0.2
 +!      else
 +!      short_r_sidechain(i)=sigma(i,i)
 +!      endif
 +      write(iout,*) "parame for long and short axis",i,vbldsc0(1,i),&
 +         sigma0(i) 
 +      enddo
 +      buff_shield=1.0d0
 +      endif
 +
        return
    111 write (iout,*) "Error reading bending energy parameters."
        goto 999
        use control_data
        use compare_data
        use MPI_data
-       use control, only: rescode,sugarcode
+ !      use control, only: rescode,sugarcode
  !      implicit real*8 (a-h,o-z)
  !      include 'DIMENSIONS'
  !      include 'COMMON.LOCAL'
        if(.not. allocated(istype)) allocate(istype(maxres))
        do i=1,100000
          read (ipdbin,'(a80)',end=10) card
- !       write (iout,'(a)') card
+        write (iout,'(a)') card
          if (card(:5).eq.'HELIX') then
            nhfrag=nhfrag+1
            lsecondary=.true.
        if (lprn) then
        write (iout,'(/a)') &
          "Cartesian coordinates of the reference structure"
-       write (iout,'(a,3(3x,a5),5x,3(3x,a5))') &
+       write (iout,'(a,16x,3(3x,a5),5x,3(3x,a5))') &
         "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
        do ires=1,nres
-         write (iout,'(5(a3,1x),i3,3f8.3,5x,3f8.3)') &
+         write (iout,'(5(a3,1x),i5,3f8.3,5x,3f8.3)') &
            (restyp(itype(ires,j),j),j=1,5),ires,(c(j,ires),j=1,3),&
            (c(j,ires+nres),j=1,3)
        enddo
         write (iout,'(a)') &
           "Backbone and SC coordinates as read from the PDB"
         do ires=1,nres
-         write (iout,'(2i3,2x,a,3f8.3,5x,3f8.3)') &
+         write (iout,'(i5,i3,2x,a,3f8.3,5x,3f8.3)') &
            ires,itype(ires,1),restyp(itype(ires,1),1),(c(j,ires),j=1,3),&
            (c(j,nres+ires),j=1,3)
         enddo
        if (lprn) then
        write (iout,'(/a)') &
          "Cartesian coordinates of the reference structure after sorting"
-       write (iout,'(a,3(3x,a5),5x,3(3x,a5))') &
+       write (iout,'(a,16x,3(3x,a5),5x,3(3x,a5))') &
         "Residue","X(CA)","Y(CA)","Z(CA)","X(SC)","Y(SC)","Z(SC)"
        do ires=1,nres
-         write (iout,'(5(a3,1x),i3,3f8.3,5x,3f8.3)') &
+         write (iout,'(5(a3,1x),i5,3f8.3,5x,3f8.3)') &
            (restyp(itype(ires,j),j),j=1,5),ires,(c(j,ires),j=1,3),&
            (c(j,ires+nres),j=1,3)
        enddo
          write (iout,*) "symetr", symetr
        do i=1,nres
        lll=lll+1
- !c      write (iout,*) "spraw lancuchy",(c(j,i),j=1,3)
+ !      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
  !       write (iout,*) "spraw lancuchy",chain_length,symetr
  !       do i=1,4
  !         do kkk=1,chain_length
- !           write (iout,*) itype(kkk),(chain_rep(j,kkk,i), j=1,3)
+ !           write (iout,*) itype(kkk,1),(chain_rep(j,kkk,i), j=1,3)
  !         enddo
  !        enddo
  ! enddiagnostic
          cou=0
          do kkk=1,symetr
           icha=tabperm(i,kkk)
- !         write (iout,*) i,icha
+          write (iout,*) i,icha
           do lll=1,chain_length
            cou=cou+1
             if (cou.le.nres) then
              kupa=mod(lll,chain_length)
              iprzes=(kkk-1)*chain_length+lll
              if (kupa.eq.0) kupa=chain_length
- !            write (iout,*) "kupa", kupa
+             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
        cref(3,i,kkk),cref(1,nres+i,kkk),&
        cref(2,nres+i,kkk),cref(3,nres+i,kkk)
        enddo
-   100 format (//'              alpha-carbon coordinates       ',&
+   100 format (//'                alpha-carbon coordinates       ',&
                  '     centroid coordinates'/ &
                  '       ', 6X,'X',11X,'Y',11X,'Z', &
                                  10X,'X',11X,'Y',11X,'Z')
-   110 format (a,'(',i3,')',6f12.5)
+   110 format (a,'(',i5,')',6f12.5)
       
        enddo
  !c enddiag
         write (iout,'(2a)') diagmeth(kdiag),&
          ' routine used to diagonalize matrices.'
        if (shield_mode.gt.0) then
 -      pi=3.141592d0
 +       pi=4.0D0*datan(1.0D0)
  !C VSolvSphere the volume of solving sphere
 -!C      print *,pi,"pi"
 +      print *,pi,"pi"
  !C rpp(1,1) is the energy r0 for peptide group contact and will be used for it 
  !C there will be no distinction between proline peptide group and normal peptide
  !C group in case of shielding parameters
 -      VSolvSphere=4.0/3.0*pi*rpp(1,1)**3
 -      VSolvSphere_div=VSolvSphere-4.0/3.0*pi*(rpp(1,1)/2.0)**3
 +      VSolvSphere=4.0/3.0*pi*(4.50d0)**3
 +      VSolvSphere_div=VSolvSphere-4.0/3.0*pi*(4.50/2.0)**3
        write (iout,*) VSolvSphere,VSolvSphere_div
  !C long axis of side chain 
 -      do i=1,ntyp
 -      long_r_sidechain(i)=vbldsc0(1,i)
 -      short_r_sidechain(i)=sigma0(i)
 -      write(iout,*) "parame for long and short axis",i,vbldsc0(1,i),&
 -         sigma0(i) 
 -      enddo
 +!      do i=1,ntyp
 +!      long_r_sidechain(i)=vbldsc0(1,i)
 +!      short_r_sidechain(i)=sigma0(i)
 +!      write(iout,*) "parame for long and short axis",i,vbldsc0(1,i),&
 +!         sigma0(i) 
 +!      enddo
        buff_shield=1.0d0
        endif
        return
        large = index(controlcard,"LARGE").gt.0
        print_compon = index(controlcard,"PRINT_COMPON").gt.0
        rattle = index(controlcard,"RATTLE").gt.0
+       preminim=(index(controlcard,'PREMINIM').gt.0)
+       write (iout,*) "PREMINIM ",preminim
+       dccart=(index(controlcard,'CART').gt.0)
+       if (preminim) call read_minim
  !  if performing umbrella sampling, fragments constrained are read from the fragment file 
        nset=0
        if(usampl) then