small cleaning
authorEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Fri, 10 Mar 2017 14:12:58 +0000 (15:12 +0100)
committerEmilia Lubecka <emilia.lubecka@ug.edu.pl>
Fri, 10 Mar 2017 14:12:58 +0000 (15:12 +0100)
source/unres/cinfo.f90
source/unres/energy.f90
source/unres/geometry.f90
source/unres/io.f90
source/unres/io_config.f90
source/wham/cinfo.f90
source/wham/conform_compar.f90

index e8a4224..d38c220 100644 (file)
@@ -1,12 +1,12 @@
 ! DO NOT EDIT THIS FILE - IT HAS BEEN GENERATED BY COMPINFO.C
-! 0 40376 55
+! 0 40376 67
       subroutine cinfo
 !      include 'COMMON.IOUNITS'
       use io_units
       write(iout,*)'++++ Compile info ++++'
-      write(iout,*)'Version 0.40376 build 55'
-      write(iout,*)'compiled Fri Feb 17 01:55:34 2017'
-      write(iout,*)'compiled by czarek@piasek4'
+      write(iout,*)'Version 0.40376 build 67'
+      write(iout,*)'compiled Fri Mar 10 14:56:02 2017'
+      write(iout,*)'compiled by emilial@piasek4'
       write(iout,*)'OS name:    Linux '
       write(iout,*)'OS release: 3.2.0-111-generic '
       write(iout,*)'OS version:',&
index 2fdb065..fdf4576 100644 (file)
       allocate(mu(2,nres))
       allocate(muder(2,nres))
       allocate(Ub2(2,nres))
-        do i=1,nres
-          Ub2(1,i)=0.0d0
-          Ub2(2,i)=0.0d0
-        enddo
+      Ub2(1,:)=0.0d0
+      Ub2(2,:)=0.0d0
       allocate(Ub2der(2,nres))
       allocate(Ctobr(2,nres))
       allocate(Ctobrder(2,nres))
 !      allocate(qinfrag(50,nprocs/20),wfrag(50,nprocs/20)) !(50,maxprocs/20)
 !      allocate(qinpair(100,nprocs/20),wpair(100,nprocs/20)) !(100,maxprocs/20)
       allocate(mset(0:nprocs))  !(maxprocs/20)
-      do i=0,nprocs
-        mset(i)=0
-      enddo
+      mset(:)=0
 !      allocate(ifrag(2,50,nprocs/20))  !(2,50,maxprocs/20)
 !      allocate(ipair(2,100,nprocs/20))  !(2,100,maxprocs/20)
       allocate(dUdconst(3,0:nres))
 ! and side-chain vectors in theta or phi.
       allocate(dyn_ssbond_ij(0:nres+4,0:nres+4))
 !(maxres,maxres)
-      do i=1,nres
-        do j=i+1,nres
-          dyn_ssbond_ij(i,j)=1.0d300
-        enddo
-      enddo
+!      do i=1,nres
+!        do j=i+1,nres
+      dyn_ssbond_ij(:,:)=1.0d300
+!        enddo
+!      enddo
 
       if (nss.gt.0) then
         allocate(idssb(nss),jdssb(nss))
       endif
       allocate(dyn_ss_mask(nres))
 !(maxres)
-      do i=1,nres
-        dyn_ss_mask(i)=.false.
-      enddo
+      dyn_ss_mask(:)=.false.
 !----------------------
 ! common.sccor
 ! Parameters of the SCCOR term
index 7a91cc7..0f3febc 100644 (file)
 !      if(.not.allocated(dc_norm2)) allocate(dc_norm2(3,0:nres2+2)) !(3,0:maxres2)      
       if(.not.allocated(dc_norm2)) then
         allocate(dc_norm2(3,0:nres2+2)) !(3,0:maxres2)
-        do i=0,nres2+2
-          dc_norm2(1,i)=0.d0
-          dc_norm2(2,i)=0.d0
-          dc_norm2(3,i)=0.d0
-        enddo
+        dc_norm2(:,:)=0.d0
       endif
 !
 !el      if(.not.allocated(dc_norm)) 
 !elwrite(iout,*) "jestem w alloc geo 1"
       if(.not.allocated(dc_norm)) then
         allocate(dc_norm(3,0:nres2+2)) !(3,0:maxres2)
