Water micro and bere and lang with gly working with D lang not
[unres4.git] / source / unres / compare.F90
index 2f47cf6..1dfe01e 100644 (file)
@@ -45,7 +45,7 @@
 
       ncont=0
       kkk=3
-      do i=nnt+kkk,nct
+      do i=nnt_molec(1)+kkk,nct_molec(1)
         iti=iabs(itype(i,molnum(i)))
         if (molnum(i).lt.3) then
                 inum=i+nres
@@ -71,6 +71,7 @@
 !         print *,'rcomp=',rcomp,' dist=',dist(nres+i,nres+j)
          if (dist(inum,jnum).lt.rcomp) then
             ncont=ncont+1
+            if (ncont.gt.nres*100) ncont=nres*100
             icont(1,ncont)=i
             icont(2,ncont)=j
           endif
 !      include 'COMMON.FFIELD'
 !      include 'COMMON.NAMES'
       integer :: ncont
-      integer,dimension(2,100*nres) :: icont   !(2,maxcont)    (maxcont=12*maxres)
+      integer,dimension(:,:),allocatable :: icont      !(2,maxcont)    (maxcont=12*maxres)
       integer :: nharp
       integer,dimension(4,nres) :: iharp       !(4,nres/3)(4,maxres/3)
       logical :: lprint,not_done
       real(kind=8) :: rcomp=6.0d0
 !el local variables
       integer :: i,j,kkk,k,i1,i2,it1,it2,j1,ii1,jj1
-!      allocate(icont(2,100*nres))
-
+      if (.not.allocated(icont)) then
+      allocate(icont(2,100*nres_molec(1)+1))
+      endif
       ncont=0
       kkk=0
 !     print *,'nnt=',nnt,' nct=',nct
-      do i=nnt,nct-3
+      do i=nnt_molec(1),nct_molec(1)-3
         do k=1,3
           c(k,2*nres+1)=0.5d0*(c(k,i)+c(k,i+1))
         enddo
       real(kind=8) :: ael6_i,ael3_i
       real(kind=8),dimension(2,2) :: app_,bpp_,rpp_
       integer :: ncont
-      integer,dimension(2,100*nres) :: icont   !(2,100*nres)(2,maxcont)        (maxcont=12*maxres)
-      real(kind=8),dimension(100*nres) :: econt        !(maxcont)
+      integer,dimension(:,:),allocatable :: icont      !(2,100*nres)(2,maxcont)        (maxcont=12*maxres)
+      real(kind=8),dimension(:),allocatable :: econt   !(maxcont)
 !el local variables
       integer :: i,j,k,iteli,itelj,i1,i2,it1,it2,ic1,ic2
       real(kind=8) :: elcutoff,elecutoff_14,rri,ees,evdw
       data elpp_3  / 0.0503d0, 0.0000d0, 0.0000d0, 0.0692d0/
 
 !el      allocate(econt(100*nres))     !(maxcont)
-
+      if (.not.allocated(icont)) then
+       allocate(icont(2,100*nres_molec(1)+1))
+      endif
+      if (.not.allocated(econt)) then
+       allocate(econt(100*nres_molec(1)+1))
+      endif
       elcutoff = -0.3d0
       elecutoff_14 = -0.5d0
       if (lprint) write (iout,'(a)') &
       ees=0.0
       evdw=0.0
 !      print *, "nntt,nct",nnt,nct-2
-      do 1 i=nnt,nct-2
+      do 1 i=nnt_molec(1),nct_molec(1)-2
         if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) goto 1
         xi=c(1,i)
         yi=c(2,i)
 !      include 'COMMON.CONTROL'
       integer :: ncont,i,j,i1,j1,nbeta,nstrand,ii1,jj1,ij,nhelix,&
              iii1,jjj1
-      integer,dimension(2,100*nres) :: icont   !(2,maxcont)    (maxcont=12*maxres)
+      integer,dimension(:,:),allocatable :: icont      !(2,maxcont)    (maxcont=12*maxres)
       integer,dimension(nres,0:4) :: isec      !(maxres,4)
       integer,dimension(nres) :: nsec  !(maxres)
       logical :: lprint,not_done       !,freeres
 !el      external freeres
 
 !el      allocate(icont(2,100*nres),isec(nres,4),nsec(nres))
-
+      if (.not.allocated(icont)) then
+       allocate(icont(2,100*nres+1))
+      endif
       if(.not.dccart) call chainbuild_cart
       if(.not.allocated(hfrag)) allocate(hfrag(2,nres/3)) !(2,maxres/3)
 !d      call write_pdb(99,'sec structure',0d0)
 !      include 'COMMON.IOUNITS'
 !      include 'COMMON.DISTFIT'
 
-      integer :: ncont,icont(2,nres*nres/2),isec(nres,3)
+      integer :: ncont,isec(nres,3)
       logical :: lprint,not_done
-      real(kind=4) :: dcont(nres*nres/2),d
+      real(kind=4) :: d
       real(kind=4) :: rcomp = 7.0
       real(kind=4) :: rbeta = 5.2
       real(kind=4) :: ralfa = 5.2
       real(kind=8),dimension(3) :: xpi,xpj
       integer :: i,k,j,i1,j1,nbeta,nstrand,ii1,jj1,ij,iii1,jjj1,&
             nhelix
+      integer, dimension(:,:),allocatable :: icont
+      real(kind=4),dimension(:),allocatable :: dcont
+      if (.not.allocated(icont)) then
+        allocate(icont(2,100*nres_molec(1)+1))
+      endif
+      if (.not.allocated(dcont)) then
+       allocate(dcont(100*nres_molec(1)+1))
+      endif
       call chainbuild_cart
 !d      call write_pdb(99,'sec structure',0d0)
       ncont=0
                (xpi(2)-xpj(2))*(xpi(2)-xpj(2)) + &
                (xpi(3)-xpj(3))*(xpi(3)-xpj(3)) 
          if ( d.lt.rcomp*rcomp) then
+            if (ncont.gt.(100*nres_molec(1)+1)) ncont=100*nres_molec(1)+1
             ncont=ncont+1
             icont(1,ncont)=i
             icont(2,ncont)=j