X-Git-Url: http://mmka.chem.univ.gda.pl/gitweb/?a=blobdiff_plain;f=source%2Funres%2Fgeometry.F90;h=af8df27b5368094b3bffedfa6dcb6a0a2b83c117;hb=bc23440fbe68672d430f71f22f46b11265f003db;hp=7af9aca42933eb3d377ec2a717a5cc1875e5dcd3;hpb=52d6371a0781ac6214af501666a2fbffbded3a40;p=unres4.git diff --git a/source/unres/geometry.F90 b/source/unres/geometry.F90 index 7af9aca..af8df27 100644 --- a/source/unres/geometry.F90 +++ b/source/unres/geometry.F90 @@ -453,7 +453,7 @@ ! print *,i,vbld(i),"vbld(i)" vbld_inv(i)=1.0d0/vbld(i) vbld(nres+i)=dist(nres+i,i) - if (itype(i,1).ne.10) then + if ((itype(i,1).ne.10).and.(molnum(i).ne.5)) then vbld_inv(nres+i)=1.0d0/vbld(nres+i) else vbld_inv(nres+i)=0.0d0 @@ -828,7 +828,7 @@ integer :: it1,it2,it,j !d print *,' CG Processor',me,' maxgen=',maxgen maxsi=1000 -! write (iout,*) 'Gen_Rand_conf: nstart=',nstart + write (iout,*) 'Gen_Rand_conf: nstart=',nstart,nres if (nstart.lt.5) then it1=iabs(itype(2,1)) phi(4)=gen_phi(4,iabs(itype(2,1)),iabs(itype(3,1))) @@ -840,11 +840,14 @@ fail=.true. do while (fail.and.nsi.le.maxsi) call gen_side(it1,theta(3),alph(2),omeg(2),fail,molnum(2)) + write (iout,*) 'nsi=',nsi,maxsi nsi=nsi+1 enddo if (nsi.gt.maxsi) return 1 endif ! it1.ne.10 + write(iout,*) "before origin_frame" call orig_frame + write(iout,*) "after origin_frame" i=4 nstart=4 else @@ -858,6 +861,7 @@ niter=0 back=.false. do while (i.le.nres .and. niter.lt.maxgen) + write(iout,*) 'i=',i,'back=',back if (i.lt.nstart) then if(iprint.gt.1) then write (iout,'(/80(1h*)/2a/80(1h*))') & @@ -906,7 +910,7 @@ if (nsi.gt.maxsi) return 1 endif call locate_next_res(i) -! write(iout,*) "overlap,",overlap(i-1) + write(iout,*) "overlap,",overlap(i-1) if (overlap(i-1)) then if (nit.lt.maxnit) then back=.true. @@ -958,12 +962,13 @@ nres2=2*nres data redfac /0.5D0/ overlap=.false. - iti=iabs(itype(i,1)) + iti=iabs(itype(i,molnum(i))) if (iti.gt.ntyp) return ! Check for SC-SC overlaps. !d print *,'nnt=',nnt,' nct=',nct do j=nnt,i-1 - +! print *, "molnum(j)",j,molnum(j) + if (molnum(j).eq.1) then itj=iabs(itype(j,1)) if (itj.eq.ntyp1) cycle if (j.lt.i-1 .or. ipot.ne.4) then @@ -974,11 +979,24 @@ !d print *,'j=',j if (dist(nres+i,nres+j).lt.redfac*rcomp) then overlap=.true. + ! print *,'overlap, SC-SC: i=',i,' j=',j, ! & ' dist=',dist(nres+i,nres+j),' rcomp=', ! & rcomp return endif + else if (molnum(j).eq.2) then + itj=iabs(itype(j,2)) + if (dist(nres+i,nres+j).lt.redfac*sigma_nucl(iti,itj)) then + overlap=.true. + +! print *,'overlap, SC-SC: i=',i,' j=',j, +! & ' dist=',dist(nres+i,nres+j),' rcomp=', +! & rcomp + return + endif + + endif enddo ! Check for overlaps between the added peptide group and the preceding ! SCs. @@ -988,6 +1006,7 @@ c(j,nres2+3)=0.5D0*(c(j,i)+c(j,i+1)) enddo do j=nnt,i-2 + if (molnum(j).ne.1) cycle itj=iabs(itype(j,1)) !d print *,'overlap, p-Sc: i=',i,' j=',j, !d & ' dist=',dist(nres+j,maxres2+1) @@ -999,6 +1018,7 @@ ! Check for overlaps between the added side chain and the preceding peptide ! groups. do j=1,nnt-2 + if (molnum(j).ne.1) cycle do k=1,3 c(k,nres2+3)=0.5D0*(c(k,j)+c(k,j+1)) enddo @@ -1011,21 +1031,29 @@ enddo ! Check for p-p overlaps do j=1,3 - c(j,nres2+4)=0.5D0*(c(j,i)+c(j,i+1)) + c(j,nres2+3)=0.5D0*(c(j,i)+c(j,i+1)) enddo do j=nnt,i-2 +! if (molnum(j).eq.1) then itelj=itel(j) do k=1,3 c(k,nres2+4)=0.5D0*(c(k,j)+c(k,j+1)) enddo !d print *,'overlap, p-p: i=',i,' j=',j, !d & ' dist=',dist(maxres2+1,maxres2+2) + if (molnum(j).eq.1) then if(iteli.ne.0.and.itelj.ne.0)then if (dist(nres2+3,nres2+4).lt.rpp(iteli,itelj)*redfac) then overlap=.true. return endif endif + else if (molnum(j).eq.2) then + if (dist(nres2+3,nres2+4).lt.3.0) then + overlap=.true. + return + endif + endif enddo return end function overlap @@ -1096,7 +1124,7 @@ gen_theta=theta_temp ! print '(a)','Exiting GENTHETA.' else if (mnum.eq.2) then - gen_theta=aa0thet_nucl(1,it,1) -0.17 + ran_number(0.0d0,0.34d0) + gen_theta=2.0d0 + ran_number(0.0d0,0.34d0) else gen_theta=ran_number(theta_max/2.0,theta_max) endif @@ -1142,6 +1170,11 @@ fail=.true. return endif + if (nlobit.eq.0) then + al=ran_number(0.05d0,pi/2) + om=ran_number(-pi,pi) + return + endif tant=dtan(the-pipol) nlobit=nlob(it) allocate(z(3,nlobit)) @@ -1512,6 +1545,7 @@ dxi=dc_norm(1,nres+i) dyi=dc_norm(2,nres+i) dzi=dc_norm(3,nres+i) + print *,i,itypi,"sc_move" dsci_inv=dsc_inv(itypi) ! do iint=1,nint_gr(i) @@ -1519,6 +1553,8 @@ if (itype(j,molnum(j)).eq.ntyp1_molec(molnum(j))) cycle ind=ind+1 itypj=iabs(itype(j,molnum(j))) + print *,j,itypj,"sc_move" + dscj_inv=dsc_inv(itypj) sig0ij=sigma(itypi,itypj) chi1=chi(itypi,itypj) @@ -1609,6 +1645,7 @@ chiom1=chi1*om1 chiom2=chi2*om2 facsig=om1*chiom1+om2*chiom2-2.0D0*om1om2*chiom12 +! print *,"TUT?",om1*chiom1,facsig,om1,om2,om12 sigsq=1.0D0-facsig*faceps1_inv sigsq_om1=(chiom1-chiom12*om2)*faceps1_inv sigsq_om2=(chiom2-chiom12*om1)*faceps1_inv @@ -3278,8 +3315,9 @@ do j=1,3 gcart(j,1)=gcart(j,1)+gloc(1,icg)*dphi(j,1,4) & +gloc(nres-2,icg)*dtheta(j,1,3) +! write(iout,*) "pierwszy gcart", gcart(j,2) if ((itype(2,1).ne.10).and.& - (itype(2,molnum(2)).ne.ntyp1_molec(molnum(2)))) then + (itype(2,molnum(2)).ne.ntyp1_molec(molnum(2)).and.(molnum(2).ne.5))) then gcart(j,1)=gcart(j,1)+gloc(ialph(2,1),icg)*dalpha(j,1,2)+ & gloc(ialph(2,1)+nside,icg)*domega(j,1,2) endif @@ -3288,7 +3326,8 @@ do j=1,3 gcart(j,2)=gcart(j,2)+gloc(1,icg)*dphi(j,2,4)+ & gloc(nres-2,icg)*dtheta(j,2,3)+gloc(nres-1,icg)*dtheta(j,1,4) - if(itype(2,1).ne.10) then +! write(iout,*) "drugi gcart", gcart(j,2) + if((itype(2,1).ne.10).and.(molnum(2).ne.5)) then gcart(j,2)=gcart(j,2)+gloc(ialph(2,1),icg)*dalpha(j,2,2)+ & gloc(ialph(2,1)+nside,icg)*domega(j,2,2) endif @@ -3328,7 +3367,7 @@ +gloc(i-1,icg)*dphi(j,2,i+2)+ & gloc(i,icg)*dphi(j,1,i+3)+gloc(nres+i-4,icg)*dtheta(j,2,i+1)+ & gloc(nres+i-3,icg)*dtheta(j,1,i+2) - if(itype(i,1).ne.10) then + if((itype(i,1).ne.10).and.(molnum(nres-1).ne.5)) then gcart(j,i)=gcart(j,i)+gloc(ialph(i,1),icg)*dalpha(j,2,i)+ & gloc(ialph(i,1)+nside,icg)*domega(j,2,i) endif @@ -3346,12 +3385,12 @@ dphi(j,3,nres-1)+gloc(nres-3,icg)*dphi(j,2,nres) & +gloc(2*nres-6,icg)* & dtheta(j,2,nres-1)+gloc(2*nres-5,icg)*dtheta(j,1,nres) - if(itype(nres-2,1).ne.10) then + if((itype(nres-2,1).ne.10).and.(molnum(nres-1).ne.5)) then gcart(j,nres-2)=gcart(j,nres-2)+gloc(ialph(nres-2,1),icg)* & dalpha(j,2,nres-2)+gloc(ialph(nres-2,1)+nside,icg)* & domega(j,2,nres-2) endif - if(itype(nres-1,1).ne.10) then + if((itype(nres-1,1).ne.10).and.(molnum(nres-1).ne.5)) then gcart(j,nres-2)=gcart(j,nres-2)+gloc(ialph(nres-1,1),icg)* & dalpha(j,1,nres-1)+gloc(ialph(nres-1,1)+nside,icg)* & domega(j,1,nres-1) @@ -3360,35 +3399,35 @@ endif ! Settind dE/ddnres-1 !#define DEBUG -#ifdef DEBUG - j=1 - write(iout,*)"in int to carta",nres-1,gcart(j,nres-1),gloc(nres-3,icg),dphi(j,3,nres), & - gloc(2*nres-5,icg),dtheta(j,2,nres) +!#ifdef DEBUG +! j=1 +! write(iout,*)"in int to carta",nres-1,gcart(j,nres-1),gloc(nres-3,icg),dphi(j,3,nres), & +! gloc(2*nres-5,icg),dtheta(j,2,nres) -#endif +!#endif !#undef DEBUG do j=1,3 gcart(j,nres-1)=gcart(j,nres-1)+gloc(nres-3,icg)*dphi(j,3,nres)+ & gloc(2*nres-5,icg)*dtheta(j,2,nres) !#define DEBUG -#ifdef DEBUG - write(iout,*)"in int to cartb",nres-1,gcart(j,nres-1),gloc(nres-3,icg),dphi(j,3,nres), & - gloc(2*nres-5,icg),dtheta(j,2,nres) - -#endif +!#ifdef DEBUG +! write(iout,*)"in int to cartb",nres-1,gcart(j,nres-1),gloc(nres-3,icg),dphi(j,3,nres), & +! gloc(2*nres-5,icg),dtheta(j,2,nres) +! +!#endif !#undef DEBUG - if(itype(nres-1,1).ne.10) then + if((itype(nres-1,1).ne.10).and.(molnum(nres-1).ne.5)) then gcart(j,nres-1)=gcart(j,nres-1)+gloc(ialph(nres-1,1),icg)* & dalpha(j,2,nres-1)+gloc(ialph(nres-1,1)+nside,icg)* & domega(j,2,nres-1) !#define DEBUG -#ifdef DEBUG - write(iout,*)"in int to cart2",i,gcart(j,nres-1),gloc(ialph(nres-1,1),icg)* & - dalpha(j,2,nres-1),gloc(ialph(nres-1,1)+nside,icg), & - domega(j,2,nres-1) +!#ifdef DEBUG +! write(iout,*)"in int to cart2",i,gcart(j,nres-1),gloc(ialph(nres-1,1),icg)* & +! dalpha(j,2,nres-1),gloc(ialph(nres-1,1)+nside,icg), & +! domega(j,2,nres-1) -#endif +!#endif !#undef DEBUG endif @@ -3396,15 +3435,16 @@ ! The side-chain vector derivatives do i=2,nres-1 if(itype(i,1).ne.10 .and. & - itype(i,molnum(i)).ne.ntyp1_molec(molnum(i))) then + itype(i,molnum(i)).ne.ntyp1_molec(molnum(i)).and.& + (molnum(i).ne.5)) then do j=1,3 gxcart(j,i)=gxcart(j,i)+gloc(ialph(i,1),icg)*dalpha(j,3,i) & +gloc(ialph(i,1)+nside,icg)*domega(j,3,i) !#define DEBUG -#ifdef DEBUG - write(iout,*)"in int to cart",i, gxcart(j,i),gloc(ialph(i,1),icg),dalpha(j,3,i), & - gloc(ialph(i,1)+nside,icg),domega(j,3,i) -#endif +!#ifdef DEBUG +! write(iout,*)"in int to cart",i, gxcart(j,i),gloc(ialph(i,1),icg),dalpha(j,3,i), & +! gloc(ialph(i,1)+nside,icg),domega(j,3,i) +!#endif !#undef DEBUG enddo endif @@ -3415,6 +3455,8 @@ ! INTERTYP=3 SC...Ca...Ca...SC ! calculating dE/ddc1 18 continue +! write(iout,*) "przed sccor gcart", gcart(1,2) + ! do i=1,nres ! gloc(i,icg)=0.0D0 ! write (iout,*) "poczotkoawy",i,gloc_sc(1,i,icg) @@ -3422,7 +3464,7 @@ if (nres.lt.2) return if ((nres.lt.3).and.(itype(1,1).eq.10)) return if ((itype(1,1).ne.10).and. & - (itype(1,molnum(1)).ne.ntyp1_molec(molnum(1)))) then + (itype(1,molnum(1)).ne.ntyp1_molec(molnum(1))).and.(molnum(1).ne.5)) then do j=1,3 !c Derviative was calculated for oposite vector of side chain therefore ! there is "-" sign before gloc_sc @@ -3431,7 +3473,7 @@ gcart(j,1)=gcart(j,1)+gloc_sc(1,0,icg)* & dtauangle(j,1,2,3) if ((itype(2,1).ne.10).and. & - (itype(2,molnum(2)).ne.ntyp1_molec(molnum(2)))) then + (itype(2,molnum(2)).ne.ntyp1_molec(molnum(2))).and.(molnum(2).ne.5)) then gxcart(j,1)= gxcart(j,1) & -gloc_sc(3,0,icg)*dtauangle(j,3,1,3) gcart(j,1)=gcart(j,1)+gloc_sc(3,0,icg)* & @@ -3450,15 +3492,17 @@ ! ommited ! & +gloc_sc(intertyp,nres-2,icg)*dtheta(j,1,3) +! write(iout,*) "przed dE/ddc2 gcart", gcart(1,2) + ! Calculating the remainder of dE/ddc2 do j=1,3 if((itype(2,1).ne.10).and. & - (itype(2,molnum(2)).ne.ntyp1_molec(molnum(2)))) then + (itype(2,molnum(2)).ne.ntyp1_molec(molnum(2)).and.(molnum(2).ne.5))) then if ((itype(1,1).ne.10).and.& - ((itype(1,molnum(1)).ne.ntyp1_molec(molnum(1)))))& + ((itype(1,molnum(1)).ne.ntyp1_molec(molnum(1)))).and.(molnum(1).ne.5))& gxcart(j,2)=gxcart(j,2)+ & gloc_sc(3,0,icg)*dtauangle(j,3,3,3) - if ((itype(3,1).ne.10).and.(nres.ge.3).and.(itype(3,molnum(3)).ne.ntyp1_molec(3))) & + if ((itype(3,1).ne.10).and.(nres.ge.3).and.(itype(3,molnum(3)).ne.ntyp1_molec(3)).and.molnum(3).ne.5) & then gxcart(j,2)=gxcart(j,2)-gloc_sc(3,1,icg)*dtauangle(j,3,1,4) !c the - above is due to different vector direction @@ -3470,33 +3514,35 @@ gxcart(j,2)=gxcart(j,2)-gloc_sc(1,1,icg)*dtauangle(j,1,1,4) !c the - above is due to different vector direction gcart(j,2)=gcart(j,2)+gloc_sc(1,1,icg)*dtauangle(j,1,2,4) -! write(iout,*) gloc_sc(1,1,icg),dtauangle(j,1,2,4),"gcart" +! write(iout,*) gloc_sc(1,1,icg),dtauangle(j,1,2,4),"gcart",gcart(j,2) ! write(iout,*) gloc_sc(1,1,icg),dtauangle(j,1,1,4),"gx" endif endif if ((itype(1,1).ne.10).and.& - (itype(1,molnum(1)).ne.ntyp1_molec(molnum(1)))) then + (itype(1,molnum(1)).ne.ntyp1_molec(molnum(1))).and.(molnum(1).ne.5)) then gcart(j,2)=gcart(j,2)+gloc_sc(1,0,icg)*dtauangle(j,1,3,3) ! write(iout,*) gloc_sc(1,0,icg),dtauangle(j,1,3,3) endif - if ((itype(3,1).ne.10).and.(nres.ge.3)) then + if ((itype(3,1).ne.10).and.(nres.ge.3).and.(molnum(3).ne.5)) then gcart(j,2)=gcart(j,2)+gloc_sc(2,1,icg)*dtauangle(j,2,2,4) ! write(iout,*) gloc_sc(2,1,icg),dtauangle(j,2,2,4) endif - if ((itype(4,1).ne.10).and.(nres.ge.4)) then + if ((itype(4,1).ne.10).and.(nres.ge.4).and.(molnum(4).ne.5)) then gcart(j,2)=gcart(j,2)+gloc_sc(2,2,icg)*dtauangle(j,2,1,5) ! write(iout,*) gloc_sc(2,2,icg),dtauangle(j,2,1,5) endif ! write(iout,*) gcart(j,2),itype(2,1),itype(1,1),itype(3,1), "gcart2" enddo +! write(iout,*) "po dE/ddc2 gcart", gcart(1,2) + ! If there are more than five residues if(nres.ge.5) then do i=3,nres-2 do j=1,3 ! write(iout,*) "before", gcart(j,i) if ((itype(i,1).ne.10).and.& - (itype(i,molnum(i)).ne.ntyp1_molec(molnum(i)))) then + (itype(i,molnum(i)).ne.ntyp1_molec(molnum(i))).and.(molnum(i).ne.5)) then gxcart(j,i)=gxcart(j,i)+gloc_sc(2,i-2,icg) & *dtauangle(j,2,3,i+1) & -gloc_sc(1,i-1,icg)*dtauangle(j,1,1,i+2) @@ -3506,14 +3552,15 @@ ! & gcart(j,i),gloc_sc(1,i-1,icg),dtauangle(j,1,2,i+2) ! if (itype(i-1,1).ne.10) then if ((itype(i-1,1).ne.10).and.& - (itype(i-1,molnum(i-1)).ne.ntyp1_molec(molnum(i-1)))) then + (itype(i-1,molnum(i-1)).ne.ntyp1_molec(molnum(i-1))).and.(molnum(i-1).eq.5)) then gxcart(j,i)=gxcart(j,i)+gloc_sc(3,i-2,icg) & *dtauangle(j,3,3,i+1) endif ! if (itype(i+1,1).ne.10) then if ((itype(i+1,1).ne.10).and.& - (itype(i+1,molnum(i+1)).ne.ntyp1_molec(molnum(i+1)))) then + (itype(i+1,molnum(i+1)).ne.ntyp1_molec(molnum(i+1))).and.& + (molnum(i+1).ne.5)) then gxcart(j,i)=gxcart(j,i)-gloc_sc(3,i-1,icg) & *dtauangle(j,3,1,i+2) gcart(j,i)=gcart(j,i)+gloc_sc(3,i-1,icg) & @@ -3522,13 +3569,15 @@ endif ! if (itype(i-1,1).ne.10) then if ((itype(i-1,1).ne.10).and.& - (itype(i-1,molnum(i-1)).ne.ntyp1_molec(molnum(i-1)))) then + (itype(i-1,molnum(i-1)).ne.ntyp1_molec(molnum(i-1))).and.& + (molnum(i-1).ne.5)) then gcart(j,i)=gcart(j,i)+gloc_sc(1,i-2,icg)* & dtauangle(j,1,3,i+1) endif ! if (itype(i+1,1).ne.10) then if ((itype(i+1,1).ne.10).and.& - (itype(i+1,molnum(i+1)).ne.ntyp1_molec(molnum(i+1)))) then + (itype(i+1,molnum(i+1)).ne.ntyp1_molec(molnum(i+1)))& + .and. (molnum(i+1).ne.5)) then gcart(j,i)=gcart(j,i)+gloc_sc(2,i-1,icg)* & dtauangle(j,2,2,i+2) ! write(iout,*) "numer",i,gloc_sc(2,i-1,icg), @@ -3536,7 +3585,7 @@ endif ! if (itype(i+2,1).ne.10) then if ((itype(i+2,1).ne.10).and.& - (itype(i+2,molnum(i+2)).ne.ntyp1_molec(molnum(i+2)))) then + (itype(i+2,molnum(i+2)).ne.ntyp1_molec(molnum(i+2))).and.(molnum(i+2).ne.5)) then gcart(j,i)=gcart(j,i)+gloc_sc(2,i,icg)* & dtauangle(j,2,1,i+3) endif @@ -3547,19 +3596,19 @@ if(nres.ge.4) then do j=1,3 if ((itype(nres-1,1).ne.10).and.& - (itype(nres-1,molnum(nres-1)).ne.ntyp1_molec(molnum(nres-1)))) then + (itype(nres-1,molnum(nres-1)).ne.ntyp1_molec(molnum(nres-1))).and.(molnum(nres-1).ne.5)) then gxcart(j,nres-1)=gxcart(j,nres-1)+gloc_sc(2,nres-3,icg) & *dtauangle(j,2,3,nres) ! write (iout,*) "gxcart(nres-1)", gloc_sc(2,nres-3,icg), ! & dtauangle(j,2,3,nres), gxcart(j,nres-1) ! if (itype(nres-2,1).ne.10) then if ((itype(nres-2,1).ne.10).and.& - (itype(nres-2,molnum(nres-2)).ne.ntyp1_molec(molnum(nres-2)))) then + (itype(nres-2,molnum(nres-2)).ne.ntyp1_molec(molnum(nres-2))).and.(molnum(nres-2).ne.5)) then gxcart(j,nres-1)=gxcart(j,nres-1)+gloc_sc(3,nres-3,icg) & *dtauangle(j,3,3,nres) endif if ((itype(nres,1).ne.10).and.& - (itype(nres,molnum(nres)).ne.ntyp1_molec(molnum(nres)))) then + (itype(nres,molnum(nres)).ne.ntyp1_molec(molnum(nres))).and.(molnum(nres).ne.5)) then gxcart(j,nres-1)=gxcart(j,nres-1)-gloc_sc(3,nres-2,icg) & *dtauangle(j,3,1,nres+1) gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(3,nres-2,icg) & @@ -3567,11 +3616,11 @@ endif endif if ((itype(nres-2,1).ne.10).and.& - (itype(nres-2,molnum(nres-2)).ne.ntyp1_molec(molnum(nres-2)))) then + (itype(nres-2,molnum(nres-2)).ne.ntyp1_molec(molnum(nres-2))).and.(molnum(nres-2).ne.5)) then gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(1,nres-3,icg)* & dtauangle(j,1,3,nres) endif - if ((itype(nres,1).ne.10).and.(itype(nres,molnum(nres)).ne.ntyp1_molec(molnum(nres)))) then + if ((itype(nres,1).ne.10).and.(itype(nres,molnum(nres)).ne.ntyp1_molec(molnum(nres))).and.(molnum(nres).ne.5)) then gcart(j,nres-1)=gcart(j,nres-1)+gloc_sc(2,nres-2,icg)* & dtauangle(j,2,2,nres+1) ! write (iout,*) "gcart(nres-1)", gloc_sc(2,nres-2,icg), @@ -3581,13 +3630,14 @@ endif ! Settind dE/ddnres if ((nres.ge.3).and.(itype(nres,1).ne.10).and. & - (itype(nres,molnum(nres)).ne.ntyp1_molec(molnum(nres))))then + (itype(nres,molnum(nres)).ne.ntyp1_molec(molnum(nres))).and.(molnum(nres).ne.5))then do j=1,3 gxcart(j,nres)=gxcart(j,nres)+gloc_sc(3,nres-2,icg) & *dtauangle(j,3,3,nres+1)+gloc_sc(2,nres-2,icg) & *dtauangle(j,2,3,nres+1) enddo endif +! write(iout,*) "final gcart",gcart(1,2) ! The side-chain vector derivatives ! print *,"gcart",gcart(:,:) return @@ -3720,7 +3770,8 @@ ! common /refstruct/ if(.not.allocated(cref)) allocate(cref(3,nres2+2,maxperm)) !(3,maxres2+2,maxperm) !elwrite(iout,*) "jestem w alloc geo 2" - allocate(crefjlee(3,nres2+2)) !(3,maxres2+2) +! allocate(crefjlee(3,nres2+2)) !(3,maxres2+2) + if (.not.allocated(crefjlee)) allocate (crefjlee(3,nres2+2)) if(.not.allocated(chain_rep)) allocate(chain_rep(3,nres2+2,maxsym)) !(3,maxres2+2,maxsym) if(.not.allocated(tabperm)) allocate(tabperm(maxperm,maxsym)) !(maxperm,maxsym) ! common /from_zscore/ in module.compare @@ -4010,8 +4061,11 @@ do i=1,nres if (molnum(i).eq.5) then c(1,i)=dmod(c(1,i),boxxsize) + if (c(1,i).lt.0) c(1,i)=c(1,i)+boxxsize c(2,i)=dmod(c(2,i),boxysize) + if (c(2,i).lt.0) c(2,i)=c(2,i)+boxysize c(3,i)=dmod(c(3,i),boxzsize) + if (c(3,i).lt.0) c(3,i)=c(3,i)+boxzsize c(1,i+nres)=dmod(c(1,i+nres),boxxsize) c(2,i+nres)=dmod(c(2,i+nres),boxysize) c(3,i+nres)=dmod(c(3,i+nres),boxzsize)