-        do i=0,nres2+2
-          dc_norm(1,i)=0.d0
-          dc_norm(2,i)=0.d0
-          dc_norm(3,i)=0.d0
-        enddo
+        dc_norm(:,:)=0.d0
       endif
 !elwrite(iout,*) "jestem w alloc geo 1"
       allocate(xloc(3,nres),xrot(3,nres))
 !elwrite(iout,*) "jestem w alloc geo 1"
-      do i=1,nres
-       do j=1,3
-         xloc(j,i)=0.0D0
-        enddo
-      enddo
+      xloc(:,:)=0.0D0
 !elwrite(iout,*) "jestem w alloc geo 1"
       allocate(dc_work(6*nres)) !(MAXRES6) maxres6=6*maxres
 !      common /rotmat/
 
 #if defined(WHAM_RUN) || defined(CLUSTER)
       allocate(vbld(2*nres))
-      do i=1,2*nres
-        vbld(i)=0.d0
-      enddo
+      vbld(:)=0.d0
       allocate(vbld_inv(2*nres))
-      do i=1,2*nres
-        vbld_inv(i)=0.d0
-      enddo
+      vbld_inv(:)=0.d0
 #endif
 
       return
index 4936ea8..243c8b6 100644 (file)
       allocate(itype(maxres)) !(maxres)
 !
 ! Zero out tables.
-!      
-      do i=1,2*maxres
-        do j=1,3
-          c(j,i)=0.0D0
-          dc(j,i)=0.0D0
-        enddo
-      enddo
-      do i=1,maxres
-         itype(i)=0
-      enddo
+!
+      c(:,:)=0.0D0
+      dc(:,:)=0.0D0
+      itype(:)=0
 !-----------------------------
 !
 ! Body
 !      allocate(dc(3,0:2*nres+2))
 !      allocate(itype(nres+2))
       allocate(itel(nres+2))
+      itel(:)=0
 
 !      do i=1,2*nres+2
 !        do j=1,3
 !          dc(j,i)=dc_alloc(j,i)
 !        enddo
 !      enddo
-      do i=1,nres+2
+!      do i=1,nres+2
 !        itype(i)=itype_alloc(i)
-        itel(i)=0
-      enddo
+!        itel(i)=0
+!      enddo
 !--------------------------
       do i=1,nres
 #ifdef PROCOR
index 393bfa4..aedb3dd 100644 (file)
       allocate(bthet(2,-ntyp:ntyp,-1:1,-1:1)) !(2,-ntyp:ntyp,-1:1,-1:1)
       allocate(polthet(0:3,-ntyp:ntyp))        !(0:3,-ntyp:ntyp)
       allocate(gthet(3,-ntyp:ntyp))    !(3,-ntyp:ntyp)
-      do i=-ntyp,ntyp
-       a0thet(i)=0.0D0
-       do j=1,2
-         do ichir1=-1,1
-          do ichir2=-1,1
-          athet(j,i,ichir1,ichir2)=0.0D0
-          bthet(j,i,ichir1,ichir2)=0.0D0
-          enddo
-         enddo
-        enddo
-        do j=0,3
-         polthet(j,i)=0.0D0
-        enddo
-       do j=1,3
-         gthet(j,i)=0.0D0
-        enddo
-       theta0(i)=0.0D0
-       sig0(i)=0.0D0
-       sigc0(i)=0.0D0
-      enddo
+
+      a0thet(:)=0.0D0
+      athet(:,:,:,:)=0.0D0
+      bthet(:,:,:,:)=0.0D0
+      polthet(:,:)=0.0D0
+      gthet(:,:)=0.0D0
+      theta0(:)=0.0D0
+      sig0(:)=0.0D0
+      sigc0(:)=0.0D0
 
 #ifdef CRYST_THETA
 !
       do i=-ntyp1,-1
         ithetyp(i)=-ithetyp(-i)
       enddo
-      do iblock=1,2
-      do i=-maxthetyp,maxthetyp
-        do j=-maxthetyp,maxthetyp
-          do k=-maxthetyp,maxthetyp
-            aa0thet(i,j,k,iblock)=0.0d0
-            do l=1,ntheterm
-              aathet(l,i,j,k,iblock)=0.0d0
-            enddo
-            do l=1,ntheterm2
-              do m=1,nsingle
-                bbthet(m,l,i,j,k,iblock)=0.0d0
-                ccthet(m,l,i,j,k,iblock)=0.0d0
-                ddthet(m,l,i,j,k,iblock)=0.0d0
-                eethet(m,l,i,j,k,iblock)=0.0d0
-              enddo
-            enddo
-            do l=1,ntheterm3
-              do m=1,ndouble
-                do mm=1,ndouble
-                 ffthet(mm,m,l,i,j,k,iblock)=0.0d0
-                 ggthet(mm,m,l,i,j,k,iblock)=0.0d0
-                enddo
-              enddo
-            enddo
-          enddo
-        enddo
-      enddo
-      enddo
+
+      aa0thet(:,:,:,:)=0.0d0
+      aathet(:,:,:,:,:)=0.0d0
+      bbthet(:,:,:,:,:,:)=0.0d0
+      ccthet(:,:,:,:,:,:)=0.0d0
+      ddthet(:,:,:,:,:,:)=0.0d0
+      eethet(:,:,:,:,:,:)=0.0d0
+      ffthet(:,:,:,:,:,:,:)=0.0d0
+      ggthet(:,:,:,:,:,:,:)=0.0d0
+
 ! VAR:iblock means terminally blocking group 1=non-proline 2=proline
       do iblock=1,2 
 ! VAR:ntethtyp is type of theta potentials type currently 0=glycine 
       allocate(censc(3,maxlob,-ntyp:ntyp)) !(3,maxlob,-ntyp:ntyp)
       allocate(gaussc(3,3,maxlob,-ntyp:ntyp)) !(3,3,maxlob,-ntyp:ntyp)
 
-      do i=1,ntyp
-       do j=1,maxlob
-         bsc(j,i)=0.0D0
-         nlob(i)=0
-        enddo
-      enddo
-      nlob(ntyp1)=0
-      dsc(ntyp1)=0.0D0
-
-      do i=-ntyp,ntyp
-       do j=1,maxlob
-         do k=1,3
-           censc(k,j,i)=0.0D0
-          enddo
-          do k=1,3
-           do l=1,3
-             gaussc(l,k,j,i)=0.0D0
-            enddo
-          enddo
-        enddo
-      enddo
-
+      bsc(:,:)=0.0D0
+      nlob(:)=0
+      nlob(:)=0
+      dsc(:)=0.0D0
+      censc(:,:,:)=0.0D0
+      gaussc(:,:,:,:)=0.0D0
 #ifdef CRYST_SC
 !
 ! Read the parameters of the probability distribution/energy expression
       allocate(v1(maxterm,-ntortyp:ntortyp,-ntortyp:ntortyp,2))
       allocate(v2(maxterm,-ntortyp:ntortyp,-ntortyp:ntortyp,2)) !(maxterm,-maxtor:maxtor,-maxtor:maxtor,2)
 !el---------------------------
-      do iblock=1,2
-        do i=-ntortyp,ntortyp
-          do j=-ntortyp,ntortyp
-            nterm(i,j,iblock)=0
-            nlor(i,j,iblock)=0
-          enddo
-        enddo
-      enddo
+      nterm(:,:,:)=0
+      nlor(:,:,:)=0
 !el---------------------------
 
       read (itorp,*,end=113,err=113) (itortyp(i),i=1,ntyp)
       allocate(eps_scp(ntyp,2),rscp(ntyp,2)) !(ntyp,2)
       allocate(sigma0(ntyp),rr0(ntyp),sigii(ntyp)) !(ntyp)
       allocate(chip(ntyp1),alp(ntyp1)) !(ntyp)
-      do i=1,ntyp
-       do j=1,ntyp
-         augm(i,j)=0.0D0
-        enddo
-       chip(i)=0.0D0
-       alp(i)=0.0D0
-       sigma0(i)=0.0D0
-       sigii(i)=0.0D0
-       rr0(i)=0.0D0
-      enddo
+
+      augm(:,:)=0.0D0
+      chip(:)=0.0D0
+      alp(:)=0.0D0
+      sigma0(:)=0.0D0
+      sigii(:)=0.0D0
+      rr0(:)=0.0D0
 !--------------------------------
 
       read (isidep,*,end=117,err=117) ipot,expon
 !el from module energy - COMMON.INTERACT-------
       allocate(aa(ntyp1,ntyp1),bb(ntyp1,ntyp1),chi(ntyp1,ntyp1)) !(ntyp,ntyp)
       allocate(sigma(0:ntyp1,0:ntyp1),r0(ntyp1,ntyp1)) !(0:ntyp1,0:ntyp1)
-      do i=1,ntyp1
-        do j=1,ntyp1
-          aa(i,j)=0.0D0
-          bb(i,j)=0.0D0
-          chi(i,j)=0.0D0
-          sigma(i,j)=0.0D0
-          r0(i,j)=0.0D0
-        enddo
-      enddo
+      aa(:,:)=0.0D0
+      bb(:,:)=0.0D0
+      chi(:,:)=0.0D0
+      sigma(:,:)=0.0D0
+      r0(:,:)=0.0D0
 !--------------------------------
 
       do i=2,ntyp
       enddo
 
       allocate(aad(ntyp,2),bad(ntyp,2)) !(ntyp,2)
-      do i=1,ntyp
-       do j=1,2
-         bad(i,j)=0.0D0
-        enddo
-      enddo
+      bad(:,:)=0.0D0
 
 #ifdef OLDSCP
 !
 !!!el
       if(.not.allocated(theta)) then
         allocate(theta(nres+2))
-!        allocate(phi(nres+2))
-!        allocate(alph(nres+2))
-!        allocate(omeg(nres+2))
-        do i=1,nres+2
-          theta(i)=0.0d0
-!          phi(i)=0.0d0
-!          alph(i)=0.0d0
-!          omeg(i)=0.0d0
-        enddo
+        theta(:)=0.0d0
       endif
-!       allocate(costtab(nres))
-!        allocate(sinttab(nres))
-!        allocate(cost2tab(nres))
-!        allocate(sint2tab(nres))
-!        allocate(xxref(nres))
-!        allocate(yyref(nres))
-!        allocate(zzref(nres)) !(maxres)
-!        do i=1,nres
-!          costtab(i)=0.0d0
-!          sinttab(i)=0.0d0
-!          cost2tab(i)=0.0d0
-!          sint2tab(i)=0.0d0
-!          xxref(i)=0.0d0
-!          yyref(i)=0.0d0
-!          zzref(i)=0.0d0
-!        enddo
-!      endif 
+
       if(.not.allocated(phi)) allocate(phi(nres+2))
       if(.not.allocated(alph)) allocate(alph(nres+2))
       if(.not.allocated(omeg)) allocate(omeg(nres+2))
       if(.not.allocated(dc_norm)) then
 !      if(.not.allocated(dc_norm)) allocate(dc_norm(3,0:2*nres+2))
         allocate(dc_norm(3,0:2*nres+2))
-        do i=0,2*nres+2
-          dc_norm(1,i)=0.d0
-          dc_norm(2,i)=0.d0
-          dc_norm(3,i)=0.d0
-        enddo
+        dc_norm(:,:)=0.d0
       endif
  
       call int_from_cart(.true.,.false.)
-      call sc_loc_geom(.true.)
-!      call sc_loc_geom(.false.)
-! wczesbiej bylo false
+      call sc_loc_geom(.false.)
       do i=1,nres
         thetaref(i)=theta(i)
         phiref(i)=phi(i)
index c50d882..b5814f0 100644 (file)
@@ -1,12 +1,12 @@
 ! DO NOT EDIT THIS FILE - IT HAS BEEN GENERATED BY COMPINFO.C
-! 0 0 1257
+! 0 0 1262
       subroutine cinfo
 !      include 'COMMON.IOUNITS'
       use IO_UNITS
       write(iout,*)'++++ Compile info ++++'
-      write(iout,*)'Version 0.0 build 1257'
-      write(iout,*)'compiled Wed Feb 15 09:01:33 2017'
-      write(iout,*)'compiled by czarek@piasek4'
+      write(iout,*)'Version 0.0 build 1262'
+      write(iout,*)'compiled Fri Mar 10 14:57:31 2017'
+      write(iout,*)'compiled by emilial@piasek4'
       write(iout,*)'OS name:    Linux '
       write(iout,*)'OS release: 3.2.0-111-generic '
       write(iout,*)'OS version:',&
index e983f7f..701e920 100644 (file)
        use w_comm_local
        integer :: nfrg,nlev
 
-write(iout,*) "in alloc conpar arrays: nlevel=", nlevel," nfrag(1)=",nfrag(1)
+!write(iout,*) "in alloc conpar arrays: nlevel=", nlevel," nfrag(1)=",nfrag(1)
 !------------------------
 ! commom.contacts
 !      common /contacts/