1 subroutine etotal(energia)
7 cMS$ATTRIBUTES C :: proc_proc
12 double precision weights_(n_ene)
13 double precision time00
16 include 'COMMON.SETUP'
17 include 'COMMON.IOUNITS'
18 double precision energia(0:n_ene)
19 include 'COMMON.LOCAL'
20 include 'COMMON.FFIELD'
21 include 'COMMON.DERIV'
22 include 'COMMON.INTERACT'
23 include 'COMMON.SBRIDGE'
24 include 'COMMON.CHAIN'
27 include 'COMMON.QRESTR'
28 include 'COMMON.CONTROL'
29 include 'COMMON.TIME1'
30 include 'COMMON.SPLITELE'
31 include 'COMMON.TORCNSTR'
34 double precision evdw,evdw1,evdw2,evdw2_14,ees,eel_loc,
35 & eello_turn3,eello_turn4,edfadis,estr,ehpb,ebe,ethetacnstr,
36 & escloc,etors,edihcnstr,etors_d,esccor,ecorr,ecorr5,ecorr6,eturn6,
37 & eliptran,Eafmforce,Etube,
38 & esaxs_constr,ehomology_constr,edfator,edfanei,edfabet
39 integer n_corr,n_corr1
41 c print*,"ETOTAL Processor",fg_rank," absolute rank",myrank,
42 c & " nfgtasks",nfgtasks
43 if (nfgtasks.gt.1) then
45 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
46 if (fg_rank.eq.0) then
47 call MPI_Bcast(0,1,MPI_INTEGER,king,FG_COMM,IERROR)
48 c print *,"Processor",myrank," BROADCAST iorder"
49 C FG master sets up the WEIGHTS_ array which will be broadcast to the
50 C FG slaves as WEIGHTS array.
73 weights_(28)=wdfa_dist
76 weights_(31)=wdfa_beta
77 C FG Master broadcasts the WEIGHTS_ array
78 call MPI_Bcast(weights_(1),n_ene,
79 & MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
81 C FG slaves receive the WEIGHTS array
82 call MPI_Bcast(weights(1),n_ene,
83 & MPI_DOUBLE_PRECISION,king,FG_COMM,IERROR)
106 wdfa_dist=weights_(28)
107 wdfa_tor=weights_(29)
108 wdfa_nei=weights_(30)
109 wdfa_beta=weights_(31)
111 time_Bcast=time_Bcast+MPI_Wtime()-time00
112 time_Bcastw=time_Bcastw+MPI_Wtime()-time00
113 c call chainbuild_cart
115 if (nfgtasks.gt.1) then
116 call MPI_Bcast(itime_mat,1,MPI_INT,king,FG_COMM,IERROR)
118 if (mod(itime_mat,imatupdate).eq.0) then
119 call make_SCp_inter_list
120 call make_SCSC_inter_list
121 call make_pp_inter_list
122 call make_pp_vdw_inter_list
124 c print *,'Processor',myrank,' calling etotal ipot=',ipot
125 c print *,'Processor',myrank,' nnt=',nnt,' nct=',nct
127 c if (modecalc.eq.12.or.modecalc.eq.14) then
128 c call int_from_cart1(.false.)
142 C Compute the side-chain and electrostatic interaction energy
145 goto (101,102,103,104,105,106) ipot
146 C Lennard-Jones potential.
148 cd print '(a)','Exit ELJ'
150 C Lennard-Jones-Kihara potential (shifted).
153 C Berne-Pechukas potential (dilated LJ, angular dependence).
156 C Gay-Berne potential (shifted LJ, angular dependence).
158 C print *,"bylem w egb"
160 C Gay-Berne-Vorobjev potential (shifted LJ, angular dependence).
163 C Soft-sphere potential
164 106 call e_softsphere(evdw)
166 C Calculate electrostatic (H-bonding) energy of the main chain.
170 C BARTEK for dfa test!
171 if (wdfa_dist.gt.0) then
176 c print*, 'edfad is finished!', edfadis
177 if (wdfa_tor.gt.0) then
182 c print*, 'edfat is finished!', edfator
183 if (wdfa_nei.gt.0) then
188 c print*, 'edfan is finished!', edfanei
189 if (wdfa_beta.gt.0) then
196 cmc Sep-06: egb takes care of dynamic ss bonds too
198 c if (dyn_ss) call dyn_set_nss
200 c print *,"Processor",myrank," computed USCSC"
206 time_vec=time_vec+MPI_Wtime()-time01
208 C Introduction of shielding effect first for each peptide group
209 C the shielding factor is set this factor is describing how each
210 C peptide group is shielded by side-chains
211 C the matrix - shield_fac(i) the i index describe the ith between i and i+1
212 C write (iout,*) "shield_mode",shield_mode
213 if (shield_mode.eq.1) then
215 else if (shield_mode.eq.2) then
218 c print *,"Processor",myrank," left VEC_AND_DERIV"
221 if (welec.gt.0d0.or.wvdwpp.gt.0d0.or.wel_loc.gt.0d0.or.
222 & wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
223 & .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
224 & .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
226 if (welec.gt.0d0.or.wel_loc.gt.0d0.or.
227 & wturn3.gt.0d0.or.wturn4.gt.0d0 .or. wcorr.gt.0.0d0
228 & .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.d0
229 & .or. wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0 ) then
231 call eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
240 write (iout,*) "Soft-spheer ELEC potential"
241 c call eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
245 c time_enecalc=time_enecalc+MPI_Wtime()-time00
247 c print *,"Processor",myrank," computed UELEC"
249 C Calculate excluded-volume interaction energy between peptide groups
254 call escp(evdw2,evdw2_14)
260 c write (iout,*) "Soft-sphere SCP potential"
261 call escp_soft_sphere(evdw2,evdw2_14)
264 c Calculate the bond-stretching energy
268 C Calculate the disulfide-bridge and other energy and the contributions
269 C from other distance constraints.
270 cd write (iout,*) 'Calling EHPB'
272 cd print *,'EHPB exitted succesfully.'
274 C Calculate the virtual-bond-angle energy.
276 if (wang.gt.0d0) then
277 if (tor_mode.eq.0) then
280 C ebend kcc is Kubo cumulant clustered rigorous attemp to derive the
288 if (with_theta_constr) call etheta_constr(ethetacnstr)
289 c print *,"Processor",myrank," computed UB"
291 C Calculate the SC local energy.
293 C print *,"TU DOCHODZE?"
295 c print *,"Processor",myrank," computed USC"
297 C Calculate the virtual-bond torsional energy.
299 cd print *,'nterm=',nterm
300 C print *,"tor",tor_mode
301 if (wtor.gt.0.0d0) then
302 if (tor_mode.eq.0) then
305 C etor kcc is Kubo cumulant clustered rigorous attemp to derive the
313 if (ndih_constr.gt.0) call etor_constr(edihcnstr)
314 c print *,"Processor",myrank," computed Utor"
315 if (constr_homology.ge.1) then
316 call e_modeller(ehomology_constr)
317 c print *,'iset=',iset,'me=',me,ehomology_constr,
318 c & 'Processor',fg_rank,' CG group',kolor,
319 c & ' absolute rank',MyRank
321 ehomology_constr=0.0d0
324 C 6/23/01 Calculate double-torsional energy
326 if ((wtor_d.gt.0.0d0).and.(tor_mode.eq.0)) then
331 c print *,"Processor",myrank," computed Utord"
333 C 21/5/07 Calculate local sicdechain correlation energy
335 if (wsccor.gt.0.0d0) then
336 call eback_sc_corr(esccor)
341 C print *,"PRZED MULIt"
342 c print *,"Processor",myrank," computed Usccorr"
344 C 12/1/95 Multi-body terms
348 if ((wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0
349 & .or. wturn6.gt.0.0d0) .and. ipot.lt.6) then
350 call multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,n_corr1)
351 c write(2,*)'MULTIBODY_EELLO n_corr=',n_corr,' n_corr1=',n_corr1,
352 c &" ecorr",ecorr," ecorr5",ecorr5," ecorr6",ecorr6," eturn6",eturn6
360 if ((wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) .and. ipot.lt.6) then
361 c write (iout,*) "Before MULTIBODY_HB ecorr",ecorr,ecorr5,ecorr6,
364 call multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
365 c write (iout,*) "MULTIBODY_HB ecorr",ecorr,ecorr5,ecorr6,n_corr,
370 c print *,"Processor",myrank," computed Ucorr"
371 c write (iout,*) "nsaxs",nsaxs," saxs_mode",saxs_mode
372 if (nsaxs.gt.0 .and. saxs_mode.eq.0) then
373 call e_saxs(Esaxs_constr)
374 c write (iout,*) "From Esaxs: Esaxs_constr",Esaxs_constr
375 else if (nsaxs.gt.0 .and. saxs_mode.gt.0) then
376 call e_saxsC(Esaxs_constr)
377 c write (iout,*) "From EsaxsC: Esaxs_constr",Esaxs_constr
382 C If performing constraint dynamics, call the constraint energy
383 C after the equilibration time
384 c if(usampl.and.totT.gt.eq_time) then
385 c write (iout,*) "usampl",usampl
389 call Econstr_back_qlike
397 C 01/27/2015 added by adasko
398 C the energy component below is energy transfer into lipid environment
399 C based on partition function
400 C print *,"przed lipidami"
401 if (wliptran.gt.0) then
402 call Eliptransfer(eliptran)
406 C print *,"za lipidami"
407 if (AFMlog.gt.0) then
408 call AFMforce(Eafmforce)
409 else if (selfguide.gt.0) then
410 call AFMvel(Eafmforce)
412 if (TUBElog.eq.1) then
413 C print *,"just before call"
415 elseif (TUBElog.eq.2) then
416 call calctube2(Etube)
422 time_enecalc=time_enecalc+MPI_Wtime()-time00
424 c print *,"Processor",myrank," computed Uconstr"
433 energia(2)=evdw2-evdw2_14
450 energia(8)=eello_turn3
451 energia(9)=eello_turn4
458 energia(19)=edihcnstr
460 energia(20)=Uconst+Uconst_back
463 energia(23)=Eafmforce
464 energia(24)=ethetacnstr
466 energia(26)=Esaxs_constr
467 energia(27)=ehomology_constr
472 c write (iout,*) "esaxs_constr",energia(26)
473 c Here are the energies showed per procesor if the are more processors
474 c per molecule then we sum it up in sum_energy subroutine
475 c print *," Processor",myrank," calls SUM_ENERGY"
476 call sum_energy(energia,.true.)
477 c write (iout,*) "After sum_energy: esaxs_constr",energia(26)
478 if (dyn_ss) call dyn_set_nss
479 c print *," Processor",myrank," left SUM_ENERGY"
481 time_sumene=time_sumene+MPI_Wtime()-time00
485 c-------------------------------------------------------------------------------
486 subroutine sum_energy(energia,reduce)
492 cMS$ATTRIBUTES C :: proc_proc
498 double precision time00
500 include 'COMMON.SETUP'
501 include 'COMMON.IOUNITS'
502 double precision energia(0:n_ene),enebuff(0:n_ene+1)
503 include 'COMMON.FFIELD'
504 include 'COMMON.DERIV'
505 include 'COMMON.INTERACT'
506 include 'COMMON.SBRIDGE'
507 include 'COMMON.CHAIN'
509 include 'COMMON.CONTROL'
510 include 'COMMON.TIME1'
513 double precision evdw,evdw1,evdw2,evdw2_14,ees,eel_loc,
514 & eello_turn3,eello_turn4,edfadis,estr,ehpb,ebe,ethetacnstr,
515 & escloc,etors,edihcnstr,etors_d,esccor,ecorr,ecorr5,ecorr6,eturn6,
516 & eliptran,Eafmforce,Etube,
517 & esaxs_constr,ehomology_constr,edfator,edfanei,edfabet
518 double precision Uconst,etot
520 if (nfgtasks.gt.1 .and. reduce) then
522 write (iout,*) "energies before REDUCE"
523 call enerprint(energia)
527 enebuff(i)=energia(i)
530 call MPI_Barrier(FG_COMM,IERR)
531 time_barrier_e=time_barrier_e+MPI_Wtime()-time00
533 call MPI_Reduce(enebuff(0),energia(0),n_ene+1,
534 & MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
536 write (iout,*) "energies after REDUCE"
537 call enerprint(energia)
540 time_Reduce=time_Reduce+MPI_Wtime()-time00
542 if (fg_rank.eq.0) then
546 evdw2=energia(2)+energia(18)
562 eello_turn3=energia(8)
563 eello_turn4=energia(9)
570 edihcnstr=energia(19)
575 Eafmforce=energia(23)
576 ethetacnstr=energia(24)
578 esaxs_constr=energia(26)
579 ehomology_constr=energia(27)
585 etot=wsc*evdw+wscp*evdw2+welec*ees+wvdwpp*evdw1
586 & +wang*ebe+wtor*etors+wscloc*escloc
587 & +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5
588 & +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3
589 & +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d
590 & +wbond*estr+wumb*Uconst+wsccor*esccor+wliptran*eliptran+Eafmforce
591 & +ethetacnstr+wtube*Etube+wsaxs*esaxs_constr+ehomology_constr
592 & +wdfa_dist*edfadis+wdfa_tor*edfator+wdfa_nei*edfanei
595 etot=wsc*evdw+wscp*evdw2+welec*(ees+evdw1)
596 & +wang*ebe+wtor*etors+wscloc*escloc
597 & +wstrain*ehpb+wcorr*ecorr+wcorr5*ecorr5
598 & +wcorr6*ecorr6+wturn4*eello_turn4+wturn3*eello_turn3
599 & +wturn6*eturn6+wel_loc*eel_loc+edihcnstr+wtor_d*etors_d
600 & +wbond*estr+wumb*Uconst+wsccor*esccor+wliptran*eliptran
602 & +ethetacnstr+wtube*Etube+wsaxs*esaxs_constr+ehomology_constr
603 & +wdfa_dist*edfadis+wdfa_tor*edfator+wdfa_nei*edfanei
610 if (isnan(etot).ne.0) energia(0)=1.0d+99
612 if (isnan(etot)) energia(0)=1.0d+99
617 idumm=proc_proc(etot,i)
619 call proc_proc(etot,i)
621 if(i.eq.1)energia(0)=1.0d+99
628 c-------------------------------------------------------------------------------
629 subroutine sum_gradient
635 cMS$ATTRIBUTES C :: proc_proc
641 double precision time00,time01
643 double precision gradbufc(3,-1:maxres),gradbufx(3,-1:maxres),
644 & glocbuf(4*maxres),gradbufc_sum(3,-1:maxres)
645 & ,gloc_scbuf(3,-1:maxres)
646 include 'COMMON.SETUP'
647 include 'COMMON.IOUNITS'
648 include 'COMMON.FFIELD'
649 include 'COMMON.DERIV'
650 include 'COMMON.INTERACT'
651 include 'COMMON.SBRIDGE'
652 include 'COMMON.CHAIN'
654 include 'COMMON.CONTROL'
655 include 'COMMON.TIME1'
656 include 'COMMON.MAXGRAD'
657 include 'COMMON.SCCOR'
658 c include 'COMMON.MD'
659 include 'COMMON.QRESTR'
661 double precision scalar
662 double precision gvdwc_norm,gvdwc_scp_norm,gelc_norm,gvdwpp_norm,
663 &gradb_norm,ghpbc_norm,gradcorr_norm,gel_loc_norm,gcorr3_turn_norm,
664 &gcorr4_turn_norm,gradcorr5_norm,gradcorr6_norm,
665 &gcorr6_turn_norm,gsccorrc_norm,gscloc_norm,gvdwx_norm,
666 &gradx_scp_norm,ghpbx_norm,gradxorr_norm,gsccorrx_norm,
672 write (iout,*) "sum_gradient gvdwc, gvdwx"
674 write (iout,'(i3,3f10.5,5x,3f10.5,5x,f10.5)')
675 & i,(gvdwx(j,i),j=1,3),(gvdwc(j,i),j=1,3)
680 write (iout,*) "sum_gradient gsaxsc, gsaxsx"
682 write (iout,'(i3,3e15.5,5x,3e15.5)')
683 & i,(gsaxsc(j,i),j=1,3),(gsaxsx(j,i),j=1,3)
688 C FG slaves call the following matching MPI_Bcast in ERGASTULUM
689 if (nfgtasks.gt.1 .and. fg_rank.eq.0)
690 & call MPI_Bcast(1,1,MPI_INTEGER,king,FG_COMM,IERROR)
693 C 9/29/08 AL Transform parts of gradients in site coordinates to the gradient
694 C in virtual-bond-vector coordinates
697 c write (iout,*) "gel_loc gel_loc_long and gel_loc_loc"
699 c write (iout,'(i5,3f10.5,2x,3f10.5,2x,f10.5)')
700 c & i,(gel_loc(j,i),j=1,3),(gel_loc_long(j,i),j=1,3),gel_loc_loc(i)
702 c write (iout,*) "gel_loc_tur3 gel_loc_turn4"
704 c write (iout,'(i5,3f10.5,2x,f10.5)')
705 c & i,(gcorr4_turn(j,i),j=1,3),gel_loc_turn4(i)
707 write (iout,*) "gradcorr5 gradcorr5_long gradcorr5_loc"
709 write (iout,'(i3,3f10.5,5x,3f10.5,5x,f10.5)')
710 & i,(gradcorr5(j,i),j=1,3),(gradcorr5_long(j,i),j=1,3),
716 write (iout,*) "gsaxsc"
718 write (iout,'(i3,3f10.5)') i,(wsaxs*gsaxsc(j,i),j=1,3)
725 gradbufc(j,i)=wsc*gvdwc(j,i)+
726 & wscp*(gvdwc_scp(j,i)+gvdwc_scpp(j,i))+
727 & welec*gelc_long(j,i)+wvdwpp*gvdwpp(j,i)+
728 & wel_loc*gel_loc_long(j,i)+
729 & wcorr*gradcorr_long(j,i)+
730 & wcorr5*gradcorr5_long(j,i)+
731 & wcorr6*gradcorr6_long(j,i)+
732 & wturn6*gcorr6_turn_long(j,i)+
734 & +wliptran*gliptranc(j,i)
736 & +welec*gshieldc(j,i)
737 & +wcorr*gshieldc_ec(j,i)
738 & +wturn3*gshieldc_t3(j,i)
739 & +wturn4*gshieldc_t4(j,i)
740 & +wel_loc*gshieldc_ll(j,i)
741 & +wtube*gg_tube(j,i)
748 gradbufc(j,i)=wsc*gvdwc(j,i)+
749 & wscp*(gvdwc_scp(j,i)+gvdwc_scpp(j,i))+
750 & welec*gelc_long(j,i)+
752 & wel_loc*gel_loc_long(j,i)+
753 & wcorr*gradcorr_long(j,i)+
754 & wcorr5*gradcorr5_long(j,i)+
755 & wcorr6*gradcorr6_long(j,i)+
756 & wturn6*gcorr6_turn_long(j,i)+
758 & +wliptran*gliptranc(j,i)
760 & +welec*gshieldc(j,i)
761 & +wcorr*gshieldc_ec(j,i)
762 & +wturn4*gshieldc_t4(j,i)
763 & +wel_loc*gshieldc_ll(j,i)
764 & +wtube*gg_tube(j,i)
771 gradbufc(j,i)=gradbufc(j,i)+
772 & wdfa_dist*gdfad(j,i)+
773 & wdfa_tor*gdfat(j,i)+
774 & wdfa_nei*gdfan(j,i)+
775 & wdfa_beta*gdfab(j,i)
779 write (iout,*) "gradc from gradbufc"
781 write (iout,'(i3,3f10.5)') i,(gradc(j,i,icg),j=1,3)
786 if (nfgtasks.gt.1) then
789 write (iout,*) "gradbufc before allreduce"
791 write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
797 gradbufc_sum(j,i)=gradbufc(j,i)
800 c call MPI_AllReduce(gradbufc(1,1),gradbufc_sum(1,1),3*nres,
801 c & MPI_DOUBLE_PRECISION,MPI_SUM,FG_COMM,IERR)
802 c time_reduce=time_reduce+MPI_Wtime()-time00
804 c write (iout,*) "gradbufc_sum after allreduce"
806 c write (iout,'(i3,3f10.5)') i,(gradbufc_sum(j,i),j=1,3)
811 c time_allreduce=time_allreduce+MPI_Wtime()-time00
819 write (iout,*) "igrad_start",igrad_start," igrad_end",igrad_end
820 write (iout,*) (i," jgrad_start",jgrad_start(i),
821 & " jgrad_end ",jgrad_end(i),
822 & i=igrad_start,igrad_end)
825 c Obsolete and inefficient code; we can make the effort O(n) and, therefore,
826 c do not parallelize this part.
828 c do i=igrad_start,igrad_end
829 c do j=jgrad_start(i),jgrad_end(i)
831 c gradbufc(k,i)=gradbufc(k,i)+gradbufc_sum(k,j)
836 gradbufc(j,nres-1)=gradbufc_sum(j,nres)
840 gradbufc(j,i)=gradbufc(j,i+1)+gradbufc_sum(j,i+1)
844 write (iout,*) "gradbufc after summing"
846 write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
853 write (iout,*) "gradbufc"
855 write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
861 gradbufc_sum(j,i)=gradbufc(j,i)
866 gradbufc(j,nres-1)=gradbufc_sum(j,nres)
870 gradbufc(j,i)=gradbufc(j,i+1)+gradbufc_sum(j,i+1)
875 c gradbufc(k,i)=0.0d0
879 c gradbufc(k,i)=gradbufc(k,i)+gradbufc(k,j)
884 write (iout,*) "gradbufc after summing"
886 write (iout,'(i3,3f10.5)') i,(gradbufc(j,i),j=1,3)
894 gradbufc(k,nres)=0.0d0
899 C print *,gradbufc(1,13)
900 C print *,welec*gelc(1,13)
901 C print *,wel_loc*gel_loc(1,13)
902 C print *,0.5d0*(wscp*gvdwc_scpp(1,13))
903 C print *,welec*gelc_long(1,13)+wvdwpp*gvdwpp(1,13)
904 C print *,wel_loc*gel_loc_long(1,13)
905 C print *,gradafm(1,13),"AFM"
906 gradc(j,i,icg)=gradbufc(j,i)+welec*gelc(j,i)+
907 & wel_loc*gel_loc(j,i)+
908 & 0.5d0*(wscp*gvdwc_scpp(j,i)+
909 & welec*gelc_long(j,i)+wvdwpp*gvdwpp(j,i)+
910 & wel_loc*gel_loc_long(j,i)+
911 & wcorr*gradcorr_long(j,i)+
912 & wcorr5*gradcorr5_long(j,i)+
913 & wcorr6*gradcorr6_long(j,i)+
914 & wturn6*gcorr6_turn_long(j,i))+
916 & wcorr*gradcorr(j,i)+
917 & wturn3*gcorr3_turn(j,i)+
918 & wturn4*gcorr4_turn(j,i)+
919 & wcorr5*gradcorr5(j,i)+
920 & wcorr6*gradcorr6(j,i)+
921 & wturn6*gcorr6_turn(j,i)+
922 & wsccor*gsccorc(j,i)
923 & +wscloc*gscloc(j,i)
924 & +wliptran*gliptranc(j,i)
926 & +welec*gshieldc(j,i)
927 & +welec*gshieldc_loc(j,i)
928 & +wcorr*gshieldc_ec(j,i)
929 & +wcorr*gshieldc_loc_ec(j,i)
930 & +wturn3*gshieldc_t3(j,i)
931 & +wturn3*gshieldc_loc_t3(j,i)
932 & +wturn4*gshieldc_t4(j,i)
933 & +wturn4*gshieldc_loc_t4(j,i)
934 & +wel_loc*gshieldc_ll(j,i)
935 & +wel_loc*gshieldc_loc_ll(j,i)
936 & +wtube*gg_tube(j,i)
939 gradc(j,i,icg)=gradbufc(j,i)+welec*gelc(j,i)+
940 & wel_loc*gel_loc(j,i)+
941 & 0.5d0*(wscp*gvdwc_scpp(j,i)+
942 & welec*gelc_long(j,i)+
943 & wel_loc*gel_loc_long(j,i)+
944 & wcorr*gcorr_long(j,i)+
945 & wcorr5*gradcorr5_long(j,i)+
946 & wcorr6*gradcorr6_long(j,i)+
947 & wturn6*gcorr6_turn_long(j,i))+
949 & wcorr*gradcorr(j,i)+
950 & wturn3*gcorr3_turn(j,i)+
951 & wturn4*gcorr4_turn(j,i)+
952 & wcorr5*gradcorr5(j,i)+
953 & wcorr6*gradcorr6(j,i)+
954 & wturn6*gcorr6_turn(j,i)+
955 & wsccor*gsccorc(j,i)
956 & +wscloc*gscloc(j,i)
957 & +wliptran*gliptranc(j,i)
959 & +welec*gshieldc(j,i)
960 & +welec*gshieldc_loc(j,i)
961 & +wcorr*gshieldc_ec(j,i)
962 & +wcorr*gshieldc_loc_ec(j,i)
963 & +wturn3*gshieldc_t3(j,i)
964 & +wturn3*gshieldc_loc_t3(j,i)
965 & +wturn4*gshieldc_t4(j,i)
966 & +wturn4*gshieldc_loc_t4(j,i)
967 & +wel_loc*gshieldc_ll(j,i)
968 & +wel_loc*gshieldc_loc_ll(j,i)
969 & +wtube*gg_tube(j,i)
973 gradx(j,i,icg)=wsc*gvdwx(j,i)+wscp*gradx_scp(j,i)+
975 & wstrain*ghpbx(j,i)+wcorr*gradxorr(j,i)+
976 & wsccor*gsccorx(j,i)
977 & +wscloc*gsclocx(j,i)
978 & +wliptran*gliptranx(j,i)
979 & +welec*gshieldx(j,i)
980 & +wcorr*gshieldx_ec(j,i)
981 & +wturn3*gshieldx_t3(j,i)
982 & +wturn4*gshieldx_t4(j,i)
983 & +wel_loc*gshieldx_ll(j,i)
984 & +wtube*gg_tube_sc(j,i)
991 if (constr_homology.gt.0) then
994 gradc(j,i,icg)=gradc(j,i,icg)+duscdiff(j,i)
995 gradx(j,i,icg)=gradx(j,i,icg)+duscdiffx(j,i)
1000 write (iout,*) "gradc gradx gloc after adding"
1002 write (iout,'(i5,3f10.5,5x,3f10.5,5x,f10.5)')
1003 & i,(gradc(j,i,icg),j=1,3),(gradx(j,i,icg),j=1,3),gloc(i,icg)
1007 write (iout,*) "gloc before adding corr"
1009 write (iout,*) i,gloc(i,icg)
1013 gloc(i,icg)=gloc(i,icg)+wcorr*gcorr_loc(i)
1014 & +wcorr5*g_corr5_loc(i)
1015 & +wcorr6*g_corr6_loc(i)
1016 & +wturn4*gel_loc_turn4(i)
1017 & +wturn3*gel_loc_turn3(i)
1018 & +wturn6*gel_loc_turn6(i)
1019 & +wel_loc*gel_loc_loc(i)
1022 write (iout,*) "gloc after adding corr"
1024 write (iout,*) i,gloc(i,icg)
1028 if (nfgtasks.gt.1) then
1031 gradbufc(j,i)=gradc(j,i,icg)
1032 gradbufx(j,i)=gradx(j,i,icg)
1036 glocbuf(i)=gloc(i,icg)
1040 write (iout,*) "gloc_sc before reduce"
1043 write (iout,*) i,j,gloc_sc(j,i,icg)
1050 gloc_scbuf(j,i)=gloc_sc(j,i,icg)
1054 call MPI_Barrier(FG_COMM,IERR)
1055 time_barrier_g=time_barrier_g+MPI_Wtime()-time00
1057 call MPI_Reduce(gradbufc(1,1),gradc(1,1,icg),3*nres,
1058 & MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
1059 call MPI_Reduce(gradbufx(1,1),gradx(1,1,icg),3*nres,
1060 & MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
1061 call MPI_Reduce(glocbuf(1),gloc(1,icg),4*nres,
1062 & MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
1063 time_reduce=time_reduce+MPI_Wtime()-time00
1064 call MPI_Reduce(gloc_scbuf(1,1),gloc_sc(1,1,icg),3*nres,
1065 & MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
1066 time_reduce=time_reduce+MPI_Wtime()-time00
1068 write (iout,*) "gradc after reduce"
1071 write (iout,*) i,j,gradc(j,i,icg)
1076 write (iout,*) "gloc_sc after reduce"
1079 write (iout,*) i,j,gloc_sc(j,i,icg)
1084 write (iout,*) "gloc after reduce"
1086 write (iout,*) i,gloc(i,icg)
1091 if (gnorm_check) then
1093 c Compute the maximum elements of the gradient
1103 gcorr3_turn_max=0.0d0
1104 gcorr4_turn_max=0.0d0
1107 gcorr6_turn_max=0.0d0
1117 gvdwc_norm=dsqrt(scalar(gvdwc(1,i),gvdwc(1,i)))
1118 if (gvdwc_norm.gt.gvdwc_max) gvdwc_max=gvdwc_norm
1119 gvdwc_scp_norm=dsqrt(scalar(gvdwc_scp(1,i),gvdwc_scp(1,i)))
1120 if (gvdwc_scp_norm.gt.gvdwc_scp_max)
1121 & gvdwc_scp_max=gvdwc_scp_norm
1122 gelc_norm=dsqrt(scalar(gelc(1,i),gelc(1,i)))
1123 if (gelc_norm.gt.gelc_max) gelc_max=gelc_norm
1124 gvdwpp_norm=dsqrt(scalar(gvdwpp(1,i),gvdwpp(1,i)))
1125 if (gvdwpp_norm.gt.gvdwpp_max) gvdwpp_max=gvdwpp_norm
1126 gradb_norm=dsqrt(scalar(gradb(1,i),gradb(1,i)))
1127 if (gradb_norm.gt.gradb_max) gradb_max=gradb_norm
1128 ghpbc_norm=dsqrt(scalar(ghpbc(1,i),ghpbc(1,i)))
1129 if (ghpbc_norm.gt.ghpbc_max) ghpbc_max=ghpbc_norm
1130 gradcorr_norm=dsqrt(scalar(gradcorr(1,i),gradcorr(1,i)))
1131 if (gradcorr_norm.gt.gradcorr_max) gradcorr_max=gradcorr_norm
1132 gel_loc_norm=dsqrt(scalar(gel_loc(1,i),gel_loc(1,i)))
1133 if (gel_loc_norm.gt.gel_loc_max) gel_loc_max=gel_loc_norm
1134 gcorr3_turn_norm=dsqrt(scalar(gcorr3_turn(1,i),
1135 & gcorr3_turn(1,i)))
1136 if (gcorr3_turn_norm.gt.gcorr3_turn_max)
1137 & gcorr3_turn_max=gcorr3_turn_norm
1138 gcorr4_turn_norm=dsqrt(scalar(gcorr4_turn(1,i),
1139 & gcorr4_turn(1,i)))
1140 if (gcorr4_turn_norm.gt.gcorr4_turn_max)
1141 & gcorr4_turn_max=gcorr4_turn_norm
1142 gradcorr5_norm=dsqrt(scalar(gradcorr5(1,i),gradcorr5(1,i)))
1143 if (gradcorr5_norm.gt.gradcorr5_max)
1144 & gradcorr5_max=gradcorr5_norm
1145 gradcorr6_norm=dsqrt(scalar(gradcorr6(1,i),gradcorr6(1,i)))
1146 if (gradcorr6_norm.gt.gradcorr6_max)gradcorr6_max=gradcorr6_norm
1147 gcorr6_turn_norm=dsqrt(scalar(gcorr6_turn(1,i),
1148 & gcorr6_turn(1,i)))
1149 if (gcorr6_turn_norm.gt.gcorr6_turn_max)
1150 & gcorr6_turn_max=gcorr6_turn_norm
1151 gsccorrc_norm=dsqrt(scalar(gsccorc(1,i),gsccorc(1,i)))
1152 if (gsccorrc_norm.gt.gsccorrc_max) gsccorrc_max=gsccorrc_norm
1153 gscloc_norm=dsqrt(scalar(gscloc(1,i),gscloc(1,i)))
1154 if (gscloc_norm.gt.gscloc_max) gscloc_max=gscloc_norm
1155 gvdwx_norm=dsqrt(scalar(gvdwx(1,i),gvdwx(1,i)))
1156 if (gvdwx_norm.gt.gvdwx_max) gvdwx_max=gvdwx_norm
1157 gradx_scp_norm=dsqrt(scalar(gradx_scp(1,i),gradx_scp(1,i)))
1158 if (gradx_scp_norm.gt.gradx_scp_max)
1159 & gradx_scp_max=gradx_scp_norm
1160 ghpbx_norm=dsqrt(scalar(ghpbx(1,i),ghpbx(1,i)))
1161 if (ghpbx_norm.gt.ghpbx_max) ghpbx_max=ghpbx_norm
1162 gradxorr_norm=dsqrt(scalar(gradxorr(1,i),gradxorr(1,i)))
1163 if (gradxorr_norm.gt.gradxorr_max) gradxorr_max=gradxorr_norm
1164 gsccorrx_norm=dsqrt(scalar(gsccorx(1,i),gsccorx(1,i)))
1165 if (gsccorrx_norm.gt.gsccorrx_max) gsccorrx_max=gsccorrx_norm
1166 gsclocx_norm=dsqrt(scalar(gsclocx(1,i),gsclocx(1,i)))
1167 if (gsclocx_norm.gt.gsclocx_max) gsclocx_max=gsclocx_norm
1170 #if (defined AIX || defined CRAY)
1171 open(istat,file=statname,position="append")
1173 open(istat,file=statname,access="append")
1175 write (istat,'(1h#,21f10.2)') gvdwc_max,gvdwc_scp_max,
1176 & gelc_max,gvdwpp_max,gradb_max,ghpbc_max,
1177 & gradcorr_max,gel_loc_max,gcorr3_turn_max,gcorr4_turn_max,
1178 & gradcorr5_max,gradcorr6_max,gcorr6_turn_max,gsccorrc_max,
1179 & gscloc_max,gvdwx_max,gradx_scp_max,ghpbx_max,gradxorr_max,
1180 & gsccorrx_max,gsclocx_max
1182 if (gvdwc_max.gt.1.0d4) then
1183 write (iout,*) "gvdwc gvdwx gradb gradbx"
1185 write(iout,'(i5,4(3f10.2,5x))') i,(gvdwc(j,i),gvdwx(j,i),
1186 & gradb(j,i),gradbx(j,i),j=1,3)
1188 call pdbout(0.0d0,'cipiszcze',iout)
1194 write (iout,*) "gradc gradx gloc"
1196 write (iout,'(i5,3f10.5,5x,3f10.5,5x,f10.5)')
1197 & i,(gradc(j,i,icg),j=1,3),(gradx(j,i,icg),j=1,3),gloc(i,icg)
1201 time_sumgradient=time_sumgradient+MPI_Wtime()-time01
1205 c-------------------------------------------------------------------------------
1206 subroutine rescale_weights(t_bath)
1212 include 'DIMENSIONS'
1213 include 'COMMON.IOUNITS'
1214 include 'COMMON.FFIELD'
1215 include 'COMMON.SBRIDGE'
1216 include 'COMMON.CONTROL'
1217 double precision t_bath
1218 double precision facT,facT2,facT3,facT4,facT5
1219 double precision kfac /2.4d0/
1220 double precision x,x2,x3,x4,x5,licznik /1.12692801104297249644/
1222 c facT=2*temp0/(t_bath+temp0)
1223 if (rescale_mode.eq.0) then
1229 else if (rescale_mode.eq.1) then
1230 facT=kfac/(kfac-1.0d0+t_bath/temp0)
1231 facT2=kfac**2/(kfac**2-1.0d0+(t_bath/temp0)**2)
1232 facT3=kfac**3/(kfac**3-1.0d0+(t_bath/temp0)**3)
1233 facT4=kfac**4/(kfac**4-1.0d0+(t_bath/temp0)**4)
1234 facT5=kfac**5/(kfac**5-1.0d0+(t_bath/temp0)**5)
1235 else if (rescale_mode.eq.2) then
1241 facT=licznik/dlog(dexp(x)+dexp(-x))
1242 facT2=licznik/dlog(dexp(x2)+dexp(-x2))
1243 facT3=licznik/dlog(dexp(x3)+dexp(-x3))
1244 facT4=licznik/dlog(dexp(x4)+dexp(-x4))
1245 facT5=licznik/dlog(dexp(x5)+dexp(-x5))
1247 write (iout,*) "Wrong RESCALE_MODE",rescale_mode
1248 write (*,*) "Wrong RESCALE_MODE",rescale_mode
1250 call MPI_Finalize(MPI_COMM_WORLD,IERROR)
1254 if (shield_mode.gt.0) then
1255 wscp=weights(2)*fact
1257 wvdwpp=weights(16)*fact
1259 welec=weights(3)*fact
1260 wcorr=weights(4)*fact3
1261 wcorr5=weights(5)*fact4
1262 wcorr6=weights(6)*fact5
1263 wel_loc=weights(7)*fact2
1264 wturn3=weights(8)*fact2
1265 wturn4=weights(9)*fact3
1266 wturn6=weights(10)*fact5
1267 wtor=weights(13)*fact
1268 wtor_d=weights(14)*fact2
1269 wsccor=weights(21)*fact
1270 if (scale_umb) wumb=t_bath/temp0
1271 c write (iout,*) "scale_umb",scale_umb
1272 c write (iout,*) "t_bath",t_bath," temp0",temp0," wumb",wumb
1276 C------------------------------------------------------------------------
1277 subroutine enerprint(energia)
1279 include 'DIMENSIONS'
1280 include 'COMMON.IOUNITS'
1281 include 'COMMON.FFIELD'
1282 include 'COMMON.SBRIDGE'
1283 include 'COMMON.QRESTR'
1284 double precision energia(0:n_ene)
1285 double precision evdw,evdw1,evdw2,evdw2_14,ees,eel_loc,
1286 & eello_turn3,eello_turn4,edfadis,estr,ehpb,ebe,ethetacnstr,
1287 & escloc,etors,edihcnstr,etors_d,esccor,ecorr,ecorr5,ecorr6,
1289 & eliptran,Eafmforce,Etube,
1290 & esaxs,ehomology_constr,edfator,edfanei,edfabet,etot
1295 evdw2=energia(2)+energia(18)
1307 eello_turn3=energia(8)
1308 eello_turn4=energia(9)
1309 eello_turn6=energia(10)
1315 edihcnstr=energia(19)
1319 eliptran=energia(22)
1320 Eafmforce=energia(23)
1321 ethetacnstr=energia(24)
1324 ehomology_constr=energia(27)
1326 edfadis = energia(28)
1327 edfator = energia(29)
1328 edfanei = energia(30)
1329 edfabet = energia(31)
1331 write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,evdw1,wvdwpp,
1332 & estr,wbond,ebe,wang,
1333 & escloc,wscloc,etors,wtor,etors_d,wtor_d,ehpb,wstrain,
1336 & ecorr5,wcorr5,ecorr6,wcorr6,
1338 & eel_loc,wel_loc,eello_turn3,wturn3,
1339 & eello_turn4,wturn4,
1341 & eello_turn6,wturn6,
1343 & esccor,wsccor,edihcnstr,
1344 & ethetacnstr,ebr*nss,Uconst,wumb,eliptran,wliptran,Eafmforce,
1345 & etube,wtube,esaxs,wsaxs,ehomology_constr,
1346 & edfadis,wdfa_dist,edfator,wdfa_tor,edfanei,wdfa_nei,
1347 & edfabet,wdfa_beta,
1349 10 format (/'Virtual-chain energies:'//
1350 & 'EVDW= ',1pE16.6,' WEIGHT=',1pE16.6,' (SC-SC)'/
1351 & 'EVDW2= ',1pE16.6,' WEIGHT=',1pE16.6,' (SC-p)'/
1352 & 'EES= ',1pE16.6,' WEIGHT=',1pE16.6,' (p-p)'/
1353 & 'EVDWPP=',1pE16.6,' WEIGHT=',1pE16.6,' (p-p VDW)'/
1354 & 'ESTR= ',1pE16.6,' WEIGHT=',1pE16.6,' (stretching)'/
1355 & 'EBE= ',1pE16.6,' WEIGHT=',1pE16.6,' (bending)'/
1356 & 'ESC= ',1pE16.6,' WEIGHT=',1pE16.6,' (SC local)'/
1357 & 'ETORS= ',1pE16.6,' WEIGHT=',1pE16.6,' (torsional)'/
1358 & 'ETORSD=',1pE16.6,' WEIGHT=',1pE16.6,' (double torsional)'/
1359 & 'EHBP= ',1pE16.6,' WEIGHT=',1pE16.6,
1360 & ' (SS bridges & dist. cnstr.)'/
1362 & 'ECORR4=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
1363 & 'ECORR5=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
1364 & 'ECORR6=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
1366 & 'EELLO= ',1pE16.6,' WEIGHT=',1pE16.6,' (electrostatic-local)'/
1367 & 'ETURN3=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 3rd order)'/
1368 & 'ETURN4=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 4th order)'/
1370 & 'ETURN6=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 6th order)'/
1372 & 'ESCCOR=',1pE16.6,' WEIGHT=',1pE16.6,' (backbone-rotamer corr)'/
1373 & 'EDIHC= ',1pE16.6,' (virtual-bond dihedral angle restraints)'/
1374 & 'ETHETC=',1pE16.6,' (virtual-bond angle restraints)'/
1375 & 'ESS= ',1pE16.6,' (disulfide-bridge intrinsic energy)'/
1376 & 'UCONST=',1pE16.6,' WEIGHT=',1pE16.6' (umbrella restraints)'/
1377 & 'ELT= ',1pE16.6,' WEIGHT=',1pE16.6,' (Lipid transfer)'/
1378 & 'EAFM= ',1pE16.6,' (atomic-force microscopy)'/
1379 & 'ETUBE= ',1pE16.6,' WEIGHT=',1pE16.6,' (tube confinment)'/
1380 & 'E_SAXS=',1pE16.6,' WEIGHT=',1pE16.6,' (SAXS restraints)'/
1381 & 'H_CONS=',1pE16.6,' (Homology model constraints energy)'/
1382 & 'EDFAD= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA distance energy)'/
1383 & 'EDFAT= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA torsion energy)'/
1384 & 'EDFAN= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA NCa energy)'/
1385 & 'EDFAB= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA Beta energy)'/
1386 & 'ETOT= ',1pE16.6,' (total)')
1389 write (iout,10) evdw,wsc,evdw2,wscp,ees,welec,
1390 & estr,wbond,ebe,wang,
1391 & escloc,wscloc,etors,wtor,etors_d,wtor_d,ehpb,wstrain,
1394 & ecorr5,wcorr5,ecorr6,wcorr6,
1396 & eel_loc,wel_loc,eello_turn3,wturn3,
1397 & eello_turn4,wturn4,
1399 & eello_turn6,wturn6,
1401 & esccor,wsccor,edihcnstr,
1402 & ethetacnstr,ebr*nss,Uconst,wumb,eliptran,wliptran,Eafmforc,
1403 & etube,wtube,esaxs,wsaxs,ehomology_constr,
1404 & edfadis,wdfa_dist,edfator,wdfa_tor,edfanei,wdfa_nei,
1405 & edfabet,wdfa_beta,
1407 10 format (/'Virtual-chain energies:'//
1408 & 'EVDW= ',1pE16.6,' WEIGHT=',1pE16.6,' (SC-SC)'/
1409 & 'EVDW2= ',1pE16.6,' WEIGHT=',1pE16.6,' (SC-p)'/
1410 & 'EES= ',1pE16.6,' WEIGHT=',1pE16.6,' (p-p)'/
1411 & 'ESTR= ',1pE16.6,' WEIGHT=',1pE16.6,' (stretching)'/
1412 & 'EBE= ',1pE16.6,' WEIGHT=',1pE16.6,' (bending)'/
1413 & 'ESC= ',1pE16.6,' WEIGHT=',1pE16.6,' (SC local)'/
1414 & 'ETORS= ',1pE16.6,' WEIGHT=',1pE16.6,' (torsional)'/
1415 & 'ETORSD=',1pE16.6,' WEIGHT=',1pE16.6,' (double torsional)'/
1416 & 'EHBP= ',1pE16.6,' WEIGHT=',1pE16.6,
1417 & ' (SS bridges & dist. restr.)'/
1419 & 'ECORR4=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
1420 & 'ECORR5=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
1421 & 'ECORR6=',1pE16.6,' WEIGHT=',1pE16.6,' (multi-body)'/
1423 & 'EELLO= ',1pE16.6,' WEIGHT=',1pE16.6,' (electrostatic-local)'/
1424 & 'ETURN3=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 3rd order)'/
1425 & 'ETURN4=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 4th order)'/
1427 & 'ETURN6=',1pE16.6,' WEIGHT=',1pE16.6,' (turns, 6th order)'/
1429 & 'ESCCOR=',1pE16.6,' WEIGHT=',1pE16.6,' (backbone-rotamer corr)'/
1430 & 'EDIHC= ',1pE16.6,' (virtual-bond dihedral angle restraints)'/
1431 & 'ETHETC=',1pE16.6,' (virtual-bond angle restraints)'/
1432 & 'ESS= ',1pE16.6,' (disulfide-bridge intrinsic energy)'/
1433 & 'UCONST=',1pE16.6,' WEIGHT=',1pE16.6' (umbrella restraints)'/
1434 & 'ELT= ',1pE16.6,' WEIGHT=',1pE16.6,' (Lipid transfer)'/
1435 & 'EAFM= ',1pE16.6,' (atomic-force microscopy)'/
1436 & 'ETUBE= ',1pE16.6,' WEIGHT=',1pE16.6,' (tube confinment)'/
1437 & 'E_SAXS=',1pE16.6,' WEIGHT=',1pE16.6,' (SAXS restraints)'/
1438 & 'H_CONS=',1pE16.6,' (Homology model constraints energy)'/
1439 & 'EDFAD= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA distance energy)'/
1440 & 'EDFAT= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA torsion energy)'/
1441 & 'EDFAN= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA NCa energy)'/
1442 & 'EDFAB= ',1pE16.6,' WEIGHT=',1pE16.6,' (DFA Beta energy)'/
1443 & 'ETOT= ',1pE16.6,' (total)')
1447 C-----------------------------------------------------------------------
1448 subroutine elj(evdw)
1450 C This subroutine calculates the interaction energy of nonbonded side chains
1451 C assuming the LJ potential of interaction.
1454 double precision accur
1455 include 'DIMENSIONS'
1456 parameter (accur=1.0d-10)
1457 include 'COMMON.GEO'
1458 include 'COMMON.VAR'
1459 include 'COMMON.LOCAL'
1460 include 'COMMON.CHAIN'
1461 include 'COMMON.DERIV'
1462 include 'COMMON.INTERACT'
1463 include 'COMMON.TORSION'
1464 include 'COMMON.SBRIDGE'
1465 include 'COMMON.NAMES'
1466 include 'COMMON.IOUNITS'
1467 include 'COMMON.SPLITELE'
1469 include 'COMMON.CONTACTS'
1470 include 'COMMON.CONTMAT'
1472 double precision gg(3)
1473 double precision evdw,evdwij
1474 integer i,j,k,itypi,itypj,itypi1,num_conti,iint,icont
1475 double precision xi,yi,zi,xj,yj,zj,rij,eps0ij,fac,e1,e2,rrij,
1476 & sigij,r0ij,rcut,sqrij,sss1,sssgrad1
1477 double precision fcont,fprimcont
1478 double precision sscale,sscagrad
1479 c write(iout,*)'Entering ELJ nnt=',nnt,' nct=',nct,' expon=',expon
1481 c do i=iatsc_s,iatsc_e
1482 do icont=g_listscsc_start,g_listscsc_end
1483 i=newcontlisti(icont)
1484 j=newcontlistj(icont)
1485 itypi=iabs(itype(i))
1486 if (itypi.eq.ntyp1) cycle
1487 itypi1=iabs(itype(i+1))
1494 C Calculate SC interaction energy.
1496 c do iint=1,nint_gr(i)
1497 cd write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
1498 cd & 'iend=',iend(i,iint)
1499 c do j=istart(i,iint),iend(i,iint)
1500 itypj=iabs(itype(j))
1501 if (itypj.eq.ntyp1) cycle
1505 C Change 12/1/95 to calculate four-body interactions
1506 rij=xj*xj+yj*yj+zj*zj
1509 sss1=sscale(sqrij,r_cut_int)
1510 if (sss1.eq.0.0d0) cycle
1511 sssgrad1=sscagrad(sqrij,r_cut_int)
1513 c write (iout,*)'i=',i,' j=',j,' itypi=',itypi,' itypj=',itypj
1514 eps0ij=eps(itypi,itypj)
1516 C have you changed here?
1520 cd sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
1521 cd epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
1522 cd write (iout,'(2(a3,i3,2x),6(1pd12.4)/2(3(1pd12.4),5x)/)')
1523 cd & restyp(itypi),i,restyp(itypj),j,a(itypi,itypj),
1524 cd & bb(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,epsi,sigm,
1525 cd & (c(k,i),k=1,3),(c(k,j),k=1,3)
1526 evdw=evdw+sss1*evdwij
1528 C Calculate the components of the gradient in DC and X
1530 fac=-rrij*(e1+evdwij)*sss1
1531 & +evdwij*sssgrad1/sqrij/expon
1536 gvdwx(k,i)=gvdwx(k,i)-gg(k)
1537 gvdwx(k,j)=gvdwx(k,j)+gg(k)
1538 gvdwc(k,i)=gvdwc(k,i)-gg(k)
1539 gvdwc(k,j)=gvdwc(k,j)+gg(k)
1543 cgrad gvdwc(l,k)=gvdwc(l,k)+gg(l)
1548 C 12/1/95, revised on 5/20/97
1550 C Calculate the contact function. The ith column of the array JCONT will
1551 C contain the numbers of atoms that make contacts with the atom I (of numbers
1552 C greater than I). The arrays FACONT and GACONT will contain the values of
1553 C the contact function and its derivative.
1555 C Uncomment next line, if the correlation interactions include EVDW explicitly.
1556 c if (j.gt.i+1 .and. evdwij.le.0.0D0) then
1557 C Uncomment next line, if the correlation interactions are contact function only
1558 if (j.gt.i+1.and. eps0ij.gt.0.0D0) then
1560 sigij=sigma(itypi,itypj)
1561 r0ij=rs0(itypi,itypj)
1563 C Check whether the SC's are not too far to make a contact.
1566 call gcont(rij,rcut,1.0d0,0.2d0*rcut,fcont,fprimcont)
1567 C Add a new contact, if the SC's are close enough, but not too close (r<sigma).
1569 if (fcont.gt.0.0D0) then
1570 C If the SC-SC distance if close to sigma, apply spline.
1571 cAdam call gcont(-rij,-1.03d0*sigij,2.0d0*sigij,1.0d0,
1572 cAdam & fcont1,fprimcont1)
1573 cAdam fcont1=1.0d0-fcont1
1574 cAdam if (fcont1.gt.0.0d0) then
1575 cAdam fprimcont=fprimcont*fcont1+fcont*fprimcont1
1576 cAdam fcont=fcont*fcont1
1578 C Uncomment following 4 lines to have the geometric average of the epsilon0's
1579 cga eps0ij=1.0d0/dsqrt(eps0ij)
1581 cga gg(k)=gg(k)*eps0ij
1583 cga eps0ij=-evdwij*eps0ij
1584 C Uncomment for AL's type of SC correlation interactions.
1585 cadam eps0ij=-evdwij
1586 num_conti=num_conti+1
1587 jcont(num_conti,i)=j
1588 facont(num_conti,i)=fcont*eps0ij
1589 fprimcont=eps0ij*fprimcont/rij
1591 cAdam gacont(1,num_conti,i)=-fprimcont*xj+fcont*gg(1)
1592 cAdam gacont(2,num_conti,i)=-fprimcont*yj+fcont*gg(2)
1593 cAdam gacont(3,num_conti,i)=-fprimcont*zj+fcont*gg(3)
1594 C Uncomment following 3 lines for Skolnick's type of SC correlation.
1595 gacont(1,num_conti,i)=-fprimcont*xj
1596 gacont(2,num_conti,i)=-fprimcont*yj
1597 gacont(3,num_conti,i)=-fprimcont*zj
1598 cd write (iout,'(2i5,2f10.5)') i,j,rij,facont(num_conti,i)
1599 cd write (iout,'(2i3,3f10.5)')
1600 cd & i,j,(gacont(kk,num_conti,i),kk=1,3)
1608 num_cont(i)=num_conti
1613 gvdwc(j,i)=expon*gvdwc(j,i)
1614 gvdwx(j,i)=expon*gvdwx(j,i)
1617 C******************************************************************************
1621 C To save time, the factor of EXPON has been extracted from ALL components
1622 C of GVDWC and GRADX. Remember to multiply them by this factor before further
1625 C******************************************************************************
1628 C-----------------------------------------------------------------------------
1629 subroutine eljk(evdw)
1631 C This subroutine calculates the interaction energy of nonbonded side chains
1632 C assuming the LJK potential of interaction.
1635 include 'DIMENSIONS'
1636 include 'COMMON.GEO'
1637 include 'COMMON.VAR'
1638 include 'COMMON.LOCAL'
1639 include 'COMMON.CHAIN'
1640 include 'COMMON.DERIV'
1641 include 'COMMON.INTERACT'
1642 include 'COMMON.IOUNITS'
1643 include 'COMMON.NAMES'
1644 include 'COMMON.SPLITELE'
1645 double precision gg(3)
1646 double precision evdw,evdwij
1647 integer i,j,k,itypi,itypj,itypi1,iint,icont
1648 double precision xi,yi,zi,xj,yj,zj,rij,eps0ij,fac,e1,e2,rrij,
1649 & fac_augm,e_augm,r_inv_ij,r_shift_inv,sss1,sssgrad1
1651 double precision sscale,sscagrad
1652 c print *,'Entering ELJK nnt=',nnt,' nct=',nct,' expon=',expon
1654 c do i=iatsc_s,iatsc_e
1655 do icont=g_listscsc_start,g_listscsc_end
1656 i=newcontlisti(icont)
1657 j=newcontlistj(icont)
1658 itypi=iabs(itype(i))
1659 if (itypi.eq.ntyp1) cycle
1660 itypi1=iabs(itype(i+1))
1665 C Calculate SC interaction energy.
1667 c do iint=1,nint_gr(i)
1668 c do j=istart(i,iint),iend(i,iint)
1669 itypj=iabs(itype(j))
1670 if (itypj.eq.ntyp1) cycle
1674 rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
1675 fac_augm=rrij**expon
1676 e_augm=augm(itypi,itypj)*fac_augm
1677 r_inv_ij=dsqrt(rrij)
1679 sss1=sscale(rij,r_cut_int)
1680 if (sss1.eq.0.0d0) cycle
1681 sssgrad1=sscagrad(rij,r_cut_int)
1682 r_shift_inv=1.0D0/(rij+r0(itypi,itypj)-sigma(itypi,itypj))
1683 fac=r_shift_inv**expon
1684 C have you changed here?
1688 cd sigm=dabs(aa(itypi,itypj)/bb(itypi,itypj))**(1.0D0/6.0D0)
1689 cd epsi=bb(itypi,itypj)**2/aa(itypi,itypj)
1690 cd write (iout,'(2(a3,i3,2x),8(1pd12.4)/2(3(1pd12.4),5x)/)')
1691 cd & restyp(itypi),i,restyp(itypj),j,aa(itypi,itypj),
1692 cd & bb(itypi,itypj),augm(itypi,itypj),epsi,sigm,
1693 cd & sigma(itypi,itypj),1.0D0/dsqrt(rrij),evdwij,
1694 cd & (c(k,i),k=1,3),(c(k,j),k=1,3)
1695 evdw=evdw+evdwij*sss1
1697 C Calculate the components of the gradient in DC and X
1699 fac=-2.0D0*rrij*e_augm-r_inv_ij*r_shift_inv*(e1+e1+e2)
1700 & +evdwij*sssgrad1*r_inv_ij/expon
1705 gvdwx(k,i)=gvdwx(k,i)-gg(k)
1706 gvdwx(k,j)=gvdwx(k,j)+gg(k)
1707 gvdwc(k,i)=gvdwc(k,i)-gg(k)
1708 gvdwc(k,j)=gvdwc(k,j)+gg(k)
1712 cgrad gvdwc(l,k)=gvdwc(l,k)+gg(l)
1720 gvdwc(j,i)=expon*gvdwc(j,i)
1721 gvdwx(j,i)=expon*gvdwx(j,i)
1726 C-----------------------------------------------------------------------------
1727 subroutine ebp(evdw)
1729 C This subroutine calculates the interaction energy of nonbonded side chains
1730 C assuming the Berne-Pechukas potential of interaction.
1733 include 'DIMENSIONS'
1734 include 'COMMON.GEO'
1735 include 'COMMON.VAR'
1736 include 'COMMON.LOCAL'
1737 include 'COMMON.CHAIN'
1738 include 'COMMON.DERIV'
1739 include 'COMMON.NAMES'
1740 include 'COMMON.INTERACT'
1741 include 'COMMON.IOUNITS'
1742 include 'COMMON.CALC'
1743 include 'COMMON.SPLITELE'
1745 common /srutu/ icall
1746 double precision evdw
1747 integer itypi,itypj,itypi1,iint,ind,icont
1748 double precision eps0ij,epsi,sigm,fac,e1,e2,rrij,xi,yi,zi,
1750 double precision sscale,sscagrad
1751 c double precision rrsave(maxdim)
1754 c print *,'Entering EBP nnt=',nnt,' nct=',nct,' expon=',expon
1756 c if (icall.eq.0) then
1762 c do i=iatsc_s,iatsc_e
1763 do icont=g_listscsc_start,g_listscsc_end
1764 i=newcontlisti(icont)
1765 j=newcontlistj(icont)
1766 itypi=iabs(itype(i))
1767 if (itypi.eq.ntyp1) cycle
1768 itypi1=iabs(itype(i+1))
1772 dxi=dc_norm(1,nres+i)
1773 dyi=dc_norm(2,nres+i)
1774 dzi=dc_norm(3,nres+i)
1775 c dsci_inv=dsc_inv(itypi)
1776 dsci_inv=vbld_inv(i+nres)
1778 C Calculate SC interaction energy.
1780 c do iint=1,nint_gr(i)
1781 c do j=istart(i,iint),iend(i,iint)
1783 itypj=iabs(itype(j))
1784 if (itypj.eq.ntyp1) cycle
1785 c dscj_inv=dsc_inv(itypj)
1786 dscj_inv=vbld_inv(j+nres)
1787 chi1=chi(itypi,itypj)
1788 chi2=chi(itypj,itypi)
1795 alf12=0.5D0*(alf1+alf2)
1796 C For diagnostics only!!!
1809 dxj=dc_norm(1,nres+j)
1810 dyj=dc_norm(2,nres+j)
1811 dzj=dc_norm(3,nres+j)
1812 rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
1813 cd if (icall.eq.0) then
1819 sss1=sscale(1.0d0/rij,r_cut_int)
1820 if (sss1.eq.0.0d0) cycle
1821 sssgrad1=sscagrad(1.0d0/rij,r_cut_int)
1822 C Calculate the angle-dependent terms of energy & contributions to derivatives.
1824 C Calculate whole angle-dependent part of epsilon and contributions
1825 C to its derivatives
1826 C have you changed here?
1827 fac=(rrij*sigsq)**expon2
1830 evdwij=eps1*eps2rt*eps3rt*(e1+e2)
1831 eps2der=evdwij*eps3rt
1832 eps3der=evdwij*eps2rt
1833 evdwij=evdwij*eps2rt*eps3rt
1834 evdw=evdw+sss1*evdwij
1836 sigm=dabs(aa/bb)**(1.0D0/6.0D0)
1838 cd write (iout,'(2(a3,i3,2x),15(0pf7.3))')
1839 cd & restyp(itypi),i,restyp(itypj),j,
1840 cd & epsi,sigm,chi1,chi2,chip1,chip2,
1841 cd & eps1,eps2rt**2,eps3rt**2,1.0D0/dsqrt(sigsq),
1842 cd & om1,om2,om12,1.0D0/dsqrt(rrij),
1845 C Calculate gradient components.
1846 e1=e1*eps1*eps2rt**2*eps3rt**2
1847 fac=-expon*(e1+evdwij)
1850 & +evdwij*sssgrad1/sss1*rij
1851 C Calculate radial part of the gradient
1855 C Calculate the angular part of the gradient and sum add the contributions
1856 C to the appropriate components of the Cartesian gradient.
1864 C-----------------------------------------------------------------------------
1865 subroutine egb(evdw)
1867 C This subroutine calculates the interaction energy of nonbonded side chains
1868 C assuming the Gay-Berne potential of interaction.
1871 include 'DIMENSIONS'
1872 include 'COMMON.GEO'
1873 include 'COMMON.VAR'
1874 include 'COMMON.LOCAL'
1875 include 'COMMON.CHAIN'
1876 include 'COMMON.DERIV'
1877 include 'COMMON.NAMES'
1878 include 'COMMON.INTERACT'
1879 include 'COMMON.IOUNITS'
1880 include 'COMMON.CALC'
1881 include 'COMMON.CONTROL'
1882 include 'COMMON.SPLITELE'
1883 include 'COMMON.SBRIDGE'
1885 integer xshift,yshift,zshift,subchap
1886 double precision evdw
1887 integer itypi,itypj,itypi1,iint,ind,icont
1888 double precision eps0ij,epsi,sigm,fac,e1,e2,rrij,xi,yi,zi
1889 double precision fracinbuf,sslipi,evdwij_przed_tri,sig0ij,
1890 & sslipj,ssgradlipj,ssgradlipi,dist_init,xj_safe,yj_safe,zj_safe,
1891 & xj_temp,yj_temp,zj_temp,dist_temp,sig,rij_shift,faclip
1892 double precision dist,sscale,sscagrad,sscagradlip,sscalelip
1894 ccccc energy_dec=.false.
1895 C print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
1898 c if (icall.eq.0) lprn=.false.
1900 C the loop over all 27 posible neigbours (for xshift=0,yshift=0,zshift=0
1901 C we have the original box)
1905 c do i=iatsc_s,iatsc_e
1906 do icont=g_listscsc_start,g_listscsc_end
1907 i=newcontlisti(icont)
1908 j=newcontlistj(icont)
1909 itypi=iabs(itype(i))
1910 if (itypi.eq.ntyp1) cycle
1911 itypi1=iabs(itype(i+1))
1915 C Return atom into box, boxxsize is size of box in x dimension
1917 c if (xi.gt.((xshift+0.5d0)*boxxsize)) xi=xi-boxxsize
1918 c if (xi.lt.((xshift-0.5d0)*boxxsize)) xi=xi+boxxsize
1919 C Condition for being inside the proper box
1920 c if ((xi.gt.((xshift+0.5d0)*boxxsize)).or.
1921 c & (xi.lt.((xshift-0.5d0)*boxxsize))) then
1925 c if (yi.gt.((yshift+0.5d0)*boxysize)) yi=yi-boxysize
1926 c if (yi.lt.((yshift-0.5d0)*boxysize)) yi=yi+boxysize
1927 C Condition for being inside the proper box
1928 c if ((yi.gt.((yshift+0.5d0)*boxysize)).or.
1929 c & (yi.lt.((yshift-0.5d0)*boxysize))) then
1933 c if (zi.gt.((zshift+0.5d0)*boxzsize)) zi=zi-boxzsize
1934 c if (zi.lt.((zshift-0.5d0)*boxzsize)) zi=zi+boxzsize
1935 C Condition for being inside the proper box
1936 c if ((zi.gt.((zshift+0.5d0)*boxzsize)).or.
1937 c & (zi.lt.((zshift-0.5d0)*boxzsize))) then
1941 if (xi.lt.0) xi=xi+boxxsize
1943 if (yi.lt.0) yi=yi+boxysize
1945 if (zi.lt.0) zi=zi+boxzsize
1946 C define scaling factor for lipids
1948 C if (positi.le.0) positi=positi+boxzsize
1950 C first for peptide groups
1951 c for each residue check if it is in lipid or lipid water border area
1952 if ((zi.gt.bordlipbot)
1953 &.and.(zi.lt.bordliptop)) then
1954 C the energy transfer exist
1955 if (zi.lt.buflipbot) then
1956 C what fraction I am in
1958 & ((zi-bordlipbot)/lipbufthick)
1959 C lipbufthick is thickenes of lipid buffore
1960 sslipi=sscalelip(fracinbuf)
1961 ssgradlipi=-sscagradlip(fracinbuf)/lipbufthick
1962 elseif (zi.gt.bufliptop) then
1963 fracinbuf=1.0d0-((bordliptop-zi)/lipbufthick)
1964 sslipi=sscalelip(fracinbuf)
1965 ssgradlipi=sscagradlip(fracinbuf)/lipbufthick
1975 C xi=xi+xshift*boxxsize
1976 C yi=yi+yshift*boxysize
1977 C zi=zi+zshift*boxzsize
1979 dxi=dc_norm(1,nres+i)
1980 dyi=dc_norm(2,nres+i)
1981 dzi=dc_norm(3,nres+i)
1982 c dsci_inv=dsc_inv(itypi)
1983 dsci_inv=vbld_inv(i+nres)
1984 c write (iout,*) "i",i,dsc_inv(itypi),dsci_inv,1.0d0/vbld(i+nres)
1985 c write (iout,*) "dcnori",dxi*dxi+dyi*dyi+dzi*dzi
1987 C Calculate SC interaction energy.
1989 c do iint=1,nint_gr(i)
1990 c do j=istart(i,iint),iend(i,iint)
1991 IF (dyn_ss_mask(i).and.dyn_ss_mask(j)) THEN
1993 c write(iout,*) "PRZED ZWYKLE", evdwij
1994 call dyn_ssbond_ene(i,j,evdwij)
1995 c write(iout,*) "PO ZWYKLE", evdwij
1998 if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)')
1999 & 'evdw',i,j,evdwij,' ss'
2000 C triple bond artifac removal
2001 do k=j+1,iend(i,iint)
2002 C search over all next residues
2003 if (dyn_ss_mask(k)) then
2004 C check if they are cysteins
2005 C write(iout,*) 'k=',k
2007 c write(iout,*) "PRZED TRI", evdwij
2008 evdwij_przed_tri=evdwij
2009 call triple_ssbond_ene(i,j,k,evdwij)
2010 c if(evdwij_przed_tri.ne.evdwij) then
2011 c write (iout,*) "TRI:", evdwij, evdwij_przed_tri
2014 c write(iout,*) "PO TRI", evdwij
2015 C call the energy function that removes the artifical triple disulfide
2016 C bond the soubroutine is located in ssMD.F
2018 if (energy_dec) write (iout,'(a6,2i5,0pf7.3,a3)')
2019 & 'evdw',i,j,evdwij,'tss'
2020 endif!dyn_ss_mask(k)
2024 itypj=iabs(itype(j))
2025 if (itypj.eq.ntyp1) cycle
2026 c dscj_inv=dsc_inv(itypj)
2027 dscj_inv=vbld_inv(j+nres)
2028 c write (iout,*) "j",j,dsc_inv(itypj),dscj_inv,
2029 c & 1.0d0/vbld(j+nres)
2030 c write (iout,*) "i",i," j", j," itype",itype(i),itype(j)
2031 sig0ij=sigma(itypi,itypj)
2032 chi1=chi(itypi,itypj)
2033 chi2=chi(itypj,itypi)
2040 alf12=0.5D0*(alf1+alf2)
2041 C For diagnostics only!!!
2054 C Return atom J into box the original box
2056 c if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
2057 c if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
2058 C Condition for being inside the proper box
2059 c if ((xj.gt.((0.5d0)*boxxsize)).or.
2060 c & (xj.lt.((-0.5d0)*boxxsize))) then
2064 c if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
2065 c if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
2066 C Condition for being inside the proper box
2067 c if ((yj.gt.((0.5d0)*boxysize)).or.
2068 c & (yj.lt.((-0.5d0)*boxysize))) then
2072 c if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxzsize
2073 c if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxzsize
2074 C Condition for being inside the proper box
2075 c if ((zj.gt.((0.5d0)*boxzsize)).or.
2076 c & (zj.lt.((-0.5d0)*boxzsize))) then
2080 if (xj.lt.0) xj=xj+boxxsize
2082 if (yj.lt.0) yj=yj+boxysize
2084 if (zj.lt.0) zj=zj+boxzsize
2085 if ((zj.gt.bordlipbot)
2086 &.and.(zj.lt.bordliptop)) then
2087 C the energy transfer exist
2088 if (zj.lt.buflipbot) then
2089 C what fraction I am in
2091 & ((zj-bordlipbot)/lipbufthick)
2092 C lipbufthick is thickenes of lipid buffore
2093 sslipj=sscalelip(fracinbuf)
2094 ssgradlipj=-sscagradlip(fracinbuf)/lipbufthick
2095 elseif (zj.gt.bufliptop) then
2096 fracinbuf=1.0d0-((bordliptop-zj)/lipbufthick)
2097 sslipj=sscalelip(fracinbuf)
2098 ssgradlipj=sscagradlip(fracinbuf)/lipbufthick
2107 aa=aa_lip(itypi,itypj)*(sslipi+sslipj)/2.0d0
2108 & +aa_aq(itypi,itypj)*(2.0d0-sslipi-sslipj)/2.0d0
2109 bb=bb_lip(itypi,itypj)*(sslipi+sslipj)/2.0d0
2110 & +bb_aq(itypi,itypj)*(2.0d0-sslipi-sslipj)/2.0d0
2111 C write(iout,*) "tu,", i,j,aa_lip(itypi,itypj),bb_lip(itypi,itypj)
2112 C if (aa.ne.aa_aq(itypi,itypj)) write(63,'(2e10.5)')
2113 C &(aa-aa_aq(itypi,itypj)),(bb-bb_aq(itypi,itypj))
2114 C if (ssgradlipj.gt.0.0d0) print *,"??WTF??"
2115 C print *,sslipi,sslipj,bordlipbot,zi,zj
2116 dist_init=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
2124 xj=xj_safe+xshift*boxxsize
2125 yj=yj_safe+yshift*boxysize
2126 zj=zj_safe+zshift*boxzsize
2127 dist_temp=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
2128 if(dist_temp.lt.dist_init) then
2138 if (subchap.eq.1) then
2147 dxj=dc_norm(1,nres+j)
2148 dyj=dc_norm(2,nres+j)
2149 dzj=dc_norm(3,nres+j)
2153 c write (iout,*) "dcnorj",dxi*dxi+dyi*dyi+dzi*dzi
2154 c write (iout,*) "j",j," dc_norm",
2155 c & dc_norm(1,nres+j),dc_norm(2,nres+j),dc_norm(3,nres+j)
2156 rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
2158 sss=sscale(1.0d0/rij,r_cut_int)
2159 c write (iout,'(a7,4f8.3)')
2160 c & "ssscale",sss,((1.0d0/rij)/sigma(itypi,itypj)),r_cut,rlamb
2161 if (sss.eq.0.0d0) cycle
2162 sssgrad=sscagrad(1.0d0/rij,r_cut_int)
2163 C Calculate angle-dependent terms of energy and contributions to their
2167 sig=sig0ij*dsqrt(sigsq)
2168 rij_shift=1.0D0/rij-sig+sig0ij
2169 c for diagnostics; uncomment
2170 c rij_shift=1.2*sig0ij
2171 C I hate to put IF's in the loops, but here don't have another choice!!!!
2172 if (rij_shift.le.0.0D0) then
2174 cd write (iout,'(2(a3,i3,2x),17(0pf7.3))')
2175 cd & restyp(itypi),i,restyp(itypj),j,
2176 cd & rij_shift,1.0D0/rij,sig,sig0ij,sigsq,1-dsqrt(sigsq)
2180 c---------------------------------------------------------------
2181 rij_shift=1.0D0/rij_shift
2182 fac=rij_shift**expon
2183 C here to start with
2188 evdwij=eps1*eps2rt*eps3rt*(e1+e2)
2189 eps2der=evdwij*eps3rt
2190 eps3der=evdwij*eps2rt
2191 C write(63,'(2i3,2e10.3,2f10.5)') i,j,aa,bb, evdwij,
2192 C &((sslipi+sslipj)/2.0d0+
2193 C &(2.0d0-sslipi-sslipj)/2.0d0)
2194 c write (iout,*) "sigsq",sigsq," sig",sig," eps2rt",eps2rt,
2195 c & " eps3rt",eps3rt," eps1",eps1," e1",e1," e2",e2
2196 evdwij=evdwij*eps2rt*eps3rt
2197 evdw=evdw+evdwij*sss
2199 sigm=dabs(aa/bb)**(1.0D0/6.0D0)
2201 write (iout,'(2(a3,i3,2x),17(0pf7.3))')
2202 & restyp(itypi),i,restyp(itypj),j,
2203 & epsi,sigm,chi1,chi2,chip1,chip2,
2204 & eps1,eps2rt**2,eps3rt**2,sig,sig0ij,
2205 & om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,
2209 if (energy_dec) write (iout,'(a,2i5,3f10.5)')
2210 & 'r sss evdw',i,j,rij,sss,evdwij
2212 C Calculate gradient components.
2213 e1=e1*eps1*eps2rt**2*eps3rt**2
2214 fac=-expon*(e1+evdwij)*rij_shift
2217 c print '(2i4,6f8.4)',i,j,sss,sssgrad*
2218 c & evdwij,fac,sigma(itypi,itypj),expon
2219 fac=fac+evdwij*sssgrad/sss*rij
2221 C Calculate the radial part of the gradient
2222 gg_lipi(3)=eps1*(eps2rt*eps2rt)
2223 & *(eps3rt*eps3rt)*sss/2.0d0*(faclip*faclip*
2224 & (aa_lip(itypi,itypj)-aa_aq(itypi,itypj))
2225 & +faclip*(bb_lip(itypi,itypj)-bb_aq(itypi,itypj)))
2226 gg_lipj(3)=ssgradlipj*gg_lipi(3)
2227 gg_lipi(3)=gg_lipi(3)*ssgradlipi
2233 C Calculate angular part of the gradient.
2234 c call sc_grad_scale(sss)
2243 c write (iout,*) "Number of loop steps in EGB:",ind
2244 cccc energy_dec=.false.
2247 C-----------------------------------------------------------------------------
2248 subroutine egbv(evdw)
2250 C This subroutine calculates the interaction energy of nonbonded side chains
2251 C assuming the Gay-Berne-Vorobjev potential of interaction.
2254 include 'DIMENSIONS'
2255 include 'COMMON.GEO'
2256 include 'COMMON.VAR'
2257 include 'COMMON.LOCAL'
2258 include 'COMMON.CHAIN'
2259 include 'COMMON.DERIV'
2260 include 'COMMON.NAMES'
2261 include 'COMMON.INTERACT'
2262 include 'COMMON.IOUNITS'
2263 include 'COMMON.CALC'
2264 include 'COMMON.SPLITELE'
2265 integer xshift,yshift,zshift,subchap
2267 common /srutu/ icall
2269 double precision evdw
2270 integer itypi,itypj,itypi1,iint,ind,icont
2271 double precision eps0ij,epsi,sigm,fac,e1,e2,rrij,r0ij,
2272 & xi,yi,zi,fac_augm,e_augm
2273 double precision fracinbuf,sslipi,evdwij_przed_tri,sig0ij,
2274 & sslipj,ssgradlipj,ssgradlipi,dist_init,xj_safe,yj_safe,zj_safe,
2275 & xj_temp,yj_temp,zj_temp,dist_temp,sig,rij_shift,faclip,sssgrad1
2276 double precision dist,sscale,sscagrad,sscagradlip,sscalelip
2278 c print *,'Entering EGB nnt=',nnt,' nct=',nct,' expon=',expon
2281 c if (icall.eq.0) lprn=.true.
2283 c do i=iatsc_s,iatsc_e
2284 do icont=g_listscsc_start,g_listscsc_end
2285 i=newcontlisti(icont)
2286 j=newcontlistj(icont)
2287 itypi=iabs(itype(i))
2288 if (itypi.eq.ntyp1) cycle
2289 itypi1=iabs(itype(i+1))
2294 if (xi.lt.0) xi=xi+boxxsize
2296 if (yi.lt.0) yi=yi+boxysize
2298 if (zi.lt.0) zi=zi+boxzsize
2299 C define scaling factor for lipids
2301 C if (positi.le.0) positi=positi+boxzsize
2303 C first for peptide groups
2304 c for each residue check if it is in lipid or lipid water border area
2305 if ((zi.gt.bordlipbot)
2306 &.and.(zi.lt.bordliptop)) then
2307 C the energy transfer exist
2308 if (zi.lt.buflipbot) then
2309 C what fraction I am in
2311 & ((zi-bordlipbot)/lipbufthick)
2312 C lipbufthick is thickenes of lipid buffore
2313 sslipi=sscalelip(fracinbuf)
2314 ssgradlipi=-sscagradlip(fracinbuf)/lipbufthick
2315 elseif (zi.gt.bufliptop) then
2316 fracinbuf=1.0d0-((bordliptop-zi)/lipbufthick)
2317 sslipi=sscalelip(fracinbuf)
2318 ssgradlipi=sscagradlip(fracinbuf)/lipbufthick
2328 dxi=dc_norm(1,nres+i)
2329 dyi=dc_norm(2,nres+i)
2330 dzi=dc_norm(3,nres+i)
2331 c dsci_inv=dsc_inv(itypi)
2332 dsci_inv=vbld_inv(i+nres)
2334 C Calculate SC interaction energy.
2336 c do iint=1,nint_gr(i)
2337 c do j=istart(i,iint),iend(i,iint)
2339 itypj=iabs(itype(j))
2340 if (itypj.eq.ntyp1) cycle
2341 c dscj_inv=dsc_inv(itypj)
2342 dscj_inv=vbld_inv(j+nres)
2343 sig0ij=sigma(itypi,itypj)
2344 r0ij=r0(itypi,itypj)
2345 chi1=chi(itypi,itypj)
2346 chi2=chi(itypj,itypi)
2353 alf12=0.5D0*(alf1+alf2)
2354 C For diagnostics only!!!
2368 if (xj.lt.0) xj=xj+boxxsize
2370 if (yj.lt.0) yj=yj+boxysize
2372 if (zj.lt.0) zj=zj+boxzsize
2373 if ((zj.gt.bordlipbot)
2374 &.and.(zj.lt.bordliptop)) then
2375 C the energy transfer exist
2376 if (zj.lt.buflipbot) then
2377 C what fraction I am in
2379 & ((zj-bordlipbot)/lipbufthick)
2380 C lipbufthick is thickenes of lipid buffore
2381 sslipj=sscalelip(fracinbuf)
2382 ssgradlipj=-sscagradlip(fracinbuf)/lipbufthick
2383 elseif (zj.gt.bufliptop) then
2384 fracinbuf=1.0d0-((bordliptop-zj)/lipbufthick)
2385 sslipj=sscalelip(fracinbuf)
2386 ssgradlipj=sscagradlip(fracinbuf)/lipbufthick
2395 aa=aa_lip(itypi,itypj)*(sslipi+sslipj)/2.0d0
2396 & +aa_aq(itypi,itypj)*(2.0d0-sslipi-sslipj)/2.0d0
2397 bb=bb_lip(itypi,itypj)*(sslipi+sslipj)/2.0d0
2398 & +bb_aq(itypi,itypj)*(2.0d0-sslipi-sslipj)/2.0d0
2399 C if (aa.ne.aa_aq(itypi,itypj)) write(63,'2e10.5')
2400 C &(aa-aa_aq(itypi,itypj)),(bb-bb_aq(itypi,itypj))
2401 C write(iout,*) "tu,", i,j,aa,bb,aa_lip(itypi,itypj),sslipi,sslipj
2402 dist_init=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
2410 xj=xj_safe+xshift*boxxsize
2411 yj=yj_safe+yshift*boxysize
2412 zj=zj_safe+zshift*boxzsize
2413 dist_temp=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
2414 if(dist_temp.lt.dist_init) then
2424 if (subchap.eq.1) then
2433 dxj=dc_norm(1,nres+j)
2434 dyj=dc_norm(2,nres+j)
2435 dzj=dc_norm(3,nres+j)
2436 rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
2438 sss=sscale(1.0d0/rij,r_cut_int)
2439 if (sss.eq.0.0d0) cycle
2440 sssgrad=sscagrad(1.0d0/rij,r_cut_int)
2441 C Calculate angle-dependent terms of energy and contributions to their
2445 sig=sig0ij*dsqrt(sigsq)
2446 rij_shift=1.0D0/rij-sig+r0ij
2447 C I hate to put IF's in the loops, but here don't have another choice!!!!
2448 if (rij_shift.le.0.0D0) then
2453 c---------------------------------------------------------------
2454 rij_shift=1.0D0/rij_shift
2455 fac=rij_shift**expon
2458 evdwij=eps1*eps2rt*eps3rt*(e1+e2)
2459 eps2der=evdwij*eps3rt
2460 eps3der=evdwij*eps2rt
2461 fac_augm=rrij**expon
2462 e_augm=augm(itypi,itypj)*fac_augm
2463 evdwij=evdwij*eps2rt*eps3rt
2464 evdw=evdw+evdwij+e_augm
2466 sigm=dabs(aa/bb)**(1.0D0/6.0D0)
2468 write (iout,'(2(a3,i3,2x),17(0pf7.3))')
2469 & restyp(itypi),i,restyp(itypj),j,
2470 & epsi,sigm,sig,(augm(itypi,itypj)/epsi)**(1.0D0/12.0D0),
2471 & chi1,chi2,chip1,chip2,
2472 & eps1,eps2rt**2,eps3rt**2,
2473 & om1,om2,om12,1.0D0/rij,1.0D0/rij_shift,
2476 C Calculate gradient components.
2477 e1=e1*eps1*eps2rt**2*eps3rt**2
2478 fac=-expon*(e1+evdwij)*rij_shift
2480 fac=rij*fac-2*expon*rrij*e_augm
2481 fac=fac+(evdwij+e_augm)*sssgrad/sss*rij
2482 C Calculate the radial part of the gradient
2486 C Calculate angular part of the gradient.
2487 c call sc_grad_scale(sss)
2493 C-----------------------------------------------------------------------------
2494 subroutine sc_angular
2495 C Calculate eps1,eps2,eps3,sigma, and parts of their derivatives in om1,om2,
2496 C om12. Called by ebp, egb, and egbv.
2498 include 'COMMON.CALC'
2499 include 'COMMON.IOUNITS'
2503 om1=dxi*erij(1)+dyi*erij(2)+dzi*erij(3)
2504 om2=dxj*erij(1)+dyj*erij(2)+dzj*erij(3)
2505 om12=dxi*dxj+dyi*dyj+dzi*dzj
2507 C Calculate eps1(om12) and its derivative in om12
2508 faceps1=1.0D0-om12*chiom12
2509 faceps1_inv=1.0D0/faceps1
2510 eps1=dsqrt(faceps1_inv)
2511 C Following variable is eps1*deps1/dom12
2512 eps1_om12=faceps1_inv*chiom12
2517 c write (iout,*) "om12",om12," eps1",eps1
2518 C Calculate sigma(om1,om2,om12) and the derivatives of sigma**2 in om1,om2,
2523 facsig=om1*chiom1+om2*chiom2-2.0D0*om1om2*chiom12
2524 sigsq=1.0D0-facsig*faceps1_inv
2525 sigsq_om1=(chiom1-chiom12*om2)*faceps1_inv
2526 sigsq_om2=(chiom2-chiom12*om1)*faceps1_inv
2527 sigsq_om12=-chi12*(om1om2*faceps1-om12*facsig)*faceps1_inv**2
2533 c write (iout,*) "chiom1",chiom1," chiom2",chiom2," chiom12",chiom12
2534 c write (iout,*) "faceps1",faceps1," faceps1_inv",faceps1_inv,
2536 C Calculate eps2 and its derivatives in om1, om2, and om12.
2539 chipom12=chip12*om12
2540 facp=1.0D0-om12*chipom12
2542 facp1=om1*chipom1+om2*chipom2-2.0D0*om1om2*chipom12
2543 c write (iout,*) "chipom1",chipom1," chipom2",chipom2,
2544 c & " chipom12",chipom12," facp",facp," facp_inv",facp_inv
2545 C Following variable is the square root of eps2
2546 eps2rt=1.0D0-facp1*facp_inv
2547 C Following three variables are the derivatives of the square root of eps
2548 C in om1, om2, and om12.
2549 eps2rt_om1=-4.0D0*(chipom1-chipom12*om2)*facp_inv
2550 eps2rt_om2=-4.0D0*(chipom2-chipom12*om1)*facp_inv
2551 eps2rt_om12=4.0D0*chip12*(om1om2*facp-om12*facp1)*facp_inv**2
2552 C Evaluate the "asymmetric" factor in the VDW constant, eps3
2553 eps3rt=1.0D0-alf1*om1+alf2*om2-alf12*om12
2554 c write (iout,*) "eps2rt",eps2rt," eps3rt",eps3rt
2555 c write (iout,*) "eps2rt_om1",eps2rt_om1," eps2rt_om2",eps2rt_om2,
2556 c & " eps2rt_om12",eps2rt_om12
2557 C Calculate whole angle-dependent part of epsilon and contributions
2558 C to its derivatives
2561 C----------------------------------------------------------------------------
2563 implicit real*8 (a-h,o-z)
2564 include 'DIMENSIONS'
2565 include 'COMMON.CHAIN'
2566 include 'COMMON.DERIV'
2567 include 'COMMON.CALC'
2568 include 'COMMON.IOUNITS'
2569 double precision dcosom1(3),dcosom2(3)
2570 cc print *,'sss=',sss
2571 eom1=eps2der*eps2rt_om1-2.0D0*alf1*eps3der+sigder*sigsq_om1
2572 eom2=eps2der*eps2rt_om2+2.0D0*alf2*eps3der+sigder*sigsq_om2
2573 eom12=evdwij*eps1_om12+eps2der*eps2rt_om12
2574 & -2.0D0*alf12*eps3der+sigder*sigsq_om12
2578 c eom12=evdwij*eps1_om12
2580 c write (iout,*) "eps2der",eps2der," eps3der",eps3der,
2581 c & " sigder",sigder
2582 c write (iout,*) "eps1_om12",eps1_om12," eps2rt_om12",eps2rt_om12
2583 c write (iout,*) "eom1",eom1," eom2",eom2," eom12",eom12
2585 dcosom1(k)=rij*(dc_norm(k,nres+i)-om1*erij(k))
2586 dcosom2(k)=rij*(dc_norm(k,nres+j)-om2*erij(k))
2589 gg(k)=(gg(k)+eom1*dcosom1(k)+eom2*dcosom2(k))*sss
2591 c write (iout,*) "gg",(gg(k),k=1,3)
2593 gvdwx(k,i)=gvdwx(k,i)-gg(k)+gg_lipi(k)
2594 & +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))
2595 & +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv*sss
2596 gvdwx(k,j)=gvdwx(k,j)+gg(k)+gg_lipj(k)
2597 & +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j))
2598 & +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv*sss
2599 c write (iout,*)(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))
2600 c & +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
2601 c write (iout,*)(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j))
2602 c & +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
2605 C Calculate the components of the gradient in DC and X
2609 cgrad gvdwc(l,k)=gvdwc(l,k)+gg(l)
2613 gvdwc(l,i)=gvdwc(l,i)-gg(l)+gg_lipi(l)
2614 gvdwc(l,j)=gvdwc(l,j)+gg(l)+gg_lipj(l)
2618 C-----------------------------------------------------------------------
2619 subroutine e_softsphere(evdw)
2621 C This subroutine calculates the interaction energy of nonbonded side chains
2622 C assuming the LJ potential of interaction.
2624 implicit real*8 (a-h,o-z)
2625 include 'DIMENSIONS'
2626 parameter (accur=1.0d-10)
2627 include 'COMMON.GEO'
2628 include 'COMMON.VAR'
2629 include 'COMMON.LOCAL'
2630 include 'COMMON.CHAIN'
2631 include 'COMMON.DERIV'
2632 include 'COMMON.INTERACT'
2633 include 'COMMON.TORSION'
2634 include 'COMMON.SBRIDGE'
2635 include 'COMMON.NAMES'
2636 include 'COMMON.IOUNITS'
2637 c include 'COMMON.CONTACTS'
2639 cd print *,'Entering Esoft_sphere nnt=',nnt,' nct=',nct
2641 c do i=iatsc_s,iatsc_e
2642 do icont=g_listscsc_start,g_listscsc_end
2643 i=newcontlisti(icont)
2644 j=newcontlistj(icont)
2645 itypi=iabs(itype(i))
2646 if (itypi.eq.ntyp1) cycle
2647 itypi1=iabs(itype(i+1))
2652 C Calculate SC interaction energy.
2654 c do iint=1,nint_gr(i)
2655 cd write (iout,*) 'i=',i,' iint=',iint,' istart=',istart(i,iint),
2656 cd & 'iend=',iend(i,iint)
2657 c do j=istart(i,iint),iend(i,iint)
2658 itypj=iabs(itype(j))
2659 if (itypj.eq.ntyp1) cycle
2663 rij=xj*xj+yj*yj+zj*zj
2664 c write (iout,*)'i=',i,' j=',j,' itypi=',itypi,' itypj=',itypj
2665 r0ij=r0(itypi,itypj)
2667 c print *,i,j,r0ij,dsqrt(rij)
2668 if (rij.lt.r0ijsq) then
2669 evdwij=0.25d0*(rij-r0ijsq)**2
2677 C Calculate the components of the gradient in DC and X
2683 gvdwx(k,i)=gvdwx(k,i)-gg(k)
2684 gvdwx(k,j)=gvdwx(k,j)+gg(k)
2685 gvdwc(k,i)=gvdwc(k,i)-gg(k)
2686 gvdwc(k,j)=gvdwc(k,j)+gg(k)
2690 cgrad gvdwc(l,k)=gvdwc(l,k)+gg(l)
2698 C--------------------------------------------------------------------------
2699 subroutine eelec_soft_sphere(ees,evdw1,eel_loc,eello_turn3,
2702 C Soft-sphere potential of p-p interaction
2704 implicit real*8 (a-h,o-z)
2705 include 'DIMENSIONS'
2706 include 'COMMON.CONTROL'
2707 include 'COMMON.IOUNITS'
2708 include 'COMMON.GEO'
2709 include 'COMMON.VAR'
2710 include 'COMMON.LOCAL'
2711 include 'COMMON.CHAIN'
2712 include 'COMMON.DERIV'
2713 include 'COMMON.INTERACT'
2714 c include 'COMMON.CONTACTS'
2715 include 'COMMON.TORSION'
2716 include 'COMMON.VECTORS'
2717 include 'COMMON.FFIELD'
2719 integer xshift,yshift,zshift
2720 C write(iout,*) 'In EELEC_soft_sphere'
2727 do i=iatel_s,iatel_e
2728 if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
2732 xmedi=c(1,i)+0.5d0*dxi
2733 ymedi=c(2,i)+0.5d0*dyi
2734 zmedi=c(3,i)+0.5d0*dzi
2735 xmedi=mod(xmedi,boxxsize)
2736 if (xmedi.lt.0) xmedi=xmedi+boxxsize
2737 ymedi=mod(ymedi,boxysize)
2738 if (ymedi.lt.0) ymedi=ymedi+boxysize
2739 zmedi=mod(zmedi,boxzsize)
2740 if (zmedi.lt.0) zmedi=zmedi+boxzsize
2742 c write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
2743 do j=ielstart(i),ielend(i)
2744 if (itype(j).eq.ntyp1 .or. itype(j+1).eq.ntyp1) cycle
2748 if (j.eq.i+2 .and. itelj.eq.2) iteli=2
2749 r0ij=rpp(iteli,itelj)
2758 if (xj.lt.0) xj=xj+boxxsize
2760 if (yj.lt.0) yj=yj+boxysize
2762 if (zj.lt.0) zj=zj+boxzsize
2763 dist_init=(xj-xmedi)**2+(yj-ymedi)**2+(zj-zmedi)**2
2771 xj=xj_safe+xshift*boxxsize
2772 yj=yj_safe+yshift*boxysize
2773 zj=zj_safe+zshift*boxzsize
2774 dist_temp=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
2775 if(dist_temp.lt.dist_init) then
2785 if (isubchap.eq.1) then
2794 rij=xj*xj+yj*yj+zj*zj
2795 sss=sscale(sqrt(rij),r_cut_int)
2796 sssgrad=sscagrad(sqrt(rij),r_cut_int)
2797 if (rij.lt.r0ijsq) then
2798 evdw1ij=0.25d0*(rij-r0ijsq)**2
2804 evdw1=evdw1+evdw1ij*sss
2806 C Calculate contributions to the Cartesian gradient.
2808 ggg(1)=fac*xj*sssgrad
2809 ggg(2)=fac*yj*sssgrad
2810 ggg(3)=fac*zj*sssgrad
2812 gvdwpp(k,i)=gvdwpp(k,i)-ggg(k)
2813 gvdwpp(k,j)=gvdwpp(k,j)+ggg(k)
2816 * Loop over residues i+1 thru j-1.
2820 cgrad gelc(l,k)=gelc(l,k)+ggg(l)
2825 cgrad do i=nnt,nct-1
2827 cgrad gelc(k,i)=gelc(k,i)+0.5d0*gelc(k,i)
2829 cgrad do j=i+1,nct-1
2831 cgrad gelc(k,i)=gelc(k,i)+gelc(k,j)
2837 c------------------------------------------------------------------------------
2838 subroutine vec_and_deriv
2839 implicit real*8 (a-h,o-z)
2840 include 'DIMENSIONS'
2844 include 'COMMON.IOUNITS'
2845 include 'COMMON.GEO'
2846 include 'COMMON.VAR'
2847 include 'COMMON.LOCAL'
2848 include 'COMMON.CHAIN'
2849 include 'COMMON.VECTORS'
2850 include 'COMMON.SETUP'
2851 include 'COMMON.TIME1'
2852 dimension uyder(3,3,2),uzder(3,3,2),vbld_inv_temp(2)
2853 C Compute the local reference systems. For reference system (i), the
2854 C X-axis points from CA(i) to CA(i+1), the Y axis is in the
2855 C CA(i)-CA(i+1)-CA(i+2) plane, and the Z axis is perpendicular to this plane.
2857 do i=ivec_start,ivec_end
2861 if (i.eq.nres-1) then
2862 C Case of the last full residue
2863 C Compute the Z-axis
2864 call vecpr(dc_norm(1,i),dc_norm(1,i-1),uz(1,i))
2865 costh=dcos(pi-theta(nres))
2866 fac=1.0d0/dsqrt(1.0d0-costh*costh)
2870 C Compute the derivatives of uz
2872 uzder(2,1,1)=-dc_norm(3,i-1)
2873 uzder(3,1,1)= dc_norm(2,i-1)
2874 uzder(1,2,1)= dc_norm(3,i-1)
2876 uzder(3,2,1)=-dc_norm(1,i-1)
2877 uzder(1,3,1)=-dc_norm(2,i-1)
2878 uzder(2,3,1)= dc_norm(1,i-1)
2881 uzder(2,1,2)= dc_norm(3,i)
2882 uzder(3,1,2)=-dc_norm(2,i)
2883 uzder(1,2,2)=-dc_norm(3,i)
2885 uzder(3,2,2)= dc_norm(1,i)
2886 uzder(1,3,2)= dc_norm(2,i)
2887 uzder(2,3,2)=-dc_norm(1,i)
2889 C Compute the Y-axis
2892 uy(k,i)=fac*(dc_norm(k,i-1)-costh*dc_norm(k,i))
2894 C Compute the derivatives of uy
2897 uyder(k,j,1)=2*dc_norm(k,i-1)*dc_norm(j,i)
2898 & -dc_norm(k,i)*dc_norm(j,i-1)
2899 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
2901 uyder(j,j,1)=uyder(j,j,1)-costh
2902 uyder(j,j,2)=1.0d0+uyder(j,j,2)
2907 uygrad(l,k,j,i)=uyder(l,k,j)
2908 uzgrad(l,k,j,i)=uzder(l,k,j)
2912 call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
2913 call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
2914 call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
2915 call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
2918 C Compute the Z-axis
2919 call vecpr(dc_norm(1,i),dc_norm(1,i+1),uz(1,i))
2920 costh=dcos(pi-theta(i+2))
2921 fac=1.0d0/dsqrt(1.0d0-costh*costh)
2925 C Compute the derivatives of uz
2927 uzder(2,1,1)=-dc_norm(3,i+1)
2928 uzder(3,1,1)= dc_norm(2,i+1)
2929 uzder(1,2,1)= dc_norm(3,i+1)
2931 uzder(3,2,1)=-dc_norm(1,i+1)
2932 uzder(1,3,1)=-dc_norm(2,i+1)
2933 uzder(2,3,1)= dc_norm(1,i+1)
2936 uzder(2,1,2)= dc_norm(3,i)
2937 uzder(3,1,2)=-dc_norm(2,i)
2938 uzder(1,2,2)=-dc_norm(3,i)
2940 uzder(3,2,2)= dc_norm(1,i)
2941 uzder(1,3,2)= dc_norm(2,i)
2942 uzder(2,3,2)=-dc_norm(1,i)
2944 C Compute the Y-axis
2947 uy(k,i)=facy*(dc_norm(k,i+1)-costh*dc_norm(k,i))
2949 C Compute the derivatives of uy
2952 uyder(k,j,1)=2*dc_norm(k,i+1)*dc_norm(j,i)
2953 & -dc_norm(k,i)*dc_norm(j,i+1)
2954 uyder(k,j,2)=-dc_norm(j,i)*dc_norm(k,i)
2956 uyder(j,j,1)=uyder(j,j,1)-costh
2957 uyder(j,j,2)=1.0d0+uyder(j,j,2)
2962 uygrad(l,k,j,i)=uyder(l,k,j)
2963 uzgrad(l,k,j,i)=uzder(l,k,j)
2967 call unormderiv(uy(1,i),uyder(1,1,1),facy,uygrad(1,1,1,i))
2968 call unormderiv(uy(1,i),uyder(1,1,2),facy,uygrad(1,1,2,i))
2969 call unormderiv(uz(1,i),uzder(1,1,1),fac,uzgrad(1,1,1,i))
2970 call unormderiv(uz(1,i),uzder(1,1,2),fac,uzgrad(1,1,2,i))
2974 vbld_inv_temp(1)=vbld_inv(i+1)
2975 if (i.lt.nres-1) then
2976 vbld_inv_temp(2)=vbld_inv(i+2)
2978 vbld_inv_temp(2)=vbld_inv(i)
2983 uygrad(l,k,j,i)=vbld_inv_temp(j)*uygrad(l,k,j,i)
2984 uzgrad(l,k,j,i)=vbld_inv_temp(j)*uzgrad(l,k,j,i)
2989 #if defined(PARVEC) && defined(MPI)
2990 if (nfgtasks1.gt.1) then
2992 c print *,"Processor",fg_rank1,kolor1," ivec_start",ivec_start,
2993 c & " ivec_displ",(ivec_displ(i),i=0,nfgtasks1-1),
2994 c & " ivec_count",(ivec_count(i),i=0,nfgtasks1-1)
2995 call MPI_Allgatherv(uy(1,ivec_start),ivec_count(fg_rank1),
2996 & MPI_UYZ,uy(1,1),ivec_count(0),ivec_displ(0),MPI_UYZ,
2998 call MPI_Allgatherv(uz(1,ivec_start),ivec_count(fg_rank1),
2999 & MPI_UYZ,uz(1,1),ivec_count(0),ivec_displ(0),MPI_UYZ,
3001 call MPI_Allgatherv(uygrad(1,1,1,ivec_start),
3002 & ivec_count(fg_rank1),MPI_UYZGRAD,uygrad(1,1,1,1),ivec_count(0),
3003 & ivec_displ(0),MPI_UYZGRAD,FG_COMM1,IERR)
3004 call MPI_Allgatherv(uzgrad(1,1,1,ivec_start),
3005 & ivec_count(fg_rank1),MPI_UYZGRAD,uzgrad(1,1,1,1),ivec_count(0),
3006 & ivec_displ(0),MPI_UYZGRAD,FG_COMM1,IERR)
3007 time_gather=time_gather+MPI_Wtime()-time00
3011 if (fg_rank.eq.0) then
3012 write (iout,*) "Arrays UY and UZ"
3014 write (iout,'(i5,3f10.5,5x,3f10.5)') i,(uy(k,i),k=1,3),
3021 C--------------------------------------------------------------------------
3022 subroutine set_matrices
3023 implicit real*8 (a-h,o-z)
3024 include 'DIMENSIONS'
3027 include "COMMON.SETUP"
3029 integer status(MPI_STATUS_SIZE)
3031 include 'COMMON.IOUNITS'
3032 include 'COMMON.GEO'
3033 include 'COMMON.VAR'
3034 include 'COMMON.LOCAL'
3035 include 'COMMON.CHAIN'
3036 include 'COMMON.DERIV'
3037 include 'COMMON.INTERACT'
3038 include 'COMMON.CORRMAT'
3039 include 'COMMON.TORSION'
3040 include 'COMMON.VECTORS'
3041 include 'COMMON.FFIELD'
3042 double precision auxvec(2),auxmat(2,2)
3044 C Compute the virtual-bond-torsional-angle dependent quantities needed
3045 C to calculate the el-loc multibody terms of various order.
3047 c write(iout,*) 'nphi=',nphi,nres
3048 c write(iout,*) "itype2loc",itype2loc
3050 do i=ivec_start+2,ivec_end+2
3055 c write (iout,*) "i",i,i-2," ii",ii
3057 innt=chain_border(1,ii)
3058 inct=chain_border(2,ii)
3059 c write (iout,*) "i",i,i-2," ii",ii," innt",innt," inct",inct
3060 c if (i.gt. nnt+2 .and. i.lt.nct+2) then
3061 if (i.gt. innt+2 .and. i.lt.inct+2) then
3062 iti = itype2loc(itype(i-2))
3066 c if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
3067 if (i.gt. innt+1 .and. i.lt.inct+1) then
3068 iti1 = itype2loc(itype(i-1))
3072 c write(iout,*),"i",i,i-2," iti",itype(i-2),iti,
3073 c & " iti1",itype(i-1),iti1
3075 cost1=dcos(theta(i-1))
3076 sint1=dsin(theta(i-1))
3078 sint1cub=sint1sq*sint1
3079 sint1cost1=2*sint1*cost1
3080 c write (iout,*) "bnew1",i,iti
3081 c write (iout,*) (bnew1(k,1,iti),k=1,3)
3082 c write (iout,*) (bnew1(k,2,iti),k=1,3)
3083 c write (iout,*) "bnew2",i,iti
3084 c write (iout,*) (bnew2(k,1,iti),k=1,3)
3085 c write (iout,*) (bnew2(k,2,iti),k=1,3)
3087 b1k=bnew1(1,k,iti)+(bnew1(2,k,iti)+bnew1(3,k,iti)*cost1)*cost1
3089 gtb1(k,i-2)=cost1*b1k-sint1sq*
3090 & (bnew1(2,k,iti)+2*bnew1(3,k,iti)*cost1)
3091 b2k=bnew2(1,k,iti)+(bnew2(2,k,iti)+bnew2(3,k,iti)*cost1)*cost1
3093 gtb2(k,i-2)=cost1*b2k-sint1sq*
3094 & (bnew2(2,k,iti)+2*bnew2(3,k,iti)*cost1)
3097 aux=ccnew(1,k,iti)+(ccnew(2,k,iti)+ccnew(3,k,iti)*cost1)*cost1
3098 cc(1,k,i-2)=sint1sq*aux
3099 gtcc(1,k,i-2)=sint1cost1*aux-sint1cub*
3100 & (ccnew(2,k,iti)+2*ccnew(3,k,iti)*cost1)
3101 aux=ddnew(1,k,iti)+(ddnew(2,k,iti)+ddnew(3,k,iti)*cost1)*cost1
3102 dd(1,k,i-2)=sint1sq*aux
3103 gtdd(1,k,i-2)=sint1cost1*aux-sint1cub*
3104 & (ddnew(2,k,iti)+2*ddnew(3,k,iti)*cost1)
3106 cc(2,1,i-2)=cc(1,2,i-2)
3107 cc(2,2,i-2)=-cc(1,1,i-2)
3108 gtcc(2,1,i-2)=gtcc(1,2,i-2)
3109 gtcc(2,2,i-2)=-gtcc(1,1,i-2)
3110 dd(2,1,i-2)=dd(1,2,i-2)
3111 dd(2,2,i-2)=-dd(1,1,i-2)
3112 gtdd(2,1,i-2)=gtdd(1,2,i-2)
3113 gtdd(2,2,i-2)=-gtdd(1,1,i-2)
3116 aux=eenew(1,l,k,iti)+eenew(2,l,k,iti)*cost1
3117 EE(l,k,i-2)=sint1sq*aux
3118 gtEE(l,k,i-2)=sint1cost1*aux-sint1cub*eenew(2,l,k,iti)
3121 EE(1,1,i-2)=EE(1,1,i-2)+e0new(1,iti)*cost1
3122 EE(1,2,i-2)=EE(1,2,i-2)+e0new(2,iti)+e0new(3,iti)*cost1
3123 EE(2,1,i-2)=EE(2,1,i-2)+e0new(2,iti)*cost1+e0new(3,iti)
3124 EE(2,2,i-2)=EE(2,2,i-2)-e0new(1,iti)
3125 gtEE(1,1,i-2)=gtEE(1,1,i-2)-e0new(1,iti)*sint1
3126 gtEE(1,2,i-2)=gtEE(1,2,i-2)-e0new(3,iti)*sint1
3127 gtEE(2,1,i-2)=gtEE(2,1,i-2)-e0new(2,iti)*sint1
3128 c b1tilde(1,i-2)=b1(1,i-2)
3129 c b1tilde(2,i-2)=-b1(2,i-2)
3130 c b2tilde(1,i-2)=b2(1,i-2)
3131 c b2tilde(2,i-2)=-b2(2,i-2)
3133 write (iout,*) 'i=',i-2,gtb1(2,i-2),gtb1(1,i-2)
3134 write(iout,*) 'b1=',(b1(k,i-2),k=1,2)
3135 write(iout,*) 'b2=',(b2(k,i-2),k=1,2)
3136 write (iout,*) 'theta=', theta(i-1)
3139 if (i.gt. innt+2 .and. i.lt.inct+2) then
3140 c if (i.gt. nnt+2 .and. i.lt.nct+2) then
3141 iti = itype2loc(itype(i-2))
3145 c write (iout,*) "i",i-1," itype",itype(i-2)," iti",iti
3146 c if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
3147 if (i.gt. nnt+1 .and. i.lt.nct+1) then
3148 iti1 = itype2loc(itype(i-1))
3158 CC(k,l,i-2)=ccold(k,l,iti)
3159 DD(k,l,i-2)=ddold(k,l,iti)
3160 EE(k,l,i-2)=eeold(k,l,iti)
3165 b1tilde(1,i-2)= b1(1,i-2)
3166 b1tilde(2,i-2)=-b1(2,i-2)
3167 b2tilde(1,i-2)= b2(1,i-2)
3168 b2tilde(2,i-2)=-b2(2,i-2)
3170 Ctilde(1,1,i-2)= CC(1,1,i-2)
3171 Ctilde(1,2,i-2)= CC(1,2,i-2)
3172 Ctilde(2,1,i-2)=-CC(2,1,i-2)
3173 Ctilde(2,2,i-2)=-CC(2,2,i-2)
3175 Dtilde(1,1,i-2)= DD(1,1,i-2)
3176 Dtilde(1,2,i-2)= DD(1,2,i-2)
3177 Dtilde(2,1,i-2)=-DD(2,1,i-2)
3178 Dtilde(2,2,i-2)=-DD(2,2,i-2)
3180 write(iout,*) "i",i," iti",iti
3181 write(iout,*) 'b1=',(b1(k,i-2),k=1,2)
3182 write(iout,*) 'b2=',(b2(k,i-2),k=1,2)
3187 do i=ivec_start+2,ivec_end+2
3191 c if (itype(i-1).eq.ntyp1 .and. itype(i).eq.ntyp1) cycle
3192 if (i .lt. nres+1 .and. itype(i-1).lt.ntyp1) then
3230 obrot_der(1,i-2)=-sin1
3231 obrot_der(2,i-2)= cos1
3232 Ugder(1,1,i-2)= sin1
3233 Ugder(1,2,i-2)=-cos1
3234 Ugder(2,1,i-2)=-cos1
3235 Ugder(2,2,i-2)=-sin1
3238 obrot2_der(1,i-2)=-dwasin2
3239 obrot2_der(2,i-2)= dwacos2
3240 Ug2der(1,1,i-2)= dwasin2
3241 Ug2der(1,2,i-2)=-dwacos2
3242 Ug2der(2,1,i-2)=-dwacos2
3243 Ug2der(2,2,i-2)=-dwasin2
3245 obrot_der(1,i-2)=0.0d0
3246 obrot_der(2,i-2)=0.0d0
3247 Ugder(1,1,i-2)=0.0d0
3248 Ugder(1,2,i-2)=0.0d0
3249 Ugder(2,1,i-2)=0.0d0
3250 Ugder(2,2,i-2)=0.0d0
3251 obrot2_der(1,i-2)=0.0d0
3252 obrot2_der(2,i-2)=0.0d0
3253 Ug2der(1,1,i-2)=0.0d0
3254 Ug2der(1,2,i-2)=0.0d0
3255 Ug2der(2,1,i-2)=0.0d0
3256 Ug2der(2,2,i-2)=0.0d0
3258 c if (i.gt. iatel_s+2 .and. i.lt.iatel_e+5) then
3259 c if (i.gt. nnt+2 .and. i.lt.nct+2) then
3260 if (i.gt.nnt+2 .and.i.lt.nct+2) then
3261 iti = itype2loc(itype(i-2))
3265 c if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
3266 if (i.gt. nnt+1 .and. i.lt.nct+1) then
3267 iti1 = itype2loc(itype(i-1))
3271 cd write (iout,*) '*******i',i,' iti1',iti
3272 cd write (iout,*) 'b1',b1(:,iti)
3273 cd write (iout,*) 'b2',b2(:,iti)
3274 cd write (iout,*) 'Ug',Ug(:,:,i-2)
3275 c if (i .gt. iatel_s+2) then
3276 if (i .gt. nnt+2) then
3277 call matvec2(Ug(1,1,i-2),b2(1,i-2),Ub2(1,i-2))
3279 call matvec2(Ug(1,1,i-2),gtb2(1,i-2),gUb2(1,i-2))
3280 c write (iout,*) Ug(1,1,i-2),gtb2(1,i-2),gUb2(1,i-2),"chuj"
3282 c write(iout,*) "co jest kurwa", iti, EE(1,1,i),EE(2,1,i),
3283 c & EE(1,2,iti),EE(2,2,i)
3284 call matmat2(EE(1,1,i-2),Ug(1,1,i-2),EUg(1,1,i-2))
3285 call matmat2(gtEE(1,1,i-2),Ug(1,1,i-2),gtEUg(1,1,i-2))
3286 c write(iout,*) "Macierz EUG",
3287 c & eug(1,1,i-2),eug(1,2,i-2),eug(2,1,i-2),
3290 if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0)
3292 call matmat2(CC(1,1,i-2),Ug(1,1,i-2),CUg(1,1,i-2))
3293 call matmat2(DD(1,1,i-2),Ug(1,1,i-2),DUg(1,1,i-2))
3294 call matmat2(Dtilde(1,1,i-2),Ug2(1,1,i-2),DtUg2(1,1,i-2))
3295 call matvec2(Ctilde(1,1,i-1),obrot(1,i-2),Ctobr(1,i-2))
3296 call matvec2(Dtilde(1,1,i-2),obrot2(1,i-2),Dtobr2(1,i-2))
3308 DtUg2(l,k,i-2)=0.0d0
3312 call matvec2(Ugder(1,1,i-2),b2(1,i-2),Ub2der(1,i-2))
3313 call matmat2(EE(1,1,i-2),Ugder(1,1,i-2),EUgder(1,1,i-2))
3315 muder(k,i-2)=Ub2der(k,i-2)
3317 c if (i.gt. iatel_s+1 .and. i.lt.iatel_e+4) then
3318 if (i.gt. nnt+1 .and. i.lt.nct+1) then
3319 if (itype(i-1).le.ntyp) then
3320 iti1 = itype2loc(itype(i-1))
3328 mu(k,i-2)=Ub2(k,i-2)+b1(k,i-1)
3329 c mu(k,i-2)=b1(k,i-1)
3330 c mu(k,i-2)=Ub2(k,i-2)
3333 write (iout,'(2hmu,i3,3f8.1,12f10.5)') i-2,rad2deg*theta(i-1),
3334 & rad2deg*theta(i),rad2deg*phi(i),mu(1,i-2),mu(2,i-2),
3335 & -b2(1,i-2),b2(2,i-2),b1(1,i-2),b1(2,i-2),
3336 & dsqrt(b2(1,i-1)**2+b2(2,i-1)**2)
3337 & +dsqrt(b1(1,i-1)**2+b1(2,i-1)**2),
3338 & ((ee(l,k,i-2),l=1,2),k=1,2)
3340 cd write (iout,*) 'mu1',mu1(:,i-2)
3341 cd write (iout,*) 'mu2',mu2(:,i-2)
3342 cd write (iout,*) 'mu',i-2,mu(:,i-2)
3344 if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or.wcorr6.gt.0.0d0)
3346 call matmat2(CC(1,1,i-1),Ugder(1,1,i-2),CUgder(1,1,i-2))
3347 call matmat2(DD(1,1,i-2),Ugder(1,1,i-2),DUgder(1,1,i-2))
3348 call matmat2(Dtilde(1,1,i-2),Ug2der(1,1,i-2),DtUg2der(1,1,i-2))
3349 call matvec2(Ctilde(1,1,i-1),obrot_der(1,i-2),Ctobrder(1,i-2))
3350 call matvec2(Dtilde(1,1,i-2),obrot2_der(1,i-2),Dtobr2der(1,i-2))
3351 C Vectors and matrices dependent on a single virtual-bond dihedral.
3352 call matvec2(DD(1,1,i-2),b1tilde(1,i-1),auxvec(1))
3353 call matvec2(Ug2(1,1,i-2),auxvec(1),Ug2Db1t(1,i-2))
3354 call matvec2(Ug2der(1,1,i-2),auxvec(1),Ug2Db1tder(1,i-2))
3355 call matvec2(CC(1,1,i-1),Ub2(1,i-2),CUgb2(1,i-2))
3356 call matvec2(CC(1,1,i-1),Ub2der(1,i-2),CUgb2der(1,i-2))
3357 call matmat2(EUg(1,1,i-2),CC(1,1,i-1),EUgC(1,1,i-2))
3358 call matmat2(EUgder(1,1,i-2),CC(1,1,i-1),EUgCder(1,1,i-2))
3359 call matmat2(EUg(1,1,i-2),DD(1,1,i-1),EUgD(1,1,i-2))
3360 call matmat2(EUgder(1,1,i-2),DD(1,1,i-1),EUgDder(1,1,i-2))
3365 C Matrices dependent on two consecutive virtual-bond dihedrals.
3366 C The order of matrices is from left to right.
3367 if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or.wcorr6.gt.0.0d0)
3369 c do i=max0(ivec_start,2),ivec_end
3371 call matmat2(DtUg2(1,1,i-1),EUg(1,1,i),DtUg2EUg(1,1,i))
3372 call matmat2(DtUg2der(1,1,i-1),EUg(1,1,i),DtUg2EUgder(1,1,1,i))
3373 call matmat2(DtUg2(1,1,i-1),EUgder(1,1,i),DtUg2EUgder(1,1,2,i))
3374 call transpose2(DtUg2(1,1,i-1),auxmat(1,1))
3375 call matmat2(auxmat(1,1),EUg(1,1,i),Ug2DtEUg(1,1,i))
3376 call matmat2(auxmat(1,1),EUgder(1,1,i),Ug2DtEUgder(1,1,2,i))
3377 call transpose2(DtUg2der(1,1,i-1),auxmat(1,1))
3378 call matmat2(auxmat(1,1),EUg(1,1,i),Ug2DtEUgder(1,1,1,i))
3382 #if defined(MPI) && defined(PARMAT)
3384 c if (fg_rank.eq.0) then
3385 write (iout,*) "Arrays UG and UGDER before GATHER"
3387 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3388 & ((ug(l,k,i),l=1,2),k=1,2),
3389 & ((ugder(l,k,i),l=1,2),k=1,2)
3391 write (iout,*) "Arrays UG2 and UG2DER"
3393 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3394 & ((ug2(l,k,i),l=1,2),k=1,2),
3395 & ((ug2der(l,k,i),l=1,2),k=1,2)
3397 write (iout,*) "Arrays OBROT OBROT2 OBROTDER and OBROT2DER"
3399 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3400 & (obrot(k,i),k=1,2),(obrot2(k,i),k=1,2),
3401 & (obrot_der(k,i),k=1,2),(obrot2_der(k,i),k=1,2)
3403 write (iout,*) "Arrays COSTAB SINTAB COSTAB2 and SINTAB2"
3405 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3406 & costab(i),sintab(i),costab2(i),sintab2(i)
3408 write (iout,*) "Array MUDER"
3410 write (iout,'(i5,2f10.5)') i,muder(1,i),muder(2,i)
3414 if (nfgtasks.gt.1) then
3416 c write(iout,*)"Processor",fg_rank,kolor," ivec_start",ivec_start,
3417 c & " ivec_displ",(ivec_displ(i),i=0,nfgtasks-1),
3418 c & " ivec_count",(ivec_count(i),i=0,nfgtasks-1)
3420 call MPI_Allgatherv(Ub2(1,ivec_start),ivec_count(fg_rank1),
3421 & MPI_MU,Ub2(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3423 call MPI_Allgatherv(Ub2der(1,ivec_start),ivec_count(fg_rank1),
3424 & MPI_MU,Ub2der(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3426 call MPI_Allgatherv(mu(1,ivec_start),ivec_count(fg_rank1),
3427 & MPI_MU,mu(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3429 call MPI_Allgatherv(muder(1,ivec_start),ivec_count(fg_rank1),
3430 & MPI_MU,muder(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3432 call MPI_Allgatherv(Eug(1,1,ivec_start),ivec_count(fg_rank1),
3433 & MPI_MAT1,Eug(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3435 call MPI_Allgatherv(Eugder(1,1,ivec_start),ivec_count(fg_rank1),
3436 & MPI_MAT1,Eugder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3438 call MPI_Allgatherv(costab(ivec_start),ivec_count(fg_rank1),
3439 & MPI_DOUBLE_PRECISION,costab(1),ivec_count(0),ivec_displ(0),
3440 & MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
3441 call MPI_Allgatherv(sintab(ivec_start),ivec_count(fg_rank1),
3442 & MPI_DOUBLE_PRECISION,sintab(1),ivec_count(0),ivec_displ(0),
3443 & MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
3444 call MPI_Allgatherv(costab2(ivec_start),ivec_count(fg_rank1),
3445 & MPI_DOUBLE_PRECISION,costab2(1),ivec_count(0),ivec_displ(0),
3446 & MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
3447 call MPI_Allgatherv(sintab2(ivec_start),ivec_count(fg_rank1),
3448 & MPI_DOUBLE_PRECISION,sintab2(1),ivec_count(0),ivec_displ(0),
3449 & MPI_DOUBLE_PRECISION,FG_COMM1,IERR)
3451 if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0)
3453 call MPI_Allgatherv(Ctobr(1,ivec_start),ivec_count(fg_rank1),
3454 & MPI_MU,Ctobr(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3456 call MPI_Allgatherv(Ctobrder(1,ivec_start),ivec_count(fg_rank1),
3457 & MPI_MU,Ctobrder(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3459 call MPI_Allgatherv(Dtobr2(1,ivec_start),ivec_count(fg_rank1),
3460 & MPI_MU,Dtobr2(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3462 call MPI_Allgatherv(Dtobr2der(1,ivec_start),ivec_count(fg_rank1),
3463 & MPI_MU,Dtobr2der(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3465 call MPI_Allgatherv(Ug2Db1t(1,ivec_start),ivec_count(fg_rank1),
3466 & MPI_MU,Ug2Db1t(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3468 call MPI_Allgatherv(Ug2Db1tder(1,ivec_start),
3469 & ivec_count(fg_rank1),
3470 & MPI_MU,Ug2Db1tder(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3472 call MPI_Allgatherv(CUgb2(1,ivec_start),ivec_count(fg_rank1),
3473 & MPI_MU,CUgb2(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3475 call MPI_Allgatherv(CUgb2der(1,ivec_start),ivec_count(fg_rank1),
3476 & MPI_MU,CUgb2der(1,1),ivec_count(0),ivec_displ(0),MPI_MU,
3478 call MPI_Allgatherv(Cug(1,1,ivec_start),ivec_count(fg_rank1),
3479 & MPI_MAT1,Cug(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3481 call MPI_Allgatherv(Cugder(1,1,ivec_start),ivec_count(fg_rank1),
3482 & MPI_MAT1,Cugder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3484 call MPI_Allgatherv(Dug(1,1,ivec_start),ivec_count(fg_rank1),
3485 & MPI_MAT1,Dug(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3487 call MPI_Allgatherv(Dugder(1,1,ivec_start),ivec_count(fg_rank1),
3488 & MPI_MAT1,Dugder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3490 call MPI_Allgatherv(Dtug2(1,1,ivec_start),ivec_count(fg_rank1),
3491 & MPI_MAT1,Dtug2(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3493 call MPI_Allgatherv(Dtug2der(1,1,ivec_start),
3494 & ivec_count(fg_rank1),
3495 & MPI_MAT1,Dtug2der(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3497 call MPI_Allgatherv(EugC(1,1,ivec_start),ivec_count(fg_rank1),
3498 & MPI_MAT1,EugC(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3500 call MPI_Allgatherv(EugCder(1,1,ivec_start),ivec_count(fg_rank1),
3501 & MPI_MAT1,EugCder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3503 call MPI_Allgatherv(EugD(1,1,ivec_start),ivec_count(fg_rank1),
3504 & MPI_MAT1,EugD(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3506 call MPI_Allgatherv(EugDder(1,1,ivec_start),ivec_count(fg_rank1),
3507 & MPI_MAT1,EugDder(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3509 call MPI_Allgatherv(DtUg2EUg(1,1,ivec_start),
3510 & ivec_count(fg_rank1),
3511 & MPI_MAT1,DtUg2EUg(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3513 call MPI_Allgatherv(Ug2DtEUg(1,1,ivec_start),
3514 & ivec_count(fg_rank1),
3515 & MPI_MAT1,Ug2DtEUg(1,1,1),ivec_count(0),ivec_displ(0),MPI_MAT1,
3517 call MPI_Allgatherv(DtUg2EUgder(1,1,1,ivec_start),
3518 & ivec_count(fg_rank1),
3519 & MPI_MAT2,DtUg2EUgder(1,1,1,1),ivec_count(0),ivec_displ(0),
3520 & MPI_MAT2,FG_COMM1,IERR)
3521 call MPI_Allgatherv(Ug2DtEUgder(1,1,1,ivec_start),
3522 & ivec_count(fg_rank1),
3523 & MPI_MAT2,Ug2DtEUgder(1,1,1,1),ivec_count(0),ivec_displ(0),
3524 & MPI_MAT2,FG_COMM1,IERR)
3528 c Passes matrix info through the ring
3531 if (irecv.lt.0) irecv=nfgtasks1-1
3534 if (inext.ge.nfgtasks1) inext=0
3536 c write (iout,*) "isend",isend," irecv",irecv
3538 lensend=lentyp(isend)
3539 lenrecv=lentyp(irecv)
3540 c write (iout,*) "lensend",lensend," lenrecv",lenrecv
3541 c call MPI_SENDRECV(ug(1,1,ivec_displ(isend)+1),1,
3542 c & MPI_ROTAT1(lensend),inext,2200+isend,
3543 c & ug(1,1,ivec_displ(irecv)+1),1,MPI_ROTAT1(lenrecv),
3544 c & iprev,2200+irecv,FG_COMM,status,IERR)
3545 c write (iout,*) "Gather ROTAT1"
3547 c call MPI_SENDRECV(obrot(1,ivec_displ(isend)+1),1,
3548 c & MPI_ROTAT2(lensend),inext,3300+isend,
3549 c & obrot(1,ivec_displ(irecv)+1),1,MPI_ROTAT2(lenrecv),
3550 c & iprev,3300+irecv,FG_COMM,status,IERR)
3551 c write (iout,*) "Gather ROTAT2"
3553 call MPI_SENDRECV(costab(ivec_displ(isend)+1),1,
3554 & MPI_ROTAT_OLD(lensend),inext,4400+isend,
3555 & costab(ivec_displ(irecv)+1),1,MPI_ROTAT_OLD(lenrecv),
3556 & iprev,4400+irecv,FG_COMM,status,IERR)
3557 c write (iout,*) "Gather ROTAT_OLD"
3559 call MPI_SENDRECV(mu(1,ivec_displ(isend)+1),1,
3560 & MPI_PRECOMP11(lensend),inext,5500+isend,
3561 & mu(1,ivec_displ(irecv)+1),1,MPI_PRECOMP11(lenrecv),
3562 & iprev,5500+irecv,FG_COMM,status,IERR)
3563 c write (iout,*) "Gather PRECOMP11"
3565 call MPI_SENDRECV(Eug(1,1,ivec_displ(isend)+1),1,
3566 & MPI_PRECOMP12(lensend),inext,6600+isend,
3567 & Eug(1,1,ivec_displ(irecv)+1),1,MPI_PRECOMP12(lenrecv),
3568 & iprev,6600+irecv,FG_COMM,status,IERR)
3569 c write (iout,*) "Gather PRECOMP12"
3572 if (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0)
3574 call MPI_SENDRECV(ug2db1t(1,ivec_displ(isend)+1),1,
3575 & MPI_ROTAT2(lensend),inext,7700+isend,
3576 & ug2db1t(1,ivec_displ(irecv)+1),1,MPI_ROTAT2(lenrecv),
3577 & iprev,7700+irecv,FG_COMM,status,IERR)
3578 c write (iout,*) "Gather PRECOMP21"
3580 call MPI_SENDRECV(EUgC(1,1,ivec_displ(isend)+1),1,
3581 & MPI_PRECOMP22(lensend),inext,8800+isend,
3582 & EUgC(1,1,ivec_displ(irecv)+1),1,MPI_PRECOMP22(lenrecv),
3583 & iprev,8800+irecv,FG_COMM,status,IERR)
3584 c write (iout,*) "Gather PRECOMP22"
3586 call MPI_SENDRECV(Ug2DtEUgder(1,1,1,ivec_displ(isend)+1),1,
3587 & MPI_PRECOMP23(lensend),inext,9900+isend,
3588 & Ug2DtEUgder(1,1,1,ivec_displ(irecv)+1),1,
3589 & MPI_PRECOMP23(lenrecv),
3590 & iprev,9900+irecv,FG_COMM,status,IERR)
3592 c write (iout,*) "Gather PRECOMP23"
3597 if (irecv.lt.0) irecv=nfgtasks1-1
3600 time_gather=time_gather+MPI_Wtime()-time00
3603 c if (fg_rank.eq.0) then
3604 write (iout,*) "Arrays UG and UGDER"
3606 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3607 & ((ug(l,k,i),l=1,2),k=1,2),
3608 & ((ugder(l,k,i),l=1,2),k=1,2)
3610 write (iout,*) "Arrays UG2 and UG2DER"
3612 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3613 & ((ug2(l,k,i),l=1,2),k=1,2),
3614 & ((ug2der(l,k,i),l=1,2),k=1,2)
3616 write (iout,*) "Arrays OBROT OBROT2 OBROTDER and OBROT2DER"
3618 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3619 & (obrot(k,i),k=1,2),(obrot2(k,i),k=1,2),
3620 & (obrot_der(k,i),k=1,2),(obrot2_der(k,i),k=1,2)
3622 write (iout,*) "Arrays COSTAB SINTAB COSTAB2 and SINTAB2"
3624 write (iout,'(i5,4f10.5,5x,4f10.5)') i,
3625 & costab(i),sintab(i),costab2(i),sintab2(i)
3627 write (iout,*) "Array MUDER"
3629 write (iout,'(i5,2f10.5)') i,muder(1,i),muder(2,i)
3635 cd iti = itype2loc(itype(i))
3638 cd write (iout,'(2f10.5,5x,2f10.5,5x,2f10.5)')
3639 cd & (EE(j,k,i),k=1,2),(Ug(j,k,i),k=1,2),(EUg(j,k,i),k=1,2)
3644 C-----------------------------------------------------------------------------
3645 subroutine eelec(ees,evdw1,eel_loc,eello_turn3,eello_turn4)
3647 C This subroutine calculates the average interaction energy and its gradient
3648 C in the virtual-bond vectors between non-adjacent peptide groups, based on
3649 C the potential described in Liwo et al., Protein Sci., 1993, 2, 1715.
3650 C The potential depends both on the distance of peptide-group centers and on
3651 C the orientation of the CA-CA virtual bonds.
3653 implicit real*8 (a-h,o-z)
3657 include 'DIMENSIONS'
3658 include 'COMMON.CONTROL'
3659 include 'COMMON.SETUP'
3660 include 'COMMON.IOUNITS'
3661 include 'COMMON.GEO'
3662 include 'COMMON.VAR'
3663 include 'COMMON.LOCAL'
3664 include 'COMMON.CHAIN'
3665 include 'COMMON.DERIV'
3666 include 'COMMON.INTERACT'
3668 include 'COMMON.CONTACTS'
3669 include 'COMMON.CONTMAT'
3671 include 'COMMON.CORRMAT'
3672 include 'COMMON.TORSION'
3673 include 'COMMON.VECTORS'
3674 include 'COMMON.FFIELD'
3675 include 'COMMON.TIME1'
3676 include 'COMMON.SPLITELE'
3677 dimension ggg(3),gggp(3),gggm(3),erij(3),dcosb(3),dcosg(3),
3678 & erder(3,3),uryg(3,3),urzg(3,3),vryg(3,3),vrzg(3,3)
3679 double precision acipa(2,2),agg(3,4),aggi(3,4),aggi1(3,4),
3680 & aggj(3,4),aggj1(3,4),a_temp(2,2),muij(4),gmuij(4)
3681 common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
3682 & dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
3684 c 4/26/02 - AL scaling factor for 1,4 repulsive VDW interactions
3686 double precision scal_el /1.0d0/
3688 double precision scal_el /0.5d0/
3691 C 13-go grudnia roku pamietnego...
3692 double precision unmat(3,3) /1.0d0,0.0d0,0.0d0,
3693 & 0.0d0,1.0d0,0.0d0,
3694 & 0.0d0,0.0d0,1.0d0/
3695 cd write(iout,*) 'In EELEC'
3697 cd write(iout,*) 'Type',i
3698 cd write(iout,*) 'B1',B1(:,i)
3699 cd write(iout,*) 'B2',B2(:,i)
3700 cd write(iout,*) 'CC',CC(:,:,i)
3701 cd write(iout,*) 'DD',DD(:,:,i)
3702 cd write(iout,*) 'EE',EE(:,:,i)
3704 cd call check_vecgrad
3706 if (icheckgrad.eq.1) then
3708 fac=1.0d0/dsqrt(scalar(dc(1,i),dc(1,i)))
3710 dc_norm(k,i)=dc(k,i)*fac
3712 c write (iout,*) 'i',i,' fac',fac
3715 if (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0
3716 & .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0 .or.
3717 & wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) then
3718 c call vec_and_deriv
3724 time_mat=time_mat+MPI_Wtime()-time01
3728 cd write (iout,*) 'i=',i
3730 cd write (iout,'(i5,2f10.5)') k,uy(k,i),uz(k,i)
3733 cd write (iout,'(f10.5,2x,3f10.5,2x,3f10.5)')
3734 cd & uz(k,i),(uzgrad(k,l,1,i),l=1,3),(uzgrad(k,l,2,i),l=1,3)
3749 cd print '(a)','Enter EELEC'
3750 cd write (iout,*) 'iatel_s=',iatel_s,' iatel_e=',iatel_e
3752 gel_loc_loc(i)=0.0d0
3757 c 9/27/08 AL Split the interaction loop to ensure load balancing of turn terms
3759 C Loop over i,i+2 and i,i+3 pairs of the peptide groups
3761 C 14/01/2014 TURN3,TUNR4 does no go under periodic boundry condition
3762 do i=iturn3_start,iturn3_end
3764 C write(iout,*) "tu jest i",i
3765 if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
3766 C changes suggested by Ana to avoid out of bounds
3767 C Adam: Unnecessary: handled by iturn3_end and iturn3_start
3768 c & .or.((i+4).gt.nres)
3769 c & .or.((i-1).le.0)
3770 C end of changes by Ana
3771 & .or. itype(i+2).eq.ntyp1
3772 & .or. itype(i+3).eq.ntyp1) cycle
3773 C Adam: Instructions below will switch off existing interactions
3775 c if(itype(i-1).eq.ntyp1)cycle
3777 c if(i.LT.nres-3)then
3778 c if (itype(i+4).eq.ntyp1) cycle
3783 dx_normi=dc_norm(1,i)
3784 dy_normi=dc_norm(2,i)
3785 dz_normi=dc_norm(3,i)
3786 xmedi=c(1,i)+0.5d0*dxi
3787 ymedi=c(2,i)+0.5d0*dyi
3788 zmedi=c(3,i)+0.5d0*dzi
3789 xmedi=mod(xmedi,boxxsize)
3790 if (xmedi.lt.0) xmedi=xmedi+boxxsize
3791 ymedi=mod(ymedi,boxysize)
3792 if (ymedi.lt.0) ymedi=ymedi+boxysize
3793 zmedi=mod(zmedi,boxzsize)
3794 if (zmedi.lt.0) zmedi=zmedi+boxzsize
3796 call eelecij(i,i+2,ees,evdw1,eel_loc)
3797 if (wturn3.gt.0.0d0) call eturn3(i,eello_turn3)
3799 num_cont_hb(i)=num_conti
3802 do i=iturn4_start,iturn4_end
3804 if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
3805 C changes suggested by Ana to avoid out of bounds
3806 c & .or.((i+5).gt.nres)
3807 c & .or.((i-1).le.0)
3808 C end of changes suggested by Ana
3809 & .or. itype(i+3).eq.ntyp1
3810 & .or. itype(i+4).eq.ntyp1
3811 c & .or. itype(i+5).eq.ntyp1
3812 c & .or. itype(i).eq.ntyp1
3813 c & .or. itype(i-1).eq.ntyp1
3818 dx_normi=dc_norm(1,i)
3819 dy_normi=dc_norm(2,i)
3820 dz_normi=dc_norm(3,i)
3821 xmedi=c(1,i)+0.5d0*dxi
3822 ymedi=c(2,i)+0.5d0*dyi
3823 zmedi=c(3,i)+0.5d0*dzi
3824 C Return atom into box, boxxsize is size of box in x dimension
3826 c if (xmedi.gt.((0.5d0)*boxxsize)) xmedi=xmedi-boxxsize
3827 c if (xmedi.lt.((-0.5d0)*boxxsize)) xmedi=xmedi+boxxsize
3828 C Condition for being inside the proper box
3829 c if ((xmedi.gt.((0.5d0)*boxxsize)).or.
3830 c & (xmedi.lt.((-0.5d0)*boxxsize))) then
3834 c if (ymedi.gt.((0.5d0)*boxysize)) ymedi=ymedi-boxysize
3835 c if (ymedi.lt.((-0.5d0)*boxysize)) ymedi=ymedi+boxysize
3836 C Condition for being inside the proper box
3837 c if ((ymedi.gt.((0.5d0)*boxysize)).or.
3838 c & (ymedi.lt.((-0.5d0)*boxysize))) then
3842 c if (zmedi.gt.((0.5d0)*boxzsize)) zmedi=zmedi-boxzsize
3843 c if (zmedi.lt.((-0.5d0)*boxzsize)) zmedi=zmedi+boxzsize
3844 C Condition for being inside the proper box
3845 c if ((zmedi.gt.((0.5d0)*boxzsize)).or.
3846 c & (zmedi.lt.((-0.5d0)*boxzsize))) then
3849 xmedi=mod(xmedi,boxxsize)
3850 if (xmedi.lt.0) xmedi=xmedi+boxxsize
3851 ymedi=mod(ymedi,boxysize)
3852 if (ymedi.lt.0) ymedi=ymedi+boxysize
3853 zmedi=mod(zmedi,boxzsize)
3854 if (zmedi.lt.0) zmedi=zmedi+boxzsize
3857 num_conti=num_cont_hb(i)
3859 c write(iout,*) "JESTEM W PETLI"
3860 call eelecij(i,i+3,ees,evdw1,eel_loc)
3861 if (wturn4.gt.0.0d0 .and. itype(i+2).ne.ntyp1)
3862 & call eturn4(i,eello_turn4)
3864 num_cont_hb(i)=num_conti
3867 C Loop over all neighbouring boxes
3872 c Loop over all pairs of interacting peptide groups except i,i+2 and i,i+3
3875 c do i=iatel_s,iatel_e
3876 do icont=g_listpp_start,g_listpp_end
3877 i=newcontlistppi(icont)
3878 j=newcontlistppj(icont)
3881 if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1
3882 C changes suggested by Ana to avoid out of bounds
3883 c & .or.((i+2).gt.nres)
3884 c & .or.((i-1).le.0)
3885 C end of changes by Ana
3886 c & .or. itype(i+2).eq.ntyp1
3887 c & .or. itype(i-1).eq.ntyp1
3892 dx_normi=dc_norm(1,i)
3893 dy_normi=dc_norm(2,i)
3894 dz_normi=dc_norm(3,i)
3895 xmedi=c(1,i)+0.5d0*dxi
3896 ymedi=c(2,i)+0.5d0*dyi
3897 zmedi=c(3,i)+0.5d0*dzi
3898 xmedi=mod(xmedi,boxxsize)
3899 if (xmedi.lt.0) xmedi=xmedi+boxxsize
3900 ymedi=mod(ymedi,boxysize)
3901 if (ymedi.lt.0) ymedi=ymedi+boxysize
3902 zmedi=mod(zmedi,boxzsize)
3903 if (zmedi.lt.0) zmedi=zmedi+boxzsize
3904 C xmedi=xmedi+xshift*boxxsize
3905 C ymedi=ymedi+yshift*boxysize
3906 C zmedi=zmedi+zshift*boxzsize
3908 C Return tom into box, boxxsize is size of box in x dimension
3910 c if (xmedi.gt.((xshift+0.5d0)*boxxsize)) xmedi=xmedi-boxxsize
3911 c if (xmedi.lt.((xshift-0.5d0)*boxxsize)) xmedi=xmedi+boxxsize
3912 C Condition for being inside the proper box
3913 c if ((xmedi.gt.((xshift+0.5d0)*boxxsize)).or.
3914 c & (xmedi.lt.((xshift-0.5d0)*boxxsize))) then
3918 c if (ymedi.gt.((yshift+0.5d0)*boxysize)) ymedi=ymedi-boxysize
3919 c if (ymedi.lt.((yshift-0.5d0)*boxysize)) ymedi=ymedi+boxysize
3920 C Condition for being inside the proper box
3921 c if ((ymedi.gt.((yshift+0.5d0)*boxysize)).or.
3922 c & (ymedi.lt.((yshift-0.5d0)*boxysize))) then
3926 c if (zmedi.gt.((zshift+0.5d0)*boxzsize)) zmedi=zmedi-boxzsize
3927 c if (zmedi.lt.((zshift-0.5d0)*boxzsize)) zmedi=zmedi+boxzsize
3928 cC Condition for being inside the proper box
3929 c if ((zmedi.gt.((zshift+0.5d0)*boxzsize)).or.
3930 c & (zmedi.lt.((zshift-0.5d0)*boxzsize))) then
3934 c write (iout,*) 'i',i,' ielstart',ielstart(i),' ielend',ielend(i)
3936 num_conti=num_cont_hb(i)
3939 c do j=ielstart(i),ielend(i)
3941 C write (iout,*) i,j
3943 if (itype(j).eq.ntyp1.or. itype(j+1).eq.ntyp1
3944 C changes suggested by Ana to avoid out of bounds
3945 c & .or.((j+2).gt.nres)
3946 c & .or.((j-1).le.0)
3947 C end of changes by Ana
3948 c & .or.itype(j+2).eq.ntyp1
3949 c & .or.itype(j-1).eq.ntyp1
3951 call eelecij(i,j,ees,evdw1,eel_loc)
3954 num_cont_hb(i)=num_conti
3961 c write (iout,*) "Number of loop steps in EELEC:",ind
3963 cd write (iout,'(i3,3f10.5,5x,3f10.5)')
3964 cd & i,(gel_loc(k,i),k=1,3),gel_loc_loc(i)
3966 c 12/7/99 Adam eello_turn3 will be considered as a separate energy term
3967 ccc eel_loc=eel_loc+eello_turn3
3968 cd print *,"Processor",fg_rank," t_eelecij",t_eelecij
3971 C-------------------------------------------------------------------------------
3972 subroutine eelecij(i,j,ees,evdw1,eel_loc)
3974 include 'DIMENSIONS'
3978 include 'COMMON.CONTROL'
3979 include 'COMMON.IOUNITS'
3980 include 'COMMON.GEO'
3981 include 'COMMON.VAR'
3982 include 'COMMON.LOCAL'
3983 include 'COMMON.CHAIN'
3984 include 'COMMON.DERIV'
3985 include 'COMMON.INTERACT'
3987 include 'COMMON.CONTACTS'
3988 include 'COMMON.CONTMAT'
3990 include 'COMMON.CORRMAT'
3991 include 'COMMON.TORSION'
3992 include 'COMMON.VECTORS'
3993 include 'COMMON.FFIELD'
3994 include 'COMMON.TIME1'
3995 include 'COMMON.SPLITELE'
3996 include 'COMMON.SHIELD'
3997 double precision ggg(3),gggp(3),gggm(3),erij(3),dcosb(3),dcosg(3),
3998 & erder(3,3),uryg(3,3),urzg(3,3),vryg(3,3),vrzg(3,3)
3999 double precision acipa(2,2),agg(3,4),aggi(3,4),aggi1(3,4),
4000 & aggj(3,4),aggj1(3,4),a_temp(2,2),muij(4),gmuij1(4),gmuji1(4),
4001 & gmuij2(4),gmuji2(4)
4002 double precision dxi,dyi,dzi
4003 double precision dx_normi,dy_normi,dz_normi,aux
4004 integer j1,j2,lll,num_conti
4005 common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
4006 & dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
4008 integer k,i,j,iteli,itelj,kkk,l,kkll,m,isubchap,ilist,iresshield
4009 double precision ael6i,rrmij,rmij,r0ij,fcont,fprimcont,ees0tmp
4010 double precision ees,evdw1,eel_loc,aaa,bbb,ael3i
4011 double precision dxj,dyj,dzj,dx_normj,dy_normj,dz_normj,xj,yj,zj,
4012 & rij,r3ij,r6ij,cosa,cosb,cosg,fac,ev1,ev2,fac3,fac4,
4013 & evdwij,el1,el2,eesij,ees0ij,facvdw,facel,fac1,ecosa,
4014 & ecosb,ecosg,ury,urz,vry,vrz,facr,a22der,a23der,a32der,
4015 & a33der,eel_loc_ij,cosa4,wij,cosbg1,cosbg2,ees0pij,
4016 & ees0pij1,ees0mij,ees0mij1,fac3p,ees0mijp,ees0pijp,
4017 & ecosa1,ecosb1,ecosg1,ecosa2,ecosb2,ecosg2,ecosap,ecosbp,
4018 & ecosgp,ecosam,ecosbm,ecosgm,ghalf,rlocshield
4019 double precision a22,a23,a32,a33,geel_loc_ij,geel_loc_ji
4020 double precision dist_init,xj_safe,yj_safe,zj_safe,
4021 & xj_temp,yj_temp,zj_temp,dist_temp,xmedi,ymedi,zmedi
4022 double precision sscale,sscagrad,scalar
4024 c 4/26/02 - AL scaling factor for 1,4 repulsive VDW interactions
4026 double precision scal_el /1.0d0/
4028 double precision scal_el /0.5d0/
4031 C 13-go grudnia roku pamietnego...
4032 double precision unmat(3,3) /1.0d0,0.0d0,0.0d0,
4033 & 0.0d0,1.0d0,0.0d0,
4034 & 0.0d0,0.0d0,1.0d0/
4035 integer xshift,yshift,zshift
4036 c time00=MPI_Wtime()
4037 cd write (iout,*) "eelecij",i,j
4041 if (j.eq.i+2 .and. itelj.eq.2) iteli=2
4042 aaa=app(iteli,itelj)
4043 bbb=bpp(iteli,itelj)
4044 ael6i=ael6(iteli,itelj)
4045 ael3i=ael3(iteli,itelj)
4049 dx_normj=dc_norm(1,j)
4050 dy_normj=dc_norm(2,j)
4051 dz_normj=dc_norm(3,j)
4052 C xj=c(1,j)+0.5D0*dxj-xmedi
4053 C yj=c(2,j)+0.5D0*dyj-ymedi
4054 C zj=c(3,j)+0.5D0*dzj-zmedi
4059 if (xj.lt.0) xj=xj+boxxsize
4061 if (yj.lt.0) yj=yj+boxysize
4063 if (zj.lt.0) zj=zj+boxzsize
4064 if ((zj.lt.0).or.(xj.lt.0).or.(yj.lt.0)) write (*,*) "CHUJ"
4065 dist_init=(xj-xmedi)**2+(yj-ymedi)**2+(zj-zmedi)**2
4073 xj=xj_safe+xshift*boxxsize
4074 yj=yj_safe+yshift*boxysize
4075 zj=zj_safe+zshift*boxzsize
4076 dist_temp=(xj-xmedi)**2+(yj-ymedi)**2+(zj-zmedi)**2
4077 if(dist_temp.lt.dist_init) then
4087 if (isubchap.eq.1) then
4096 C if ((i+3).lt.j) then !this condition keeps for turn3 and turn4 not subject to PBC
4098 c if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
4099 c if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
4100 C Condition for being inside the proper box
4101 c if ((xj.gt.((0.5d0)*boxxsize)).or.
4102 c & (xj.lt.((-0.5d0)*boxxsize))) then
4106 c if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
4107 c if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
4108 C Condition for being inside the proper box
4109 c if ((yj.gt.((0.5d0)*boxysize)).or.
4110 c & (yj.lt.((-0.5d0)*boxysize))) then
4114 c if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxzsize
4115 c if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxzsize
4116 C Condition for being inside the proper box
4117 c if ((zj.gt.((0.5d0)*boxzsize)).or.
4118 c & (zj.lt.((-0.5d0)*boxzsize))) then
4121 C endif !endPBC condintion
4125 rij=xj*xj+yj*yj+zj*zj
4127 sss=sscale(dsqrt(rij),r_cut_int)
4128 if (sss.eq.0.0d0) return
4129 sssgrad=sscagrad(dsqrt(rij),r_cut_int)
4130 c if (sss.gt.0.0d0) then
4136 cosa=dx_normi*dx_normj+dy_normi*dy_normj+dz_normi*dz_normj
4137 cosb=(xj*dx_normi+yj*dy_normi+zj*dz_normi)*rmij
4138 cosg=(xj*dx_normj+yj*dy_normj+zj*dz_normj)*rmij
4139 fac=cosa-3.0D0*cosb*cosg
4141 c 4/26/02 - AL scaling down 1,4 repulsive VDW interactions
4142 if (j.eq.i+2) ev1=scal_el*ev1
4147 el1=fac3*(4.0D0+fac*fac-3.0D0*(cosb*cosb+cosg*cosg))
4151 C 12/26/95 - for the evaluation of multi-body H-bonding interactions
4152 ees0ij=4.0D0+fac*fac-3.0D0*(cosb*cosb+cosg*cosg)
4153 if (shield_mode.gt.0) then
4156 el1=el1*fac_shield(i)**2*fac_shield(j)**2
4157 el2=el2*fac_shield(i)**2*fac_shield(j)**2
4166 evdw1=evdw1+evdwij*sss
4167 cd write(iout,'(2(2i3,2x),7(1pd12.4)/2(3(1pd12.4),5x)/)')
4168 cd & iteli,i,itelj,j,aaa,bbb,ael6i,ael3i,
4169 cd & 1.0D0/dsqrt(rrmij),evdwij,eesij,
4170 cd & xmedi,ymedi,zmedi,xj,yj,zj
4172 if (energy_dec) then
4173 write (iout,'(a6,2i5,0pf7.3,2i5,e11.3,3f10.5)')
4174 & 'evdw1',i,j,evdwij,iteli,itelj,aaa,evdw1,sss,rij
4175 write (iout,'(a6,2i5,0pf7.3,2f8.3)') 'ees',i,j,eesij,
4176 & fac_shield(i),fac_shield(j)
4180 C Calculate contributions to the Cartesian gradient.
4183 facvdw=-6*rrmij*(ev1+evdwij)*sss
4184 facel=-3*rrmij*(el1+eesij)
4191 * Radial derivatives. First process both termini of the fragment (i,j)
4193 aux=facel*sss+rmij*sssgrad*eesij
4197 if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
4198 & (shield_mode.gt.0)) then
4200 do ilist=1,ishield_list(i)
4201 iresshield=shield_list(ilist,i)
4203 rlocshield=grad_shield_side(k,ilist,i)*eesij/fac_shield(i)
4205 gshieldx(k,iresshield)=gshieldx(k,iresshield)+
4207 & +grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)*2.0
4208 gshieldc(k,iresshield-1)=gshieldc(k,iresshield-1)+rlocshield
4209 C gshieldc_loc(k,iresshield)=gshieldc_loc(k,iresshield)
4210 C & +grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)
4211 C if (iresshield.gt.i) then
4212 C do ishi=i+1,iresshield-1
4213 C gshieldc(k,ishi)=gshieldc(k,ishi)+rlocshield
4214 C & +grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)
4218 C do ishi=iresshield,i
4219 C gshieldc(k,ishi)=gshieldc(k,ishi)-rlocshield
4220 C & -grad_shield_loc(k,ilist,i)*eesij/fac_shield(i)
4226 do ilist=1,ishield_list(j)
4227 iresshield=shield_list(ilist,j)
4229 rlocshield=grad_shield_side(k,ilist,j)*eesij/fac_shield(j)
4231 gshieldx(k,iresshield)=gshieldx(k,iresshield)+
4233 & +grad_shield_loc(k,ilist,j)*eesij/fac_shield(j)*2.0*sss
4234 gshieldc(k,iresshield-1)=gshieldc(k,iresshield-1)+rlocshield
4236 C & +grad_shield_loc(k,ilist,j)*eesij/fac_shield(j)
4237 C gshieldc_loc(k,iresshield)=gshieldc_loc(k,iresshield)
4238 C & +grad_shield_loc(k,ilist,j)*eesij/fac_shield(j)
4239 C if (iresshield.gt.j) then
4240 C do ishi=j+1,iresshield-1
4241 C gshieldc(k,ishi)=gshieldc(k,ishi)+rlocshield
4242 C & +grad_shield_loc(k,ilist,j)*eesij/fac_shield(j)
4246 C do ishi=iresshield,j
4247 C gshieldc(k,ishi)=gshieldc(k,ishi)-rlocshield
4248 C & -grad_shield_loc(k,ilist,j)*eesij/fac_shield(j)
4255 gshieldc(k,i)=gshieldc(k,i)+
4256 & grad_shield(k,i)*eesij/fac_shield(i)*2.0*sss
4257 gshieldc(k,j)=gshieldc(k,j)+
4258 & grad_shield(k,j)*eesij/fac_shield(j)*2.0*sss
4259 gshieldc(k,i-1)=gshieldc(k,i-1)+
4260 & grad_shield(k,i)*eesij/fac_shield(i)*2.0*sss
4261 gshieldc(k,j-1)=gshieldc(k,j-1)+
4262 & grad_shield(k,j)*eesij/fac_shield(j)*2.0*sss
4267 c ghalf=0.5D0*ggg(k)
4268 c gelc(k,i)=gelc(k,i)+ghalf
4269 c gelc(k,j)=gelc(k,j)+ghalf
4271 c 9/28/08 AL Gradient compotents will be summed only at the end
4272 C print *,"before", gelc_long(1,i), gelc_long(1,j)
4274 gelc_long(k,j)=gelc_long(k,j)+ggg(k)
4275 C & +grad_shield(k,j)*eesij/fac_shield(j)
4276 gelc_long(k,i)=gelc_long(k,i)-ggg(k)
4277 C & +grad_shield(k,i)*eesij/fac_shield(i)
4278 C gelc_long(k,i-1)=gelc_long(k,i-1)
4279 C & +grad_shield(k,i)*eesij/fac_shield(i)
4280 C gelc_long(k,j-1)=gelc_long(k,j-1)
4281 C & +grad_shield(k,j)*eesij/fac_shield(j)
4283 C print *,"bafter", gelc_long(1,i), gelc_long(1,j)
4286 * Loop over residues i+1 thru j-1.
4290 cgrad gelc(l,k)=gelc(l,k)+ggg(l)
4293 facvdw=facvdw+sssgrad*rmij*evdwij
4298 c ghalf=0.5D0*ggg(k)
4299 c gvdwpp(k,i)=gvdwpp(k,i)+ghalf
4300 c gvdwpp(k,j)=gvdwpp(k,j)+ghalf
4302 c 9/28/08 AL Gradient compotents will be summed only at the end
4304 gvdwpp(k,j)=gvdwpp(k,j)+ggg(k)
4305 gvdwpp(k,i)=gvdwpp(k,i)-ggg(k)
4308 * Loop over residues i+1 thru j-1.
4312 cgrad gvdwpp(l,k)=gvdwpp(l,k)+ggg(l)
4320 fac=-3*rrmij*(facvdw+facvdw+facel)*sss
4321 & +(evdwij+eesij)*sssgrad*rrmij
4326 * Radial derivatives. First process both termini of the fragment (i,j)
4329 C+eesij*grad_shield(1,i)+eesij*grad_shield(1,j)
4331 C+eesij*grad_shield(2,i)+eesij*grad_shield(2,j)
4333 C+eesij*grad_shield(3,i)+eesij*grad_shield(3,j)
4335 c ghalf=0.5D0*ggg(k)
4336 c gelc(k,i)=gelc(k,i)+ghalf
4337 c gelc(k,j)=gelc(k,j)+ghalf
4339 c 9/28/08 AL Gradient compotents will be summed only at the end
4341 gelc_long(k,j)=gelc(k,j)+ggg(k)
4342 gelc_long(k,i)=gelc(k,i)-ggg(k)
4345 * Loop over residues i+1 thru j-1.
4349 cgrad gelc(l,k)=gelc(l,k)+ggg(l)
4352 c 9/28/08 AL Gradient compotents will be summed only at the end
4353 ggg(1)=facvdw*xj+sssgrad*rmij*evdwij*xj
4354 ggg(2)=facvdw*yj+sssgrad*rmij*evdwij*yj
4355 ggg(3)=facvdw*zj+sssgrad*rmij*evdwij*zj
4357 gvdwpp(k,j)=gvdwpp(k,j)+ggg(k)
4358 gvdwpp(k,i)=gvdwpp(k,i)-ggg(k)
4364 ecosa=2.0D0*fac3*fac1+fac4
4367 ecosb=(fac3*(fac1*cosg+cosb)+cosg*fac4)
4368 ecosg=(fac3*(fac1*cosb+cosg)+cosb*fac4)
4370 dcosb(k)=rmij*(dc_norm(k,i)-erij(k)*cosb)
4371 dcosg(k)=rmij*(dc_norm(k,j)-erij(k)*cosg)
4373 cd print '(2i3,2(3(1pd14.5),3x))',i,j,(dcosb(k),k=1,3),
4374 cd & (dcosg(k),k=1,3)
4376 ggg(k)=(ecosb*dcosb(k)+ecosg*dcosg(k))*
4377 & fac_shield(i)**2*fac_shield(j)**2*sss
4380 c ghalf=0.5D0*ggg(k)
4381 c gelc(k,i)=gelc(k,i)+ghalf
4382 c & +(ecosa*(dc_norm(k,j)-cosa*dc_norm(k,i))
4383 c & + ecosb*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
4384 c gelc(k,j)=gelc(k,j)+ghalf
4385 c & +(ecosa*(dc_norm(k,i)-cosa*dc_norm(k,j))
4386 c & + ecosg*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
4390 cgrad gelc(l,k)=gelc(l,k)+ggg(l)
4393 C print *,"before22", gelc_long(1,i), gelc_long(1,j)
4396 & +((ecosa*(dc_norm(k,j)-cosa*dc_norm(k,i))
4397 & + ecosb*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1))*sss
4398 & *fac_shield(i)**2*fac_shield(j)**2
4400 & +((ecosa*(dc_norm(k,i)-cosa*dc_norm(k,j))
4401 & + ecosg*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1))*sss
4402 & *fac_shield(i)**2*fac_shield(j)**2
4403 gelc_long(k,j)=gelc_long(k,j)+ggg(k)
4404 gelc_long(k,i)=gelc_long(k,i)-ggg(k)
4406 C print *,"before33", gelc_long(1,i), gelc_long(1,j)
4410 IF (wel_loc.gt.0.0d0 .or. wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0
4411 & .or. wcorr6.gt.0.0d0 .or. wturn3.gt.0.0d0
4412 & .or. wturn4.gt.0.0d0 .or. wturn6.gt.0.0d0) THEN
4414 C 9/25/99 Mixed third-order local-electrostatic terms. The local-interaction
4415 C energy of a peptide unit is assumed in the form of a second-order
4416 C Fourier series in the angles lambda1 and lambda2 (see Nishikawa et al.
4417 C Macromolecules, 1974, 7, 797-806 for definition). This correlation terms
4418 C are computed for EVERY pair of non-contiguous peptide groups.
4421 if (j.lt.nres-1) then
4433 muij(kkk)=mu(k,i)*mu(l,j)
4434 c write(iout,*) 'mumu=', mu(k,i),mu(l,j),i,j,k,l
4436 gmuij1(kkk)=gtb1(k,i+1)*mu(l,j)
4437 c write(iout,*) 'k=',k,i,gtb1(k,i+1),gtb1(k,i+1)*mu(l,j)
4438 gmuij2(kkk)=gUb2(k,i)*mu(l,j)
4439 gmuji1(kkk)=mu(k,i)*gtb1(l,j+1)
4440 c write(iout,*) 'l=',l,j,gtb1(l,j+1),gtb1(l,j+1)*mu(k,i)
4441 gmuji2(kkk)=mu(k,i)*gUb2(l,j)
4446 write (iout,*) 'EELEC: i',i,' j',j
4447 write (iout,*) 'j',j,' j1',j1,' j2',j2
4448 write(iout,*) 'muij',muij
4450 ury=scalar(uy(1,i),erij)
4451 urz=scalar(uz(1,i),erij)
4452 vry=scalar(uy(1,j),erij)
4453 vrz=scalar(uz(1,j),erij)
4454 a22=scalar(uy(1,i),uy(1,j))-3*ury*vry
4455 a23=scalar(uy(1,i),uz(1,j))-3*ury*vrz
4456 a32=scalar(uz(1,i),uy(1,j))-3*urz*vry
4457 a33=scalar(uz(1,i),uz(1,j))-3*urz*vrz
4458 fac=dsqrt(-ael6i)*r3ij
4460 write (iout,*) "ury",ury," urz",urz," vry",vry," vrz",vrz
4461 write (iout,*) "uyvy",scalar(uy(1,i),uy(1,j)),
4462 & "uyvz",scalar(uy(1,i),uz(1,j)),
4463 & "uzvy",scalar(uz(1,i),uy(1,j)),
4464 & "uzvz",scalar(uz(1,i),uz(1,j))
4465 write (iout,*) "a22",a22," a23",a23," a32",a32," a33",a33
4466 write (iout,*) "fac",fac
4473 write (iout,*) "a22",a22," a23",a23," a32",a32," a33",a33
4476 cd write (iout,'(4i5,4f10.5)')
4477 cd & i,itortyp(itype(i)),j,itortyp(itype(j)),a22,a23,a32,a33
4478 cd write (iout,'(6f10.5)') (muij(k),k=1,4),fac,eel_loc_ij
4479 cd write (iout,'(2(3f10.5,5x)/2(3f10.5,5x))') uy(:,i),uz(:,i),
4480 cd & uy(:,j),uz(:,j)
4481 cd write (iout,'(4f10.5)')
4482 cd & scalar(uy(1,i),uy(1,j)),scalar(uy(1,i),uz(1,j)),
4483 cd & scalar(uz(1,i),uy(1,j)),scalar(uz(1,i),uz(1,j))
4484 cd write (iout,'(4f10.5)') ury,urz,vry,vrz
4485 cd write (iout,'(9f10.5/)')
4486 cd & fac22,a22,fac23,a23,fac32,a32,fac33,a33,eel_loc_ij
4487 C Derivatives of the elements of A in virtual-bond vectors
4488 call unormderiv(erij(1),unmat(1,1),rmij,erder(1,1))
4490 uryg(k,1)=scalar(erder(1,k),uy(1,i))
4491 uryg(k,2)=scalar(uygrad(1,k,1,i),erij(1))
4492 uryg(k,3)=scalar(uygrad(1,k,2,i),erij(1))
4493 urzg(k,1)=scalar(erder(1,k),uz(1,i))
4494 urzg(k,2)=scalar(uzgrad(1,k,1,i),erij(1))
4495 urzg(k,3)=scalar(uzgrad(1,k,2,i),erij(1))
4496 vryg(k,1)=scalar(erder(1,k),uy(1,j))
4497 vryg(k,2)=scalar(uygrad(1,k,1,j),erij(1))
4498 vryg(k,3)=scalar(uygrad(1,k,2,j),erij(1))
4499 vrzg(k,1)=scalar(erder(1,k),uz(1,j))
4500 vrzg(k,2)=scalar(uzgrad(1,k,1,j),erij(1))
4501 vrzg(k,3)=scalar(uzgrad(1,k,2,j),erij(1))
4503 C Compute radial contributions to the gradient
4521 C Add the contributions coming from er
4524 agg(k,1)=agg(k,1)+fac3*(uryg(k,1)*vry+vryg(k,1)*ury)
4525 agg(k,2)=agg(k,2)+fac3*(uryg(k,1)*vrz+vrzg(k,1)*ury)
4526 agg(k,3)=agg(k,3)+fac3*(urzg(k,1)*vry+vryg(k,1)*urz)
4527 agg(k,4)=agg(k,4)+fac3*(urzg(k,1)*vrz+vrzg(k,1)*urz)
4530 C Derivatives in DC(i)
4531 cgrad ghalf1=0.5d0*agg(k,1)
4532 cgrad ghalf2=0.5d0*agg(k,2)
4533 cgrad ghalf3=0.5d0*agg(k,3)
4534 cgrad ghalf4=0.5d0*agg(k,4)
4535 aggi(k,1)=fac*(scalar(uygrad(1,k,1,i),uy(1,j))
4536 & -3.0d0*uryg(k,2)*vry)!+ghalf1
4537 aggi(k,2)=fac*(scalar(uygrad(1,k,1,i),uz(1,j))
4538 & -3.0d0*uryg(k,2)*vrz)!+ghalf2
4539 aggi(k,3)=fac*(scalar(uzgrad(1,k,1,i),uy(1,j))
4540 & -3.0d0*urzg(k,2)*vry)!+ghalf3
4541 aggi(k,4)=fac*(scalar(uzgrad(1,k,1,i),uz(1,j))
4542 & -3.0d0*urzg(k,2)*vrz)!+ghalf4
4543 C Derivatives in DC(i+1)
4544 aggi1(k,1)=fac*(scalar(uygrad(1,k,2,i),uy(1,j))
4545 & -3.0d0*uryg(k,3)*vry)!+agg(k,1)
4546 aggi1(k,2)=fac*(scalar(uygrad(1,k,2,i),uz(1,j))
4547 & -3.0d0*uryg(k,3)*vrz)!+agg(k,2)
4548 aggi1(k,3)=fac*(scalar(uzgrad(1,k,2,i),uy(1,j))
4549 & -3.0d0*urzg(k,3)*vry)!+agg(k,3)
4550 aggi1(k,4)=fac*(scalar(uzgrad(1,k,2,i),uz(1,j))
4551 & -3.0d0*urzg(k,3)*vrz)!+agg(k,4)
4552 C Derivatives in DC(j)
4553 aggj(k,1)=fac*(scalar(uygrad(1,k,1,j),uy(1,i))
4554 & -3.0d0*vryg(k,2)*ury)!+ghalf1
4555 aggj(k,2)=fac*(scalar(uzgrad(1,k,1,j),uy(1,i))
4556 & -3.0d0*vrzg(k,2)*ury)!+ghalf2
4557 aggj(k,3)=fac*(scalar(uygrad(1,k,1,j),uz(1,i))
4558 & -3.0d0*vryg(k,2)*urz)!+ghalf3
4559 aggj(k,4)=fac*(scalar(uzgrad(1,k,1,j),uz(1,i))
4560 & -3.0d0*vrzg(k,2)*urz)!+ghalf4
4561 C Derivatives in DC(j+1) or DC(nres-1)
4562 aggj1(k,1)=fac*(scalar(uygrad(1,k,2,j),uy(1,i))
4563 & -3.0d0*vryg(k,3)*ury)
4564 aggj1(k,2)=fac*(scalar(uzgrad(1,k,2,j),uy(1,i))
4565 & -3.0d0*vrzg(k,3)*ury)
4566 aggj1(k,3)=fac*(scalar(uygrad(1,k,2,j),uz(1,i))
4567 & -3.0d0*vryg(k,3)*urz)
4568 aggj1(k,4)=fac*(scalar(uzgrad(1,k,2,j),uz(1,i))
4569 & -3.0d0*vrzg(k,3)*urz)
4570 cgrad if (j.eq.nres-1 .and. i.lt.j-2) then
4572 cgrad aggj1(k,l)=aggj1(k,l)+agg(k,l)
4585 aggi(k,l)=-aggi(k,l)
4586 aggi1(k,l)=-aggi1(k,l)
4587 aggj(k,l)=-aggj(k,l)
4588 aggj1(k,l)=-aggj1(k,l)
4591 if (j.lt.nres-1) then
4597 aggi(k,l)=-aggi(k,l)
4598 aggi1(k,l)=-aggi1(k,l)
4599 aggj(k,l)=-aggj(k,l)
4600 aggj1(k,l)=-aggj1(k,l)
4611 aggi(k,l)=-aggi(k,l)
4612 aggi1(k,l)=-aggi1(k,l)
4613 aggj(k,l)=-aggj(k,l)
4614 aggj1(k,l)=-aggj1(k,l)
4619 IF (wel_loc.gt.0.0d0) THEN
4620 C Contribution to the local-electrostatic energy coming from the i-j pair
4621 eel_loc_ij=a22*muij(1)+a23*muij(2)+a32*muij(3)
4624 write (iout,*) "muij",muij," a22",a22," a23",a23," a32",a32,
4626 write (iout,*) "ij",i,j," eel_loc_ij",eel_loc_ij,
4627 & " wel_loc",wel_loc
4629 if (shield_mode.eq.0) then
4636 eel_loc_ij=eel_loc_ij
4637 & *fac_shield(i)*fac_shield(j)*sss
4638 c if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
4639 c & 'eelloc',i,j,eel_loc_ij
4640 C Now derivative over eel_loc
4641 if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
4642 & (shield_mode.gt.0)) then
4645 do ilist=1,ishield_list(i)
4646 iresshield=shield_list(ilist,i)
4648 rlocshield=grad_shield_side(k,ilist,i)*eel_loc_ij
4651 gshieldx_ll(k,iresshield)=gshieldx_ll(k,iresshield)+
4653 & +grad_shield_loc(k,ilist,i)*eel_loc_ij/fac_shield(i)
4654 gshieldc_ll(k,iresshield-1)=gshieldc_ll(k,iresshield-1)
4658 do ilist=1,ishield_list(j)
4659 iresshield=shield_list(ilist,j)
4661 rlocshield=grad_shield_side(k,ilist,j)*eel_loc_ij
4664 gshieldx_ll(k,iresshield)=gshieldx_ll(k,iresshield)+
4666 & +grad_shield_loc(k,ilist,j)*eel_loc_ij/fac_shield(j)
4667 gshieldc_ll(k,iresshield-1)=gshieldc_ll(k,iresshield-1)
4674 gshieldc_ll(k,i)=gshieldc_ll(k,i)+
4675 & grad_shield(k,i)*eel_loc_ij/fac_shield(i)
4676 gshieldc_ll(k,j)=gshieldc_ll(k,j)+
4677 & grad_shield(k,j)*eel_loc_ij/fac_shield(j)
4678 gshieldc_ll(k,i-1)=gshieldc_ll(k,i-1)+
4679 & grad_shield(k,i)*eel_loc_ij/fac_shield(i)
4680 gshieldc_ll(k,j-1)=gshieldc_ll(k,j-1)+
4681 & grad_shield(k,j)*eel_loc_ij/fac_shield(j)
4686 c write (iout,*) 'i',i,' j',j,itype(i),itype(j),
4687 c & ' eel_loc_ij',eel_loc_ij
4688 C write(iout,*) 'muije=',i,j,muij(1),muij(2),muij(3),muij(4)
4689 C Calculate patrial derivative for theta angle
4691 geel_loc_ij=(a22*gmuij1(1)
4695 & *fac_shield(i)*fac_shield(j)*sss
4696 c write(iout,*) "derivative over thatai"
4697 c write(iout,*) a22*gmuij1(1), a23*gmuij1(2) ,a32*gmuij1(3),
4699 gloc(nphi+i,icg)=gloc(nphi+i,icg)+
4700 & geel_loc_ij*wel_loc
4701 c write(iout,*) "derivative over thatai-1"
4702 c write(iout,*) a22*gmuij2(1), a23*gmuij2(2) ,a32*gmuij2(3),
4709 gloc(nphi+i-1,icg)=gloc(nphi+i-1,icg)+
4710 & geel_loc_ij*wel_loc
4711 & *fac_shield(i)*fac_shield(j)*sss
4713 c Derivative over j residue
4714 geel_loc_ji=a22*gmuji1(1)
4718 c write(iout,*) "derivative over thataj"
4719 c write(iout,*) a22*gmuji1(1), a23*gmuji1(2) ,a32*gmuji1(3),
4722 gloc(nphi+j,icg)=gloc(nphi+j,icg)+
4723 & geel_loc_ji*wel_loc
4724 & *fac_shield(i)*fac_shield(j)*sss
4731 c write(iout,*) "derivative over thataj-1"
4732 c write(iout,*) a22*gmuji2(1), a23*gmuji2(2) ,a32*gmuji2(3),
4734 gloc(nphi+j-1,icg)=gloc(nphi+j-1,icg)+
4735 & geel_loc_ji*wel_loc
4736 & *fac_shield(i)*fac_shield(j)*sss
4738 cd write (iout,*) 'i',i,' j',j,' eel_loc_ij',eel_loc_ij
4740 if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
4741 & 'eelloc',i,j,eel_loc_ij
4742 c if (eel_loc_ij.ne.0)
4743 c & write (iout,'(a4,2i4,8f9.5)')'chuj',
4744 c & i,j,a22,muij(1),a23,muij(2),a32,muij(3),a33,muij(4)
4746 eel_loc=eel_loc+eel_loc_ij
4747 C Partial derivatives in virtual-bond dihedral angles gamma
4749 & gel_loc_loc(i-1)=gel_loc_loc(i-1)+
4750 & (a22*muder(1,i)*mu(1,j)+a23*muder(1,i)*mu(2,j)
4751 & +a32*muder(2,i)*mu(1,j)+a33*muder(2,i)*mu(2,j))
4752 & *fac_shield(i)*fac_shield(j)*sss
4754 gel_loc_loc(j-1)=gel_loc_loc(j-1)+
4755 & (a22*mu(1,i)*muder(1,j)+a23*mu(1,i)*muder(2,j)
4756 & +a32*mu(2,i)*muder(1,j)+a33*mu(2,i)*muder(2,j))
4757 & *fac_shield(i)*fac_shield(j)*sss
4758 C Derivatives of eello in DC(i+1) thru DC(j-1) or DC(nres-2)
4759 aux=eel_loc_ij/sss*sssgrad*rmij
4764 ggg(l)=ggg(l)+(agg(l,1)*muij(1)+
4765 & agg(l,2)*muij(2)+agg(l,3)*muij(3)+agg(l,4)*muij(4))
4766 & *fac_shield(i)*fac_shield(j)*sss
4767 gel_loc_long(l,j)=gel_loc_long(l,j)+ggg(l)
4768 gel_loc_long(l,i)=gel_loc_long(l,i)-ggg(l)
4769 cgrad ghalf=0.5d0*ggg(l)
4770 cgrad gel_loc(l,i)=gel_loc(l,i)+ghalf
4771 cgrad gel_loc(l,j)=gel_loc(l,j)+ghalf
4775 cgrad gel_loc(l,k)=gel_loc(l,k)+ggg(l)
4778 C Remaining derivatives of eello
4780 gel_loc(l,i)=gel_loc(l,i)+(aggi(l,1)*muij(1)+
4781 & aggi(l,2)*muij(2)+aggi(l,3)*muij(3)+aggi(l,4)*muij(4))
4782 & *fac_shield(i)*fac_shield(j)*sss
4784 gel_loc(l,i+1)=gel_loc(l,i+1)+(aggi1(l,1)*muij(1)+
4785 & aggi1(l,2)*muij(2)+aggi1(l,3)*muij(3)+aggi1(l,4)*muij(4))
4786 & *fac_shield(i)*fac_shield(j)*sss
4788 gel_loc(l,j)=gel_loc(l,j)+(aggj(l,1)*muij(1)+
4789 & aggj(l,2)*muij(2)+aggj(l,3)*muij(3)+aggj(l,4)*muij(4))
4790 & *fac_shield(i)*fac_shield(j)*sss
4792 gel_loc(l,j1)=gel_loc(l,j1)+(aggj1(l,1)*muij(1)+
4793 & aggj1(l,2)*muij(2)+aggj1(l,3)*muij(3)+aggj1(l,4)*muij(4))
4794 & *fac_shield(i)*fac_shield(j)*sss
4798 C Change 12/26/95 to calculate four-body contributions to H-bonding energy
4799 c if (j.gt.i+1 .and. num_conti.le.maxconts) then
4801 if (wcorr+wcorr4+wcorr5+wcorr6.gt.0.0d0
4802 & .and. num_conti.le.maxconts) then
4803 c write (iout,*) i,j," entered corr"
4805 C Calculate the contact function. The ith column of the array JCONT will
4806 C contain the numbers of atoms that make contacts with the atom I (of numbers
4807 C greater than I). The arrays FACONT and GACONT will contain the values of
4808 C the contact function and its derivative.
4809 c r0ij=1.02D0*rpp(iteli,itelj)
4810 c r0ij=1.11D0*rpp(iteli,itelj)
4811 r0ij=2.20D0*rpp(iteli,itelj)
4812 c r0ij=1.55D0*rpp(iteli,itelj)
4813 call gcont(rij,r0ij,1.0D0,0.2d0*r0ij,fcont,fprimcont)
4814 if (fcont.gt.0.0D0) then
4815 num_conti=num_conti+1
4816 if (num_conti.gt.maxconts) then
4817 write (iout,*) 'WARNING - max. # of contacts exceeded;',
4818 & ' will skip next contacts for this conf.'
4820 jcont_hb(num_conti,i)=j
4821 cd write (iout,*) "i",i," j",j," num_conti",num_conti,
4822 cd & " jcont_hb",jcont_hb(num_conti,i)
4823 IF (wcorr4.gt.0.0d0 .or. wcorr5.gt.0.0d0 .or.
4824 & wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0) THEN
4825 C 9/30/99 (AL) - store components necessary to evaluate higher-order loc-el
4827 d_cont(num_conti,i)=rij
4828 cd write (2,'(3e15.5)') rij,r0ij+0.2d0*r0ij,rij
4829 C --- Electrostatic-interaction matrix ---
4830 a_chuj(1,1,num_conti,i)=a22
4831 a_chuj(1,2,num_conti,i)=a23
4832 a_chuj(2,1,num_conti,i)=a32
4833 a_chuj(2,2,num_conti,i)=a33
4834 C --- Gradient of rij
4836 grij_hb_cont(kkk,num_conti,i)=erij(kkk)
4843 a_chuj_der(k,l,m,1,num_conti,i)=agg(m,kkll)
4844 a_chuj_der(k,l,m,2,num_conti,i)=aggi(m,kkll)
4845 a_chuj_der(k,l,m,3,num_conti,i)=aggi1(m,kkll)
4846 a_chuj_der(k,l,m,4,num_conti,i)=aggj(m,kkll)
4847 a_chuj_der(k,l,m,5,num_conti,i)=aggj1(m,kkll)
4852 IF (wcorr4.eq.0.0d0 .and. wcorr.gt.0.0d0) THEN
4853 C Calculate contact energies
4855 wij=cosa-3.0D0*cosb*cosg
4858 c fac3=dsqrt(-ael6i)/r0ij**3
4859 fac3=dsqrt(-ael6i)*r3ij
4860 c ees0pij=dsqrt(4.0D0+cosa4+wij*wij-3.0D0*cosbg1*cosbg1)
4861 ees0tmp=4.0D0+cosa4+wij*wij-3.0D0*cosbg1*cosbg1
4862 if (ees0tmp.gt.0) then
4863 ees0pij=dsqrt(ees0tmp)
4867 c ees0mij=dsqrt(4.0D0-cosa4+wij*wij-3.0D0*cosbg2*cosbg2)
4868 ees0tmp=4.0D0-cosa4+wij*wij-3.0D0*cosbg2*cosbg2
4869 if (ees0tmp.gt.0) then
4870 ees0mij=dsqrt(ees0tmp)
4875 if (shield_mode.eq.0) then
4879 ees0plist(num_conti,i)=j
4880 C fac_shield(i)=0.4d0
4881 C fac_shield(j)=0.6d0
4883 ees0p(num_conti,i)=0.5D0*fac3*(ees0pij+ees0mij)
4884 & *fac_shield(i)*fac_shield(j)*sss
4885 ees0m(num_conti,i)=0.5D0*fac3*(ees0pij-ees0mij)
4886 & *fac_shield(i)*fac_shield(j)*sss
4887 C Diagnostics. Comment out or remove after debugging!
4888 c ees0p(num_conti,i)=0.5D0*fac3*ees0pij
4889 c ees0m(num_conti,i)=0.5D0*fac3*ees0mij
4890 c ees0m(num_conti,i)=0.0D0
4892 c write (iout,*) 'i=',i,' j=',j,' rij=',rij,' r0ij=',r0ij,
4893 c & ' ees0ij=',ees0p(num_conti,i),ees0m(num_conti,i),' fcont=',fcont
4894 C Angular derivatives of the contact function
4895 ees0pij1=fac3/ees0pij
4896 ees0mij1=fac3/ees0mij
4897 fac3p=-3.0D0*fac3*rrmij
4898 ees0pijp=0.5D0*fac3p*(ees0pij+ees0mij)
4899 ees0mijp=0.5D0*fac3p*(ees0pij-ees0mij)
4901 ecosa1= ees0pij1*( 1.0D0+0.5D0*wij)
4902 ecosb1=-1.5D0*ees0pij1*(wij*cosg+cosbg1)
4903 ecosg1=-1.5D0*ees0pij1*(wij*cosb+cosbg1)
4904 ecosa2= ees0mij1*(-1.0D0+0.5D0*wij)
4905 ecosb2=-1.5D0*ees0mij1*(wij*cosg+cosbg2)
4906 ecosg2=-1.5D0*ees0mij1*(wij*cosb-cosbg2)
4907 ecosap=ecosa1+ecosa2
4908 ecosbp=ecosb1+ecosb2
4909 ecosgp=ecosg1+ecosg2
4910 ecosam=ecosa1-ecosa2
4911 ecosbm=ecosb1-ecosb2
4912 ecosgm=ecosg1-ecosg2
4921 facont_hb(num_conti,i)=fcont
4922 fprimcont=fprimcont/rij
4923 cd facont_hb(num_conti,i)=1.0D0
4924 C Following line is for diagnostics.
4927 dcosb(k)=rmij*(dc_norm(k,i)-erij(k)*cosb)
4928 dcosg(k)=rmij*(dc_norm(k,j)-erij(k)*cosg)
4931 gggp(k)=ecosbp*dcosb(k)+ecosgp*dcosg(k)
4932 gggm(k)=ecosbm*dcosb(k)+ecosgm*dcosg(k)
4934 gggp(1)=gggp(1)+ees0pijp*xj
4935 & +ees0p(num_conti,i)/sss*rmij*xj*sssgrad
4936 gggp(2)=gggp(2)+ees0pijp*yj
4937 & +ees0p(num_conti,i)/sss*rmij*yj*sssgrad
4938 gggp(3)=gggp(3)+ees0pijp*zj
4939 & +ees0p(num_conti,i)/sss*rmij*zj*sssgrad
4940 gggm(1)=gggm(1)+ees0mijp*xj
4941 & +ees0m(num_conti,i)/sss*rmij*xj*sssgrad
4942 gggm(2)=gggm(2)+ees0mijp*yj
4943 & +ees0m(num_conti,i)/sss*rmij*yj*sssgrad
4944 gggm(3)=gggm(3)+ees0mijp*zj
4945 & +ees0m(num_conti,i)/sss*rmij*zj*sssgrad
4946 C Derivatives due to the contact function
4947 gacont_hbr(1,num_conti,i)=fprimcont*xj
4948 gacont_hbr(2,num_conti,i)=fprimcont*yj
4949 gacont_hbr(3,num_conti,i)=fprimcont*zj
4952 c 10/24/08 cgrad and ! comments indicate the parts of the code removed
4953 c following the change of gradient-summation algorithm.
4955 cgrad ghalfp=0.5D0*gggp(k)
4956 cgrad ghalfm=0.5D0*gggm(k)
4957 gacontp_hb1(k,num_conti,i)=!ghalfp
4958 & +(ecosap*(dc_norm(k,j)-cosa*dc_norm(k,i))
4959 & + ecosbp*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
4960 & *fac_shield(i)*fac_shield(j)*sss
4962 gacontp_hb2(k,num_conti,i)=!ghalfp
4963 & +(ecosap*(dc_norm(k,i)-cosa*dc_norm(k,j))
4964 & + ecosgp*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
4965 & *fac_shield(i)*fac_shield(j)*sss
4967 gacontp_hb3(k,num_conti,i)=gggp(k)
4968 & *fac_shield(i)*fac_shield(j)*sss
4970 gacontm_hb1(k,num_conti,i)=!ghalfm
4971 & +(ecosam*(dc_norm(k,j)-cosa*dc_norm(k,i))
4972 & + ecosbm*(erij(k)-cosb*dc_norm(k,i)))*vbld_inv(i+1)
4973 & *fac_shield(i)*fac_shield(j)*sss
4975 gacontm_hb2(k,num_conti,i)=!ghalfm
4976 & +(ecosam*(dc_norm(k,i)-cosa*dc_norm(k,j))
4977 & + ecosgm*(erij(k)-cosg*dc_norm(k,j)))*vbld_inv(j+1)
4978 & *fac_shield(i)*fac_shield(j)*sss
4980 gacontm_hb3(k,num_conti,i)=gggm(k)
4981 & *fac_shield(i)*fac_shield(j)*sss
4984 C Diagnostics. Comment out or remove after debugging!
4986 cdiag gacontp_hb1(k,num_conti,i)=0.0D0
4987 cdiag gacontp_hb2(k,num_conti,i)=0.0D0
4988 cdiag gacontp_hb3(k,num_conti,i)=0.0D0
4989 cdiag gacontm_hb1(k,num_conti,i)=0.0D0
4990 cdiag gacontm_hb2(k,num_conti,i)=0.0D0
4991 cdiag gacontm_hb3(k,num_conti,i)=0.0D0
4994 endif ! num_conti.le.maxconts
4998 if (wturn3.gt.0.0d0 .or. wturn4.gt.0.0d0) then
5001 ghalf=0.5d0*agg(l,k)
5002 aggi(l,k)=aggi(l,k)+ghalf
5003 aggi1(l,k)=aggi1(l,k)+agg(l,k)
5004 aggj(l,k)=aggj(l,k)+ghalf
5007 if (j.eq.nres-1 .and. i.lt.j-2) then
5010 aggj1(l,k)=aggj1(l,k)+agg(l,k)
5015 c t_eelecij=t_eelecij+MPI_Wtime()-time00
5018 C-----------------------------------------------------------------------------
5019 subroutine eturn3(i,eello_turn3)
5020 C Third- and fourth-order contributions from turns
5021 implicit real*8 (a-h,o-z)
5022 include 'DIMENSIONS'
5023 include 'COMMON.IOUNITS'
5024 include 'COMMON.GEO'
5025 include 'COMMON.VAR'
5026 include 'COMMON.LOCAL'
5027 include 'COMMON.CHAIN'
5028 include 'COMMON.DERIV'
5029 include 'COMMON.INTERACT'
5030 include 'COMMON.CORRMAT'
5031 include 'COMMON.TORSION'
5032 include 'COMMON.VECTORS'
5033 include 'COMMON.FFIELD'
5034 include 'COMMON.CONTROL'
5035 include 'COMMON.SHIELD'
5037 double precision auxmat(2,2),auxmat1(2,2),auxmat2(2,2),pizda(2,2),
5038 & e1t(2,2),e2t(2,2),e3t(2,2),e1tder(2,2),e2tder(2,2),e3tder(2,2),
5039 & e1a(2,2),ae3(2,2),ae3e2(2,2),auxvec(2),auxvec1(2),gpizda1(2,2),
5040 & gpizda2(2,2),auxgmat1(2,2),auxgmatt1(2,2),
5041 & auxgmat2(2,2),auxgmatt2(2,2)
5042 double precision agg(3,4),aggi(3,4),aggi1(3,4),
5043 & aggj(3,4),aggj1(3,4),a_temp(2,2),auxmat3(2,2)
5044 common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
5045 & dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
5048 c write (iout,*) "eturn3",i,j,j1,j2
5053 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
5055 C Third-order contributions
5062 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
5063 cd call checkint_turn3(i,a_temp,eello_turn3_num)
5064 call matmat2(EUg(1,1,i+1),EUg(1,1,i+2),auxmat(1,1))
5065 c auxalary matices for theta gradient
5066 c auxalary matrix for i+1 and constant i+2
5067 call matmat2(gtEUg(1,1,i+1),EUg(1,1,i+2),auxgmat1(1,1))
5068 c auxalary matrix for i+2 and constant i+1
5069 call matmat2(EUg(1,1,i+1),gtEUg(1,1,i+2),auxgmat2(1,1))
5070 call transpose2(auxmat(1,1),auxmat1(1,1))
5071 call transpose2(auxgmat1(1,1),auxgmatt1(1,1))
5072 call transpose2(auxgmat2(1,1),auxgmatt2(1,1))
5073 call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
5074 call matmat2(a_temp(1,1),auxgmatt1(1,1),gpizda1(1,1))
5075 call matmat2(a_temp(1,1),auxgmatt2(1,1),gpizda2(1,1))
5076 if (shield_mode.eq.0) then
5083 eello_turn3=eello_turn3+0.5d0*(pizda(1,1)+pizda(2,2))
5084 & *fac_shield(i)*fac_shield(j)
5085 eello_t3=0.5d0*(pizda(1,1)+pizda(2,2))
5086 & *fac_shield(i)*fac_shield(j)
5087 if (energy_dec) write (iout,'(6heturn3,2i5,0pf7.3)') i,i+2,
5090 C Derivatives in theta
5091 gloc(nphi+i,icg)=gloc(nphi+i,icg)
5092 & +0.5d0*(gpizda1(1,1)+gpizda1(2,2))*wturn3
5093 & *fac_shield(i)*fac_shield(j)
5094 gloc(nphi+i+1,icg)=gloc(nphi+i+1,icg)
5095 & +0.5d0*(gpizda2(1,1)+gpizda2(2,2))*wturn3
5096 & *fac_shield(i)*fac_shield(j)
5099 C Derivatives in shield mode
5100 if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
5101 & (shield_mode.gt.0)) then
5104 do ilist=1,ishield_list(i)
5105 iresshield=shield_list(ilist,i)
5107 rlocshield=grad_shield_side(k,ilist,i)*eello_t3/fac_shield(i)
5109 gshieldx_t3(k,iresshield)=gshieldx_t3(k,iresshield)+
5111 & +grad_shield_loc(k,ilist,i)*eello_t3/fac_shield(i)
5112 gshieldc_t3(k,iresshield-1)=gshieldc_t3(k,iresshield-1)
5116 do ilist=1,ishield_list(j)
5117 iresshield=shield_list(ilist,j)
5119 rlocshield=grad_shield_side(k,ilist,j)*eello_t3/fac_shield(j)
5121 gshieldx_t3(k,iresshield)=gshieldx_t3(k,iresshield)+
5123 & +grad_shield_loc(k,ilist,j)*eello_t3/fac_shield(j)
5124 gshieldc_t3(k,iresshield-1)=gshieldc_t3(k,iresshield-1)
5131 gshieldc_t3(k,i)=gshieldc_t3(k,i)+
5132 & grad_shield(k,i)*eello_t3/fac_shield(i)
5133 gshieldc_t3(k,j)=gshieldc_t3(k,j)+
5134 & grad_shield(k,j)*eello_t3/fac_shield(j)
5135 gshieldc_t3(k,i-1)=gshieldc_t3(k,i-1)+
5136 & grad_shield(k,i)*eello_t3/fac_shield(i)
5137 gshieldc_t3(k,j-1)=gshieldc_t3(k,j-1)+
5138 & grad_shield(k,j)*eello_t3/fac_shield(j)
5142 C if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
5143 cd write (2,*) 'i,',i,' j',j,'eello_turn3',
5144 cd & 0.5d0*(pizda(1,1)+pizda(2,2)),
5145 cd & ' eello_turn3_num',4*eello_turn3_num
5146 C Derivatives in gamma(i)
5147 call matmat2(EUgder(1,1,i+1),EUg(1,1,i+2),auxmat2(1,1))
5148 call transpose2(auxmat2(1,1),auxmat3(1,1))
5149 call matmat2(a_temp(1,1),auxmat3(1,1),pizda(1,1))
5150 gel_loc_turn3(i)=gel_loc_turn3(i)+0.5d0*(pizda(1,1)+pizda(2,2))
5151 & *fac_shield(i)*fac_shield(j)
5152 C Derivatives in gamma(i+1)
5153 call matmat2(EUg(1,1,i+1),EUgder(1,1,i+2),auxmat2(1,1))
5154 call transpose2(auxmat2(1,1),auxmat3(1,1))
5155 call matmat2(a_temp(1,1),auxmat3(1,1),pizda(1,1))
5156 gel_loc_turn3(i+1)=gel_loc_turn3(i+1)
5157 & +0.5d0*(pizda(1,1)+pizda(2,2))
5158 & *fac_shield(i)*fac_shield(j)
5159 C Cartesian derivatives
5161 c ghalf1=0.5d0*agg(l,1)
5162 c ghalf2=0.5d0*agg(l,2)
5163 c ghalf3=0.5d0*agg(l,3)
5164 c ghalf4=0.5d0*agg(l,4)
5165 a_temp(1,1)=aggi(l,1)!+ghalf1
5166 a_temp(1,2)=aggi(l,2)!+ghalf2
5167 a_temp(2,1)=aggi(l,3)!+ghalf3
5168 a_temp(2,2)=aggi(l,4)!+ghalf4
5169 call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
5170 gcorr3_turn(l,i)=gcorr3_turn(l,i)
5171 & +0.5d0*(pizda(1,1)+pizda(2,2))
5172 & *fac_shield(i)*fac_shield(j)
5174 a_temp(1,1)=aggi1(l,1)!+agg(l,1)
5175 a_temp(1,2)=aggi1(l,2)!+agg(l,2)
5176 a_temp(2,1)=aggi1(l,3)!+agg(l,3)
5177 a_temp(2,2)=aggi1(l,4)!+agg(l,4)
5178 call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
5179 gcorr3_turn(l,i+1)=gcorr3_turn(l,i+1)
5180 & +0.5d0*(pizda(1,1)+pizda(2,2))
5181 & *fac_shield(i)*fac_shield(j)
5182 a_temp(1,1)=aggj(l,1)!+ghalf1
5183 a_temp(1,2)=aggj(l,2)!+ghalf2
5184 a_temp(2,1)=aggj(l,3)!+ghalf3
5185 a_temp(2,2)=aggj(l,4)!+ghalf4
5186 call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
5187 gcorr3_turn(l,j)=gcorr3_turn(l,j)
5188 & +0.5d0*(pizda(1,1)+pizda(2,2))
5189 & *fac_shield(i)*fac_shield(j)
5190 a_temp(1,1)=aggj1(l,1)
5191 a_temp(1,2)=aggj1(l,2)
5192 a_temp(2,1)=aggj1(l,3)
5193 a_temp(2,2)=aggj1(l,4)
5194 call matmat2(a_temp(1,1),auxmat1(1,1),pizda(1,1))
5195 gcorr3_turn(l,j1)=gcorr3_turn(l,j1)
5196 & +0.5d0*(pizda(1,1)+pizda(2,2))
5197 & *fac_shield(i)*fac_shield(j)
5201 C-------------------------------------------------------------------------------
5202 subroutine eturn4(i,eello_turn4)
5203 C Third- and fourth-order contributions from turns
5204 implicit real*8 (a-h,o-z)
5205 include 'DIMENSIONS'
5206 include 'COMMON.IOUNITS'
5207 include 'COMMON.GEO'
5208 include 'COMMON.VAR'
5209 include 'COMMON.LOCAL'
5210 include 'COMMON.CHAIN'
5211 include 'COMMON.DERIV'
5212 include 'COMMON.INTERACT'
5213 include 'COMMON.CORRMAT'
5214 include 'COMMON.TORSION'
5215 include 'COMMON.VECTORS'
5216 include 'COMMON.FFIELD'
5217 include 'COMMON.CONTROL'
5218 include 'COMMON.SHIELD'
5220 double precision auxmat(2,2),auxmat1(2,2),auxmat2(2,2),pizda(2,2),
5221 & e1t(2,2),e2t(2,2),e3t(2,2),e1tder(2,2),e2tder(2,2),e3tder(2,2),
5222 & e1a(2,2),ae3(2,2),ae3e2(2,2),auxvec(2),auxvec1(2),auxgvec(2),
5223 & auxgEvec1(2),auxgEvec2(2),auxgEvec3(2),
5224 & gte1t(2,2),gte2t(2,2),gte3t(2,2),
5225 & gte1a(2,2),gtae3(2,2),gtae3e2(2,2), ae3gte2(2,2),
5226 & gtEpizda1(2,2),gtEpizda2(2,2),gtEpizda3(2,2)
5227 double precision agg(3,4),aggi(3,4),aggi1(3,4),
5228 & aggj(3,4),aggj1(3,4),a_temp(2,2),auxmat3(2,2)
5229 common /locel/ a_temp,agg,aggi,aggi1,aggj,aggj1,a22,a23,a32,a33,
5230 & dxi,dyi,dzi,dx_normi,dy_normi,dz_normi,xmedi,ymedi,zmedi,
5233 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
5235 C Fourth-order contributions
5243 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
5244 cd call checkint_turn4(i,a_temp,eello_turn4_num)
5245 c write (iout,*) "eturn4 i",i," j",j," j1",j1," j2",j2
5246 c write(iout,*)"WCHODZE W PROGRAM"
5251 iti1=itype2loc(itype(i+1))
5252 iti2=itype2loc(itype(i+2))
5253 iti3=itype2loc(itype(i+3))
5254 c write(iout,*) "iti1",iti1," iti2",iti2," iti3",iti3
5255 call transpose2(EUg(1,1,i+1),e1t(1,1))
5256 call transpose2(Eug(1,1,i+2),e2t(1,1))
5257 call transpose2(Eug(1,1,i+3),e3t(1,1))
5258 C Ematrix derivative in theta
5259 call transpose2(gtEUg(1,1,i+1),gte1t(1,1))
5260 call transpose2(gtEug(1,1,i+2),gte2t(1,1))
5261 call transpose2(gtEug(1,1,i+3),gte3t(1,1))
5262 call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
5263 c eta1 in derivative theta
5264 call matmat2(gte1t(1,1),a_temp(1,1),gte1a(1,1))
5265 call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
5266 c auxgvec is derivative of Ub2 so i+3 theta
5267 call matvec2(e1a(1,1),gUb2(1,i+3),auxgvec(1))
5268 c auxalary matrix of E i+1
5269 call matvec2(gte1a(1,1),Ub2(1,i+3),auxgEvec1(1))
5272 s1=scalar2(b1(1,i+2),auxvec(1))
5273 c derivative of theta i+2 with constant i+3
5274 gs23=scalar2(gtb1(1,i+2),auxvec(1))
5275 c derivative of theta i+2 with constant i+2
5276 gs32=scalar2(b1(1,i+2),auxgvec(1))
5277 c derivative of E matix in theta of i+1
5278 gsE13=scalar2(b1(1,i+2),auxgEvec1(1))
5280 call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
5281 c ea31 in derivative theta
5282 call matmat2(a_temp(1,1),gte3t(1,1),gtae3(1,1))
5283 call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1))
5284 c auxilary matrix auxgvec of Ub2 with constant E matirx
5285 call matvec2(ae3(1,1),gUb2(1,i+2),auxgvec(1))
5286 c auxilary matrix auxgEvec1 of E matix with Ub2 constant
5287 call matvec2(gtae3(1,1),Ub2(1,i+2),auxgEvec3(1))
5291 s2=scalar2(b1(1,i+1),auxvec(1))
5292 c derivative of theta i+1 with constant i+3
5293 gs13=scalar2(gtb1(1,i+1),auxvec(1))
5294 c derivative of theta i+2 with constant i+1
5295 gs21=scalar2(b1(1,i+1),auxgvec(1))
5296 c derivative of theta i+3 with constant i+1
5297 gsE31=scalar2(b1(1,i+1),auxgEvec3(1))
5298 c write(iout,*) gs1,gs2,'i=',i,auxgvec(1),gUb2(1,i+2),gtb1(1,i+2),
5300 call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
5301 c two derivatives over diffetent matrices
5302 c gtae3e2 is derivative over i+3
5303 call matmat2(gtae3(1,1),e2t(1,1),gtae3e2(1,1))
5304 c ae3gte2 is derivative over i+2
5305 call matmat2(ae3(1,1),gte2t(1,1),ae3gte2(1,1))
5306 call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
5307 c three possible derivative over theta E matices
5309 call matmat2(ae3e2(1,1),gte1t(1,1),gtEpizda1(1,1))
5311 call matmat2(ae3gte2(1,1),e1t(1,1),gtEpizda2(1,1))
5313 call matmat2(gtae3e2(1,1),e1t(1,1),gtEpizda3(1,1))
5314 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5316 gsEE1=0.5d0*(gtEpizda1(1,1)+gtEpizda1(2,2))
5317 gsEE2=0.5d0*(gtEpizda2(1,1)+gtEpizda2(2,2))
5318 gsEE3=0.5d0*(gtEpizda3(1,1)+gtEpizda3(2,2))
5319 if (shield_mode.eq.0) then
5326 eello_turn4=eello_turn4-(s1+s2+s3)
5327 & *fac_shield(i)*fac_shield(j)
5328 eello_t4=-(s1+s2+s3)
5329 & *fac_shield(i)*fac_shield(j)
5330 c write(iout,*)'chujOWO', auxvec(1),b1(1,iti2)
5331 if (energy_dec) write (iout,'(a6,2i5,0pf7.3,3f7.3)')
5332 & 'eturn4',i,j,-(s1+s2+s3),s1,s2,s3
5333 C Now derivative over shield:
5334 if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
5335 & (shield_mode.gt.0)) then
5338 do ilist=1,ishield_list(i)
5339 iresshield=shield_list(ilist,i)
5341 rlocshield=grad_shield_side(k,ilist,i)*eello_t4/fac_shield(i)
5343 gshieldx_t4(k,iresshield)=gshieldx_t4(k,iresshield)+
5345 & +grad_shield_loc(k,ilist,i)*eello_t4/fac_shield(i)
5346 gshieldc_t4(k,iresshield-1)=gshieldc_t4(k,iresshield-1)
5350 do ilist=1,ishield_list(j)
5351 iresshield=shield_list(ilist,j)
5353 rlocshield=grad_shield_side(k,ilist,j)*eello_t4/fac_shield(j)
5355 gshieldx_t4(k,iresshield)=gshieldx_t4(k,iresshield)+
5357 & +grad_shield_loc(k,ilist,j)*eello_t4/fac_shield(j)
5358 gshieldc_t4(k,iresshield-1)=gshieldc_t4(k,iresshield-1)
5365 gshieldc_t4(k,i)=gshieldc_t4(k,i)+
5366 & grad_shield(k,i)*eello_t4/fac_shield(i)
5367 gshieldc_t4(k,j)=gshieldc_t4(k,j)+
5368 & grad_shield(k,j)*eello_t4/fac_shield(j)
5369 gshieldc_t4(k,i-1)=gshieldc_t4(k,i-1)+
5370 & grad_shield(k,i)*eello_t4/fac_shield(i)
5371 gshieldc_t4(k,j-1)=gshieldc_t4(k,j-1)+
5372 & grad_shield(k,j)*eello_t4/fac_shield(j)
5381 cd write (2,*) 'i,',i,' j',j,'eello_turn4',-(s1+s2+s3),
5382 cd & ' eello_turn4_num',8*eello_turn4_num
5384 gloc(nphi+i,icg)=gloc(nphi+i,icg)
5385 & -(gs13+gsE13+gsEE1)*wturn4
5386 & *fac_shield(i)*fac_shield(j)
5387 gloc(nphi+i+1,icg)= gloc(nphi+i+1,icg)
5388 & -(gs23+gs21+gsEE2)*wturn4
5389 & *fac_shield(i)*fac_shield(j)
5391 gloc(nphi+i+2,icg)= gloc(nphi+i+2,icg)
5392 & -(gs32+gsE31+gsEE3)*wturn4
5393 & *fac_shield(i)*fac_shield(j)
5395 c gloc(nphi+i+1,icg)=gloc(nphi+i+1,icg)-
5398 if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
5399 & 'eturn4',i,j,-(s1+s2+s3)
5400 c write (iout,*) 'i,',i,' j',j,'eello_turn4',-(s1+s2+s3),
5401 c & ' eello_turn4_num',8*eello_turn4_num
5402 C Derivatives in gamma(i)
5403 call transpose2(EUgder(1,1,i+1),e1tder(1,1))
5404 call matmat2(e1tder(1,1),a_temp(1,1),auxmat(1,1))
5405 call matvec2(auxmat(1,1),Ub2(1,i+3),auxvec(1))
5406 s1=scalar2(b1(1,i+2),auxvec(1))
5407 call matmat2(ae3e2(1,1),e1tder(1,1),pizda(1,1))
5408 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5409 gel_loc_turn4(i)=gel_loc_turn4(i)-(s1+s3)
5410 & *fac_shield(i)*fac_shield(j)
5411 C Derivatives in gamma(i+1)
5412 call transpose2(EUgder(1,1,i+2),e2tder(1,1))
5413 call matvec2(ae3(1,1),Ub2der(1,i+2),auxvec(1))
5414 s2=scalar2(b1(1,i+1),auxvec(1))
5415 call matmat2(ae3(1,1),e2tder(1,1),auxmat(1,1))
5416 call matmat2(auxmat(1,1),e1t(1,1),pizda(1,1))
5417 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5418 gel_loc_turn4(i+1)=gel_loc_turn4(i+1)-(s2+s3)
5419 & *fac_shield(i)*fac_shield(j)
5420 C Derivatives in gamma(i+2)
5421 call transpose2(EUgder(1,1,i+3),e3tder(1,1))
5422 call matvec2(e1a(1,1),Ub2der(1,i+3),auxvec(1))
5423 s1=scalar2(b1(1,i+2),auxvec(1))
5424 call matmat2(a_temp(1,1),e3tder(1,1),auxmat(1,1))
5425 call matvec2(auxmat(1,1),Ub2(1,i+2),auxvec(1))
5426 s2=scalar2(b1(1,i+1),auxvec(1))
5427 call matmat2(auxmat(1,1),e2t(1,1),auxmat3(1,1))
5428 call matmat2(auxmat3(1,1),e1t(1,1),pizda(1,1))
5429 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5430 gel_loc_turn4(i+2)=gel_loc_turn4(i+2)-(s1+s2+s3)
5431 & *fac_shield(i)*fac_shield(j)
5432 C Cartesian derivatives
5433 C Derivatives of this turn contributions in DC(i+2)
5434 if (j.lt.nres-1) then
5436 a_temp(1,1)=agg(l,1)
5437 a_temp(1,2)=agg(l,2)
5438 a_temp(2,1)=agg(l,3)
5439 a_temp(2,2)=agg(l,4)
5440 call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
5441 call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
5442 s1=scalar2(b1(1,i+2),auxvec(1))
5443 call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
5444 call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1))
5445 s2=scalar2(b1(1,i+1),auxvec(1))
5446 call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
5447 call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
5448 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5450 gcorr4_turn(l,i+2)=gcorr4_turn(l,i+2)-(s1+s2+s3)
5451 & *fac_shield(i)*fac_shield(j)
5454 C Remaining derivatives of this turn contribution
5456 a_temp(1,1)=aggi(l,1)
5457 a_temp(1,2)=aggi(l,2)
5458 a_temp(2,1)=aggi(l,3)
5459 a_temp(2,2)=aggi(l,4)
5460 call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
5461 call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
5462 s1=scalar2(b1(1,i+2),auxvec(1))
5463 call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
5464 call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1))
5465 s2=scalar2(b1(1,i+1),auxvec(1))
5466 call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
5467 call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
5468 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5469 gcorr4_turn(l,i)=gcorr4_turn(l,i)-(s1+s2+s3)
5470 & *fac_shield(i)*fac_shield(j)
5471 a_temp(1,1)=aggi1(l,1)
5472 a_temp(1,2)=aggi1(l,2)
5473 a_temp(2,1)=aggi1(l,3)
5474 a_temp(2,2)=aggi1(l,4)
5475 call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
5476 call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
5477 s1=scalar2(b1(1,i+2),auxvec(1))
5478 call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
5479 call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1))
5480 s2=scalar2(b1(1,i+1),auxvec(1))
5481 call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
5482 call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
5483 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5484 gcorr4_turn(l,i+1)=gcorr4_turn(l,i+1)-(s1+s2+s3)
5485 & *fac_shield(i)*fac_shield(j)
5486 a_temp(1,1)=aggj(l,1)
5487 a_temp(1,2)=aggj(l,2)
5488 a_temp(2,1)=aggj(l,3)
5489 a_temp(2,2)=aggj(l,4)
5490 call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
5491 call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
5492 s1=scalar2(b1(1,i+2),auxvec(1))
5493 call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
5494 call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1))
5495 s2=scalar2(b1(1,i+1),auxvec(1))
5496 call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
5497 call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
5498 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5499 gcorr4_turn(l,j)=gcorr4_turn(l,j)-(s1+s2+s3)
5500 & *fac_shield(i)*fac_shield(j)
5501 a_temp(1,1)=aggj1(l,1)
5502 a_temp(1,2)=aggj1(l,2)
5503 a_temp(2,1)=aggj1(l,3)
5504 a_temp(2,2)=aggj1(l,4)
5505 call matmat2(e1t(1,1),a_temp(1,1),e1a(1,1))
5506 call matvec2(e1a(1,1),Ub2(1,i+3),auxvec(1))
5507 s1=scalar2(b1(1,i+2),auxvec(1))
5508 call matmat2(a_temp(1,1),e3t(1,1),ae3(1,1))
5509 call matvec2(ae3(1,1),Ub2(1,i+2),auxvec(1))
5510 s2=scalar2(b1(1,i+1),auxvec(1))
5511 call matmat2(ae3(1,1),e2t(1,1),ae3e2(1,1))
5512 call matmat2(ae3e2(1,1),e1t(1,1),pizda(1,1))
5513 s3=0.5d0*(pizda(1,1)+pizda(2,2))
5514 c write (iout,*) "s1",s1," s2",s2," s3",s3," s1+s2+s3",s1+s2+s3
5515 gcorr4_turn(l,j1)=gcorr4_turn(l,j1)-(s1+s2+s3)
5516 & *fac_shield(i)*fac_shield(j)
5520 C-----------------------------------------------------------------------------
5521 subroutine vecpr(u,v,w)
5522 implicit real*8(a-h,o-z)
5523 dimension u(3),v(3),w(3)
5524 w(1)=u(2)*v(3)-u(3)*v(2)
5525 w(2)=-u(1)*v(3)+u(3)*v(1)
5526 w(3)=u(1)*v(2)-u(2)*v(1)
5529 C-----------------------------------------------------------------------------
5530 subroutine unormderiv(u,ugrad,unorm,ungrad)
5531 C This subroutine computes the derivatives of a normalized vector u, given
5532 C the derivatives computed without normalization conditions, ugrad. Returns
5535 double precision u(3),ugrad(3,3),unorm,ungrad(3,3)
5536 double precision vec(3)
5537 double precision scalar
5539 c write (2,*) 'ugrad',ugrad
5542 vec(i)=scalar(ugrad(1,i),u(1))
5544 c write (2,*) 'vec',vec
5547 ungrad(j,i)=(ugrad(j,i)-u(j)*vec(i))*unorm
5550 c write (2,*) 'ungrad',ungrad
5553 C-----------------------------------------------------------------------------
5554 subroutine escp_soft_sphere(evdw2,evdw2_14)
5556 C This subroutine calculates the excluded-volume interaction energy between
5557 C peptide-group centers and side chains and its gradient in virtual-bond and
5558 C side-chain vectors.
5560 implicit real*8 (a-h,o-z)
5561 include 'DIMENSIONS'
5562 include 'COMMON.GEO'
5563 include 'COMMON.VAR'
5564 include 'COMMON.LOCAL'
5565 include 'COMMON.CHAIN'
5566 include 'COMMON.DERIV'
5567 include 'COMMON.INTERACT'
5568 include 'COMMON.FFIELD'
5569 include 'COMMON.IOUNITS'
5570 include 'COMMON.CONTROL'
5572 integer xshift,yshift,zshift
5576 cd print '(a)','Enter ESCP'
5577 cd write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
5581 c do i=iatscp_s,iatscp_e
5582 do icont=g_listscp_start,g_listscp_end
5583 i=newcontlistscpi(icont)
5584 j=newcontlistscpj(icont)
5585 if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
5587 xi=0.5D0*(c(1,i)+c(1,i+1))
5588 yi=0.5D0*(c(2,i)+c(2,i+1))
5589 zi=0.5D0*(c(3,i)+c(3,i+1))
5590 C Return atom into box, boxxsize is size of box in x dimension
5592 c if (xi.gt.((xshift+0.5d0)*boxxsize)) xi=xi-boxxsize
5593 c if (xi.lt.((xshift-0.5d0)*boxxsize)) xi=xi+boxxsize
5594 C Condition for being inside the proper box
5595 c if ((xi.gt.((xshift+0.5d0)*boxxsize)).or.
5596 c & (xi.lt.((xshift-0.5d0)*boxxsize))) then
5600 c if (yi.gt.((yshift+0.5d0)*boxysize)) yi=yi-boxysize
5601 c if (yi.lt.((yshift-0.5d0)*boxysize)) yi=yi+boxysize
5602 C Condition for being inside the proper box
5603 c if ((yi.gt.((yshift+0.5d0)*boxysize)).or.
5604 c & (yi.lt.((yshift-0.5d0)*boxysize))) then
5608 c if (zi.gt.((zshift+0.5d0)*boxzsize)) zi=zi-boxzsize
5609 c if (zi.lt.((zshift-0.5d0)*boxzsize)) zi=zi+boxzsize
5610 cC Condition for being inside the proper box
5611 c if ((zi.gt.((zshift+0.5d0)*boxzsize)).or.
5612 c & (zi.lt.((zshift-0.5d0)*boxzsize))) then
5616 if (xi.lt.0) xi=xi+boxxsize
5618 if (yi.lt.0) yi=yi+boxysize
5620 if (zi.lt.0) zi=zi+boxzsize
5621 C xi=xi+xshift*boxxsize
5622 C yi=yi+yshift*boxysize
5623 C zi=zi+zshift*boxzsize
5624 c do iint=1,nscp_gr(i)
5626 c do j=iscpstart(i,iint),iscpend(i,iint)
5627 if (itype(j).eq.ntyp1) cycle
5628 itypj=iabs(itype(j))
5629 C Uncomment following three lines for SC-p interactions
5633 C Uncomment following three lines for Ca-p interactions
5638 c if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
5639 c if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
5640 C Condition for being inside the proper box
5641 c if ((xj.gt.((0.5d0)*boxxsize)).or.
5642 c & (xj.lt.((-0.5d0)*boxxsize))) then
5646 c if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
5647 c if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
5648 cC Condition for being inside the proper box
5649 c if ((yj.gt.((0.5d0)*boxysize)).or.
5650 c & (yj.lt.((-0.5d0)*boxysize))) then
5654 c if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxzsize
5655 c if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxzsize
5656 C Condition for being inside the proper box
5657 c if ((zj.gt.((0.5d0)*boxzsize)).or.
5658 c & (zj.lt.((-0.5d0)*boxzsize))) then
5661 if (xj.lt.0) xj=xj+boxxsize
5663 if (yj.lt.0) yj=yj+boxysize
5665 if (zj.lt.0) zj=zj+boxzsize
5666 dist_init=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
5674 xj=xj_safe+xshift*boxxsize
5675 yj=yj_safe+yshift*boxysize
5676 zj=zj_safe+zshift*boxzsize
5677 dist_temp=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
5678 if(dist_temp.lt.dist_init) then
5688 if (subchap.eq.1) then
5701 rij=xj*xj+yj*yj+zj*zj
5705 if (rij.lt.r0ijsq) then
5706 evdwij=0.25d0*(rij-r0ijsq)**2
5714 C Calculate contributions to the gradient in the virtual-bond and SC vectors.
5719 cgrad if (j.lt.i) then
5720 cd write (iout,*) 'j<i'
5721 C Uncomment following three lines for SC-p interactions
5723 c gradx_scp(k,j)=gradx_scp(k,j)+ggg(k)
5726 cd write (iout,*) 'j>i'
5728 cgrad ggg(k)=-ggg(k)
5729 C Uncomment following line for SC-p interactions
5730 c gradx_scp(k,j)=gradx_scp(k,j)-ggg(k)
5734 cgrad gvdwc_scp(k,i)=gvdwc_scp(k,i)-0.5D0*ggg(k)
5736 cgrad kstart=min0(i+1,j)
5737 cgrad kend=max0(i-1,j-1)
5738 cd write (iout,*) 'i=',i,' j=',j,' kstart=',kstart,' kend=',kend
5739 cd write (iout,*) ggg(1),ggg(2),ggg(3)
5740 cgrad do k=kstart,kend
5742 cgrad gvdwc_scp(l,k)=gvdwc_scp(l,k)-ggg(l)
5746 gvdwc_scpp(k,i)=gvdwc_scpp(k,i)-ggg(k)
5747 gvdwc_scp(k,j)=gvdwc_scp(k,j)+ggg(k)
5758 C-----------------------------------------------------------------------------
5759 subroutine escp(evdw2,evdw2_14)
5761 C This subroutine calculates the excluded-volume interaction energy between
5762 C peptide-group centers and side chains and its gradient in virtual-bond and
5763 C side-chain vectors.
5766 include 'DIMENSIONS'
5767 include 'COMMON.GEO'
5768 include 'COMMON.VAR'
5769 include 'COMMON.LOCAL'
5770 include 'COMMON.CHAIN'
5771 include 'COMMON.DERIV'
5772 include 'COMMON.INTERACT'
5773 include 'COMMON.FFIELD'
5774 include 'COMMON.IOUNITS'
5775 include 'COMMON.CONTROL'
5776 include 'COMMON.SPLITELE'
5777 integer xshift,yshift,zshift
5778 double precision ggg(3)
5779 integer i,iint,j,k,iteli,itypj,subchap,icont
5780 double precision xi,yi,zi,xj,yj,zj,rrij,sss1,sssgrad1,
5782 double precision evdw2,evdw2_14,evdwij
5783 double precision xj_safe,yj_safe,zj_safe,xj_temp,yj_temp,zj_temp,
5784 & dist_temp, dist_init
5785 double precision sscale,sscagrad
5788 c print *,boxxsize,boxysize,boxzsize,'wymiary pudla'
5789 cd print '(a)','Enter ESCP'
5790 cd write (iout,*) 'iatscp_s=',iatscp_s,' iatscp_e=',iatscp_e
5794 if (energy_dec) write (iout,*) "escp:",r_cut_int,rlamb
5795 c do i=iatscp_s,iatscp_e
5796 do icont=g_listscp_start,g_listscp_end
5797 i=newcontlistscpi(icont)
5798 j=newcontlistscpj(icont)
5799 if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) cycle
5801 xi=0.5D0*(c(1,i)+c(1,i+1))
5802 yi=0.5D0*(c(2,i)+c(2,i+1))
5803 zi=0.5D0*(c(3,i)+c(3,i+1))
5805 if (xi.lt.0) xi=xi+boxxsize
5807 if (yi.lt.0) yi=yi+boxysize
5809 if (zi.lt.0) zi=zi+boxzsize
5810 c xi=xi+xshift*boxxsize
5811 c yi=yi+yshift*boxysize
5812 c zi=zi+zshift*boxzsize
5813 c print *,xi,yi,zi,'polozenie i'
5814 C Return atom into box, boxxsize is size of box in x dimension
5816 c if (xi.gt.((xshift+0.5d0)*boxxsize)) xi=xi-boxxsize
5817 c if (xi.lt.((xshift-0.5d0)*boxxsize)) xi=xi+boxxsize
5818 C Condition for being inside the proper box
5819 c if ((xi.gt.((xshift+0.5d0)*boxxsize)).or.
5820 c & (xi.lt.((xshift-0.5d0)*boxxsize))) then
5824 c print *,xi,boxxsize,"pierwszy"
5826 c if (yi.gt.((yshift+0.5d0)*boxysize)) yi=yi-boxysize
5827 c if (yi.lt.((yshift-0.5d0)*boxysize)) yi=yi+boxysize
5828 C Condition for being inside the proper box
5829 c if ((yi.gt.((yshift+0.5d0)*boxysize)).or.
5830 c & (yi.lt.((yshift-0.5d0)*boxysize))) then
5834 c if (zi.gt.((zshift+0.5d0)*boxzsize)) zi=zi-boxzsize
5835 c if (zi.lt.((zshift-0.5d0)*boxzsize)) zi=zi+boxzsize
5836 C Condition for being inside the proper box
5837 c if ((zi.gt.((zshift+0.5d0)*boxzsize)).or.
5838 c & (zi.lt.((zshift-0.5d0)*boxzsize))) then
5841 c do iint=1,nscp_gr(i)
5843 c do j=iscpstart(i,iint),iscpend(i,iint)
5844 itypj=iabs(itype(j))
5845 if (itypj.eq.ntyp1) cycle
5846 C Uncomment following three lines for SC-p interactions
5850 C Uncomment following three lines for Ca-p interactions
5855 if (xj.lt.0) xj=xj+boxxsize
5857 if (yj.lt.0) yj=yj+boxysize
5859 if (zj.lt.0) zj=zj+boxzsize
5861 c if (xj.gt.((0.5d0)*boxxsize)) xj=xj-boxxsize
5862 c if (xj.lt.((-0.5d0)*boxxsize)) xj=xj+boxxsize
5863 C Condition for being inside the proper box
5864 c if ((xj.gt.((0.5d0)*boxxsize)).or.
5865 c & (xj.lt.((-0.5d0)*boxxsize))) then
5869 c if (yj.gt.((0.5d0)*boxysize)) yj=yj-boxysize
5870 c if (yj.lt.((-0.5d0)*boxysize)) yj=yj+boxysize
5871 cC Condition for being inside the proper box
5872 c if ((yj.gt.((0.5d0)*boxysize)).or.
5873 c & (yj.lt.((-0.5d0)*boxysize))) then
5877 c if (zj.gt.((0.5d0)*boxzsize)) zj=zj-boxzsize
5878 c if (zj.lt.((-0.5d0)*boxzsize)) zj=zj+boxzsize
5879 C Condition for being inside the proper box
5880 c if ((zj.gt.((0.5d0)*boxzsize)).or.
5881 c & (zj.lt.((-0.5d0)*boxzsize))) then
5884 CHERE IS THE CALCULATION WHICH MIRROR IMAGE IS THE CLOSEST ONE
5885 dist_init=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
5893 xj=xj_safe+xshift*boxxsize
5894 yj=yj_safe+yshift*boxysize
5895 zj=zj_safe+zshift*boxzsize
5896 dist_temp=(xj-xi)**2+(yj-yi)**2+(zj-zi)**2
5897 if(dist_temp.lt.dist_init) then
5907 if (subchap.eq.1) then
5916 c print *,xj,yj,zj,'polozenie j'
5917 rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
5919 sss=sscale(1.0d0/(dsqrt(rrij)),r_cut_int)
5920 c print *,r_cut,1.0d0/dsqrt(rrij),sss,'tu patrz'
5921 c if (sss.eq.0) print *,'czasem jest OK'
5922 if (sss.le.0.0d0) cycle
5923 sssgrad=sscagrad(1.0d0/(dsqrt(rrij)),r_cut_int)
5925 e1=fac*fac*aad(itypj,iteli)
5926 e2=fac*bad(itypj,iteli)
5927 if (iabs(j-i) .le. 2) then
5930 evdw2_14=evdw2_14+(e1+e2)*sss
5933 evdw2=evdw2+evdwij*sss
5934 if (energy_dec) write (iout,'(a6,2i5,3f7.3,2i3,3e11.3)')
5935 & 'evdw2',i,j,1.0d0/dsqrt(rrij),sss,
5936 & evdwij,iteli,itypj,fac,aad(itypj,iteli),
5939 C Calculate contributions to the gradient in the virtual-bond and SC vectors.
5941 fac=-(evdwij+e1)*rrij*sss
5942 fac=fac+(evdwij)*sssgrad*dsqrt(rrij)/expon
5946 cgrad if (j.lt.i) then
5947 cd write (iout,*) 'j<i'
5948 C Uncomment following three lines for SC-p interactions
5950 c gradx_scp(k,j)=gradx_scp(k,j)+ggg(k)
5953 cd write (iout,*) 'j>i'
5955 cgrad ggg(k)=-ggg(k)
5956 C Uncomment following line for SC-p interactions
5957 ccgrad gradx_scp(k,j)=gradx_scp(k,j)-ggg(k)
5958 c gradx_scp(k,j)=gradx_scp(k,j)+ggg(k)
5962 cgrad gvdwc_scp(k,i)=gvdwc_scp(k,i)-0.5D0*ggg(k)
5964 cgrad kstart=min0(i+1,j)
5965 cgrad kend=max0(i-1,j-1)
5966 cd write (iout,*) 'i=',i,' j=',j,' kstart=',kstart,' kend=',kend
5967 cd write (iout,*) ggg(1),ggg(2),ggg(3)
5968 cgrad do k=kstart,kend
5970 cgrad gvdwc_scp(l,k)=gvdwc_scp(l,k)-ggg(l)
5974 gvdwc_scpp(k,i)=gvdwc_scpp(k,i)-ggg(k)
5975 gvdwc_scp(k,j)=gvdwc_scp(k,j)+ggg(k)
5977 c endif !endif for sscale cutoff
5987 gvdwc_scp(j,i)=expon*gvdwc_scp(j,i)
5988 gvdwc_scpp(j,i)=expon*gvdwc_scpp(j,i)
5989 gradx_scp(j,i)=expon*gradx_scp(j,i)
5992 C******************************************************************************
5996 C To save time the factor EXPON has been extracted from ALL components
5997 C of GVDWC and GRADX. Remember to multiply them by this factor before further
6000 C******************************************************************************
6003 C--------------------------------------------------------------------------
6004 subroutine edis(ehpb)
6006 C Evaluate bridge-strain energy and its gradient in virtual-bond and SC vectors.
6008 implicit real*8 (a-h,o-z)
6009 include 'DIMENSIONS'
6010 include 'COMMON.SBRIDGE'
6011 include 'COMMON.CHAIN'
6012 include 'COMMON.DERIV'
6013 include 'COMMON.VAR'
6014 include 'COMMON.INTERACT'
6015 include 'COMMON.IOUNITS'
6016 include 'COMMON.CONTROL'
6017 dimension ggg(3),ggg_peak(3,1000)
6022 c 8/21/18 AL: added explicit restraints on reference coords
6023 c write (iout,*) "restr_on_coord",restr_on_coord
6024 if (restr_on_coord) then
6028 if (itype(i).eq.ntyp1) cycle
6030 ecoor=ecoor+(c(j,i)-cref(j,i))**2
6031 ghpbc(j,i)=ghpbc(j,i)+bfac(i)*(c(j,i)-cref(j,i))
6033 if (itype(i).ne.10) then
6035 ecoor=ecoor+(c(j,i+nres)-cref(j,i+nres))**2
6036 ghpbx(j,i)=ghpbx(j,i)+bfac(i)*(c(j,i+nres)-cref(j,i+nres))
6039 if (energy_dec) write (iout,*)
6040 & "i",i," bfac",bfac(i)," ecoor",ecoor
6041 ehpb=ehpb+0.5d0*bfac(i)*ecoor
6045 C write (iout,*) ,"link_end",link_end,constr_dist
6046 cd write(iout,*)'edis: nhpb=',nhpb,' fbr=',fbr
6047 c write(iout,*)'link_start=',link_start,' link_end=',link_end,
6048 c & " constr_dist",constr_dist," link_start_peak",link_start_peak,
6049 c & " link_end_peak",link_end_peak
6050 if (link_end.eq.0.and.link_end_peak.eq.0) return
6051 do i=link_start_peak,link_end_peak
6053 c print *,"i",i," link_end_peak",link_end_peak," ipeak",
6054 c & ipeak(1,i),ipeak(2,i)
6055 do ip=ipeak(1,i),ipeak(2,i)
6060 C iii and jjj point to the residues for which the distance is assigned.
6061 c if (ii.gt.nres) then
6068 if (ii.gt.nres) then
6073 if (jj.gt.nres) then
6078 aux=rlornmr1(dd,dhpb_peak(ip),dhpb1_peak(ip),forcon_peak(ip))
6079 aux=dexp(-scal_peak*aux)
6080 ehpb_peak=ehpb_peak+aux
6081 fac=rlornmr1prim(dd,dhpb_peak(ip),dhpb1_peak(ip),
6082 & forcon_peak(ip))*aux/dd
6084 ggg_peak(j,iip)=fac*(c(j,jj)-c(j,ii))
6086 if (energy_dec) write (iout,'(a6,3i5,6f10.3,i5)')
6087 & "edisL",i,ii,jj,dd,dhpb_peak(ip),dhpb1_peak(ip),
6088 & forcon_peak(ip),fordepth_peak(ip),ehpb_peak
6090 c write (iout,*) "ehpb_peak",ehpb_peak," scal_peak",scal_peak
6091 ehpb=ehpb-fordepth_peak(ipeak(1,i))*dlog(ehpb_peak)/scal_peak
6092 do ip=ipeak(1,i),ipeak(2,i)
6095 ggg(j)=ggg_peak(j,iip)/ehpb_peak
6099 C iii and jjj point to the residues for which the distance is assigned.
6100 c if (ii.gt.nres) then
6107 if (ii.gt.nres) then
6112 if (jj.gt.nres) then
6119 ghpbx(j,iii)=ghpbx(j,iii)-ggg(j)
6124 ghpbx(j,jjj)=ghpbx(j,jjj)+ggg(j)
6128 ghpbc(k,jjj)=ghpbc(k,jjj)+ggg(k)
6129 ghpbc(k,iii)=ghpbc(k,iii)-ggg(k)
6133 do i=link_start,link_end
6134 C If ihpb(i) and jhpb(i) > NRES, this is a SC-SC distance, otherwise a
6135 C CA-CA distance used in regularization of structure.
6138 C iii and jjj point to the residues for which the distance is assigned.
6139 if (ii.gt.nres) then
6144 if (jj.gt.nres) then
6149 c write (iout,*) "i",i," ii",ii," iii",iii," jj",jj," jjj",jjj,
6150 c & dhpb(i),dhpb1(i),forcon(i)
6151 C 24/11/03 AL: SS bridges handled separately because of introducing a specific
6152 C distance and angle dependent SS bond potential.
6153 C if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and.
6154 C & iabs(itype(jjj)).eq.1) then
6155 cmc if (ii.gt.nres .and. itype(iii).eq.1 .and. itype(jjj).eq.1) then
6156 C 18/07/06 MC: Use the convention that the first nss pairs are SS bonds
6157 if (.not.dyn_ss .and. i.le.nss) then
6158 C 15/02/13 CC dynamic SSbond - additional check
6159 if (ii.gt.nres .and. iabs(itype(iii)).eq.1 .and.
6160 & iabs(itype(jjj)).eq.1) then
6161 call ssbond_ene(iii,jjj,eij)
6164 cd write (iout,*) "eij",eij
6165 cd & ' waga=',waga,' fac=',fac
6166 ! else if (ii.gt.nres .and. jj.gt.nres) then
6168 C Calculate the distance between the two points and its difference from the
6171 if (irestr_type(i).eq.11) then
6172 ehpb=ehpb+fordepth(i)!**4.0d0
6173 & *rlornmr1(dd,dhpb(i),dhpb1(i),forcon(i))
6174 fac=fordepth(i)!**4.0d0
6175 & *rlornmr1prim(dd,dhpb(i),dhpb1(i),forcon(i))/dd
6176 if (energy_dec) write (iout,'(a6,2i5,6f10.3,i5)')
6177 & "edisL",ii,jj,dd,dhpb(i),dhpb1(i),forcon(i),fordepth(i),
6178 & ehpb,irestr_type(i)
6179 else if (irestr_type(i).eq.10) then
6180 c AL 6//19/2018 cross-link restraints
6181 xdis = 0.5d0*(dd/forcon(i))**2
6182 expdis = dexp(-xdis)
6183 c aux=(dhpb(i)+dhpb1(i)*xdis)*expdis+fordepth(i)
6184 aux=(dhpb(i)+dhpb1(i)*xdis*xdis)*expdis+fordepth(i)
6185 c write (iout,*)"HERE: xdis",xdis," expdis",expdis," aux",aux,
6186 c & " wboltzd",wboltzd
6187 ehpb=ehpb-wboltzd*xlscore(i)*dlog(aux)
6188 c fac=-wboltzd*(dhpb1(i)*(1.0d0-xdis)-dhpb(i))
6189 fac=-wboltzd*xlscore(i)*(dhpb1(i)*(2.0d0-xdis)*xdis-dhpb(i))
6190 & *expdis/(aux*forcon(i)**2)
6191 if (energy_dec) write(iout,'(a6,2i5,6f10.3,i5)')
6192 & "edisX",ii,jj,dd,dhpb(i),dhpb1(i),forcon(i),fordepth(i),
6193 & -wboltzd*xlscore(i)*dlog(aux),irestr_type(i)
6194 else if (irestr_type(i).eq.2) then
6195 c Quartic restraints
6196 ehpb=ehpb+forcon(i)*gnmr1(dd,dhpb(i),dhpb1(i))
6197 if (energy_dec) write(iout,'(a6,2i5,5f10.3,i5)')
6198 & "edisQ",ii,jj,dd,dhpb(i),dhpb1(i),forcon(i),
6199 & forcon(i)*gnmr1(dd,dhpb(i),dhpb1(i)),irestr_type(i)
6200 fac=forcon(i)*gnmr1prim(dd,dhpb(i),dhpb1(i))/dd
6202 c Quadratic restraints
6204 C Get the force constant corresponding to this distance.
6206 C Calculate the contribution to energy.
6207 ehpb=ehpb+0.5d0*waga*rdis*rdis
6208 if (energy_dec) write(iout,'(a6,2i5,5f10.3,i5)')
6209 & "edisS",ii,jj,dd,dhpb(i),dhpb1(i),forcon(i),
6210 & 0.5d0*waga*rdis*rdis,irestr_type(i)
6212 C Evaluate gradient.
6216 c Calculate Cartesian gradient
6218 ggg(j)=fac*(c(j,jj)-c(j,ii))
6220 cd print '(i3,3(1pe14.5))',i,(ggg(j),j=1,3)
6221 C If this is a SC-SC distance, we need to calculate the contributions to the
6222 C Cartesian gradient in the SC vectors (ghpbx).
6225 ghpbx(j,iii)=ghpbx(j,iii)-ggg(j)
6230 ghpbx(j,jjj)=ghpbx(j,jjj)+ggg(j)
6234 ghpbc(k,jjj)=ghpbc(k,jjj)+ggg(k)
6235 ghpbc(k,iii)=ghpbc(k,iii)-ggg(k)
6241 C--------------------------------------------------------------------------
6242 subroutine ssbond_ene(i,j,eij)
6244 C Calculate the distance and angle dependent SS-bond potential energy
6245 C using a free-energy function derived based on RHF/6-31G** ab initio
6246 C calculations of diethyl disulfide.
6248 C A. Liwo and U. Kozlowska, 11/24/03
6250 implicit real*8 (a-h,o-z)
6251 include 'DIMENSIONS'
6252 include 'COMMON.SBRIDGE'
6253 include 'COMMON.CHAIN'
6254 include 'COMMON.DERIV'
6255 include 'COMMON.LOCAL'
6256 include 'COMMON.INTERACT'
6257 include 'COMMON.VAR'
6258 include 'COMMON.IOUNITS'
6259 double precision erij(3),dcosom1(3),dcosom2(3),gg(3)
6260 itypi=iabs(itype(i))
6264 dxi=dc_norm(1,nres+i)
6265 dyi=dc_norm(2,nres+i)
6266 dzi=dc_norm(3,nres+i)
6267 c dsci_inv=dsc_inv(itypi)
6268 dsci_inv=vbld_inv(nres+i)
6269 itypj=iabs(itype(j))
6270 c dscj_inv=dsc_inv(itypj)
6271 dscj_inv=vbld_inv(nres+j)
6275 dxj=dc_norm(1,nres+j)
6276 dyj=dc_norm(2,nres+j)
6277 dzj=dc_norm(3,nres+j)
6278 rrij=1.0D0/(xj*xj+yj*yj+zj*zj)
6283 om1=dxi*erij(1)+dyi*erij(2)+dzi*erij(3)
6284 om2=dxj*erij(1)+dyj*erij(2)+dzj*erij(3)
6285 om12=dxi*dxj+dyi*dyj+dzi*dzj
6287 dcosom1(k)=rij*(dc_norm(k,nres+i)-om1*erij(k))
6288 dcosom2(k)=rij*(dc_norm(k,nres+j)-om2*erij(k))
6294 deltat12=om2-om1+2.0d0
6296 eij=akcm*deltad*deltad+akth*(deltat1*deltat1+deltat2*deltat2)
6297 & +akct*deltad*deltat12
6298 & +v1ss*cosphi+v2ss*cosphi*cosphi+v3ss*cosphi*cosphi*cosphi+ebr
6299 c write(iout,*) i,j,"rij",rij,"d0cm",d0cm," akcm",akcm," akth",akth,
6300 c & " akct",akct," deltad",deltad," deltat",deltat1,deltat2,
6301 c & " deltat12",deltat12," eij",eij
6302 ed=2*akcm*deltad+akct*deltat12
6304 pom2=v1ss+2*v2ss*cosphi+3*v3ss*cosphi*cosphi
6305 eom1=-2*akth*deltat1-pom1-om2*pom2
6306 eom2= 2*akth*deltat2+pom1-om1*pom2
6309 ggk=ed*erij(k)+eom1*dcosom1(k)+eom2*dcosom2(k)
6310 ghpbx(k,i)=ghpbx(k,i)-ggk
6311 & +(eom12*(dc_norm(k,nres+j)-om12*dc_norm(k,nres+i))
6312 & +eom1*(erij(k)-om1*dc_norm(k,nres+i)))*dsci_inv
6313 ghpbx(k,j)=ghpbx(k,j)+ggk
6314 & +(eom12*(dc_norm(k,nres+i)-om12*dc_norm(k,nres+j))
6315 & +eom2*(erij(k)-om2*dc_norm(k,nres+j)))*dscj_inv
6316 ghpbc(k,i)=ghpbc(k,i)-ggk
6317 ghpbc(k,j)=ghpbc(k,j)+ggk
6320 C Calculate the components of the gradient in DC and X
6324 cgrad ghpbc(l,k)=ghpbc(l,k)+gg(l)
6329 C--------------------------------------------------------------------------
6330 subroutine ebond(estr)
6332 c Evaluate the energy of stretching of the CA-CA and CA-SC virtual bonds
6334 implicit real*8 (a-h,o-z)
6335 include 'DIMENSIONS'
6336 include 'COMMON.LOCAL'
6337 include 'COMMON.GEO'
6338 include 'COMMON.INTERACT'
6339 include 'COMMON.DERIV'
6340 include 'COMMON.VAR'
6341 include 'COMMON.CHAIN'
6342 include 'COMMON.IOUNITS'
6343 include 'COMMON.NAMES'
6344 include 'COMMON.FFIELD'
6345 include 'COMMON.CONTROL'
6346 include 'COMMON.SETUP'
6347 double precision u(3),ud(3)
6350 do i=ibondp_start,ibondp_end
6351 c 3/4/2020 Adam: removed dummy bond graient if Calpha and SC coords are
6354 if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) cycle
6355 diff = vbld(i)-vbldp0
6357 if (itype(i-1).eq.ntyp1 .and. itype(i).eq.ntyp1) cycle
6358 c estr1=estr1+gnmr1(vbld(i),-1.0d0,distchainmax)
6360 c gradb(j,i-1)=gnmr1prim(vbld(i),-1.0d0,distchainmax)
6361 c & *dc(j,i-1)/vbld(i)
6363 c if (energy_dec) write(iout,*)
6364 c & "estr1",i,gnmr1(vbld(i),-1.0d0,distchainmax)
6366 C Checking if it involves dummy (NH3+ or COO-) group
6367 if (itype(i-1).eq.ntyp1 .or. itype(i).eq.ntyp1) then
6368 C YES vbldpDUM is the equlibrium length of spring for Dummy atom
6369 diff = vbld(i)-vbldpDUM
6370 if (energy_dec) write(iout,*) "dum_bond",i,diff
6372 C NO vbldp0 is the equlibrium length of spring for peptide group
6373 diff = vbld(i)-vbldp0
6376 if (energy_dec) write (iout,'(a7,i5,4f7.3)')
6377 & "estr bb",i,vbld(i),vbldp0,diff,AKP*diff*diff
6380 gradb(j,i-1)=AKP*diff*dc(j,i-1)/vbld(i)
6382 c write (iout,'(i5,3f10.5)') i,(gradb(j,i-1),j=1,3)
6386 estr=0.5d0*AKP*estr+estr1
6388 c 09/18/07 AL: multimodal bond potential based on AM1 CA-SC PMF's included
6390 do i=ibond_start,ibond_end
6392 if (iti.ne.10 .and. iti.ne.ntyp1) then
6395 diff=vbld(i+nres)-vbldsc0(1,iti)
6396 if (energy_dec) write (iout,*)
6397 & "estr sc",i,iti,vbld(i+nres),vbldsc0(1,iti),diff,
6398 & AKSC(1,iti),AKSC(1,iti)*diff*diff
6399 estr=estr+0.5d0*AKSC(1,iti)*diff*diff
6401 gradbx(j,i)=AKSC(1,iti)*diff*dc(j,i+nres)/vbld(i+nres)
6405 diff=vbld(i+nres)-vbldsc0(j,iti)
6406 ud(j)=aksc(j,iti)*diff
6407 u(j)=abond0(j,iti)+0.5d0*ud(j)*diff
6421 uprod2=uprod2*u(k)*u(k)
6425 usumsqder=usumsqder+ud(j)*uprod2
6427 estr=estr+uprod/usum
6429 gradbx(j,i)=usumsqder/(usum*usum)*dc(j,i+nres)/vbld(i+nres)
6437 C--------------------------------------------------------------------------
6438 subroutine ebend(etheta)
6440 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
6441 C angles gamma and its derivatives in consecutive thetas and gammas.
6443 implicit real*8 (a-h,o-z)
6444 include 'DIMENSIONS'
6445 include 'COMMON.LOCAL'
6446 include 'COMMON.GEO'
6447 include 'COMMON.INTERACT'
6448 include 'COMMON.DERIV'
6449 include 'COMMON.VAR'
6450 include 'COMMON.CHAIN'
6451 include 'COMMON.IOUNITS'
6452 include 'COMMON.NAMES'
6453 include 'COMMON.FFIELD'
6454 include 'COMMON.CONTROL'
6455 include 'COMMON.TORCNSTR'
6456 common /calcthet/ term1,term2,termm,diffak,ratak,
6457 & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
6458 & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
6459 double precision y(2),z(2)
6461 c time11=dexp(-2*time)
6464 c write (*,'(a,i2)') 'EBEND ICG=',icg
6465 do i=ithet_start,ithet_end
6466 if ((itype(i-1).eq.ntyp1).or.itype(i-2).eq.ntyp1
6467 & .or.itype(i).eq.ntyp1) cycle
6468 C Zero the energy function and its derivative at 0 or pi.
6469 call splinthet(theta(i),0.5d0*delta,ss,ssd)
6471 ichir1=isign(1,itype(i-2))
6472 ichir2=isign(1,itype(i))
6473 if (itype(i-2).eq.10) ichir1=isign(1,itype(i-1))
6474 if (itype(i).eq.10) ichir2=isign(1,itype(i-1))
6475 if (itype(i-1).eq.10) then
6476 itype1=isign(10,itype(i-2))
6477 ichir11=isign(1,itype(i-2))
6478 ichir12=isign(1,itype(i-2))
6479 itype2=isign(10,itype(i))
6480 ichir21=isign(1,itype(i))
6481 ichir22=isign(1,itype(i))
6484 if (i.gt.3 .and. itype(i-3).ne.ntyp1) then
6487 if (phii.ne.phii) phii=150.0
6497 if (i.lt.nres .and. itype(i+1).ne.ntyp1) then
6500 if (phii1.ne.phii1) phii1=150.0
6512 C Calculate the "mean" value of theta from the part of the distribution
6513 C dependent on the adjacent virtual-bond-valence angles (gamma1 & gamma2).
6514 C In following comments this theta will be referred to as t_c.
6515 thet_pred_mean=0.0d0
6517 athetk=athet(k,it,ichir1,ichir2)
6518 bthetk=bthet(k,it,ichir1,ichir2)
6520 athetk=athet(k,itype1,ichir11,ichir12)
6521 bthetk=bthet(k,itype2,ichir21,ichir22)
6523 thet_pred_mean=thet_pred_mean+athetk*y(k)+bthetk*z(k)
6524 c write(iout,*) 'chuj tu', y(k),z(k)
6526 dthett=thet_pred_mean*ssd
6527 thet_pred_mean=thet_pred_mean*ss+a0thet(it)
6528 C Derivatives of the "mean" values in gamma1 and gamma2.
6529 dthetg1=(-athet(1,it,ichir1,ichir2)*y(2)
6530 &+athet(2,it,ichir1,ichir2)*y(1))*ss
6531 dthetg2=(-bthet(1,it,ichir1,ichir2)*z(2)
6532 & +bthet(2,it,ichir1,ichir2)*z(1))*ss
6534 dthetg1=(-athet(1,itype1,ichir11,ichir12)*y(2)
6535 &+athet(2,itype1,ichir11,ichir12)*y(1))*ss
6536 dthetg2=(-bthet(1,itype2,ichir21,ichir22)*z(2)
6537 & +bthet(2,itype2,ichir21,ichir22)*z(1))*ss
6539 if (theta(i).gt.pi-delta) then
6540 call theteng(pi-delta,thet_pred_mean,theta0(it),f0,fprim0,
6542 call mixder(pi-delta,thet_pred_mean,theta0(it),fprim_tc0)
6543 call theteng(pi,thet_pred_mean,theta0(it),f1,fprim1,E_tc1)
6544 call spline1(theta(i),pi-delta,delta,f0,f1,fprim0,ethetai,
6546 call spline2(theta(i),pi-delta,delta,E_tc0,E_tc1,fprim_tc0,
6548 else if (theta(i).lt.delta) then
6549 call theteng(delta,thet_pred_mean,theta0(it),f0,fprim0,E_tc0)
6550 call theteng(0.0d0,thet_pred_mean,theta0(it),f1,fprim1,E_tc1)
6551 call spline1(theta(i),delta,-delta,f0,f1,fprim0,ethetai,
6553 call mixder(delta,thet_pred_mean,theta0(it),fprim_tc0)
6554 call spline2(theta(i),delta,-delta,E_tc0,E_tc1,fprim_tc0,
6557 call theteng(theta(i),thet_pred_mean,theta0(it),ethetai,
6560 etheta=etheta+ethetai
6561 if (energy_dec) write (iout,'(a6,i5,0pf7.3,f7.3,i5)')
6562 & 'ebend',i,ethetai,theta(i),itype(i)
6563 if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*E_tc*dthetg1
6564 if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*E_tc*dthetg2
6565 gloc(nphi+i-2,icg)=wang*(E_theta+E_tc*dthett)+gloc(nphi+i-2,icg)
6568 C Ufff.... We've done all this!!!
6571 C---------------------------------------------------------------------------
6572 subroutine theteng(thetai,thet_pred_mean,theta0i,ethetai,E_theta,
6574 implicit real*8 (a-h,o-z)
6575 include 'DIMENSIONS'
6576 include 'COMMON.LOCAL'
6577 include 'COMMON.IOUNITS'
6578 common /calcthet/ term1,term2,termm,diffak,ratak,
6579 & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
6580 & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
6581 C Calculate the contributions to both Gaussian lobes.
6582 C 6/6/97 - Deform the Gaussians using the factor of 1/(1+time)
6583 C The "polynomial part" of the "standard deviation" of this part of
6584 C the distributioni.
6585 ccc write (iout,*) thetai,thet_pred_mean
6588 sig=sig*thet_pred_mean+polthet(j,it)
6590 C Derivative of the "interior part" of the "standard deviation of the"
6591 C gamma-dependent Gaussian lobe in t_c.
6592 sigtc=3*polthet(3,it)
6594 sigtc=sigtc*thet_pred_mean+j*polthet(j,it)
6597 C Set the parameters of both Gaussian lobes of the distribution.
6598 C "Standard deviation" of the gamma-dependent Gaussian lobe (sigtc)
6599 fac=sig*sig+sigc0(it)
6602 C Following variable (sigsqtc) is -(1/2)d[sigma(t_c)**(-2))]/dt_c
6603 sigsqtc=-4.0D0*sigcsq*sigtc
6604 c print *,i,sig,sigtc,sigsqtc
6605 C Following variable (sigtc) is d[sigma(t_c)]/dt_c
6606 sigtc=-sigtc/(fac*fac)
6607 C Following variable is sigma(t_c)**(-2)
6608 sigcsq=sigcsq*sigcsq
6610 sig0inv=1.0D0/sig0i**2
6611 delthec=thetai-thet_pred_mean
6612 delthe0=thetai-theta0i
6613 term1=-0.5D0*sigcsq*delthec*delthec
6614 term2=-0.5D0*sig0inv*delthe0*delthe0
6615 C write (iout,*)'term1',term1,term2,sigcsq,delthec,sig0inv,delthe0
6616 C Following fuzzy logic is to avoid underflows in dexp and subsequent INFs and
6617 C NaNs in taking the logarithm. We extract the largest exponent which is added
6618 C to the energy (this being the log of the distribution) at the end of energy
6619 C term evaluation for this virtual-bond angle.
6620 if (term1.gt.term2) then
6622 term2=dexp(term2-termm)
6626 term1=dexp(term1-termm)
6629 C The ratio between the gamma-independent and gamma-dependent lobes of
6630 C the distribution is a Gaussian function of thet_pred_mean too.
6631 diffak=gthet(2,it)-thet_pred_mean
6632 ratak=diffak/gthet(3,it)**2
6633 ak=dexp(gthet(1,it)-0.5D0*diffak*ratak)
6634 C Let's differentiate it in thet_pred_mean NOW.
6636 C Now put together the distribution terms to make complete distribution.
6637 termexp=term1+ak*term2
6638 termpre=sigc+ak*sig0i
6639 C Contribution of the bending energy from this theta is just the -log of
6640 C the sum of the contributions from the two lobes and the pre-exponential
6641 C factor. Simple enough, isn't it?
6642 ethetai=(-dlog(termexp)-termm+dlog(termpre))
6643 C write (iout,*) 'termexp',termexp,termm,termpre,i
6644 C NOW the derivatives!!!
6645 C 6/6/97 Take into account the deformation.
6646 E_theta=(delthec*sigcsq*term1
6647 & +ak*delthe0*sig0inv*term2)/termexp
6648 E_tc=((sigtc+aktc*sig0i)/termpre
6649 & -((delthec*sigcsq+delthec*delthec*sigsqtc)*term1+
6650 & aktc*term2)/termexp)
6653 c-----------------------------------------------------------------------------
6654 subroutine mixder(thetai,thet_pred_mean,theta0i,E_tc_t)
6655 implicit real*8 (a-h,o-z)
6656 include 'DIMENSIONS'
6657 include 'COMMON.LOCAL'
6658 include 'COMMON.IOUNITS'
6659 common /calcthet/ term1,term2,termm,diffak,ratak,
6660 & ak,aktc,termpre,termexp,sigc,sig0i,time11,time12,sigcsq,
6661 & delthe0,sig0inv,sigtc,sigsqtc,delthec,it
6662 delthec=thetai-thet_pred_mean
6663 delthe0=thetai-theta0i
6664 C "Thank you" to MAPLE (probably spared one day of hand-differentiation).
6665 t3 = thetai-thet_pred_mean
6669 t14 = t12+t6*sigsqtc
6671 t21 = thetai-theta0i
6677 E_tc_t = -((sigcsq+2.D0*t3*sigsqtc)*t9-t14*sigcsq*t3*t16*t9
6678 & -aktc*sig0inv*t27)/t32+(t14*t9+aktc*t26)/t40
6679 & *(-t12*t9-ak*sig0inv*t27)
6683 C--------------------------------------------------------------------------
6684 subroutine ebend(etheta)
6686 C Evaluate the virtual-bond-angle energy given the virtual-bond dihedral
6687 C angles gamma and its derivatives in consecutive thetas and gammas.
6688 C ab initio-derived potentials from
6689 c Kozlowska et al., J. Phys.: Condens. Matter 19 (2007) 285203
6691 implicit real*8 (a-h,o-z)
6692 include 'DIMENSIONS'
6693 include 'COMMON.LOCAL'
6694 include 'COMMON.GEO'
6695 include 'COMMON.INTERACT'
6696 include 'COMMON.DERIV'
6697 include 'COMMON.VAR'
6698 include 'COMMON.CHAIN'
6699 include 'COMMON.IOUNITS'
6700 include 'COMMON.NAMES'
6701 include 'COMMON.FFIELD'
6702 include 'COMMON.CONTROL'
6703 include 'COMMON.TORCNSTR'
6704 double precision coskt(mmaxtheterm),sinkt(mmaxtheterm),
6705 & cosph1(maxsingle),sinph1(maxsingle),cosph2(maxsingle),
6706 & sinph2(maxsingle),cosph1ph2(maxdouble,maxdouble),
6707 & sinph1ph2(maxdouble,maxdouble)
6708 logical lprn /.false./, lprn1 /.false./
6710 do i=ithet_start,ithet_end
6711 c print *,i,itype(i-1),itype(i),itype(i-2)
6712 if ((itype(i-1).eq.ntyp1).or.itype(i-2).eq.ntyp1
6713 & .or.itype(i).eq.ntyp1) cycle
6714 C print *,i,theta(i)
6715 if (iabs(itype(i+1)).eq.20) iblock=2
6716 if (iabs(itype(i+1)).ne.20) iblock=1
6720 theti2=0.5d0*theta(i)
6721 ityp2=ithetyp((itype(i-1)))
6723 coskt(k)=dcos(k*theti2)
6724 sinkt(k)=dsin(k*theti2)
6727 if (i.gt.3 .and. itype(i-3).ne.ntyp1) then
6730 if (phii.ne.phii) phii=150.0
6734 ityp1=ithetyp((itype(i-2)))
6735 C propagation of chirality for glycine type
6737 cosph1(k)=dcos(k*phii)
6738 sinph1(k)=dsin(k*phii)
6743 ityp1=ithetyp((itype(i-2)))
6748 if (i.lt.nres .and. itype(i+1).ne.ntyp1) then
6751 if (phii1.ne.phii1) phii1=150.0
6756 ityp3=ithetyp((itype(i)))
6758 cosph2(k)=dcos(k*phii1)
6759 sinph2(k)=dsin(k*phii1)
6763 ityp3=ithetyp((itype(i)))
6769 ethetai=aa0thet(ityp1,ityp2,ityp3,iblock)
6772 ccl=cosph1(l)*cosph2(k-l)
6773 ssl=sinph1(l)*sinph2(k-l)
6774 scl=sinph1(l)*cosph2(k-l)
6775 csl=cosph1(l)*sinph2(k-l)
6776 cosph1ph2(l,k)=ccl-ssl
6777 cosph1ph2(k,l)=ccl+ssl
6778 sinph1ph2(l,k)=scl+csl
6779 sinph1ph2(k,l)=scl-csl
6783 write (iout,*) "i",i," ityp1",ityp1," ityp2",ityp2,
6784 & " ityp3",ityp3," theti2",theti2," phii",phii," phii1",phii1
6785 write (iout,*) "coskt and sinkt"
6787 write (iout,*) k,coskt(k),sinkt(k)
6791 ethetai=ethetai+aathet(k,ityp1,ityp2,ityp3,iblock)*sinkt(k)
6792 dethetai=dethetai+0.5d0*k*aathet(k,ityp1,ityp2,ityp3,iblock)
6795 & write (iout,*) "k",k,"
6796 & aathet",aathet(k,ityp1,ityp2,ityp3,iblock),
6797 & " ethetai",ethetai
6800 write (iout,*) "cosph and sinph"
6802 write (iout,*) k,cosph1(k),sinph1(k),cosph2(k),sinph2(k)
6804 write (iout,*) "cosph1ph2 and sinph2ph2"
6807 write (iout,*) l,k,cosph1ph2(l,k),cosph1ph2(k,l),
6808 & sinph1ph2(l,k),sinph1ph2(k,l)
6811 write(iout,*) "ethetai",ethetai
6816 aux=bbthet(k,m,ityp1,ityp2,ityp3,iblock)*cosph1(k)
6817 & +ccthet(k,m,ityp1,ityp2,ityp3,iblock)*sinph1(k)
6818 & +ddthet(k,m,ityp1,ityp2,ityp3,iblock)*cosph2(k)
6819 & +eethet(k,m,ityp1,ityp2,ityp3,iblock)*sinph2(k)
6820 ethetai=ethetai+sinkt(m)*aux
6821 dethetai=dethetai+0.5d0*m*aux*coskt(m)
6822 dephii=dephii+k*sinkt(m)*(
6823 & ccthet(k,m,ityp1,ityp2,ityp3,iblock)*cosph1(k)-
6824 & bbthet(k,m,ityp1,ityp2,ityp3,iblock)*sinph1(k))
6825 dephii1=dephii1+k*sinkt(m)*(
6826 & eethet(k,m,ityp1,ityp2,ityp3,iblock)*cosph2(k)-
6827 & ddthet(k,m,ityp1,ityp2,ityp3,iblock)*sinph2(k))
6829 & write (iout,*) "m",m," k",k," bbthet",
6830 & bbthet(k,m,ityp1,ityp2,ityp3,iblock)," ccthet",
6831 & ccthet(k,m,ityp1,ityp2,ityp3,iblock)," ddthet",
6832 & ddthet(k,m,ityp1,ityp2,ityp3,iblock)," eethet",
6833 & eethet(k,m,ityp1,ityp2,ityp3,iblock)," ethetai",ethetai
6834 C print *,"tu",cosph1(k),sinph1(k),cosph2(k),sinph2(k)
6837 C print *,"cosph1", (cosph1(k), k=1,nsingle)
6838 C print *,"cosph2", (cosph2(k), k=1,nsingle)
6839 C print *,"sinph1", (sinph1(k), k=1,nsingle)
6840 C print *,"sinph2", (sinph2(k), k=1,nsingle)
6842 & write(iout,*) "ethetai",ethetai
6843 C print *,"tu",cosph1(k),sinph1(k),cosph2(k),sinph2(k)
6847 aux=ffthet(l,k,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(l,k)+
6848 & ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(k,l)+
6849 & ggthet(l,k,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(l,k)+
6850 & ggthet(k,l,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(k,l)
6851 ethetai=ethetai+sinkt(m)*aux
6852 dethetai=dethetai+0.5d0*m*coskt(m)*aux
6853 dephii=dephii+l*sinkt(m)*(
6854 & -ffthet(l,k,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(l,k)-
6855 & ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(k,l)+
6856 & ggthet(l,k,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(l,k)+
6857 & ggthet(k,l,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(k,l))
6858 dephii1=dephii1+(k-l)*sinkt(m)*(
6859 & -ffthet(l,k,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(l,k)+
6860 & ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)*sinph1ph2(k,l)+
6861 & ggthet(l,k,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(l,k)-
6862 & ggthet(k,l,m,ityp1,ityp2,ityp3,iblock)*cosph1ph2(k,l))
6864 write (iout,*) "m",m," k",k," l",l," ffthet",
6865 & ffthet(l,k,m,ityp1,ityp2,ityp3,iblock),
6866 & ffthet(k,l,m,ityp1,ityp2,ityp3,iblock)," ggthet",
6867 & ggthet(l,k,m,ityp1,ityp2,ityp3,iblock),
6868 & ggthet(k,l,m,ityp1,ityp2,ityp3,iblock),
6869 & " ethetai",ethetai
6870 write (iout,*) cosph1ph2(l,k)*sinkt(m),
6871 & cosph1ph2(k,l)*sinkt(m),
6872 & sinph1ph2(l,k)*sinkt(m),sinph1ph2(k,l)*sinkt(m)
6881 & write (iout,'(i2,3f8.1,9h ethetai ,f10.5)')
6882 & i,theta(i)*rad2deg,phii*rad2deg,
6883 & phii1*rad2deg,ethetai
6885 etheta=etheta+ethetai
6886 if (i.gt.3) gloc(i-3,icg)=gloc(i-3,icg)+wang*dephii
6887 if (i.lt.nres) gloc(i-2,icg)=gloc(i-2,icg)+wang*dephii1
6888 gloc(nphi+i-2,icg)=gloc(nphi+i-2,icg)+wang*dethetai
6895 c-----------------------------------------------------------------------------
6896 subroutine esc(escloc)
6897 C Calculate the local energy of a side chain and its derivatives in the
6898 C corresponding virtual-bond valence angles THETA and the spherical angles
6900 implicit real*8 (a-h,o-z)
6901 include 'DIMENSIONS'
6902 include 'COMMON.GEO'
6903 include 'COMMON.LOCAL'
6904 include 'COMMON.VAR'
6905 include 'COMMON.INTERACT'
6906 include 'COMMON.DERIV'
6907 include 'COMMON.CHAIN'
6908 include 'COMMON.IOUNITS'
6909 include 'COMMON.NAMES'
6910 include 'COMMON.FFIELD'
6911 include 'COMMON.CONTROL'
6912 double precision x(3),dersc(3),xemp(3),dersc0(3),dersc1(3),
6913 & ddersc0(3),ddummy(3),xtemp(3),temp(3)
6914 common /sccalc/ time11,time12,time112,theti,it,nlobit
6917 c write (iout,'(a)') 'ESC'
6918 do i=loc_start,loc_end
6920 if (it.eq.ntyp1) cycle
6921 if (it.eq.10) goto 1
6922 nlobit=nlob(iabs(it))
6923 c print *,'i=',i,' it=',it,' nlobit=',nlobit
6924 c write (iout,*) 'i=',i,' ssa=',ssa,' ssad=',ssad
6925 theti=theta(i+1)-pipol
6930 if (x(2).gt.pi-delta) then
6934 call enesc(xtemp,escloci0,dersc0,ddersc0,.true.)
6936 call enesc(xtemp,escloci1,dersc1,ddummy,.false.)
6937 call spline1(x(2),pi-delta,delta,escloci0,escloci1,dersc0(2),
6939 call spline2(x(2),pi-delta,delta,dersc0(1),dersc1(1),
6940 & ddersc0(1),dersc(1))
6941 call spline2(x(2),pi-delta,delta,dersc0(3),dersc1(3),
6942 & ddersc0(3),dersc(3))
6944 call enesc_bound(xtemp,esclocbi0,dersc0,dersc12,.true.)
6946 call enesc_bound(xtemp,esclocbi1,dersc1,chuju,.false.)
6947 call spline1(x(2),pi-delta,delta,esclocbi0,esclocbi1,
6948 & dersc0(2),esclocbi,dersc02)
6949 call spline2(x(2),pi-delta,delta,dersc0(1),dersc1(1),
6951 call splinthet(x(2),0.5d0*delta,ss,ssd)
6956 dersc(k)=ss*dersc(k)+(1.0d0-ss)*dersc0(k)
6958 dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
6959 c write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
6961 escloci=ss*escloci+(1.0d0-ss)*esclocbi
6963 c write (iout,*) escloci
6964 else if (x(2).lt.delta) then
6968 call enesc(xtemp,escloci0,dersc0,ddersc0,.true.)
6970 call enesc(xtemp,escloci1,dersc1,ddummy,.false.)
6971 call spline1(x(2),delta,-delta,escloci0,escloci1,dersc0(2),
6973 call spline2(x(2),delta,-delta,dersc0(1),dersc1(1),
6974 & ddersc0(1),dersc(1))
6975 call spline2(x(2),delta,-delta,dersc0(3),dersc1(3),
6976 & ddersc0(3),dersc(3))
6978 call enesc_bound(xtemp,esclocbi0,dersc0,dersc12,.true.)
6980 call enesc_bound(xtemp,esclocbi1,dersc1,chuju,.false.)
6981 call spline1(x(2),delta,-delta,esclocbi0,esclocbi1,
6982 & dersc0(2),esclocbi,dersc02)
6983 call spline2(x(2),delta,-delta,dersc0(1),dersc1(1),
6988 call splinthet(x(2),0.5d0*delta,ss,ssd)
6990 dersc(k)=ss*dersc(k)+(1.0d0-ss)*dersc0(k)
6992 dersc(2)=dersc(2)+ssd*(escloci-esclocbi)
6993 c write (iout,*) 'i=',i,x(2)*rad2deg,escloci0,escloci,
6995 escloci=ss*escloci+(1.0d0-ss)*esclocbi
6996 c write (iout,*) escloci
6998 call enesc(x,escloci,dersc,ddummy,.false.)
7001 escloc=escloc+escloci
7002 if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
7003 & 'escloc',i,escloci
7004 c write (iout,*) 'i=',i,' escloci=',escloci,' dersc=',dersc
7006 gloc(nphi+i-1,icg)=gloc(nphi+i-1,icg)+
7008 gloc(ialph(i,1),icg)=wscloc*dersc(2)
7009 gloc(ialph(i,1)+nside,icg)=wscloc*dersc(3)
7014 C---------------------------------------------------------------------------
7015 subroutine enesc(x,escloci,dersc,ddersc,mixed)
7016 implicit real*8 (a-h,o-z)
7017 include 'DIMENSIONS'
7018 include 'COMMON.GEO'
7019 include 'COMMON.LOCAL'
7020 include 'COMMON.IOUNITS'
7021 common /sccalc/ time11,time12,time112,theti,it,nlobit
7022 double precision x(3),z(3),Ax(3,maxlob,-1:1),dersc(3),ddersc(3)
7023 double precision contr(maxlob,-1:1)
7025 c write (iout,*) 'it=',it,' nlobit=',nlobit
7029 if (mixed) ddersc(j)=0.0d0
7033 C Because of periodicity of the dependence of the SC energy in omega we have
7034 C to add up the contributions from x(3)-2*pi, x(3), and x(3+2*pi).
7035 C To avoid underflows, first compute & store the exponents.
7043 z(k)=x(k)-censc(k,j,it)
7048 Axk=Axk+gaussc(l,k,j,it)*z(l)
7054 expfac=expfac+Ax(k,j,iii)*z(k)
7062 C As in the case of ebend, we want to avoid underflows in exponentiation and
7063 C subsequent NaNs and INFs in energy calculation.
7064 C Find the largest exponent
7068 if (emin.gt.contr(j,iii)) emin=contr(j,iii)
7072 cd print *,'it=',it,' emin=',emin
7074 C Compute the contribution to SC energy and derivatives
7079 adexp=bsc(j,iabs(it))-0.5D0*contr(j,iii)+emin
7080 if(adexp.ne.adexp) adexp=1.0
7083 expfac=dexp(bsc(j,iabs(it))-0.5D0*contr(j,iii)+emin)
7085 cd print *,'j=',j,' expfac=',expfac
7086 escloc_i=escloc_i+expfac
7088 dersc(k)=dersc(k)+Ax(k,j,iii)*expfac
7092 ddersc(k)=ddersc(k)+(-Ax(2,j,iii)*Ax(k,j,iii)
7093 & +gaussc(k,2,j,it))*expfac
7100 dersc(1)=dersc(1)/cos(theti)**2
7101 ddersc(1)=ddersc(1)/cos(theti)**2
7104 escloci=-(dlog(escloc_i)-emin)
7106 dersc(j)=dersc(j)/escloc_i
7110 ddersc(j)=(ddersc(j)/escloc_i+dersc(2)*dersc(j))
7115 C------------------------------------------------------------------------------
7116 subroutine enesc_bound(x,escloci,dersc,dersc12,mixed)
7117 implicit real*8 (a-h,o-z)
7118 include 'DIMENSIONS'
7119 include 'COMMON.GEO'
7120 include 'COMMON.LOCAL'
7121 include 'COMMON.IOUNITS'
7122 common /sccalc/ time11,time12,time112,theti,it,nlobit
7123 double precision x(3),z(3),Ax(3,maxlob),dersc(3)
7124 double precision contr(maxlob)
7135 z(k)=x(k)-censc(k,j,it)
7141 Axk=Axk+gaussc(l,k,j,it)*z(l)
7147 expfac=expfac+Ax(k,j)*z(k)
7152 C As in the case of ebend, we want to avoid underflows in exponentiation and
7153 C subsequent NaNs and INFs in energy calculation.
7154 C Find the largest exponent
7157 if (emin.gt.contr(j)) emin=contr(j)
7161 C Compute the contribution to SC energy and derivatives
7165 expfac=dexp(bsc(j,iabs(it))-0.5D0*contr(j)+emin)
7166 escloc_i=escloc_i+expfac
7168 dersc(k)=dersc(k)+Ax(k,j)*expfac
7170 if (mixed) dersc12=dersc12+(-Ax(2,j)*Ax(1,j)
7171 & +gaussc(1,2,j,it))*expfac
7175 dersc(1)=dersc(1)/cos(theti)**2
7176 dersc12=dersc12/cos(theti)**2
7177 escloci=-(dlog(escloc_i)-emin)
7179 dersc(j)=dersc(j)/escloc_i
7181 if (mixed) dersc12=(dersc12/escloc_i+dersc(2)*dersc(1))
7185 c----------------------------------------------------------------------------------
7186 subroutine esc(escloc)
7187 C Calculate the local energy of a side chain and its derivatives in the
7188 C corresponding virtual-bond valence angles THETA and the spherical angles
7189 C ALPHA and OMEGA derived from AM1 all-atom calculations.
7190 C added by Urszula Kozlowska. 07/11/2007
7192 implicit real*8 (a-h,o-z)
7193 include 'DIMENSIONS'
7194 include 'COMMON.GEO'
7195 include 'COMMON.LOCAL'
7196 include 'COMMON.VAR'
7197 include 'COMMON.SCROT'
7198 include 'COMMON.INTERACT'
7199 include 'COMMON.DERIV'
7200 include 'COMMON.CHAIN'
7201 include 'COMMON.IOUNITS'
7202 include 'COMMON.NAMES'
7203 include 'COMMON.FFIELD'
7204 include 'COMMON.CONTROL'
7205 include 'COMMON.VECTORS'
7206 double precision x_prime(3),y_prime(3),z_prime(3)
7207 & , sumene,dsc_i,dp2_i,x(65),
7208 & xx,yy,zz,sumene1,sumene2,sumene3,sumene4,s1,s1_6,s2,s2_6,
7209 & de_dxx,de_dyy,de_dzz,de_dt
7210 double precision s1_t,s1_6_t,s2_t,s2_6_t
7212 & dXX_Ci1(3),dYY_Ci1(3),dZZ_Ci1(3),dXX_Ci(3),
7213 & dYY_Ci(3),dZZ_Ci(3),dXX_XYZ(3),dYY_XYZ(3),dZZ_XYZ(3),
7214 & dt_dCi(3),dt_dCi1(3)
7215 common /sccalc/ time11,time12,time112,theti,it,nlobit
7218 do i=loc_start,loc_end
7219 if (itype(i).eq.ntyp1) cycle
7220 costtab(i+1) =dcos(theta(i+1))
7221 sinttab(i+1) =dsqrt(1-costtab(i+1)*costtab(i+1))
7222 cost2tab(i+1)=dsqrt(0.5d0*(1.0d0+costtab(i+1)))
7223 sint2tab(i+1)=dsqrt(0.5d0*(1.0d0-costtab(i+1)))
7224 cosfac2=0.5d0/(1.0d0+costtab(i+1))
7225 cosfac=dsqrt(cosfac2)
7226 sinfac2=0.5d0/(1.0d0-costtab(i+1))
7227 sinfac=dsqrt(sinfac2)
7229 if (it.eq.10) goto 1
7231 C Compute the axes of tghe local cartesian coordinates system; store in
7232 c x_prime, y_prime and z_prime
7239 C write(2,*) "dc_norm", dc_norm(1,i+nres),dc_norm(2,i+nres),
7240 C & dc_norm(3,i+nres)
7242 x_prime(j) = (dc_norm(j,i) - dc_norm(j,i-1))*cosfac
7243 y_prime(j) = (dc_norm(j,i) + dc_norm(j,i-1))*sinfac
7246 z_prime(j) = -uz(j,i-1)*dsign(1.0d0,dfloat(itype(i)))
7249 c write (2,*) "x_prime",(x_prime(j),j=1,3)
7250 c write (2,*) "y_prime",(y_prime(j),j=1,3)
7251 c write (2,*) "z_prime",(z_prime(j),j=1,3)
7252 c write (2,*) "xx",scalar(x_prime(1),x_prime(1)),
7253 c & " xy",scalar(x_prime(1),y_prime(1)),
7254 c & " xz",scalar(x_prime(1),z_prime(1)),
7255 c & " yy",scalar(y_prime(1),y_prime(1)),
7256 c & " yz",scalar(y_prime(1),z_prime(1)),
7257 c & " zz",scalar(z_prime(1),z_prime(1))
7259 C Transform the unit vector of the ith side-chain centroid, dC_norm(*,i),
7260 C to local coordinate system. Store in xx, yy, zz.
7266 xx = xx + x_prime(j)*dc_norm(j,i+nres)
7267 yy = yy + y_prime(j)*dc_norm(j,i+nres)
7268 zz = zz + z_prime(j)*dc_norm(j,i+nres)
7275 C Compute the energy of the ith side cbain
7277 c write (2,*) "xx",xx," yy",yy," zz",zz
7280 x(j) = sc_parmin(j,it)
7283 Cc diagnostics - remove later
7285 yy1 = dsin(alph(2))*dcos(omeg(2))
7286 zz1 = -dsign(1.0,dfloat(itype(i)))*dsin(alph(2))*dsin(omeg(2))
7287 write(2,'(3f8.1,3f9.3,1x,3f9.3)')
7288 & alph(2)*rad2deg,omeg(2)*rad2deg,theta(3)*rad2deg,xx,yy,zz,
7290 C," --- ", xx_w,yy_w,zz_w
7293 sumene1= x(1)+ x(2)*xx+ x(3)*yy+ x(4)*zz+ x(5)*xx**2
7294 & + x(6)*yy**2+ x(7)*zz**2+ x(8)*xx*zz+ x(9)*xx*yy
7296 sumene2= x(11) + x(12)*xx + x(13)*yy + x(14)*zz + x(15)*xx**2
7297 & + x(16)*yy**2 + x(17)*zz**2 + x(18)*xx*zz + x(19)*xx*yy
7299 sumene3= x(21) +x(22)*xx +x(23)*yy +x(24)*zz +x(25)*xx**2
7300 & +x(26)*yy**2 +x(27)*zz**2 +x(28)*xx*zz +x(29)*xx*yy
7301 & +x(30)*yy*zz +x(31)*xx**3 +x(32)*yy**3 +x(33)*zz**3
7302 & +x(34)*(xx**2)*yy +x(35)*(xx**2)*zz +x(36)*(yy**2)*xx
7303 & +x(37)*(yy**2)*zz +x(38)*(zz**2)*xx +x(39)*(zz**2)*yy
7305 sumene4= x(41) +x(42)*xx +x(43)*yy +x(44)*zz +x(45)*xx**2
7306 & +x(46)*yy**2 +x(47)*zz**2 +x(48)*xx*zz +x(49)*xx*yy
7307 & +x(50)*yy*zz +x(51)*xx**3 +x(52)*yy**3 +x(53)*zz**3
7308 & +x(54)*(xx**2)*yy +x(55)*(xx**2)*zz +x(56)*(yy**2)*xx
7309 & +x(57)*(yy**2)*zz +x(58)*(zz**2)*xx +x(59)*(zz**2)*yy
7311 dsc_i = 0.743d0+x(61)
7313 dscp1=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
7314 & *(xx*cost2tab(i+1)+yy*sint2tab(i+1)))
7315 dscp2=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
7316 & *(xx*cost2tab(i+1)-yy*sint2tab(i+1)))
7317 s1=(1+x(63))/(0.1d0 + dscp1)
7318 s1_6=(1+x(64))/(0.1d0 + dscp1**6)
7319 s2=(1+x(65))/(0.1d0 + dscp2)
7320 s2_6=(1+x(65))/(0.1d0 + dscp2**6)
7321 sumene = ( sumene3*sint2tab(i+1) + sumene1)*(s1+s1_6)
7322 & + (sumene4*cost2tab(i+1) +sumene2)*(s2+s2_6)
7323 c write(2,'(i2," sumene",7f9.3)') i,sumene1,sumene2,sumene3,
7325 c & dscp1,dscp2,sumene
7326 c sumene = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
7327 escloc = escloc + sumene
7328 if (energy_dec) write (2,*) "i",i," itype",itype(i)," it",it,
7329 & " escloc",sumene,escloc,it,itype(i)
7334 C This section to check the numerical derivatives of the energy of ith side
7335 C chain in xx, yy, zz, and theta. Use the -DDEBUG compiler option or insert
7336 C #define DEBUG in the code to turn it on.
7338 write (2,*) "sumene =",sumene
7342 write (2,*) xx,yy,zz
7343 sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
7344 de_dxx_num=(sumenep-sumene)/aincr
7346 write (2,*) "xx+ sumene from enesc=",sumenep
7349 write (2,*) xx,yy,zz
7350 sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
7351 de_dyy_num=(sumenep-sumene)/aincr
7353 write (2,*) "yy+ sumene from enesc=",sumenep
7356 write (2,*) xx,yy,zz
7357 sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
7358 de_dzz_num=(sumenep-sumene)/aincr
7360 write (2,*) "zz+ sumene from enesc=",sumenep
7361 costsave=cost2tab(i+1)
7362 sintsave=sint2tab(i+1)
7363 cost2tab(i+1)=dcos(0.5d0*(theta(i+1)+aincr))
7364 sint2tab(i+1)=dsin(0.5d0*(theta(i+1)+aincr))
7365 sumenep = enesc(x,xx,yy,zz,cost2tab(i+1),sint2tab(i+1))
7366 de_dt_num=(sumenep-sumene)/aincr
7367 write (2,*) " t+ sumene from enesc=",sumenep
7368 cost2tab(i+1)=costsave
7369 sint2tab(i+1)=sintsave
7370 C End of diagnostics section.
7373 C Compute the gradient of esc
7375 c zz=zz*dsign(1.0,dfloat(itype(i)))
7376 pom_s1=(1.0d0+x(63))/(0.1d0 + dscp1)**2
7377 pom_s16=6*(1.0d0+x(64))/(0.1d0 + dscp1**6)**2
7378 pom_s2=(1.0d0+x(65))/(0.1d0 + dscp2)**2
7379 pom_s26=6*(1.0d0+x(65))/(0.1d0 + dscp2**6)**2
7380 pom_dx=dsc_i*dp2_i*cost2tab(i+1)
7381 pom_dy=dsc_i*dp2_i*sint2tab(i+1)
7382 pom_dt1=-0.5d0*dsc_i*dp2_i*(xx*sint2tab(i+1)-yy*cost2tab(i+1))
7383 pom_dt2=-0.5d0*dsc_i*dp2_i*(xx*sint2tab(i+1)+yy*cost2tab(i+1))
7384 pom1=(sumene3*sint2tab(i+1)+sumene1)
7385 & *(pom_s1/dscp1+pom_s16*dscp1**4)
7386 pom2=(sumene4*cost2tab(i+1)+sumene2)
7387 & *(pom_s2/dscp2+pom_s26*dscp2**4)
7388 sumene1x=x(2)+2*x(5)*xx+x(8)*zz+ x(9)*yy
7389 sumene3x=x(22)+2*x(25)*xx+x(28)*zz+x(29)*yy+3*x(31)*xx**2
7390 & +2*x(34)*xx*yy +2*x(35)*xx*zz +x(36)*(yy**2) +x(38)*(zz**2)
7392 sumene2x=x(12)+2*x(15)*xx+x(18)*zz+ x(19)*yy
7393 sumene4x=x(42)+2*x(45)*xx +x(48)*zz +x(49)*yy +3*x(51)*xx**2
7394 & +2*x(54)*xx*yy+2*x(55)*xx*zz+x(56)*(yy**2)+x(58)*(zz**2)
7396 de_dxx =(sumene1x+sumene3x*sint2tab(i+1))*(s1+s1_6)
7397 & +(sumene2x+sumene4x*cost2tab(i+1))*(s2+s2_6)
7398 & +(pom1+pom2)*pom_dx
7400 write(2,*), "de_dxx = ", de_dxx,de_dxx_num,itype(i)
7403 sumene1y=x(3) + 2*x(6)*yy + x(9)*xx + x(10)*zz
7404 sumene3y=x(23) +2*x(26)*yy +x(29)*xx +x(30)*zz +3*x(32)*yy**2
7405 & +x(34)*(xx**2) +2*x(36)*yy*xx +2*x(37)*yy*zz +x(39)*(zz**2)
7407 sumene2y=x(13) + 2*x(16)*yy + x(19)*xx + x(20)*zz
7408 sumene4y=x(43)+2*x(46)*yy+x(49)*xx +x(50)*zz
7409 & +3*x(52)*yy**2+x(54)*xx**2+2*x(56)*yy*xx +2*x(57)*yy*zz
7410 & +x(59)*zz**2 +x(60)*xx*zz
7411 de_dyy =(sumene1y+sumene3y*sint2tab(i+1))*(s1+s1_6)
7412 & +(sumene2y+sumene4y*cost2tab(i+1))*(s2+s2_6)
7413 & +(pom1-pom2)*pom_dy
7415 write(2,*), "de_dyy = ", de_dyy,de_dyy_num,itype(i)
7418 de_dzz =(x(24) +2*x(27)*zz +x(28)*xx +x(30)*yy
7419 & +3*x(33)*zz**2 +x(35)*xx**2 +x(37)*yy**2 +2*x(38)*zz*xx
7420 & +2*x(39)*zz*yy +x(40)*xx*yy)*sint2tab(i+1)*(s1+s1_6)
7421 & +(x(4) + 2*x(7)*zz+ x(8)*xx + x(10)*yy)*(s1+s1_6)
7422 & +(x(44)+2*x(47)*zz +x(48)*xx +x(50)*yy +3*x(53)*zz**2
7423 & +x(55)*xx**2 +x(57)*(yy**2)+2*x(58)*zz*xx +2*x(59)*zz*yy
7424 & +x(60)*xx*yy)*cost2tab(i+1)*(s2+s2_6)
7425 & + ( x(14) + 2*x(17)*zz+ x(18)*xx + x(20)*yy)*(s2+s2_6)
7427 write(2,*), "de_dzz = ", de_dzz,de_dzz_num,itype(i)
7430 de_dt = 0.5d0*sumene3*cost2tab(i+1)*(s1+s1_6)
7431 & -0.5d0*sumene4*sint2tab(i+1)*(s2+s2_6)
7432 & +pom1*pom_dt1+pom2*pom_dt2
7434 write(2,*), "de_dt = ", de_dt,de_dt_num,itype(i)
7439 cossc=scalar(dc_norm(1,i),dc_norm(1,i+nres))
7440 cossc1=scalar(dc_norm(1,i-1),dc_norm(1,i+nres))
7441 cosfac2xx=cosfac2*xx
7442 sinfac2yy=sinfac2*yy
7444 dt_dCi(k) = -(dc_norm(k,i-1)+costtab(i+1)*dc_norm(k,i))*
7446 dt_dCi1(k)= -(dc_norm(k,i)+costtab(i+1)*dc_norm(k,i-1))*
7448 pom=(dC_norm(k,i+nres)-cossc*dC_norm(k,i))*vbld_inv(i+1)
7449 pom1=(dC_norm(k,i+nres)-cossc1*dC_norm(k,i-1))*vbld_inv(i)
7450 c write (iout,*) "i",i," k",k," pom",pom," pom1",pom1,
7451 c & " dt_dCi",dt_dCi(k)," dt_dCi1",dt_dCi1(k)
7452 c write (iout,*) "dC_norm",(dC_norm(j,i),j=1,3),
7453 c & (dC_norm(j,i-1),j=1,3)," vbld_inv",vbld_inv(i+1),vbld_inv(i)
7454 dXX_Ci(k)=pom*cosfac-dt_dCi(k)*cosfac2xx
7455 dXX_Ci1(k)=-pom1*cosfac-dt_dCi1(k)*cosfac2xx
7456 dYY_Ci(k)=pom*sinfac+dt_dCi(k)*sinfac2yy
7457 dYY_Ci1(k)=pom1*sinfac+dt_dCi1(k)*sinfac2yy
7461 dZZ_Ci(k)=dZZ_Ci(k)-uzgrad(j,k,2,i-1)
7462 & *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
7463 dZZ_Ci1(k)=dZZ_Ci1(k)-uzgrad(j,k,1,i-1)
7464 & *dsign(1.0d0,dfloat(itype(i)))*dC_norm(j,i+nres)
7467 dXX_XYZ(k)=vbld_inv(i+nres)*(x_prime(k)-xx*dC_norm(k,i+nres))
7468 dYY_XYZ(k)=vbld_inv(i+nres)*(y_prime(k)-yy*dC_norm(k,i+nres))
7469 dZZ_XYZ(k)=vbld_inv(i+nres)*
7470 & (z_prime(k)-zz*dC_norm(k,i+nres))
7472 dt_dCi(k) = -dt_dCi(k)/sinttab(i+1)
7473 dt_dCi1(k)= -dt_dCi1(k)/sinttab(i+1)
7477 dXX_Ctab(k,i)=dXX_Ci(k)
7478 dXX_C1tab(k,i)=dXX_Ci1(k)
7479 dYY_Ctab(k,i)=dYY_Ci(k)
7480 dYY_C1tab(k,i)=dYY_Ci1(k)
7481 dZZ_Ctab(k,i)=dZZ_Ci(k)
7482 dZZ_C1tab(k,i)=dZZ_Ci1(k)
7483 dXX_XYZtab(k,i)=dXX_XYZ(k)
7484 dYY_XYZtab(k,i)=dYY_XYZ(k)
7485 dZZ_XYZtab(k,i)=dZZ_XYZ(k)
7489 c write (iout,*) "k",k," dxx_ci1",dxx_ci1(k)," dyy_ci1",
7490 c & dyy_ci1(k)," dzz_ci1",dzz_ci1(k)
7491 c write (iout,*) "k",k," dxx_ci",dxx_ci(k)," dyy_ci",
7492 c & dyy_ci(k)," dzz_ci",dzz_ci(k)
7493 c write (iout,*) "k",k," dt_dci",dt_dci(k)," dt_dci",
7495 c write (iout,*) "k",k," dxx_XYZ",dxx_XYZ(k)," dyy_XYZ",
7496 c & dyy_XYZ(k)," dzz_XYZ",dzz_XYZ(k)
7497 gscloc(k,i-1)=gscloc(k,i-1)+de_dxx*dxx_ci1(k)
7498 & +de_dyy*dyy_ci1(k)+de_dzz*dzz_ci1(k)+de_dt*dt_dCi1(k)
7499 gscloc(k,i)=gscloc(k,i)+de_dxx*dxx_Ci(k)
7500 & +de_dyy*dyy_Ci(k)+de_dzz*dzz_Ci(k)+de_dt*dt_dCi(k)
7501 gsclocx(k,i)= de_dxx*dxx_XYZ(k)
7502 & +de_dyy*dyy_XYZ(k)+de_dzz*dzz_XYZ(k)
7504 c write(iout,*) "ENERGY GRAD = ", (gscloc(k,i-1),k=1,3),
7505 c & (gscloc(k,i),k=1,3),(gsclocx(k,i),k=1,3)
7507 C to check gradient call subroutine check_grad
7513 c------------------------------------------------------------------------------
7514 double precision function enesc(x,xx,yy,zz,cost2,sint2)
7516 double precision x(65),xx,yy,zz,cost2,sint2,sumene1,sumene2,
7517 & sumene3,sumene4,sumene,dsc_i,dp2_i,dscp1,dscp2,s1,s1_6,s2,s2_6
7518 sumene1= x(1)+ x(2)*xx+ x(3)*yy+ x(4)*zz+ x(5)*xx**2
7519 & + x(6)*yy**2+ x(7)*zz**2+ x(8)*xx*zz+ x(9)*xx*yy
7521 sumene2= x(11) + x(12)*xx + x(13)*yy + x(14)*zz + x(15)*xx**2
7522 & + x(16)*yy**2 + x(17)*zz**2 + x(18)*xx*zz + x(19)*xx*yy
7524 sumene3= x(21) +x(22)*xx +x(23)*yy +x(24)*zz +x(25)*xx**2
7525 & +x(26)*yy**2 +x(27)*zz**2 +x(28)*xx*zz +x(29)*xx*yy
7526 & +x(30)*yy*zz +x(31)*xx**3 +x(32)*yy**3 +x(33)*zz**3
7527 & +x(34)*(xx**2)*yy +x(35)*(xx**2)*zz +x(36)*(yy**2)*xx
7528 & +x(37)*(yy**2)*zz +x(38)*(zz**2)*xx +x(39)*(zz**2)*yy
7530 sumene4= x(41) +x(42)*xx +x(43)*yy +x(44)*zz +x(45)*xx**2
7531 & +x(46)*yy**2 +x(47)*zz**2 +x(48)*xx*zz +x(49)*xx*yy
7532 & +x(50)*yy*zz +x(51)*xx**3 +x(52)*yy**3 +x(53)*zz**3
7533 & +x(54)*(xx**2)*yy +x(55)*(xx**2)*zz +x(56)*(yy**2)*xx
7534 & +x(57)*(yy**2)*zz +x(58)*(zz**2)*xx +x(59)*(zz**2)*yy
7536 dsc_i = 0.743d0+x(61)
7538 dscp1=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
7539 & *(xx*cost2+yy*sint2))
7540 dscp2=dsqrt(dsc_i**2+dp2_i**2-2*dsc_i*dp2_i
7541 & *(xx*cost2-yy*sint2))
7542 s1=(1+x(63))/(0.1d0 + dscp1)
7543 s1_6=(1+x(64))/(0.1d0 + dscp1**6)
7544 s2=(1+x(65))/(0.1d0 + dscp2)
7545 s2_6=(1+x(65))/(0.1d0 + dscp2**6)
7546 sumene = ( sumene3*sint2 + sumene1)*(s1+s1_6)
7547 & + (sumene4*cost2 +sumene2)*(s2+s2_6)
7552 c------------------------------------------------------------------------------
7553 subroutine gcont(rij,r0ij,eps0ij,delta,fcont,fprimcont)
7555 C This procedure calculates two-body contact function g(rij) and its derivative:
7558 C g(rij) = esp0ij*(-0.9375*x+0.625*x**3-0.1875*x**5) ! -1 =< x =< 1
7561 C where x=(rij-r0ij)/delta
7563 C rij - interbody distance, r0ij - contact distance, eps0ij - contact energy
7566 double precision rij,r0ij,eps0ij,fcont,fprimcont
7567 double precision x,x2,x4,delta
7571 if (x.lt.-1.0D0) then
7574 else if (x.le.1.0D0) then
7577 fcont=eps0ij*(x*(-0.9375D0+0.6250D0*x2-0.1875D0*x4)+0.5D0)
7578 fprimcont=eps0ij * (-0.9375D0+1.8750D0*x2-0.9375D0*x4)/delta
7585 c------------------------------------------------------------------------------
7586 subroutine splinthet(theti,delta,ss,ssder)
7587 implicit real*8 (a-h,o-z)
7588 include 'DIMENSIONS'
7589 include 'COMMON.VAR'
7590 include 'COMMON.GEO'
7593 if (theti.gt.pipol) then
7594 call gcont(theti,thetup,1.0d0,delta,ss,ssder)
7596 call gcont(-theti,-thetlow,1.0d0,delta,ss,ssder)
7601 c------------------------------------------------------------------------------
7602 subroutine spline1(x,x0,delta,f0,f1,fprim0,f,fprim)
7604 double precision x,x0,delta,f0,f1,fprim0,f,fprim
7605 double precision ksi,ksi2,ksi3,a1,a2,a3
7606 a1=fprim0*delta/(f1-f0)
7612 f=f0+(f1-f0)*ksi*(a1+ksi*(a2+a3*ksi))
7613 fprim=(f1-f0)/delta*(a1+ksi*(2*a2+3*ksi*a3))
7616 c------------------------------------------------------------------------------
7617 subroutine spline2(x,x0,delta,f0x,f1x,fprim0x,fx)
7619 double precision x,x0,delta,f0x,f1x,fprim0x,fx
7620 double precision ksi,ksi2,ksi3,a1,a2,a3
7625 a2=3*(f1x-f0x)-2*fprim0x*delta
7626 a3=fprim0x*delta-2*(f1x-f0x)
7627 fx=f0x+a1*ksi+a2*ksi2+a3*ksi3
7630 C-----------------------------------------------------------------------------
7632 C-----------------------------------------------------------------------------
7633 subroutine etor(etors)
7634 implicit real*8 (a-h,o-z)
7635 include 'DIMENSIONS'
7636 include 'COMMON.VAR'
7637 include 'COMMON.GEO'
7638 include 'COMMON.LOCAL'
7639 include 'COMMON.TORSION'
7640 include 'COMMON.INTERACT'
7641 include 'COMMON.DERIV'
7642 include 'COMMON.CHAIN'
7643 include 'COMMON.NAMES'
7644 include 'COMMON.IOUNITS'
7645 include 'COMMON.FFIELD'
7646 include 'COMMON.TORCNSTR'
7647 include 'COMMON.CONTROL'
7649 C Set lprn=.true. for debugging
7653 do i=iphi_start,iphi_end
7655 if (itype(i-2).eq.ntyp1.or. itype(i-1).eq.ntyp1
7656 & .or. itype(i).eq.ntyp1 .or. itype(i-3).eq.ntyp1) cycle
7657 itori=itortyp(itype(i-2))
7658 itori1=itortyp(itype(i-1))
7661 C Proline-Proline pair is a special case...
7662 if (itori.eq.3 .and. itori1.eq.3) then
7663 if (phii.gt.-dwapi3) then
7665 fac=1.0D0/(1.0D0-cosphi)
7666 etorsi=v1(1,3,3)*fac
7667 etorsi=etorsi+etorsi
7668 etors=etors+etorsi-v1(1,3,3)
7669 if (energy_dec) etors_ii=etors_ii+etorsi-v1(1,3,3)
7670 gloci=gloci-3*fac*etorsi*dsin(3*phii)
7673 v1ij=v1(j+1,itori,itori1)
7674 v2ij=v2(j+1,itori,itori1)
7677 etors=etors+v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
7678 if (energy_dec) etors_ii=etors_ii+
7679 & v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
7680 gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
7684 v1ij=v1(j,itori,itori1)
7685 v2ij=v2(j,itori,itori1)
7688 etors=etors+v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
7689 if (energy_dec) etors_ii=etors_ii+
7690 & v1ij*cosphi+v2ij*sinphi+dabs(v1ij)+dabs(v2ij)
7691 gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
7694 if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
7697 & write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
7698 & restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
7699 & (v1(j,itori,itori1),j=1,6),(v2(j,itori,itori1),j=1,6)
7700 gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
7701 c write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
7705 c------------------------------------------------------------------------------
7706 subroutine etor_d(etors_d)
7710 c----------------------------------------------------------------------------
7711 c LICZENIE WIEZOW Z ROWNANIA ENERGII MODELLERA
7712 subroutine e_modeller(ehomology_constr)
7713 ehomology_constr=0.0d0
7714 write (iout,*) "!!!!!UWAGA, JESTEM W DZIWNEJ PETLI, TEST!!!!!"
7717 C !!!!!!!! NIE CZYTANE !!!!!!!!!!!
7719 c------------------------------------------------------------------------------
7720 subroutine etor_d(etors_d)
7724 c----------------------------------------------------------------------------
7726 subroutine etor(etors)
7727 implicit real*8 (a-h,o-z)
7728 include 'DIMENSIONS'
7729 include 'COMMON.VAR'
7730 include 'COMMON.GEO'
7731 include 'COMMON.LOCAL'
7732 include 'COMMON.TORSION'
7733 include 'COMMON.INTERACT'
7734 include 'COMMON.DERIV'
7735 include 'COMMON.CHAIN'
7736 include 'COMMON.NAMES'
7737 include 'COMMON.IOUNITS'
7738 include 'COMMON.FFIELD'
7739 include 'COMMON.TORCNSTR'
7740 include 'COMMON.CONTROL'
7742 C Set lprn=.true. for debugging
7746 do i=iphi_start,iphi_end
7747 C ANY TWO ARE DUMMY ATOMS in row CYCLE
7748 c if (((itype(i-3).eq.ntyp1).and.(itype(i-2).eq.ntyp1)).or.
7749 c & ((itype(i-2).eq.ntyp1).and.(itype(i-1).eq.ntyp1)) .or.
7750 c & ((itype(i-1).eq.ntyp1).and.(itype(i).eq.ntyp1))) cycle
7751 if (itype(i-2).eq.ntyp1.or. itype(i-1).eq.ntyp1
7752 & .or. itype(i).eq.ntyp1 .or. itype(i-3).eq.ntyp1) cycle
7753 C In current verion the ALL DUMMY ATOM POTENTIALS ARE OFF
7754 C For introducing the NH3+ and COO- group please check the etor_d for reference
7757 if (iabs(itype(i)).eq.20) then
7762 itori=itortyp(itype(i-2))
7763 itori1=itortyp(itype(i-1))
7766 C Regular cosine and sine terms
7767 do j=1,nterm(itori,itori1,iblock)
7768 v1ij=v1(j,itori,itori1,iblock)
7769 v2ij=v2(j,itori,itori1,iblock)
7772 etors=etors+v1ij*cosphi+v2ij*sinphi
7773 if (energy_dec) etors_ii=etors_ii+
7774 & v1ij*cosphi+v2ij*sinphi
7775 gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
7779 C E = SUM ----------------------------------- - v1
7780 C [v2 cos(phi/2)+v3 sin(phi/2)]^2 + 1
7782 cosphi=dcos(0.5d0*phii)
7783 sinphi=dsin(0.5d0*phii)
7784 do j=1,nlor(itori,itori1,iblock)
7785 vl1ij=vlor1(j,itori,itori1)
7786 vl2ij=vlor2(j,itori,itori1)
7787 vl3ij=vlor3(j,itori,itori1)
7788 pom=vl2ij*cosphi+vl3ij*sinphi
7789 pom1=1.0d0/(pom*pom+1.0d0)
7790 etors=etors+vl1ij*pom1
7791 if (energy_dec) etors_ii=etors_ii+
7794 gloci=gloci+vl1ij*(vl3ij*cosphi-vl2ij*sinphi)*pom
7796 C Subtract the constant term
7797 etors=etors-v0(itori,itori1,iblock)
7798 if (energy_dec) write (iout,'(a6,i5,0pf7.3)')
7799 & 'etor',i,etors_ii-v0(itori,itori1,iblock)
7801 & write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
7802 & restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,itori,itori1,
7803 & (v1(j,itori,itori1,iblock),j=1,6),
7804 & (v2(j,itori,itori1,iblock),j=1,6)
7805 gloc(i-3,icg)=gloc(i-3,icg)+wtor*gloci
7806 c write (iout,*) 'i=',i,' gloc=',gloc(i-3,icg)
7810 c----------------------------------------------------------------------------
7811 subroutine etor_d(etors_d)
7812 C 6/23/01 Compute double torsional energy
7813 implicit real*8 (a-h,o-z)
7814 include 'DIMENSIONS'
7815 include 'COMMON.VAR'
7816 include 'COMMON.GEO'
7817 include 'COMMON.LOCAL'
7818 include 'COMMON.TORSION'
7819 include 'COMMON.INTERACT'
7820 include 'COMMON.DERIV'
7821 include 'COMMON.CHAIN'
7822 include 'COMMON.NAMES'
7823 include 'COMMON.IOUNITS'
7824 include 'COMMON.FFIELD'
7825 include 'COMMON.TORCNSTR'
7827 C Set lprn=.true. for debugging
7831 c write(iout,*) "a tu??"
7832 do i=iphid_start,iphid_end
7833 C ANY TWO ARE DUMMY ATOMS in row CYCLE
7834 C if (((itype(i-3).eq.ntyp1).and.(itype(i-2).eq.ntyp1)).or.
7835 C & ((itype(i-2).eq.ntyp1).and.(itype(i-1).eq.ntyp1)).or.
7836 C & ((itype(i-1).eq.ntyp1).and.(itype(i).eq.ntyp1)) .or.
7837 C & ((itype(i).eq.ntyp1).and.(itype(i+1).eq.ntyp1))) cycle
7838 if ((itype(i-2).eq.ntyp1).or.itype(i-3).eq.ntyp1.or.
7839 & (itype(i-1).eq.ntyp1).or.(itype(i).eq.ntyp1).or.
7840 & (itype(i+1).eq.ntyp1)) cycle
7841 C In current verion the ALL DUMMY ATOM POTENTIALS ARE OFF
7842 itori=itortyp(itype(i-2))
7843 itori1=itortyp(itype(i-1))
7844 itori2=itortyp(itype(i))
7850 if (iabs(itype(i+1)).eq.20) iblock=2
7851 C Iblock=2 Proline type
7852 C ADASKO: WHEN PARAMETERS FOR THIS TYPE OF BLOCKING GROUP IS READY UNCOMMENT
7853 C CHECK WEATHER THERE IS NECCESITY FOR iblock=3 for COO-
7854 C if (itype(i+1).eq.ntyp1) iblock=3
7855 C The problem of NH3+ group can be resolved by adding new parameters please note if there
7856 C IS or IS NOT need for this
7857 C IF Yes uncomment below and add to parmread.F appropriate changes and to v1cij and so on
7858 C is (itype(i-3).eq.ntyp1) ntblock=2
7859 C ntblock is N-terminal blocking group
7861 C Regular cosine and sine terms
7862 do j=1,ntermd_1(itori,itori1,itori2,iblock)
7863 C Example of changes for NH3+ blocking group
7864 C do j=1,ntermd_1(itori,itori1,itori2,iblock,ntblock)
7865 C v1cij=v1c(1,j,itori,itori1,itori2,iblock,ntblock)
7866 v1cij=v1c(1,j,itori,itori1,itori2,iblock)
7867 v1sij=v1s(1,j,itori,itori1,itori2,iblock)
7868 v2cij=v1c(2,j,itori,itori1,itori2,iblock)
7869 v2sij=v1s(2,j,itori,itori1,itori2,iblock)
7870 cosphi1=dcos(j*phii)
7871 sinphi1=dsin(j*phii)
7872 cosphi2=dcos(j*phii1)
7873 sinphi2=dsin(j*phii1)
7874 etors_d=etors_d+v1cij*cosphi1+v1sij*sinphi1+
7875 & v2cij*cosphi2+v2sij*sinphi2
7876 gloci1=gloci1+j*(v1sij*cosphi1-v1cij*sinphi1)
7877 gloci2=gloci2+j*(v2sij*cosphi2-v2cij*sinphi2)
7879 do k=2,ntermd_2(itori,itori1,itori2,iblock)
7881 v1cdij = v2c(k,l,itori,itori1,itori2,iblock)
7882 v2cdij = v2c(l,k,itori,itori1,itori2,iblock)
7883 v1sdij = v2s(k,l,itori,itori1,itori2,iblock)
7884 v2sdij = v2s(l,k,itori,itori1,itori2,iblock)
7885 cosphi1p2=dcos(l*phii+(k-l)*phii1)
7886 cosphi1m2=dcos(l*phii-(k-l)*phii1)
7887 sinphi1p2=dsin(l*phii+(k-l)*phii1)
7888 sinphi1m2=dsin(l*phii-(k-l)*phii1)
7889 etors_d=etors_d+v1cdij*cosphi1p2+v2cdij*cosphi1m2+
7890 & v1sdij*sinphi1p2+v2sdij*sinphi1m2
7891 gloci1=gloci1+l*(v1sdij*cosphi1p2+v2sdij*cosphi1m2
7892 & -v1cdij*sinphi1p2-v2cdij*sinphi1m2)
7893 gloci2=gloci2+(k-l)*(v1sdij*cosphi1p2-v2sdij*cosphi1m2
7894 & -v1cdij*sinphi1p2+v2cdij*sinphi1m2)
7897 gloc(i-3,icg)=gloc(i-3,icg)+wtor_d*gloci1
7898 gloc(i-2,icg)=gloc(i-2,icg)+wtor_d*gloci2
7903 C----------------------------------------------------------------------------------
7904 C The rigorous attempt to derive energy function
7905 subroutine etor_kcc(etors)
7906 implicit real*8 (a-h,o-z)
7907 include 'DIMENSIONS'
7908 include 'COMMON.VAR'
7909 include 'COMMON.GEO'
7910 include 'COMMON.LOCAL'
7911 include 'COMMON.TORSION'
7912 include 'COMMON.INTERACT'
7913 include 'COMMON.DERIV'
7914 include 'COMMON.CHAIN'
7915 include 'COMMON.NAMES'
7916 include 'COMMON.IOUNITS'
7917 include 'COMMON.FFIELD'
7918 include 'COMMON.TORCNSTR'
7919 include 'COMMON.CONTROL'
7920 double precision c1(0:maxval_kcc),c2(0:maxval_kcc)
7922 c double precision thybt1(maxtermkcc),thybt2(maxtermkcc)
7923 C Set lprn=.true. for debugging
7926 C print *,"wchodze kcc"
7927 if (lprn) write (iout,*) "etor_kcc tor_mode",tor_mode
7929 do i=iphi_start,iphi_end
7930 C ANY TWO ARE DUMMY ATOMS in row CYCLE
7931 c if (((itype(i-3).eq.ntyp1).and.(itype(i-2).eq.ntyp1)).or.
7932 c & ((itype(i-2).eq.ntyp1).and.(itype(i-1).eq.ntyp1)) .or.
7933 c & ((itype(i-1).eq.ntyp1).and.(itype(i).eq.ntyp1))) cycle
7934 if (itype(i-2).eq.ntyp1.or. itype(i-1).eq.ntyp1
7935 & .or. itype(i).eq.ntyp1 .or. itype(i-3).eq.ntyp1) cycle
7936 itori=itortyp(itype(i-2))
7937 itori1=itortyp(itype(i-1))
7942 C to avoid multiple devision by 2
7943 c theti22=0.5d0*theta(i)
7944 C theta 12 is the theta_1 /2
7945 C theta 22 is theta_2 /2
7946 c theti12=0.5d0*theta(i-1)
7947 C and appropriate sinus function
7948 sinthet1=dsin(theta(i-1))
7949 sinthet2=dsin(theta(i))
7950 costhet1=dcos(theta(i-1))
7951 costhet2=dcos(theta(i))
7952 C to speed up lets store its mutliplication
7953 sint1t2=sinthet2*sinthet1
7955 C \sum_{i=1}^n (sin(theta_1) * sin(theta_2))^n * (c_n* cos(n*gamma)
7956 C +d_n*sin(n*gamma)) *
7957 C \sum_{i=1}^m (1+a_m*Tb_m(cos(theta_1 /2))+b_m*Tb_m(cos(theta_2 /2)))
7958 C we have two sum 1) Non-Chebyshev which is with n and gamma
7959 nval=nterm_kcc_Tb(itori,itori1)
7965 c1(j)=c1(j-1)*costhet1
7966 c2(j)=c2(j-1)*costhet2
7969 do j=1,nterm_kcc(itori,itori1)
7973 sint1t2n=sint1t2n*sint1t2
7979 sumvalc=sumvalc+v1_kcc(l,k,j,itori1,itori)*c1(k)*c2(l)
7980 gradvalct1=gradvalct1+
7981 & (k-1)*v1_kcc(l,k,j,itori1,itori)*c1(k-1)*c2(l)
7982 gradvalct2=gradvalct2+
7983 & (l-1)*v1_kcc(l,k,j,itori1,itori)*c1(k)*c2(l-1)
7986 gradvalct1=-gradvalct1*sinthet1
7987 gradvalct2=-gradvalct2*sinthet2
7993 sumvals=sumvals+v2_kcc(l,k,j,itori1,itori)*c1(k)*c2(l)
7994 gradvalst1=gradvalst1+
7995 & (k-1)*v2_kcc(l,k,j,itori1,itori)*c1(k-1)*c2(l)
7996 gradvalst2=gradvalst2+
7997 & (l-1)*v2_kcc(l,k,j,itori1,itori)*c1(k)*c2(l-1)
8000 gradvalst1=-gradvalst1*sinthet1
8001 gradvalst2=-gradvalst2*sinthet2
8002 if (lprn) write (iout,*)j,"sumvalc",sumvalc," sumvals",sumvals
8003 etori=etori+sint1t2n*(sumvalc*cosphi+sumvals*sinphi)
8004 C glocig is the gradient local i site in gamma
8005 glocig=glocig+j*sint1t2n*(sumvals*cosphi-sumvalc*sinphi)
8006 C now gradient over theta_1
8007 glocit1=glocit1+sint1t2n*(gradvalct1*cosphi+gradvalst1*sinphi)
8008 & +j*sint1t2n1*costhet1*sinthet2*(sumvalc*cosphi+sumvals*sinphi)
8009 glocit2=glocit2+sint1t2n*(gradvalct2*cosphi+gradvalst2*sinphi)
8010 & +j*sint1t2n1*sinthet1*costhet2*(sumvalc*cosphi+sumvals*sinphi)
8013 C derivative over gamma
8014 gloc(i-3,icg)=gloc(i-3,icg)+wtor*glocig
8015 C derivative over theta1
8016 gloc(nphi+i-3,icg)=gloc(nphi+i-3,icg)+wtor*glocit1
8017 C now derivative over theta2
8018 gloc(nphi+i-2,icg)=gloc(nphi+i-2,icg)+wtor*glocit2
8020 write (iout,*) i-2,i-1,itype(i-2),itype(i-1),itori,itori1,
8021 & theta(i-1)*rad2deg,theta(i)*rad2deg,phii*rad2deg,etori
8022 write (iout,*) "c1",(c1(k),k=0,nval),
8023 & " c2",(c2(k),k=0,nval)
8028 c---------------------------------------------------------------------------------------------
8029 subroutine etor_constr(edihcnstr)
8030 implicit real*8 (a-h,o-z)
8031 include 'DIMENSIONS'
8032 include 'COMMON.VAR'
8033 include 'COMMON.GEO'
8034 include 'COMMON.LOCAL'
8035 include 'COMMON.TORSION'
8036 include 'COMMON.INTERACT'
8037 include 'COMMON.DERIV'
8038 include 'COMMON.CHAIN'
8039 include 'COMMON.NAMES'
8040 include 'COMMON.IOUNITS'
8041 include 'COMMON.FFIELD'
8042 include 'COMMON.TORCNSTR'
8043 include 'COMMON.BOUNDS'
8044 include 'COMMON.CONTROL'
8045 ! 6/20/98 - dihedral angle constraints
8047 c do i=1,ndih_constr
8048 if (raw_psipred) then
8049 do i=idihconstr_start,idihconstr_end
8050 itori=idih_constr(i)
8052 gaudih_i=vpsipred(1,i)
8056 cos_i=(1.0d0-dcos(phii-phibound(j,i)))/s**2
8057 dexpcos_i=dexp(-cos_i*cos_i)
8058 gaudih_i=gaudih_i+vpsipred(j+1,i)*dexpcos_i
8059 gauder_i=gauder_i-2*vpsipred(j+1,i)*dsin(phii-phibound(j,i))
8060 & *cos_i*dexpcos_i/s**2
8062 edihcnstr=edihcnstr-wdihc*dlog(gaudih_i)
8063 gloc(itori-3,icg)=gloc(itori-3,icg)-wdihc*gauder_i/gaudih_i
8065 & write (iout,'(2i5,f8.3,f8.5,2(f8.5,2f8.3),f10.5)')
8066 & i,itori,phii*rad2deg,vpsipred(1,i),vpsipred(2,i),
8067 & phibound(1,i)*rad2deg,sdihed(1,i)*rad2deg,vpsipred(3,i),
8068 & phibound(2,i)*rad2deg,sdihed(2,i)*rad2deg,
8069 & -wdihc*dlog(gaudih_i)
8073 do i=idihconstr_start,idihconstr_end
8074 itori=idih_constr(i)
8076 difi=pinorm(phii-phi0(i))
8077 if (difi.gt.drange(i)) then
8079 edihcnstr=edihcnstr+0.25d0*ftors(i)*difi**4
8080 gloc(itori-3,icg)=gloc(itori-3,icg)+ftors(i)*difi**3
8081 else if (difi.lt.-drange(i)) then
8083 edihcnstr=edihcnstr+0.25d0*ftors(i)*difi**4
8084 gloc(itori-3,icg)=gloc(itori-3,icg)+ftors(i)*difi**3
8094 c----------------------------------------------------------------------------
8095 c MODELLER restraint function
8096 subroutine e_modeller(ehomology_constr)
8098 include 'DIMENSIONS'
8100 double precision ehomology_constr
8101 integer nnn,i,ii,j,k,ijk,jik,ki,kk,nexl,irec,l
8102 integer katy, odleglosci, test7
8103 real*8 odleg, odleg2, odleg3, kat, kat2, kat3, gdih(max_template)
8105 real*8 distance(max_template),distancek(max_template),
8106 & min_odl,godl(max_template),dih_diff(max_template)
8109 c FP - 30/10/2014 Temporary specifications for homology restraints
8111 double precision utheta_i,gutheta_i,sum_gtheta,sum_sgtheta,
8113 double precision, dimension (maxres) :: guscdiff,usc_diff
8114 double precision, dimension (max_template) ::
8115 & gtheta,dscdiff,uscdiffk,guscdiff2,guscdiff3,
8117 double precision sum_godl,sgodl,grad_odl3,ggodl,sum_gdih,
8118 & sum_guscdiff,sum_sgdih,sgdih,grad_dih3,usc_diff_i,dxx,dyy,dzz,
8119 & betai,sum_sgodl,dij
8120 double precision dist,pinorm
8122 include 'COMMON.SBRIDGE'
8123 include 'COMMON.CHAIN'
8124 include 'COMMON.GEO'
8125 include 'COMMON.DERIV'
8126 include 'COMMON.LOCAL'
8127 include 'COMMON.INTERACT'
8128 include 'COMMON.VAR'
8129 include 'COMMON.IOUNITS'
8130 c include 'COMMON.MD'
8131 include 'COMMON.CONTROL'
8132 include 'COMMON.HOMOLOGY'
8133 include 'COMMON.QRESTR'
8135 c From subroutine Econstr_back
8137 include 'COMMON.NAMES'
8138 include 'COMMON.TIME1'
8143 distancek(i)=9999999.9
8149 c Pseudo-energy and gradient from homology restraints (MODELLER-like
8151 C AL 5/2/14 - Introduce list of restraints
8152 c write(iout,*) "waga_theta",waga_theta,"waga_d",waga_d
8154 write(iout,*) "------- dist restrs start -------"
8156 do ii = link_start_homo,link_end_homo
8160 c write (iout,*) "dij(",i,j,") =",dij
8162 do k=1,constr_homology
8163 c write(iout,*) ii,k,i,j,l_homo(k,ii),dij,odl(k,ii)
8164 if(.not.l_homo(k,ii)) then
8168 distance(k)=odl(k,ii)-dij
8169 c write (iout,*) "distance(",k,") =",distance(k)
8171 c For Gaussian-type Urestr
8173 distancek(k)=0.5d0*distance(k)**2*sigma_odl(k,ii) ! waga_dist rmvd from Gaussian argument
8174 c write (iout,*) "sigma_odl(",k,ii,") =",sigma_odl(k,ii)
8175 c write (iout,*) "distancek(",k,") =",distancek(k)
8176 c distancek(k)=0.5d0*waga_dist*distance(k)**2*sigma_odl(k,ii)
8178 c For Lorentzian-type Urestr
8180 if (waga_dist.lt.0.0d0) then
8181 sigma_odlir(k,ii)=dsqrt(1/sigma_odl(k,ii))
8182 distancek(k)=distance(k)**2/(sigma_odlir(k,ii)*
8183 & (distance(k)**2+sigma_odlir(k,ii)**2))
8187 c min_odl=minval(distancek)
8188 do kk=1,constr_homology
8189 if(l_homo(kk,ii)) then
8190 min_odl=distancek(kk)
8194 do kk=1,constr_homology
8195 if(l_homo(kk,ii) .and. distancek(kk).lt.min_odl)
8196 & min_odl=distancek(kk)
8199 c write (iout,* )"min_odl",min_odl
8201 write (iout,*) "ij dij",i,j,dij
8202 write (iout,*) "distance",(distance(k),k=1,constr_homology)
8203 write (iout,*) "distancek",(distancek(k),k=1,constr_homology)
8204 write (iout,* )"min_odl",min_odl
8209 if (waga_dist.ge.0.0d0) then
8215 do k=1,constr_homology
8216 c Nie wiem po co to liczycie jeszcze raz!
8217 c odleg3=-waga_dist(iset)*((distance(i,j,k)**2)/
8218 c & (2*(sigma_odl(i,j,k))**2))
8219 if(.not.l_homo(k,ii)) cycle
8220 if (waga_dist.ge.0.0d0) then
8222 c For Gaussian-type Urestr
8224 godl(k)=dexp(-distancek(k)+min_odl)
8225 odleg2=odleg2+godl(k)
8227 c For Lorentzian-type Urestr
8230 odleg2=odleg2+distancek(k)
8233 ccc write(iout,779) i,j,k, "odleg2=",odleg2, "odleg3=", odleg3,
8234 ccc & "dEXP(odleg3)=", dEXP(odleg3),"distance(i,j,k)^2=",
8235 ccc & distance(i,j,k)**2, "dist(i+1,j+1)=", dist(i+1,j+1),
8236 ccc & "sigma_odl(i,j,k)=", sigma_odl(i,j,k)
8239 c write (iout,*) "godl",(godl(k),k=1,constr_homology) ! exponents
8240 c write (iout,*) "ii i j",ii,i,j," odleg2",odleg2 ! sum of exps
8242 write (iout,*) "godl",(godl(k),k=1,constr_homology) ! exponents
8243 write (iout,*) "ii i j",ii,i,j," odleg2",odleg2 ! sum of exps
8245 if (waga_dist.ge.0.0d0) then
8247 c For Gaussian-type Urestr
8249 odleg=odleg-dLOG(odleg2/constr_homology)+min_odl
8251 c For Lorentzian-type Urestr
8254 odleg=odleg+odleg2/constr_homology
8257 c write (iout,*) "odleg",odleg ! sum of -ln-s
8260 c For Gaussian-type Urestr
8262 if (waga_dist.ge.0.0d0) sum_godl=odleg2
8264 do k=1,constr_homology
8265 c godl=dexp(((-(distance(i,j,k)**2)/(2*(sigma_odl(i,j,k))**2))
8266 c & *waga_dist)+min_odl
8267 c sgodl=-godl(k)*distance(k)*sigma_odl(k,ii)*waga_dist
8269 if(.not.l_homo(k,ii)) cycle
8270 if (waga_dist.ge.0.0d0) then
8271 c For Gaussian-type Urestr
8273 sgodl=-godl(k)*distance(k)*sigma_odl(k,ii) ! waga_dist rmvd
8275 c For Lorentzian-type Urestr
8278 sgodl=-2*sigma_odlir(k,ii)*(distance(k)/(distance(k)**2+
8279 & sigma_odlir(k,ii)**2)**2)
8281 sum_sgodl=sum_sgodl+sgodl
8283 c sgodl2=sgodl2+sgodl
8284 c write(iout,*) i, j, k, distance(i,j,k), "W GRADIENCIE1"
8285 c write(iout,*) "constr_homology=",constr_homology
8286 c write(iout,*) i, j, k, "TEST K"
8288 if (waga_dist.ge.0.0d0) then
8290 c For Gaussian-type Urestr
8292 grad_odl3=waga_homology(iset)*waga_dist
8293 & *sum_sgodl/(sum_godl*dij)
8295 c For Lorentzian-type Urestr
8298 c Original grad expr modified by analogy w Gaussian-type Urestr grad
8299 c grad_odl3=-waga_homology(iset)*waga_dist*sum_sgodl
8300 grad_odl3=-waga_homology(iset)*waga_dist*
8301 & sum_sgodl/(constr_homology*dij)
8304 c grad_odl3=sum_sgodl/(sum_godl*dij)
8307 c write(iout,*) i, j, k, distance(i,j,k), "W GRADIENCIE2"
8308 c write(iout,*) (distance(i,j,k)**2), (2*(sigma_odl(i,j,k))**2),
8309 c & (-(distance(i,j,k)**2)/(2*(sigma_odl(i,j,k))**2))
8311 ccc write(iout,*) godl, sgodl, grad_odl3
8313 c grad_odl=grad_odl+grad_odl3
8316 ggodl=grad_odl3*(c(jik,i)-c(jik,j))
8317 ccc write(iout,*) c(jik,i+1), c(jik,j+1), (c(jik,i+1)-c(jik,j+1))
8318 ccc write(iout,746) "GRAD_ODL_1", i, j, jik, ggodl,
8319 ccc & ghpbc(jik,i+1), ghpbc(jik,j+1)
8320 ghpbc(jik,i)=ghpbc(jik,i)+ggodl
8321 ghpbc(jik,j)=ghpbc(jik,j)-ggodl
8322 ccc write(iout,746) "GRAD_ODL_2", i, j, jik, ggodl,
8323 ccc & ghpbc(jik,i+1), ghpbc(jik,j+1)
8324 c if (i.eq.25.and.j.eq.27) then
8325 c write(iout,*) "jik",jik,"i",i,"j",j
8326 c write(iout,*) "sum_sgodl",sum_sgodl,"sgodl",sgodl
8327 c write(iout,*) "grad_odl3",grad_odl3
8328 c write(iout,*) "c(",jik,i,")",c(jik,i),"c(",jik,j,")",c(jik,j)
8329 c write(iout,*) "ggodl",ggodl
8330 c write(iout,*) "ghpbc(",jik,i,")",
8331 c & ghpbc(jik,i),"ghpbc(",jik,j,")",
8335 ccc write(iout,778)"TEST: odleg2=", odleg2, "DLOG(odleg2)=",
8336 ccc & dLOG(odleg2),"-odleg=", -odleg
8338 enddo ! ii-loop for dist
8340 write(iout,*) "------- dist restrs end -------"
8341 c if (waga_angle.eq.1.0d0 .or. waga_theta.eq.1.0d0 .or.
8342 c & waga_d.eq.1.0d0) call sum_gradient
8344 c Pseudo-energy and gradient from dihedral-angle restraints from
8345 c homology templates
8346 c write (iout,*) "End of distance loop"
8349 c write (iout,*) idihconstr_start_homo,idihconstr_end_homo
8351 write(iout,*) "------- dih restrs start -------"
8352 do i=idihconstr_start_homo,idihconstr_end_homo
8353 write (iout,*) "gloc_init(",i,icg,")",gloc(i,icg)
8356 do i=idihconstr_start_homo,idihconstr_end_homo
8358 c betai=beta(i,i+1,i+2,i+3)
8360 c write (iout,*) "betai =",betai
8361 do k=1,constr_homology
8362 dih_diff(k)=pinorm(dih(k,i)-betai)
8363 cd write (iout,'(a8,2i4,2f15.8)') "dih_diff",i,k,dih_diff(k)
8364 cd & ,sigma_dih(k,i)
8365 c if (dih_diff(i,k).gt.3.14159) dih_diff(i,k)=
8366 c & -(6.28318-dih_diff(i,k))
8367 c if (dih_diff(i,k).lt.-3.14159) dih_diff(i,k)=
8368 c & 6.28318+dih_diff(i,k)
8370 kat3=-0.5d0*dih_diff(k)**2*sigma_dih(k,i) ! waga_angle rmvd from Gaussian argument
8372 kat3=(dcos(dih_diff(k))-1)*sigma_dih(k,i) ! waga_angle rmvd from Gaussian argument
8374 c kat3=-0.5d0*waga_angle*dih_diff(k)**2*sigma_dih(k,i)
8377 c write(iout,*) "kat2=", kat2, "exp(kat3)=", exp(kat3)
8380 c write (iout,*) "gdih",(gdih(k),k=1,constr_homology) ! exps
8381 c write (iout,*) "i",i," betai",betai," kat2",kat2 ! sum of exps
8383 write (iout,*) "i",i," betai",betai," kat2",kat2
8384 write (iout,*) "gdih",(gdih(k),k=1,constr_homology)
8386 if (kat2.le.1.0d-14) cycle
8387 kat=kat-dLOG(kat2/constr_homology)
8388 c write (iout,*) "kat",kat ! sum of -ln-s
8390 ccc write(iout,778)"TEST: kat2=", kat2, "DLOG(kat2)=",
8391 ccc & dLOG(kat2), "-kat=", -kat
8393 c ----------------------------------------------------------------------
8395 c ----------------------------------------------------------------------
8399 do k=1,constr_homology
8401 sgdih=-gdih(k)*dih_diff(k)*sigma_dih(k,i) ! waga_angle rmvd
8403 sgdih=-gdih(k)*dsin(dih_diff(k))*sigma_dih(k,i) ! waga_angle rmvd
8405 c sgdih=-gdih(k)*dih_diff(k)*sigma_dih(k,i)*waga_angle
8406 sum_sgdih=sum_sgdih+sgdih
8408 c grad_dih3=sum_sgdih/sum_gdih
8409 grad_dih3=waga_homology(iset)*waga_angle*sum_sgdih/sum_gdih
8411 c write(iout,*)i,k,gdih,sgdih,beta(i+1,i+2,i+3,i+4),grad_dih3
8412 ccc write(iout,747) "GRAD_KAT_1", i, nphi, icg, grad_dih3,
8413 ccc & gloc(nphi+i-3,icg)
8414 gloc(i-3,icg)=gloc(i-3,icg)+grad_dih3
8416 c write(iout,*) "i",i,"icg",icg,"gloc(",i,icg,")",gloc(i,icg)
8418 ccc write(iout,747) "GRAD_KAT_2", i, nphi, icg, grad_dih3,
8419 ccc & gloc(nphi+i-3,icg)
8421 enddo ! i-loop for dih
8423 write(iout,*) "------- dih restrs end -------"
8426 c Pseudo-energy and gradient for theta angle restraints from
8427 c homology templates
8428 c FP 01/15 - inserted from econstr_local_test.F, loop structure
8432 c For constr_homology reference structures (FP)
8434 c Uconst_back_tot=0.0d0
8437 c Econstr_back legacy
8439 c do i=ithet_start,ithet_end
8442 c do i=loc_start,loc_end
8445 duscdiffx(j,i)=0.0d0
8450 c write (iout,*) "ithet_start =",ithet_start,"ithet_end =",ithet_end
8451 c write (iout,*) "waga_theta",waga_theta
8452 if (waga_theta.gt.0.0d0) then
8454 write (iout,*) "usampl",usampl
8455 write(iout,*) "------- theta restrs start -------"
8456 c do i=ithet_start,ithet_end
8457 c write (iout,*) "gloc_init(",nphi+i,icg,")",gloc(nphi+i,icg)
8460 c write (iout,*) "maxres",maxres,"nres",nres
8462 do i=ithet_start,ithet_end
8465 c ii = ifrag_back(2,i,iset)-ifrag_back(1,i,iset)
8467 c Deviation of theta angles wrt constr_homology ref structures
8469 utheta_i=0.0d0 ! argument of Gaussian for single k
8470 gutheta_i=0.0d0 ! Sum of Gaussians over constr_homology ref structures
8471 c do j=ifrag_back(1,i,iset)+2,ifrag_back(2,i,iset) ! original loop
8472 c over residues in a fragment
8473 c write (iout,*) "theta(",i,")=",theta(i)
8474 do k=1,constr_homology
8476 c dtheta_i=theta(j)-thetaref(j,iref)
8477 c dtheta_i=thetaref(k,i)-theta(i) ! original form without indexing
8478 theta_diff(k)=thetatpl(k,i)-theta(i)
8479 cd write (iout,'(a8,2i4,2f15.8)') "theta_diff",i,k,theta_diff(k)
8480 cd & ,sigma_theta(k,i)
8483 utheta_i=-0.5d0*theta_diff(k)**2*sigma_theta(k,i) ! waga_theta rmvd from Gaussian argument
8484 c utheta_i=-0.5d0*waga_theta*theta_diff(k)**2*sigma_theta(k,i) ! waga_theta?
8485 gtheta(k)=dexp(utheta_i) ! + min_utheta_i?
8486 gutheta_i=gutheta_i+gtheta(k) ! Sum of Gaussians (pk)
8487 c Gradient for single Gaussian restraint in subr Econstr_back
8488 c dutheta(j-2)=dutheta(j-2)+wfrag_back(1,i,iset)*dtheta_i/(ii-1)
8491 c write (iout,*) "gtheta",(gtheta(k),k=1,constr_homology) ! exps
8492 c write (iout,*) "i",i," gutheta_i",gutheta_i ! sum of exps
8495 c Gradient for multiple Gaussian restraint
8496 sum_gtheta=gutheta_i
8498 do k=1,constr_homology
8499 c New generalized expr for multiple Gaussian from Econstr_back
8500 sgtheta=-gtheta(k)*theta_diff(k)*sigma_theta(k,i) ! waga_theta rmvd
8502 c sgtheta=-gtheta(k)*theta_diff(k)*sigma_theta(k,i)*waga_theta ! right functional form?
8503 sum_sgtheta=sum_sgtheta+sgtheta ! cum variable
8505 c Final value of gradient using same var as in Econstr_back
8506 gloc(nphi+i-2,icg)=gloc(nphi+i-2,icg)
8507 & +sum_sgtheta/sum_gtheta*waga_theta
8508 & *waga_homology(iset)
8509 c dutheta(i-2)=sum_sgtheta/sum_gtheta*waga_theta
8510 c & *waga_homology(iset)
8511 c dutheta(i)=sum_sgtheta/sum_gtheta
8513 c Uconst_back=Uconst_back+waga_theta*utheta(i) ! waga_theta added as weight
8514 Eval=Eval-dLOG(gutheta_i/constr_homology)
8515 c write (iout,*) "utheta(",i,")=",utheta(i) ! -ln of sum of exps
8516 c write (iout,*) "Uconst_back",Uconst_back ! sum of -ln-s
8517 c Uconst_back=Uconst_back+utheta(i)
8518 enddo ! (i-loop for theta)
8520 write(iout,*) "------- theta restrs end -------"
8524 c Deviation of local SC geometry
8526 c Separation of two i-loops (instructed by AL - 11/3/2014)
8528 c write (iout,*) "loc_start =",loc_start,"loc_end =",loc_end
8529 c write (iout,*) "waga_d",waga_d
8532 write(iout,*) "------- SC restrs start -------"
8533 write (iout,*) "Initial duscdiff,duscdiffx"
8534 do i=loc_start,loc_end
8535 write (iout,*) i,(duscdiff(jik,i),jik=1,3),
8536 & (duscdiffx(jik,i),jik=1,3)
8539 do i=loc_start,loc_end
8540 usc_diff_i=0.0d0 ! argument of Gaussian for single k
8541 guscdiff(i)=0.0d0 ! Sum of Gaussians over constr_homology ref structures
8542 c do j=ifrag_back(1,i,iset)+1,ifrag_back(2,i,iset)-1 ! Econstr_back legacy
8543 c write(iout,*) "xxtab, yytab, zztab"
8544 c write(iout,'(i5,3f8.2)') i,xxtab(i),yytab(i),zztab(i)
8545 do k=1,constr_homology
8547 dxx=-xxtpl(k,i)+xxtab(i) ! Diff b/w x component of ith SC vector in model and kth ref str?
8548 c Original sign inverted for calc of gradients (s. Econstr_back)
8549 dyy=-yytpl(k,i)+yytab(i) ! ibid y
8550 dzz=-zztpl(k,i)+zztab(i) ! ibid z
8551 c write(iout,*) "dxx, dyy, dzz"
8552 cd write(iout,'(2i5,4f8.2)') k,i,dxx,dyy,dzz,sigma_d(k,i)
8554 usc_diff_i=-0.5d0*(dxx**2+dyy**2+dzz**2)*sigma_d(k,i) ! waga_d rmvd from Gaussian argument
8555 c usc_diff(i)=-0.5d0*waga_d*(dxx**2+dyy**2+dzz**2)*sigma_d(k,i) ! waga_d?
8556 c uscdiffk(k)=usc_diff(i)
8557 guscdiff2(k)=dexp(usc_diff_i) ! without min_scdiff
8558 c write(iout,*) "i",i," k",k," sigma_d",sigma_d(k,i),
8559 c & " guscdiff2",guscdiff2(k)
8560 guscdiff(i)=guscdiff(i)+guscdiff2(k) !Sum of Gaussians (pk)
8561 c write (iout,'(i5,6f10.5)') j,xxtab(j),yytab(j),zztab(j),
8562 c & xxref(j),yyref(j),zzref(j)
8567 c Generalized expression for multiple Gaussian acc to that for a single
8568 c Gaussian in Econstr_back as instructed by AL (FP - 03/11/2014)
8570 c Original implementation
8571 c sum_guscdiff=guscdiff(i)
8573 c sum_sguscdiff=0.0d0
8574 c do k=1,constr_homology
8575 c sguscdiff=-guscdiff2(k)*dscdiff(k)*sigma_d(k,i)*waga_d !waga_d?
8576 c sguscdiff=-guscdiff3(k)*dscdiff(k)*sigma_d(k,i)*waga_d ! w min_uscdiff
8577 c sum_sguscdiff=sum_sguscdiff+sguscdiff
8580 c Implementation of new expressions for gradient (Jan. 2015)
8582 c grad_uscdiff=sum_sguscdiff/(sum_guscdiff*dtab) !?
8583 do k=1,constr_homology
8585 c New calculation of dxx, dyy, and dzz corrected by AL (07/11), was missing and wrong
8586 c before. Now the drivatives should be correct
8588 dxx=-xxtpl(k,i)+xxtab(i) ! Diff b/w x component of ith SC vector in model and kth ref str?
8589 c Original sign inverted for calc of gradients (s. Econstr_back)
8590 dyy=-yytpl(k,i)+yytab(i) ! ibid y
8591 dzz=-zztpl(k,i)+zztab(i) ! ibid z
8593 c New implementation
8595 sum_guscdiff=guscdiff2(k)*!(dsqrt(dxx*dxx+dyy*dyy+dzz*dzz))* -> wrong!
8596 & sigma_d(k,i) ! for the grad wrt r'
8597 c sum_sguscdiff=sum_sguscdiff+sum_guscdiff
8600 c New implementation
8601 sum_guscdiff = waga_homology(iset)*waga_d*sum_guscdiff
8603 duscdiff(jik,i-1)=duscdiff(jik,i-1)+
8604 & sum_guscdiff*(dXX_C1tab(jik,i)*dxx+
8605 & dYY_C1tab(jik,i)*dyy+dZZ_C1tab(jik,i)*dzz)/guscdiff(i)
8606 duscdiff(jik,i)=duscdiff(jik,i)+
8607 & sum_guscdiff*(dXX_Ctab(jik,i)*dxx+
8608 & dYY_Ctab(jik,i)*dyy+dZZ_Ctab(jik,i)*dzz)/guscdiff(i)
8609 duscdiffx(jik,i)=duscdiffx(jik,i)+
8610 & sum_guscdiff*(dXX_XYZtab(jik,i)*dxx+
8611 & dYY_XYZtab(jik,i)*dyy+dZZ_XYZtab(jik,i)*dzz)/guscdiff(i)
8614 write(iout,*) "jik",jik,"i",i
8615 write(iout,*) "dxx, dyy, dzz"
8616 write(iout,'(2i5,3f8.2)') k,i,dxx,dyy,dzz
8617 write(iout,*) "guscdiff2(",k,")",guscdiff2(k)
8618 c write(iout,*) "sum_sguscdiff",sum_sguscdiff
8619 cc write(iout,*) "dXX_Ctab(",jik,i,")",dXX_Ctab(jik,i)
8620 c write(iout,*) "dYY_Ctab(",jik,i,")",dYY_Ctab(jik,i)
8621 c write(iout,*) "dZZ_Ctab(",jik,i,")",dZZ_Ctab(jik,i)
8622 c write(iout,*) "dXX_C1tab(",jik,i,")",dXX_C1tab(jik,i)
8623 c write(iout,*) "dYY_C1tab(",jik,i,")",dYY_C1tab(jik,i)
8624 c write(iout,*) "dZZ_C1tab(",jik,i,")",dZZ_C1tab(jik,i)
8625 c write(iout,*) "dXX_XYZtab(",jik,i,")",dXX_XYZtab(jik,i)
8626 c write(iout,*) "dYY_XYZtab(",jik,i,")",dYY_XYZtab(jik,i)
8627 c write(iout,*) "dZZ_XYZtab(",jik,i,")",dZZ_XYZtab(jik,i)
8628 c write(iout,*) "duscdiff(",jik,i-1,")",duscdiff(jik,i-1)
8629 c write(iout,*) "duscdiff(",jik,i,")",duscdiff(jik,i)
8630 c write(iout,*) "duscdiffx(",jik,i,")",duscdiffx(jik,i)
8636 c uscdiff(i)=-dLOG(guscdiff(i)/(ii-1)) ! Weighting by (ii-1) required?
8637 c usc_diff(i)=-dLOG(guscdiff(i)/constr_homology) ! + min_uscdiff ?
8639 c write (iout,*) i," uscdiff",uscdiff(i)
8641 c Put together deviations from local geometry
8643 c Uconst_back=Uconst_back+wfrag_back(1,i,iset)*utheta(i)+
8644 c & wfrag_back(3,i,iset)*uscdiff(i)
8645 Erot=Erot-dLOG(guscdiff(i)/constr_homology)
8646 c write (iout,*) "usc_diff(",i,")=",usc_diff(i) ! -ln of sum of exps
8647 c write (iout,*) "Uconst_back",Uconst_back ! cum sum of -ln-s
8648 c Uconst_back=Uconst_back+usc_diff(i)
8650 c Gradient of multiple Gaussian restraint (FP - 04/11/2014 - right?)
8652 c New implment: multiplied by sum_sguscdiff
8655 enddo ! (i-loop for dscdiff)
8660 write(iout,*) "------- SC restrs end -------"
8661 write (iout,*) "------ After SC loop in e_modeller ------"
8662 do i=loc_start,loc_end
8663 write (iout,*) "i",i," gradc",(gradc(j,i,icg),j=1,3)
8664 write (iout,*) "i",i," gradx",(gradx(j,i,icg),j=1,3)
8666 if (waga_theta.eq.1.0d0) then
8667 write (iout,*) "in e_modeller after SC restr end: dutheta"
8668 do i=ithet_start,ithet_end
8669 write (iout,*) i,dutheta(i)
8672 if (waga_d.eq.1.0d0) then
8673 write (iout,*) "e_modeller after SC loop: duscdiff/x"
8675 write (iout,*) i,(duscdiff(j,i),j=1,3)
8676 write (iout,*) i,(duscdiffx(j,i),j=1,3)
8681 c Total energy from homology restraints
8683 write (iout,*) "odleg",odleg," kat",kat
8686 c Addition of energy of theta angle and SC local geom over constr_homologs ref strs
8688 c ehomology_constr=odleg+kat
8690 c For Lorentzian-type Urestr
8693 if (waga_dist.ge.0.0d0) then
8695 c For Gaussian-type Urestr
8697 ehomology_constr=(waga_dist*odleg+waga_angle*kat+
8698 & waga_theta*Eval+waga_d*Erot)*waga_homology(iset)
8699 c write (iout,*) "ehomology_constr=",ehomology_constr
8702 c For Lorentzian-type Urestr
8704 ehomology_constr=(-waga_dist*odleg+waga_angle*kat+
8705 & waga_theta*Eval+waga_d*Erot)*waga_homology(iset)
8706 c write (iout,*) "ehomology_constr=",ehomology_constr
8709 write (iout,*) "odleg",waga_dist,odleg," kat",waga_angle,kat,
8710 & "Eval",waga_theta,eval,
8711 & "Erot",waga_d,Erot
8712 write (iout,*) "ehomology_constr",ehomology_constr
8718 748 format(a8,f12.3,a6,f12.3,a7,f12.3)
8719 747 format(a12,i4,i4,i4,f8.3,f8.3)
8720 746 format(a12,i4,i4,i4,f8.3,f8.3,f8.3)
8721 778 format(a7,1X,f10.3,1X,a4,1X,f10.3,1X,a5,1X,f10.3)
8722 779 format(i3,1X,i3,1X,i2,1X,a7,1X,f7.3,1X,a7,1X,f7.3,1X,a13,1X,
8723 & f7.3,1X,a17,1X,f9.3,1X,a10,1X,f8.3,1X,a10,1X,f8.3)
8725 c----------------------------------------------------------------------------
8726 C The rigorous attempt to derive energy function
8727 subroutine ebend_kcc(etheta)
8729 implicit real*8 (a-h,o-z)
8730 include 'DIMENSIONS'
8731 include 'COMMON.VAR'
8732 include 'COMMON.GEO'
8733 include 'COMMON.LOCAL'
8734 include 'COMMON.TORSION'
8735 include 'COMMON.INTERACT'
8736 include 'COMMON.DERIV'
8737 include 'COMMON.CHAIN'
8738 include 'COMMON.NAMES'
8739 include 'COMMON.IOUNITS'
8740 include 'COMMON.FFIELD'
8741 include 'COMMON.TORCNSTR'
8742 include 'COMMON.CONTROL'
8744 double precision thybt1(maxang_kcc)
8745 C Set lprn=.true. for debugging
8748 C print *,"wchodze kcc"
8749 if (lprn) write (iout,*) "ebend_kcc tor_mode",tor_mode
8751 do i=ithet_start,ithet_end
8752 c print *,i,itype(i-1),itype(i),itype(i-2)
8753 if ((itype(i-1).eq.ntyp1).or.itype(i-2).eq.ntyp1
8754 & .or.itype(i).eq.ntyp1) cycle
8755 iti=iabs(itortyp(itype(i-1)))
8756 sinthet=dsin(theta(i))
8757 costhet=dcos(theta(i))
8758 do j=1,nbend_kcc_Tb(iti)
8759 thybt1(j)=v1bend_chyb(j,iti)
8761 sumth1thyb=v1bend_chyb(0,iti)+
8762 & tschebyshev(1,nbend_kcc_Tb(iti),thybt1(1),costhet)
8763 if (lprn) write (iout,*) i-1,itype(i-1),iti,theta(i)*rad2deg,
8765 ihelp=nbend_kcc_Tb(iti)-1
8766 gradthybt1=gradtschebyshev(0,ihelp,thybt1(1),costhet)
8767 etheta=etheta+sumth1thyb
8768 C print *,sumth1thyb,gradthybt1,sinthet*(-0.5d0)
8769 gloc(nphi+i-2,icg)=gloc(nphi+i-2,icg)-wang*gradthybt1*sinthet
8773 c-------------------------------------------------------------------------------------
8774 subroutine etheta_constr(ethetacnstr)
8776 implicit real*8 (a-h,o-z)
8777 include 'DIMENSIONS'
8778 include 'COMMON.VAR'
8779 include 'COMMON.GEO'
8780 include 'COMMON.LOCAL'
8781 include 'COMMON.TORSION'
8782 include 'COMMON.INTERACT'
8783 include 'COMMON.DERIV'
8784 include 'COMMON.CHAIN'
8785 include 'COMMON.NAMES'
8786 include 'COMMON.IOUNITS'
8787 include 'COMMON.FFIELD'
8788 include 'COMMON.TORCNSTR'
8789 include 'COMMON.CONTROL'
8791 C print *,ithetaconstr_start,ithetaconstr_end,"TU"
8792 do i=ithetaconstr_start,ithetaconstr_end
8793 itheta=itheta_constr(i)
8794 thetiii=theta(itheta)
8795 difi=pinorm(thetiii-theta_constr0(i))
8796 if (difi.gt.theta_drange(i)) then
8797 difi=difi-theta_drange(i)
8798 ethetacnstr=ethetacnstr+0.25d0*for_thet_constr(i)*difi**4
8799 gloc(itheta+nphi-2,icg)=gloc(itheta+nphi-2,icg)
8800 & +for_thet_constr(i)*difi**3
8801 else if (difi.lt.-drange(i)) then
8803 ethetacnstr=ethetacnstr+0.25d0*for_thet_constr(i)*difi**4
8804 gloc(itheta+nphi-2,icg)=gloc(itheta+nphi-2,icg)
8805 & +for_thet_constr(i)*difi**3
8809 if (energy_dec) then
8810 write (iout,'(a6,2i5,4f8.3,2e14.5)') "ethetc",
8811 & i,itheta,rad2deg*thetiii,
8812 & rad2deg*theta_constr0(i), rad2deg*theta_drange(i),
8813 & rad2deg*difi,0.25d0*for_thet_constr(i)*difi**4,
8814 & gloc(itheta+nphi-2,icg)
8819 c------------------------------------------------------------------------------
8820 subroutine eback_sc_corr(esccor)
8821 c 7/21/2007 Correlations between the backbone-local and side-chain-local
8822 c conformational states; temporarily implemented as differences
8823 c between UNRES torsional potentials (dependent on three types of
8824 c residues) and the torsional potentials dependent on all 20 types
8825 c of residues computed from AM1 energy surfaces of terminally-blocked
8826 c amino-acid residues.
8827 implicit real*8 (a-h,o-z)
8828 include 'DIMENSIONS'
8829 include 'COMMON.VAR'
8830 include 'COMMON.GEO'
8831 include 'COMMON.LOCAL'
8832 include 'COMMON.TORSION'
8833 include 'COMMON.SCCOR'
8834 include 'COMMON.INTERACT'
8835 include 'COMMON.DERIV'
8836 include 'COMMON.CHAIN'
8837 include 'COMMON.NAMES'
8838 include 'COMMON.IOUNITS'
8839 include 'COMMON.FFIELD'
8840 include 'COMMON.CONTROL'
8842 C Set lprn=.true. for debugging
8845 c write (iout,*) "EBACK_SC_COR",itau_start,itau_end
8847 do i=itau_start,itau_end
8848 if ((itype(i-2).eq.ntyp1).or.(itype(i-1).eq.ntyp1)) cycle
8850 isccori=isccortyp(itype(i-2))
8851 isccori1=isccortyp(itype(i-1))
8852 c write (iout,*) "EBACK_SC_COR",i,nterm_sccor(isccori,isccori1)
8854 do intertyp=1,3 !intertyp
8855 cc Added 09 May 2012 (Adasko)
8856 cc Intertyp means interaction type of backbone mainchain correlation:
8857 c 1 = SC...Ca...Ca...Ca
8858 c 2 = Ca...Ca...Ca...SC
8859 c 3 = SC...Ca...Ca...SCi
8861 if (((intertyp.eq.3).and.((itype(i-2).eq.10).or.
8862 & (itype(i-1).eq.10).or.(itype(i-2).eq.ntyp1).or.
8863 & (itype(i-1).eq.ntyp1)))
8864 & .or. ((intertyp.eq.1).and.((itype(i-2).eq.10)
8865 & .or.(itype(i-2).eq.ntyp1).or.(itype(i-1).eq.ntyp1)
8866 & .or.(itype(i).eq.ntyp1)))
8867 & .or.((intertyp.eq.2).and.((itype(i-1).eq.10).or.
8868 & (itype(i-1).eq.ntyp1).or.(itype(i-2).eq.ntyp1).or.
8869 & (itype(i-3).eq.ntyp1)))) cycle
8870 if ((intertyp.eq.2).and.(i.eq.4).and.(itype(1).eq.ntyp1)) cycle
8871 if ((intertyp.eq.1).and.(i.eq.nres).and.(itype(nres).eq.ntyp1))
8873 do j=1,nterm_sccor(isccori,isccori1)
8874 v1ij=v1sccor(j,intertyp,isccori,isccori1)
8875 v2ij=v2sccor(j,intertyp,isccori,isccori1)
8876 cosphi=dcos(j*tauangle(intertyp,i))
8877 sinphi=dsin(j*tauangle(intertyp,i))
8878 esccor=esccor+v1ij*cosphi+v2ij*sinphi
8879 gloci=gloci+j*(v2ij*cosphi-v1ij*sinphi)
8881 c write (iout,*) "EBACK_SC_COR",i,v1ij*cosphi+v2ij*sinphi,intertyp
8882 gloc_sc(intertyp,i-3,icg)=gloc_sc(intertyp,i-3,icg)+wsccor*gloci
8884 & write (iout,'(2(a3,2x,i3,2x),2i3,6f8.3/26x,6f8.3/)')
8885 & restyp(itype(i-2)),i-2,restyp(itype(i-1)),i-1,isccori,isccori1,
8886 & (v1sccor(j,intertyp,isccori,isccori1),j=1,6)
8887 & ,(v2sccor(j,intertyp,isccori,isccori1),j=1,6)
8888 gsccor_loc(i-3)=gsccor_loc(i-3)+gloci
8895 c----------------------------------------------------------------------------
8896 subroutine multibody(ecorr)
8897 C This subroutine calculates multi-body contributions to energy following
8898 C the idea of Skolnick et al. If side chains I and J make a contact and
8899 C at the same time side chains I+1 and J+1 make a contact, an extra
8900 C contribution equal to sqrt(eps(i,j)*eps(i+1,j+1)) is added.
8901 implicit real*8 (a-h,o-z)
8902 include 'DIMENSIONS'
8903 include 'COMMON.IOUNITS'
8904 include 'COMMON.DERIV'
8905 include 'COMMON.INTERACT'
8906 include 'COMMON.CONTACTS'
8907 include 'COMMON.CONTMAT'
8908 include 'COMMON.CORRMAT'
8909 double precision gx(3),gx1(3)
8912 C Set lprn=.true. for debugging
8916 write (iout,'(a)') 'Contact function values:'
8918 write (iout,'(i2,20(1x,i2,f10.5))')
8919 & i,(jcont(j,i),facont(j,i),j=1,num_cont(i))
8934 num_conti=num_cont(i)
8935 num_conti1=num_cont(i1)
8940 if (j1.eq.j+ishift .or. j1.eq.j-ishift) then
8941 cd write(iout,*)'i=',i,' j=',j,' i1=',i1,' j1=',j1,
8942 cd & ' ishift=',ishift
8943 C Contacts I--J and I+ISHIFT--J+-ISHIFT1 occur simultaneously.
8944 C The system gains extra energy.
8945 ecorr=ecorr+esccorr(i,j,i1,j1,jj,kk)
8946 endif ! j1==j+-ishift
8955 c------------------------------------------------------------------------------
8956 double precision function esccorr(i,j,k,l,jj,kk)
8957 implicit real*8 (a-h,o-z)
8958 include 'DIMENSIONS'
8959 include 'COMMON.IOUNITS'
8960 include 'COMMON.DERIV'
8961 include 'COMMON.INTERACT'
8962 include 'COMMON.CONTACTS'
8963 include 'COMMON.CONTMAT'
8964 include 'COMMON.CORRMAT'
8965 include 'COMMON.SHIELD'
8966 double precision gx(3),gx1(3)
8971 cd write (iout,'(4i5,3f10.5)') i,j,k,l,eij,ekl,-eij*ekl
8972 C Calculate the multi-body contribution to energy.
8973 C Calculate multi-body contributions to the gradient.
8974 cd write (iout,'(2(2i3,3f10.5))')i,j,(gacont(m,jj,i),m=1,3),
8975 cd & k,l,(gacont(m,kk,k),m=1,3)
8977 gx(m) =ekl*gacont(m,jj,i)
8978 gx1(m)=eij*gacont(m,kk,k)
8979 gradxorr(m,i)=gradxorr(m,i)-gx(m)
8980 gradxorr(m,j)=gradxorr(m,j)+gx(m)
8981 gradxorr(m,k)=gradxorr(m,k)-gx1(m)
8982 gradxorr(m,l)=gradxorr(m,l)+gx1(m)
8986 gradcorr(ll,m)=gradcorr(ll,m)+gx(ll)
8991 gradcorr(ll,m)=gradcorr(ll,m)+gx1(ll)
8997 c------------------------------------------------------------------------------
8998 subroutine multibody_hb(ecorr,ecorr5,ecorr6,n_corr,n_corr1)
8999 C This subroutine calculates multi-body contributions to hydrogen-bonding
9000 implicit real*8 (a-h,o-z)
9001 include 'DIMENSIONS'
9002 include 'COMMON.IOUNITS'
9005 parameter (max_cont=maxconts)
9006 parameter (max_dim=26)
9007 integer source,CorrelType,CorrelID,CorrelType1,CorrelID1,Error
9008 double precision zapas(max_dim,maxconts,max_fg_procs),
9009 & zapas_recv(max_dim,maxconts,max_fg_procs)
9010 common /przechowalnia/ zapas
9011 integer status(MPI_STATUS_SIZE),req(maxconts*2),
9012 & status_array(MPI_STATUS_SIZE,maxconts*2)
9014 include 'COMMON.SETUP'
9015 include 'COMMON.FFIELD'
9016 include 'COMMON.DERIV'
9017 include 'COMMON.INTERACT'
9018 include 'COMMON.CONTACTS'
9019 include 'COMMON.CONTMAT'
9020 include 'COMMON.CORRMAT'
9021 include 'COMMON.CONTROL'
9022 include 'COMMON.LOCAL'
9023 double precision gx(3),gx1(3),time00
9026 C Set lprn=.true. for debugging
9031 if (nfgtasks.le.1) goto 30
9033 write (iout,'(a)') 'Contact function values before RECEIVE:'
9035 write (iout,'(2i3,50(1x,i2,f5.2))')
9036 & i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
9037 & j=1,num_cont_hb(i))
9041 do i=1,ntask_cont_from
9044 do i=1,ntask_cont_to
9047 c write (iout,*) "ntask_cont_from",ntask_cont_from," ntask_cont_to",
9049 C Make the list of contacts to send to send to other procesors
9050 c write (iout,*) "limits",max0(iturn4_end-1,iatel_s),iturn3_end
9052 do i=iturn3_start,iturn3_end
9053 c write (iout,*) "make contact list turn3",i," num_cont",
9055 call add_hb_contact(i,i+2,iturn3_sent_local(1,i))
9057 do i=iturn4_start,iturn4_end
9058 c write (iout,*) "make contact list turn4",i," num_cont",
9060 call add_hb_contact(i,i+3,iturn4_sent_local(1,i))
9064 c write (iout,*) "make contact list longrange",i,ii," num_cont",
9066 do j=1,num_cont_hb(i)
9069 iproc=iint_sent_local(k,jjc,ii)
9070 c write (iout,*) "i",i," j",j," k",k," jjc",jjc," iproc",iproc
9071 if (iproc.gt.0) then
9072 ncont_sent(iproc)=ncont_sent(iproc)+1
9073 nn=ncont_sent(iproc)
9075 zapas(2,nn,iproc)=jjc
9076 zapas(3,nn,iproc)=facont_hb(j,i)
9077 zapas(4,nn,iproc)=ees0p(j,i)
9078 zapas(5,nn,iproc)=ees0m(j,i)
9079 zapas(6,nn,iproc)=gacont_hbr(1,j,i)
9080 zapas(7,nn,iproc)=gacont_hbr(2,j,i)
9081 zapas(8,nn,iproc)=gacont_hbr(3,j,i)
9082 zapas(9,nn,iproc)=gacontm_hb1(1,j,i)
9083 zapas(10,nn,iproc)=gacontm_hb1(2,j,i)
9084 zapas(11,nn,iproc)=gacontm_hb1(3,j,i)
9085 zapas(12,nn,iproc)=gacontp_hb1(1,j,i)
9086 zapas(13,nn,iproc)=gacontp_hb1(2,j,i)
9087 zapas(14,nn,iproc)=gacontp_hb1(3,j,i)
9088 zapas(15,nn,iproc)=gacontm_hb2(1,j,i)
9089 zapas(16,nn,iproc)=gacontm_hb2(2,j,i)
9090 zapas(17,nn,iproc)=gacontm_hb2(3,j,i)
9091 zapas(18,nn,iproc)=gacontp_hb2(1,j,i)
9092 zapas(19,nn,iproc)=gacontp_hb2(2,j,i)
9093 zapas(20,nn,iproc)=gacontp_hb2(3,j,i)
9094 zapas(21,nn,iproc)=gacontm_hb3(1,j,i)
9095 zapas(22,nn,iproc)=gacontm_hb3(2,j,i)
9096 zapas(23,nn,iproc)=gacontm_hb3(3,j,i)
9097 zapas(24,nn,iproc)=gacontp_hb3(1,j,i)
9098 zapas(25,nn,iproc)=gacontp_hb3(2,j,i)
9099 zapas(26,nn,iproc)=gacontp_hb3(3,j,i)
9106 & "Numbers of contacts to be sent to other processors",
9107 & (ncont_sent(i),i=1,ntask_cont_to)
9108 write (iout,*) "Contacts sent"
9109 do ii=1,ntask_cont_to
9111 iproc=itask_cont_to(ii)
9112 write (iout,*) nn," contacts to processor",iproc,
9113 & " of CONT_TO_COMM group"
9115 write(iout,'(2f5.0,4f10.5)')(zapas(j,i,ii),j=1,5)
9123 CorrelID1=nfgtasks+fg_rank+1
9125 C Receive the numbers of needed contacts from other processors
9126 do ii=1,ntask_cont_from
9127 iproc=itask_cont_from(ii)
9129 call MPI_Irecv(ncont_recv(ii),1,MPI_INTEGER,iproc,CorrelType,
9130 & FG_COMM,req(ireq),IERR)
9132 c write (iout,*) "IRECV ended"
9134 C Send the number of contacts needed by other processors
9135 do ii=1,ntask_cont_to
9136 iproc=itask_cont_to(ii)
9138 call MPI_Isend(ncont_sent(ii),1,MPI_INTEGER,iproc,CorrelType,
9139 & FG_COMM,req(ireq),IERR)
9141 c write (iout,*) "ISEND ended"
9142 c write (iout,*) "number of requests (nn)",ireq
9145 & call MPI_Waitall(ireq,req,status_array,ierr)
9147 c & "Numbers of contacts to be received from other processors",
9148 c & (ncont_recv(i),i=1,ntask_cont_from)
9152 do ii=1,ntask_cont_from
9153 iproc=itask_cont_from(ii)
9155 c write (iout,*) "Receiving",nn," contacts from processor",iproc,
9156 c & " of CONT_TO_COMM group"
9160 call MPI_Irecv(zapas_recv(1,1,ii),nn*max_dim,
9161 & MPI_DOUBLE_PRECISION,iproc,CorrelType1,FG_COMM,req(ireq),IERR)
9162 c write (iout,*) "ireq,req",ireq,req(ireq)
9165 C Send the contacts to processors that need them
9166 do ii=1,ntask_cont_to
9167 iproc=itask_cont_to(ii)
9169 c write (iout,*) nn," contacts to processor",iproc,
9170 c & " of CONT_TO_COMM group"
9173 call MPI_Isend(zapas(1,1,ii),nn*max_dim,MPI_DOUBLE_PRECISION,
9174 & iproc,CorrelType1,FG_COMM,req(ireq),IERR)
9175 c write (iout,*) "ireq,req",ireq,req(ireq)
9177 c write(iout,'(2f5.0,4f10.5)')(zapas(j,i,ii),j=1,5)
9181 c write (iout,*) "number of requests (contacts)",ireq
9182 c write (iout,*) "req",(req(i),i=1,4)
9185 & call MPI_Waitall(ireq,req,status_array,ierr)
9186 do iii=1,ntask_cont_from
9187 iproc=itask_cont_from(iii)
9190 write (iout,*) "Received",nn," contacts from processor",iproc,
9191 & " of CONT_FROM_COMM group"
9194 write(iout,'(2f5.0,4f10.5)')(zapas_recv(j,i,iii),j=1,5)
9199 ii=zapas_recv(1,i,iii)
9200 c Flag the received contacts to prevent double-counting
9201 jj=-zapas_recv(2,i,iii)
9202 c write (iout,*) "iii",iii," i",i," ii",ii," jj",jj
9204 nnn=num_cont_hb(ii)+1
9207 facont_hb(nnn,ii)=zapas_recv(3,i,iii)
9208 ees0p(nnn,ii)=zapas_recv(4,i,iii)
9209 ees0m(nnn,ii)=zapas_recv(5,i,iii)
9210 gacont_hbr(1,nnn,ii)=zapas_recv(6,i,iii)
9211 gacont_hbr(2,nnn,ii)=zapas_recv(7,i,iii)
9212 gacont_hbr(3,nnn,ii)=zapas_recv(8,i,iii)
9213 gacontm_hb1(1,nnn,ii)=zapas_recv(9,i,iii)
9214 gacontm_hb1(2,nnn,ii)=zapas_recv(10,i,iii)
9215 gacontm_hb1(3,nnn,ii)=zapas_recv(11,i,iii)
9216 gacontp_hb1(1,nnn,ii)=zapas_recv(12,i,iii)
9217 gacontp_hb1(2,nnn,ii)=zapas_recv(13,i,iii)
9218 gacontp_hb1(3,nnn,ii)=zapas_recv(14,i,iii)
9219 gacontm_hb2(1,nnn,ii)=zapas_recv(15,i,iii)
9220 gacontm_hb2(2,nnn,ii)=zapas_recv(16,i,iii)
9221 gacontm_hb2(3,nnn,ii)=zapas_recv(17,i,iii)
9222 gacontp_hb2(1,nnn,ii)=zapas_recv(18,i,iii)
9223 gacontp_hb2(2,nnn,ii)=zapas_recv(19,i,iii)
9224 gacontp_hb2(3,nnn,ii)=zapas_recv(20,i,iii)
9225 gacontm_hb3(1,nnn,ii)=zapas_recv(21,i,iii)
9226 gacontm_hb3(2,nnn,ii)=zapas_recv(22,i,iii)
9227 gacontm_hb3(3,nnn,ii)=zapas_recv(23,i,iii)
9228 gacontp_hb3(1,nnn,ii)=zapas_recv(24,i,iii)
9229 gacontp_hb3(2,nnn,ii)=zapas_recv(25,i,iii)
9230 gacontp_hb3(3,nnn,ii)=zapas_recv(26,i,iii)
9234 write (iout,'(a)') 'Contact function values after receive:'
9236 write (iout,'(2i3,50(1x,i3,f5.2))')
9237 & i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
9238 & j=1,num_cont_hb(i))
9245 write (iout,'(a)') 'Contact function values:'
9247 write (iout,'(2i3,50(1x,i3,f5.2))')
9248 & i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
9249 & j=1,num_cont_hb(i))
9254 C Remove the loop below after debugging !!!
9261 C Calculate the local-electrostatic correlation terms
9262 do i=min0(iatel_s,iturn4_start),max0(iatel_e,iturn3_end)
9264 num_conti=num_cont_hb(i)
9265 num_conti1=num_cont_hb(i+1)
9272 c write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
9273 c & ' jj=',jj,' kk=',kk
9275 if ((j.gt.0 .and. j1.gt.0 .or. j.gt.0 .and. j1.lt.0
9276 & .or. j.lt.0 .and. j1.gt.0) .and.
9277 & (jp1.eq.jp+1 .or. jp1.eq.jp-1)) then
9278 C Contacts I-J and (I+1)-(J+1) or (I+1)-(J-1) occur simultaneously.
9279 C The system gains extra energy.
9280 ecorr=ecorr+ehbcorr(i,jp,i+1,jp1,jj,kk,0.72D0,0.32D0)
9281 if (energy_dec) write (iout,'(a6,2i5,0pf7.3)')
9282 & 'ecorrh',i,j,ehbcorr(i,j,i+1,j1,jj,kk,0.72D0,0.32D0)
9284 else if (j1.eq.j) then
9285 C Contacts I-J and I-(J+1) occur simultaneously.
9286 C The system loses extra energy.
9287 c ecorr=ecorr+ehbcorr(i,j,i+1,j,jj,kk,0.60D0,-0.40D0)
9292 c write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
9293 c & ' jj=',jj,' kk=',kk
9295 C Contacts I-J and (I+1)-J occur simultaneously.
9296 C The system loses extra energy.
9297 c ecorr=ecorr+ehbcorr(i,j,i,j+1,jj,kk,0.60D0,-0.40D0)
9304 c------------------------------------------------------------------------------
9305 subroutine add_hb_contact(ii,jj,itask)
9306 implicit real*8 (a-h,o-z)
9307 include "DIMENSIONS"
9308 include "COMMON.IOUNITS"
9311 parameter (max_cont=maxconts)
9312 parameter (max_dim=26)
9313 include "COMMON.CONTACTS"
9314 include 'COMMON.CONTMAT'
9315 include 'COMMON.CORRMAT'
9316 double precision zapas(max_dim,maxconts,max_fg_procs),
9317 & zapas_recv(max_dim,maxconts,max_fg_procs)
9318 common /przechowalnia/ zapas
9319 integer i,j,ii,jj,iproc,itask(4),nn
9320 c write (iout,*) "itask",itask
9323 if (iproc.gt.0) then
9324 do j=1,num_cont_hb(ii)
9326 c write (iout,*) "i",ii," j",jj," jjc",jjc
9328 ncont_sent(iproc)=ncont_sent(iproc)+1
9329 nn=ncont_sent(iproc)
9330 zapas(1,nn,iproc)=ii
9331 zapas(2,nn,iproc)=jjc
9332 zapas(3,nn,iproc)=facont_hb(j,ii)
9333 zapas(4,nn,iproc)=ees0p(j,ii)
9334 zapas(5,nn,iproc)=ees0m(j,ii)
9335 zapas(6,nn,iproc)=gacont_hbr(1,j,ii)
9336 zapas(7,nn,iproc)=gacont_hbr(2,j,ii)
9337 zapas(8,nn,iproc)=gacont_hbr(3,j,ii)
9338 zapas(9,nn,iproc)=gacontm_hb1(1,j,ii)
9339 zapas(10,nn,iproc)=gacontm_hb1(2,j,ii)
9340 zapas(11,nn,iproc)=gacontm_hb1(3,j,ii)
9341 zapas(12,nn,iproc)=gacontp_hb1(1,j,ii)
9342 zapas(13,nn,iproc)=gacontp_hb1(2,j,ii)
9343 zapas(14,nn,iproc)=gacontp_hb1(3,j,ii)
9344 zapas(15,nn,iproc)=gacontm_hb2(1,j,ii)
9345 zapas(16,nn,iproc)=gacontm_hb2(2,j,ii)
9346 zapas(17,nn,iproc)=gacontm_hb2(3,j,ii)
9347 zapas(18,nn,iproc)=gacontp_hb2(1,j,ii)
9348 zapas(19,nn,iproc)=gacontp_hb2(2,j,ii)
9349 zapas(20,nn,iproc)=gacontp_hb2(3,j,ii)
9350 zapas(21,nn,iproc)=gacontm_hb3(1,j,ii)
9351 zapas(22,nn,iproc)=gacontm_hb3(2,j,ii)
9352 zapas(23,nn,iproc)=gacontm_hb3(3,j,ii)
9353 zapas(24,nn,iproc)=gacontp_hb3(1,j,ii)
9354 zapas(25,nn,iproc)=gacontp_hb3(2,j,ii)
9355 zapas(26,nn,iproc)=gacontp_hb3(3,j,ii)
9363 c------------------------------------------------------------------------------
9364 subroutine multibody_eello(ecorr,ecorr5,ecorr6,eturn6,n_corr,
9366 C This subroutine calculates multi-body contributions to hydrogen-bonding
9367 implicit real*8 (a-h,o-z)
9368 include 'DIMENSIONS'
9369 include 'COMMON.IOUNITS'
9372 parameter (max_cont=maxconts)
9373 parameter (max_dim=70)
9374 integer source,CorrelType,CorrelID,CorrelType1,CorrelID1,Error
9375 double precision zapas(max_dim,maxconts,max_fg_procs),
9376 & zapas_recv(max_dim,maxconts,max_fg_procs)
9377 common /przechowalnia/ zapas
9378 integer status(MPI_STATUS_SIZE),req(maxconts*2),
9379 & status_array(MPI_STATUS_SIZE,maxconts*2)
9381 include 'COMMON.SETUP'
9382 include 'COMMON.FFIELD'
9383 include 'COMMON.DERIV'
9384 include 'COMMON.LOCAL'
9385 include 'COMMON.INTERACT'
9386 include 'COMMON.CONTACTS'
9387 include 'COMMON.CONTMAT'
9388 include 'COMMON.CORRMAT'
9389 include 'COMMON.CHAIN'
9390 include 'COMMON.CONTROL'
9391 include 'COMMON.SHIELD'
9392 double precision gx(3),gx1(3)
9393 integer num_cont_hb_old(maxres)
9395 double precision eello4,eello5,eelo6,eello_turn6
9396 external eello4,eello5,eello6,eello_turn6
9397 C Set lprn=.true. for debugging
9402 num_cont_hb_old(i)=num_cont_hb(i)
9406 if (nfgtasks.le.1) goto 30
9408 write (iout,'(a)') 'Contact function values before RECEIVE:'
9410 write (iout,'(2i3,50(1x,i2,f5.2))')
9411 & i,num_cont_hb(i),(jcont_hb(j,i),facont_hb(j,i),
9412 & j=1,num_cont_hb(i))
9415 do i=1,ntask_cont_from
9418 do i=1,ntask_cont_to
9421 c write (iout,*) "ntask_cont_from",ntask_cont_from," ntask_cont_to",
9423 C Make the list of contacts to send to send to other procesors
9424 do i=iturn3_start,iturn3_end
9425 c write (iout,*) "make contact list turn3",i," num_cont",
9427 call add_hb_contact_eello(i,i+2,iturn3_sent_local(1,i))
9429 do i=iturn4_start,iturn4_end
9430 c write (iout,*) "make contact list turn4",i," num_cont",
9432 call add_hb_contact_eello(i,i+3,iturn4_sent_local(1,i))
9436 c write (iout,*) "make contact list longrange",i,ii," num_cont",
9438 do j=1,num_cont_hb(i)
9441 iproc=iint_sent_local(k,jjc,ii)
9442 c write (iout,*) "i",i," j",j," k",k," jjc",jjc," iproc",iproc
9443 if (iproc.ne.0) then
9444 ncont_sent(iproc)=ncont_sent(iproc)+1
9445 nn=ncont_sent(iproc)
9447 zapas(2,nn,iproc)=jjc
9448 zapas(3,nn,iproc)=d_cont(j,i)
9452 zapas(ind,nn,iproc)=grij_hb_cont(kk,j,i)
9457 zapas(ind,nn,iproc)=a_chuj(ll,kk,j,i)
9465 zapas(ind,nn,iproc)=a_chuj_der(mm,ll,kk,jj,j,i)
9476 & "Numbers of contacts to be sent to other processors",
9477 & (ncont_sent(i),i=1,ntask_cont_to)
9478 write (iout,*) "Contacts sent"
9479 do ii=1,ntask_cont_to
9481 iproc=itask_cont_to(ii)
9482 write (iout,*) nn," contacts to processor",iproc,
9483 & " of CONT_TO_COMM group"
9485 write(iout,'(2f5.0,10f10.5)')(zapas(j,i,ii),j=1,10)
9493 CorrelID1=nfgtasks+fg_rank+1
9495 C Receive the numbers of needed contacts from other processors
9496 do ii=1,ntask_cont_from
9497 iproc=itask_cont_from(ii)
9499 call MPI_Irecv(ncont_recv(ii),1,MPI_INTEGER,iproc,CorrelType,
9500 & FG_COMM,req(ireq),IERR)
9502 c write (iout,*) "IRECV ended"
9504 C Send the number of contacts needed by other processors
9505 do ii=1,ntask_cont_to
9506 iproc=itask_cont_to(ii)
9508 call MPI_Isend(ncont_sent(ii),1,MPI_INTEGER,iproc,CorrelType,
9509 & FG_COMM,req(ireq),IERR)
9511 c write (iout,*) "ISEND ended"
9512 c write (iout,*) "number of requests (nn)",ireq
9515 & call MPI_Waitall(ireq,req,status_array,ierr)
9517 c & "Numbers of contacts to be received from other processors",
9518 c & (ncont_recv(i),i=1,ntask_cont_from)
9522 do ii=1,ntask_cont_from
9523 iproc=itask_cont_from(ii)
9525 c write (iout,*) "Receiving",nn," contacts from processor",iproc,
9526 c & " of CONT_TO_COMM group"
9530 call MPI_Irecv(zapas_recv(1,1,ii),nn*max_dim,
9531 & MPI_DOUBLE_PRECISION,iproc,CorrelType1,FG_COMM,req(ireq),IERR)
9532 c write (iout,*) "ireq,req",ireq,req(ireq)
9535 C Send the contacts to processors that need them
9536 do ii=1,ntask_cont_to
9537 iproc=itask_cont_to(ii)
9539 c write (iout,*) nn," contacts to processor",iproc,
9540 c & " of CONT_TO_COMM group"
9543 call MPI_Isend(zapas(1,1,ii),nn*max_dim,MPI_DOUBLE_PRECISION,
9544 & iproc,CorrelType1,FG_COMM,req(ireq),IERR)
9545 c write (iout,*) "ireq,req",ireq,req(ireq)
9547 c write(iout,'(2f5.0,4f10.5)')(zapas(j,i,ii),j=1,5)
9551 c write (iout,*) "number of requests (contacts)",ireq
9552 c write (iout,*) "req",(req(i),i=1,4)
9555 & call MPI_Waitall(ireq,req,status_array,ierr)
9556 do iii=1,ntask_cont_from
9557 iproc=itask_cont_from(iii)
9560 write (iout,*) "Received",nn," contacts from processor",iproc,
9561 & " of CONT_FROM_COMM group"
9564 write(iout,'(2f5.0,10f10.5)')(zapas_recv(j,i,iii),j=1,10)
9569 ii=zapas_recv(1,i,iii)
9570 c Flag the received contacts to prevent double-counting
9571 jj=-zapas_recv(2,i,iii)
9572 c write (iout,*) "iii",iii," i",i," ii",ii," jj",jj
9574 nnn=num_cont_hb(ii)+1
9577 d_cont(nnn,ii)=zapas_recv(3,i,iii)
9581 grij_hb_cont(kk,nnn,ii)=zapas_recv(ind,i,iii)
9586 a_chuj(ll,kk,nnn,ii)=zapas_recv(ind,i,iii)
9594 a_chuj_der(mm,ll,kk,jj,nnn,ii)=zapas_recv(ind,i,iii)
9602 write (iout,'(a)') 'Contact function values after receive:'
9604 write (iout,'(2i3,50(1x,i3,5f6.3))')
9605 & i,num_cont_hb(i),(jcont_hb(j,i),d_cont(j,i),
9606 & ((a_chuj(ll,kk,j,i),ll=1,2),kk=1,2),j=1,num_cont_hb(i))
9613 write (iout,'(a)') 'Contact function values:'
9615 write (iout,'(2i3,50(1x,i2,5f6.3))')
9616 & i,num_cont_hb(i),(jcont_hb(j,i),d_cont(j,i),
9617 & ((a_chuj(ll,kk,j,i),ll=1,2),kk=1,2),j=1,num_cont_hb(i))
9623 C Remove the loop below after debugging !!!
9630 C Calculate the dipole-dipole interaction energies
9631 if (wcorr6.gt.0.0d0 .or. wturn6.gt.0.0d0) then
9632 do i=iatel_s,iatel_e+1
9633 num_conti=num_cont_hb(i)
9642 C Calculate the local-electrostatic correlation terms
9643 c write (iout,*) "gradcorr5 in eello5 before loop"
9645 c write (iout,'(i5,3f10.5)')
9646 c & iii,(gradcorr5(jjj,iii),jjj=1,3)
9648 do i=min0(iatel_s,iturn4_start),max0(iatel_e+1,iturn3_end+1)
9649 c write (iout,*) "corr loop i",i
9651 num_conti=num_cont_hb(i)
9652 num_conti1=num_cont_hb(i+1)
9659 c write (iout,*) 'i=',i,' j=',j,' i1=',i1,' j1=',j1,
9660 c & ' jj=',jj,' kk=',kk
9661 c if (j1.eq.j+1 .or. j1.eq.j-1) then
9662 if ((j.gt.0 .and. j1.gt.0 .or. j.gt.0 .and. j1.lt.0
9663 & .or. j.lt.0 .and. j1.gt.0) .and.
9664 & (jp1.eq.jp+1 .or. jp1.eq.jp-1)) then
9665 C Contacts I-J and (I+1)-(J+1) or (I+1)-(J-1) occur simultaneously.
9666 C The system gains extra energy.
9668 sqd1=dsqrt(d_cont(jj,i))
9669 sqd2=dsqrt(d_cont(kk,i1))
9670 sred_geom = sqd1*sqd2
9671 IF (sred_geom.lt.cutoff_corr) THEN
9672 call gcont(sred_geom,r0_corr,1.0D0,delt_corr,
9674 cd write (iout,*) 'i=',i,' j=',jp,' i1=',i1,' j1=',jp1,
9675 cd & ' jj=',jj,' kk=',kk
9676 fac_prim1=0.5d0*sqd2/sqd1*fprimcont
9677 fac_prim2=0.5d0*sqd1/sqd2*fprimcont
9679 g_contij(l,1)=fac_prim1*grij_hb_cont(l,jj,i)
9680 g_contij(l,2)=fac_prim2*grij_hb_cont(l,kk,i1)
9683 cd write (iout,*) 'sred_geom=',sred_geom,
9684 cd & ' ekont=',ekont,' fprim=',fprimcont,
9685 cd & ' fac_prim1',fac_prim1,' fac_prim2',fac_prim2
9686 cd write (iout,*) "g_contij",g_contij
9687 cd write (iout,*) "grij_hb_cont i",grij_hb_cont(:,jj,i)
9688 cd write (iout,*) "grij_hb_cont i1",grij_hb_cont(:,jj,i1)
9689 call calc_eello(i,jp,i+1,jp1,jj,kk)
9690 if (wcorr4.gt.0.0d0)
9691 & ecorr=ecorr+eello4(i,jp,i+1,jp1,jj,kk)
9692 CC & *fac_shield(i)**2*fac_shield(j)**2
9693 if (energy_dec.and.wcorr4.gt.0.0d0)
9694 1 write (iout,'(a6,4i5,0pf7.3)')
9695 2 'ecorr4',i,j,i+1,j1,eello4(i,jp,i+1,jp1,jj,kk)
9696 c write (iout,*) "gradcorr5 before eello5"
9698 c write (iout,'(i5,3f10.5)')
9699 c & iii,(gradcorr5(jjj,iii),jjj=1,3)
9701 if (wcorr5.gt.0.0d0)
9702 & ecorr5=ecorr5+eello5(i,jp,i+1,jp1,jj,kk)
9703 c write (iout,*) "gradcorr5 after eello5"
9705 c write (iout,'(i5,3f10.5)')
9706 c & iii,(gradcorr5(jjj,iii),jjj=1,3)
9708 if (energy_dec.and.wcorr5.gt.0.0d0)
9709 1 write (iout,'(a6,4i5,0pf7.3)')
9710 2 'ecorr5',i,j,i+1,j1,eello5(i,jp,i+1,jp1,jj,kk)
9711 cd write(2,*)'wcorr6',wcorr6,' wturn6',wturn6
9712 cd write(2,*)'ijkl',i,jp,i+1,jp1
9713 if (wcorr6.gt.0.0d0 .and. (jp.ne.i+4 .or. jp1.ne.i+3
9714 & .or. wturn6.eq.0.0d0))then
9715 cd write (iout,*) '******ecorr6: i,j,i+1,j1',i,j,i+1,j1
9716 ecorr6=ecorr6+eello6(i,jp,i+1,jp1,jj,kk)
9717 if (energy_dec) write (iout,'(a6,4i5,0pf7.3)')
9718 1 'ecorr6',i,j,i+1,j1,eello6(i,jp,i+1,jp1,jj,kk)
9719 cd write (iout,*) 'ecorr',ecorr,' ecorr5=',ecorr5,
9720 cd & 'ecorr6=',ecorr6
9721 cd write (iout,'(4e15.5)') sred_geom,
9722 cd & dabs(eello4(i,jp,i+1,jp1,jj,kk)),
9723 cd & dabs(eello5(i,jp,i+1,jp1,jj,kk)),
9724 cd & dabs(eello6(i,jp,i+1,jp1,jj,kk))
9725 else if (wturn6.gt.0.0d0
9726 & .and. (jp.eq.i+4 .and. jp1.eq.i+3)) then
9727 cd write (iout,*) '******eturn6: i,j,i+1,j1',i,jip,i+1,jp1
9728 eturn6=eturn6+eello_turn6(i,jj,kk)
9729 if (energy_dec) write (iout,'(a6,4i5,0pf7.3)')
9730 1 'eturn6',i,j,i+1,j1,eello_turn6(i,jj,kk)
9731 cd write (2,*) 'multibody_eello:eturn6',eturn6
9740 num_cont_hb(i)=num_cont_hb_old(i)
9742 c write (iout,*) "gradcorr5 in eello5"
9744 c write (iout,'(i5,3f10.5)')
9745 c & iii,(gradcorr5(jjj,iii),jjj=1,3)
9749 c------------------------------------------------------------------------------
9750 subroutine add_hb_contact_eello(ii,jj,itask)
9751 implicit real*8 (a-h,o-z)
9752 include "DIMENSIONS"
9753 include "COMMON.IOUNITS"
9756 parameter (max_cont=maxconts)
9757 parameter (max_dim=70)
9758 include "COMMON.CONTACTS"
9759 include 'COMMON.CONTMAT'
9760 include 'COMMON.CORRMAT'
9761 double precision zapas(max_dim,maxconts,max_fg_procs),
9762 & zapas_recv(max_dim,maxconts,max_fg_procs)
9763 common /przechowalnia/ zapas
9764 integer i,j,ii,jj,iproc,itask(4),nn
9765 c write (iout,*) "itask",itask
9768 if (iproc.gt.0) then
9769 do j=1,num_cont_hb(ii)
9771 c write (iout,*) "send turns i",ii," j",jj," jjc",jjc
9773 ncont_sent(iproc)=ncont_sent(iproc)+1
9774 nn=ncont_sent(iproc)
9775 zapas(1,nn,iproc)=ii
9776 zapas(2,nn,iproc)=jjc
9777 zapas(3,nn,iproc)=d_cont(j,ii)
9781 zapas(ind,nn,iproc)=grij_hb_cont(kk,j,ii)
9786 zapas(ind,nn,iproc)=a_chuj(ll,kk,j,ii)
9794 zapas(ind,nn,iproc)=a_chuj_der(mm,ll,kk,jj,j,ii)
9806 c------------------------------------------------------------------------------
9807 double precision function ehbcorr(i,j,k,l,jj,kk,coeffp,coeffm)
9808 implicit real*8 (a-h,o-z)
9809 include 'DIMENSIONS'
9810 include 'COMMON.IOUNITS'
9811 include 'COMMON.DERIV'
9812 include 'COMMON.INTERACT'
9813 include 'COMMON.CONTACTS'
9814 include 'COMMON.CONTMAT'
9815 include 'COMMON.CORRMAT'
9816 include 'COMMON.SHIELD'
9817 include 'COMMON.CONTROL'
9818 double precision gx(3),gx1(3)
9821 C print *,"wchodze",fac_shield(i),shield_mode
9829 ees=-(coeffp*ees0pij*ees0pkl+coeffm*ees0mij*ees0mkl)
9831 C & fac_shield(i)**2*fac_shield(j)**2
9832 cd ees=-(coeffp*ees0pkl+coeffm*ees0mkl)
9833 C Following 4 lines for diagnostics.
9838 c write (iout,'(2(a,2i3,a,f10.5,a,2f10.5),a,f10.5,a,$)')
9839 c & 'Contacts ',i,j,
9840 c & ' eij',eij,' eesij',ees0pij,ees0mij,' and ',k,l
9841 c & ,' fcont ',ekl,' eeskl',ees0pkl,ees0mkl,' energy=',ekont*ees,
9843 C Calculate the multi-body contribution to energy.
9844 C ecorr=ecorr+ekont*ees
9845 C Calculate multi-body contributions to the gradient.
9846 coeffpees0pij=coeffp*ees0pij
9847 coeffmees0mij=coeffm*ees0mij
9848 coeffpees0pkl=coeffp*ees0pkl
9849 coeffmees0mkl=coeffm*ees0mkl
9851 cgrad ghalfi=ees*ekl*gacont_hbr(ll,jj,i)
9852 gradcorr(ll,i)=gradcorr(ll,i)!+0.5d0*ghalfi
9853 & -ekont*(coeffpees0pkl*gacontp_hb1(ll,jj,i)+
9854 & coeffmees0mkl*gacontm_hb1(ll,jj,i))
9855 gradcorr(ll,j)=gradcorr(ll,j)!+0.5d0*ghalfi
9856 & -ekont*(coeffpees0pkl*gacontp_hb2(ll,jj,i)+
9857 & coeffmees0mkl*gacontm_hb2(ll,jj,i))
9858 cgrad ghalfk=ees*eij*gacont_hbr(ll,kk,k)
9859 gradcorr(ll,k)=gradcorr(ll,k)!+0.5d0*ghalfk
9860 & -ekont*(coeffpees0pij*gacontp_hb1(ll,kk,k)+
9861 & coeffmees0mij*gacontm_hb1(ll,kk,k))
9862 gradcorr(ll,l)=gradcorr(ll,l)!+0.5d0*ghalfk
9863 & -ekont*(coeffpees0pij*gacontp_hb2(ll,kk,k)+
9864 & coeffmees0mij*gacontm_hb2(ll,kk,k))
9865 gradlongij=ees*ekl*gacont_hbr(ll,jj,i)-
9866 & ekont*(coeffpees0pkl*gacontp_hb3(ll,jj,i)+
9867 & coeffmees0mkl*gacontm_hb3(ll,jj,i))
9868 gradcorr_long(ll,j)=gradcorr_long(ll,j)+gradlongij
9869 gradcorr_long(ll,i)=gradcorr_long(ll,i)-gradlongij
9870 gradlongkl=ees*eij*gacont_hbr(ll,kk,k)-
9871 & ekont*(coeffpees0pij*gacontp_hb3(ll,kk,k)+
9872 & coeffmees0mij*gacontm_hb3(ll,kk,k))
9873 gradcorr_long(ll,l)=gradcorr_long(ll,l)+gradlongkl
9874 gradcorr_long(ll,k)=gradcorr_long(ll,k)-gradlongkl
9875 c write (iout,'(2f10.5,2x,$)') gradlongij,gradlongkl
9880 cgrad gradcorr(ll,m)=gradcorr(ll,m)+
9881 cgrad & ees*ekl*gacont_hbr(ll,jj,i)-
9882 cgrad & ekont*(coeffp*ees0pkl*gacontp_hb3(ll,jj,i)+
9883 cgrad & coeffm*ees0mkl*gacontm_hb3(ll,jj,i))
9888 cgrad gradcorr(ll,m)=gradcorr(ll,m)+
9889 cgrad & ees*eij*gacont_hbr(ll,kk,k)-
9890 cgrad & ekont*(coeffp*ees0pij*gacontp_hb3(ll,kk,k)+
9891 cgrad & coeffm*ees0mij*gacontm_hb3(ll,kk,k))
9894 c write (iout,*) "ehbcorr",ekont*ees
9895 C print *,ekont,ees,i,k
9897 C now gradient over shielding
9899 if (shield_mode.gt.0) then
9902 C print *,i,j,fac_shield(i),fac_shield(j),
9903 C &fac_shield(k),fac_shield(l)
9904 if ((fac_shield(i).gt.0).and.(fac_shield(j).gt.0).and.
9905 & (fac_shield(k).gt.0).and.(fac_shield(l).gt.0)) then
9906 do ilist=1,ishield_list(i)
9907 iresshield=shield_list(ilist,i)
9909 rlocshield=grad_shield_side(m,ilist,i)*ehbcorr/fac_shield(i)
9911 gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
9913 & +grad_shield_loc(m,ilist,i)*ehbcorr/fac_shield(i)
9914 gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
9918 do ilist=1,ishield_list(j)
9919 iresshield=shield_list(ilist,j)
9921 rlocshield=grad_shield_side(m,ilist,j)*ehbcorr/fac_shield(j)
9923 gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
9925 & +grad_shield_loc(m,ilist,j)*ehbcorr/fac_shield(j)
9926 gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
9931 do ilist=1,ishield_list(k)
9932 iresshield=shield_list(ilist,k)
9934 rlocshield=grad_shield_side(m,ilist,k)*ehbcorr/fac_shield(k)
9936 gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
9938 & +grad_shield_loc(m,ilist,k)*ehbcorr/fac_shield(k)
9939 gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
9943 do ilist=1,ishield_list(l)
9944 iresshield=shield_list(ilist,l)
9946 rlocshield=grad_shield_side(m,ilist,l)*ehbcorr/fac_shield(l)
9948 gshieldx_ec(m,iresshield)=gshieldx_ec(m,iresshield)+
9950 & +grad_shield_loc(m,ilist,l)*ehbcorr/fac_shield(l)
9951 gshieldc_ec(m,iresshield-1)=gshieldc_ec(m,iresshield-1)
9955 C print *,gshieldx(m,iresshield)
9957 gshieldc_ec(m,i)=gshieldc_ec(m,i)+
9958 & grad_shield(m,i)*ehbcorr/fac_shield(i)
9959 gshieldc_ec(m,j)=gshieldc_ec(m,j)+
9960 & grad_shield(m,j)*ehbcorr/fac_shield(j)
9961 gshieldc_ec(m,i-1)=gshieldc_ec(m,i-1)+
9962 & grad_shield(m,i)*ehbcorr/fac_shield(i)
9963 gshieldc_ec(m,j-1)=gshieldc_ec(m,j-1)+
9964 & grad_shield(m,j)*ehbcorr/fac_shield(j)
9966 gshieldc_ec(m,k)=gshieldc_ec(m,k)+
9967 & grad_shield(m,k)*ehbcorr/fac_shield(k)
9968 gshieldc_ec(m,l)=gshieldc_ec(m,l)+
9969 & grad_shield(m,l)*ehbcorr/fac_shield(l)
9970 gshieldc_ec(m,k-1)=gshieldc_ec(m,k-1)+
9971 & grad_shield(m,k)*ehbcorr/fac_shield(k)
9972 gshieldc_ec(m,l-1)=gshieldc_ec(m,l-1)+
9973 & grad_shield(m,l)*ehbcorr/fac_shield(l)
9981 C---------------------------------------------------------------------------
9982 subroutine dipole(i,j,jj)
9983 implicit real*8 (a-h,o-z)
9984 include 'DIMENSIONS'
9985 include 'COMMON.IOUNITS'
9986 include 'COMMON.CHAIN'
9987 include 'COMMON.FFIELD'
9988 include 'COMMON.DERIV'
9989 include 'COMMON.INTERACT'
9990 include 'COMMON.CONTACTS'
9991 include 'COMMON.CONTMAT'
9992 include 'COMMON.CORRMAT'
9993 include 'COMMON.TORSION'
9994 include 'COMMON.VAR'
9995 include 'COMMON.GEO'
9996 dimension dipi(2,2),dipj(2,2),dipderi(2),dipderj(2),auxvec(2),
9998 iti1 = itortyp(itype(i+1))
9999 if (j.lt.nres-1) then
10000 itj1 = itype2loc(itype(j+1))
10005 dipi(iii,1)=Ub2(iii,i)
10006 dipderi(iii)=Ub2der(iii,i)
10007 dipi(iii,2)=b1(iii,i+1)
10008 dipj(iii,1)=Ub2(iii,j)
10009 dipderj(iii)=Ub2der(iii,j)
10010 dipj(iii,2)=b1(iii,j+1)
10014 call matvec2(a_chuj(1,1,jj,i),dipj(1,iii),auxvec(1))
10017 dip(kkk,jj,i)=scalar2(dipi(1,jjj),auxvec(1))
10024 call matvec2(a_chuj_der(1,1,lll,kkk,jj,i),dipj(1,iii),
10028 dipderx(lll,kkk,mmm,jj,i)=scalar2(dipi(1,jjj),auxvec(1))
10033 call transpose2(a_chuj(1,1,jj,i),auxmat(1,1))
10034 call matvec2(auxmat(1,1),dipderi(1),auxvec(1))
10036 dipderg(iii,jj,i)=scalar2(auxvec(1),dipj(1,iii))
10038 call matvec2(a_chuj(1,1,jj,i),dipderj(1),auxvec(1))
10040 dipderg(iii+2,jj,i)=scalar2(auxvec(1),dipi(1,iii))
10045 C---------------------------------------------------------------------------
10046 subroutine calc_eello(i,j,k,l,jj,kk)
10048 C This subroutine computes matrices and vectors needed to calculate
10049 C the fourth-, fifth-, and sixth-order local-electrostatic terms.
10051 implicit real*8 (a-h,o-z)
10052 include 'DIMENSIONS'
10053 include 'COMMON.IOUNITS'
10054 include 'COMMON.CHAIN'
10055 include 'COMMON.DERIV'
10056 include 'COMMON.INTERACT'
10057 include 'COMMON.CONTACTS'
10058 include 'COMMON.CONTMAT'
10059 include 'COMMON.CORRMAT'
10060 include 'COMMON.TORSION'
10061 include 'COMMON.VAR'
10062 include 'COMMON.GEO'
10063 include 'COMMON.FFIELD'
10064 double precision aa1(2,2),aa2(2,2),aa1t(2,2),aa2t(2,2),
10065 & aa1tder(2,2,3,5),aa2tder(2,2,3,5),auxmat(2,2)
10067 common /kutas/ lprn
10068 cd write (iout,*) 'calc_eello: i=',i,' j=',j,' k=',k,' l=',l,
10069 cd & ' jj=',jj,' kk=',kk
10070 cd if (i.ne.2 .or. j.ne.4 .or. k.ne.3 .or. l.ne.5) return
10071 cd write (iout,*) "a_chujij",((a_chuj(iii,jjj,jj,i),iii=1,2),jjj=1,2)
10072 cd write (iout,*) "a_chujkl",((a_chuj(iii,jjj,kk,k),iii=1,2),jjj=1,2)
10075 aa1(iii,jjj)=a_chuj(iii,jjj,jj,i)
10076 aa2(iii,jjj)=a_chuj(iii,jjj,kk,k)
10079 call transpose2(aa1(1,1),aa1t(1,1))
10080 call transpose2(aa2(1,1),aa2t(1,1))
10083 call transpose2(a_chuj_der(1,1,lll,kkk,jj,i),
10084 & aa1tder(1,1,lll,kkk))
10085 call transpose2(a_chuj_der(1,1,lll,kkk,kk,k),
10086 & aa2tder(1,1,lll,kkk))
10090 C parallel orientation of the two CA-CA-CA frames.
10092 iti=itype2loc(itype(i))
10096 itk1=itype2loc(itype(k+1))
10097 itj=itype2loc(itype(j))
10098 if (l.lt.nres-1) then
10099 itl1=itype2loc(itype(l+1))
10103 C A1 kernel(j+1) A2T
10105 cd write (iout,'(3f10.5,5x,3f10.5)')
10106 cd & (EUg(iii,jjj,k),jjj=1,2),(EUg(iii,jjj,l),jjj=1,2)
10108 call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10109 & aa2tder(1,1,1,1),1,.false.,EUg(1,1,l),EUgder(1,1,l),
10110 & AEA(1,1,1),AEAderg(1,1,1),AEAderx(1,1,1,1,1,1))
10111 C Following matrices are needed only for 6-th order cumulants
10112 IF (wcorr6.gt.0.0d0) THEN
10113 call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10114 & aa2tder(1,1,1,1),1,.false.,EUgC(1,1,l),EUgCder(1,1,l),
10115 & AECA(1,1,1),AECAderg(1,1,1),AECAderx(1,1,1,1,1,1))
10116 call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10117 & aa2tder(1,1,1,1),2,.false.,Ug2DtEUg(1,1,l),
10118 & Ug2DtEUgder(1,1,1,l),ADtEA(1,1,1),ADtEAderg(1,1,1,1),
10119 & ADtEAderx(1,1,1,1,1,1))
10121 call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10122 & aa2tder(1,1,1,1),2,.false.,DtUg2EUg(1,1,l),
10123 & DtUg2EUgder(1,1,1,l),ADtEA1(1,1,1),ADtEA1derg(1,1,1,1),
10124 & ADtEA1derx(1,1,1,1,1,1))
10126 C End 6-th order cumulants
10129 cd write (2,*) 'In calc_eello6'
10131 cd write (2,*) 'iii=',iii
10133 cd write (2,*) 'kkk=',kkk
10135 cd write (2,'(3(2f10.5),5x)')
10136 cd & ((ADtEA1derx(jjj,mmm,lll,kkk,iii,1),mmm=1,2),lll=1,3)
10141 call transpose2(EUgder(1,1,k),auxmat(1,1))
10142 call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,1,1))
10143 call transpose2(EUg(1,1,k),auxmat(1,1))
10144 call matmat2(auxmat(1,1),AEA(1,1,1),EAEA(1,1,1))
10145 call matmat2(auxmat(1,1),AEAderg(1,1,1),EAEAderg(1,1,2,1))
10146 C AL 4/16/16: Derivatives of the quantitied related to matrices C, D, and E
10147 c in theta; to be sriten later.
10149 c call transpose2(gtEE(1,1,k),auxmat(1,1))
10150 c call matmat2(auxmat(1,1),AEA(1,1,1),EAEAdert(1,1,1,1))
10151 c call transpose2(EUg(1,1,k),auxmat(1,1))
10152 c call matmat2(auxmat(1,1),AEAdert(1,1,1),EAEAdert(1,1,2,1))
10157 call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
10158 & EAEAderx(1,1,lll,kkk,iii,1))
10162 C A1T kernel(i+1) A2
10163 call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
10164 & a_chuj_der(1,1,1,1,kk,k),1,.false.,EUg(1,1,k),EUgder(1,1,k),
10165 & AEA(1,1,2),AEAderg(1,1,2),AEAderx(1,1,1,1,1,2))
10166 C Following matrices are needed only for 6-th order cumulants
10167 IF (wcorr6.gt.0.0d0) THEN
10168 call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
10169 & a_chuj_der(1,1,1,1,kk,k),1,.false.,EUgC(1,1,k),EUgCder(1,1,k),
10170 & AECA(1,1,2),AECAderg(1,1,2),AECAderx(1,1,1,1,1,2))
10171 call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
10172 & a_chuj_der(1,1,1,1,kk,k),2,.false.,Ug2DtEUg(1,1,k),
10173 & Ug2DtEUgder(1,1,1,k),ADtEA(1,1,2),ADtEAderg(1,1,1,2),
10174 & ADtEAderx(1,1,1,1,1,2))
10175 call kernel(aa1t(1,1),aa2(1,1),aa1tder(1,1,1,1),
10176 & a_chuj_der(1,1,1,1,kk,k),2,.false.,DtUg2EUg(1,1,k),
10177 & DtUg2EUgder(1,1,1,k),ADtEA1(1,1,2),ADtEA1derg(1,1,1,2),
10178 & ADtEA1derx(1,1,1,1,1,2))
10180 C End 6-th order cumulants
10181 call transpose2(EUgder(1,1,l),auxmat(1,1))
10182 call matmat2(auxmat(1,1),AEA(1,1,2),EAEAderg(1,1,1,2))
10183 call transpose2(EUg(1,1,l),auxmat(1,1))
10184 call matmat2(auxmat(1,1),AEA(1,1,2),EAEA(1,1,2))
10185 call matmat2(auxmat(1,1),AEAderg(1,1,2),EAEAderg(1,1,2,2))
10189 call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
10190 & EAEAderx(1,1,lll,kkk,iii,2))
10195 C Calculate the vectors and their derivatives in virtual-bond dihedral angles.
10196 C They are needed only when the fifth- or the sixth-order cumulants are
10198 IF (wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0) THEN
10199 call transpose2(AEA(1,1,1),auxmat(1,1))
10200 call matvec2(auxmat(1,1),b1(1,i),AEAb1(1,1,1))
10201 call matvec2(auxmat(1,1),Ub2(1,i),AEAb2(1,1,1))
10202 call matvec2(auxmat(1,1),Ub2der(1,i),AEAb2derg(1,2,1,1))
10203 call transpose2(AEAderg(1,1,1),auxmat(1,1))
10204 call matvec2(auxmat(1,1),b1(1,i),AEAb1derg(1,1,1))
10205 call matvec2(auxmat(1,1),Ub2(1,i),AEAb2derg(1,1,1,1))
10206 call matvec2(AEA(1,1,1),b1(1,k+1),AEAb1(1,2,1))
10207 call matvec2(AEAderg(1,1,1),b1(1,k+1),AEAb1derg(1,2,1))
10208 call matvec2(AEA(1,1,1),Ub2(1,k+1),AEAb2(1,2,1))
10209 call matvec2(AEAderg(1,1,1),Ub2(1,k+1),AEAb2derg(1,1,2,1))
10210 call matvec2(AEA(1,1,1),Ub2der(1,k+1),AEAb2derg(1,2,2,1))
10211 call transpose2(AEA(1,1,2),auxmat(1,1))
10212 call matvec2(auxmat(1,1),b1(1,j),AEAb1(1,1,2))
10213 call matvec2(auxmat(1,1),Ub2(1,j),AEAb2(1,1,2))
10214 call matvec2(auxmat(1,1),Ub2der(1,j),AEAb2derg(1,2,1,2))
10215 call transpose2(AEAderg(1,1,2),auxmat(1,1))
10216 call matvec2(auxmat(1,1),b1(1,j),AEAb1derg(1,1,2))
10217 call matvec2(auxmat(1,1),Ub2(1,j),AEAb2derg(1,1,1,2))
10218 call matvec2(AEA(1,1,2),b1(1,l+1),AEAb1(1,2,2))
10219 call matvec2(AEAderg(1,1,2),b1(1,l+1),AEAb1derg(1,2,2))
10220 call matvec2(AEA(1,1,2),Ub2(1,l+1),AEAb2(1,2,2))
10221 call matvec2(AEAderg(1,1,2),Ub2(1,l+1),AEAb2derg(1,1,2,2))
10222 call matvec2(AEA(1,1,2),Ub2der(1,l+1),AEAb2derg(1,2,2,2))
10223 C Calculate the Cartesian derivatives of the vectors.
10227 call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1))
10228 call matvec2(auxmat(1,1),b1(1,i),
10229 & AEAb1derx(1,lll,kkk,iii,1,1))
10230 call matvec2(auxmat(1,1),Ub2(1,i),
10231 & AEAb2derx(1,lll,kkk,iii,1,1))
10232 call matvec2(AEAderx(1,1,lll,kkk,iii,1),b1(1,k+1),
10233 & AEAb1derx(1,lll,kkk,iii,2,1))
10234 call matvec2(AEAderx(1,1,lll,kkk,iii,1),Ub2(1,k+1),
10235 & AEAb2derx(1,lll,kkk,iii,2,1))
10236 call transpose2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1))
10237 call matvec2(auxmat(1,1),b1(1,j),
10238 & AEAb1derx(1,lll,kkk,iii,1,2))
10239 call matvec2(auxmat(1,1),Ub2(1,j),
10240 & AEAb2derx(1,lll,kkk,iii,1,2))
10241 call matvec2(AEAderx(1,1,lll,kkk,iii,2),b1(1,l+1),
10242 & AEAb1derx(1,lll,kkk,iii,2,2))
10243 call matvec2(AEAderx(1,1,lll,kkk,iii,2),Ub2(1,l+1),
10244 & AEAb2derx(1,lll,kkk,iii,2,2))
10251 C Antiparallel orientation of the two CA-CA-CA frames.
10253 iti=itype2loc(itype(i))
10257 itk1=itype2loc(itype(k+1))
10258 itl=itype2loc(itype(l))
10259 itj=itype2loc(itype(j))
10260 if (j.lt.nres-1) then
10261 itj1=itype2loc(itype(j+1))
10265 C A2 kernel(j-1)T A1T
10266 call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10267 & aa2tder(1,1,1,1),1,.true.,EUg(1,1,j),EUgder(1,1,j),
10268 & AEA(1,1,1),AEAderg(1,1,1),AEAderx(1,1,1,1,1,1))
10269 C Following matrices are needed only for 6-th order cumulants
10270 IF (wcorr6.gt.0.0d0 .or. (wturn6.gt.0.0d0 .and.
10271 & j.eq.i+4 .and. l.eq.i+3)) THEN
10272 call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10273 & aa2tder(1,1,1,1),1,.true.,EUgC(1,1,j),EUgCder(1,1,j),
10274 & AECA(1,1,1),AECAderg(1,1,1),AECAderx(1,1,1,1,1,1))
10275 call kernel(aa2(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10276 & aa2tder(1,1,1,1),2,.true.,Ug2DtEUg(1,1,j),
10277 & Ug2DtEUgder(1,1,1,j),ADtEA(1,1,1),ADtEAderg(1,1,1,1),
10278 & ADtEAderx(1,1,1,1,1,1))
10279 call kernel(aa1(1,1),aa2t(1,1),a_chuj_der(1,1,1,1,jj,i),
10280 & aa2tder(1,1,1,1),2,.true.,DtUg2EUg(1,1,j),
10281 & DtUg2EUgder(1,1,1,j),ADtEA1(1,1,1),ADtEA1derg(1,1,1,1),
10282 & ADtEA1derx(1,1,1,1,1,1))
10284 C End 6-th order cumulants
10285 call transpose2(EUgder(1,1,k),auxmat(1,1))
10286 call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,1,1))
10287 call transpose2(EUg(1,1,k),auxmat(1,1))
10288 call matmat2(auxmat(1,1),AEA(1,1,1),EAEA(1,1,1))
10289 call matmat2(auxmat(1,1),AEAderg(1,1,1),EAEAderg(1,1,2,1))
10293 call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
10294 & EAEAderx(1,1,lll,kkk,iii,1))
10298 C A2T kernel(i+1)T A1
10299 call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
10300 & a_chuj_der(1,1,1,1,jj,i),1,.true.,EUg(1,1,k),EUgder(1,1,k),
10301 & AEA(1,1,2),AEAderg(1,1,2),AEAderx(1,1,1,1,1,2))
10302 C Following matrices are needed only for 6-th order cumulants
10303 IF (wcorr6.gt.0.0d0 .or. (wturn6.gt.0.0d0 .and.
10304 & j.eq.i+4 .and. l.eq.i+3)) THEN
10305 call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
10306 & a_chuj_der(1,1,1,1,jj,i),1,.true.,EUgC(1,1,k),EUgCder(1,1,k),
10307 & AECA(1,1,2),AECAderg(1,1,2),AECAderx(1,1,1,1,1,2))
10308 call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
10309 & a_chuj_der(1,1,1,1,jj,i),2,.true.,Ug2DtEUg(1,1,k),
10310 & Ug2DtEUgder(1,1,1,k),ADtEA(1,1,2),ADtEAderg(1,1,1,2),
10311 & ADtEAderx(1,1,1,1,1,2))
10312 call kernel(aa2t(1,1),aa1(1,1),aa2tder(1,1,1,1),
10313 & a_chuj_der(1,1,1,1,jj,i),2,.true.,DtUg2EUg(1,1,k),
10314 & DtUg2EUgder(1,1,1,k),ADtEA1(1,1,2),ADtEA1derg(1,1,1,2),
10315 & ADtEA1derx(1,1,1,1,1,2))
10317 C End 6-th order cumulants
10318 call transpose2(EUgder(1,1,j),auxmat(1,1))
10319 call matmat2(auxmat(1,1),AEA(1,1,1),EAEAderg(1,1,2,2))
10320 call transpose2(EUg(1,1,j),auxmat(1,1))
10321 call matmat2(auxmat(1,1),AEA(1,1,2),EAEA(1,1,2))
10322 call matmat2(auxmat(1,1),AEAderg(1,1,2),EAEAderg(1,1,2,2))
10326 call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
10327 & EAEAderx(1,1,lll,kkk,iii,2))
10332 C Calculate the vectors and their derivatives in virtual-bond dihedral angles.
10333 C They are needed only when the fifth- or the sixth-order cumulants are
10335 IF (wcorr5.gt.0.0d0 .or. wcorr6.gt.0.0d0 .or.
10336 & (wturn6.gt.0.0d0 .and. j.eq.i+4 .and. l.eq.i+3)) THEN
10337 call transpose2(AEA(1,1,1),auxmat(1,1))
10338 call matvec2(auxmat(1,1),b1(1,i),AEAb1(1,1,1))
10339 call matvec2(auxmat(1,1),Ub2(1,i),AEAb2(1,1,1))
10340 call matvec2(auxmat(1,1),Ub2der(1,i),AEAb2derg(1,2,1,1))
10341 call transpose2(AEAderg(1,1,1),auxmat(1,1))
10342 call matvec2(auxmat(1,1),b1(1,i),AEAb1derg(1,1,1))
10343 call matvec2(auxmat(1,1),Ub2(1,i),AEAb2derg(1,1,1,1))
10344 call matvec2(AEA(1,1,1),b1(1,k+1),AEAb1(1,2,1))
10345 call matvec2(AEAderg(1,1,1),b1(1,k+1),AEAb1derg(1,2,1))
10346 call matvec2(AEA(1,1,1),Ub2(1,k+1),AEAb2(1,2,1))
10347 call matvec2(AEAderg(1,1,1),Ub2(1,k+1),AEAb2derg(1,1,2,1))
10348 call matvec2(AEA(1,1,1),Ub2der(1,k+1),AEAb2derg(1,2,2,1))
10349 call transpose2(AEA(1,1,2),auxmat(1,1))
10350 call matvec2(auxmat(1,1),b1(1,j+1),AEAb1(1,1,2))
10351 call matvec2(auxmat(1,1),Ub2(1,l),AEAb2(1,1,2))
10352 call matvec2(auxmat(1,1),Ub2der(1,l),AEAb2derg(1,2,1,2))
10353 call transpose2(AEAderg(1,1,2),auxmat(1,1))
10354 call matvec2(auxmat(1,1),b1(1,l),AEAb1(1,1,2))
10355 call matvec2(auxmat(1,1),Ub2(1,l),AEAb2derg(1,1,1,2))
10356 call matvec2(AEA(1,1,2),b1(1,j+1),AEAb1(1,2,2))
10357 call matvec2(AEAderg(1,1,2),b1(1,j+1),AEAb1derg(1,2,2))
10358 call matvec2(AEA(1,1,2),Ub2(1,j),AEAb2(1,2,2))
10359 call matvec2(AEAderg(1,1,2),Ub2(1,j),AEAb2derg(1,1,2,2))
10360 call matvec2(AEA(1,1,2),Ub2der(1,j),AEAb2derg(1,2,2,2))
10361 C Calculate the Cartesian derivatives of the vectors.
10365 call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1))
10366 call matvec2(auxmat(1,1),b1(1,i),
10367 & AEAb1derx(1,lll,kkk,iii,1,1))
10368 call matvec2(auxmat(1,1),Ub2(1,i),
10369 & AEAb2derx(1,lll,kkk,iii,1,1))
10370 call matvec2(AEAderx(1,1,lll,kkk,iii,1),b1(1,k+1),
10371 & AEAb1derx(1,lll,kkk,iii,2,1))
10372 call matvec2(AEAderx(1,1,lll,kkk,iii,1),Ub2(1,k+1),
10373 & AEAb2derx(1,lll,kkk,iii,2,1))
10374 call transpose2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1))
10375 call matvec2(auxmat(1,1),b1(1,l),
10376 & AEAb1derx(1,lll,kkk,iii,1,2))
10377 call matvec2(auxmat(1,1),Ub2(1,l),
10378 & AEAb2derx(1,lll,kkk,iii,1,2))
10379 call matvec2(AEAderx(1,1,lll,kkk,iii,2),b1(1,j+1),
10380 & AEAb1derx(1,lll,kkk,iii,2,2))
10381 call matvec2(AEAderx(1,1,lll,kkk,iii,2),Ub2(1,j),
10382 & AEAb2derx(1,lll,kkk,iii,2,2))
10391 C---------------------------------------------------------------------------
10392 subroutine kernel(aa1,aa2t,aa1derx,aa2tderx,nderg,transp,
10393 & KK,KKderg,AKA,AKAderg,AKAderx)
10397 double precision aa1(2,2),aa2t(2,2),aa1derx(2,2,3,5),
10398 & aa2tderx(2,2,3,5),KK(2,2),KKderg(2,2,nderg),AKA(2,2),
10399 & AKAderg(2,2,nderg),AKAderx(2,2,3,5,2)
10400 integer iii,kkk,lll
10403 common /kutas/ lprn
10404 call prodmat3(aa1(1,1),aa2t(1,1),KK(1,1),transp,AKA(1,1))
10406 call prodmat3(aa1(1,1),aa2t(1,1),KKderg(1,1,iii),transp,
10407 & AKAderg(1,1,iii))
10409 cd if (lprn) write (2,*) 'In kernel'
10411 cd if (lprn) write (2,*) 'kkk=',kkk
10413 call prodmat3(aa1derx(1,1,lll,kkk),aa2t(1,1),
10414 & KK(1,1),transp,AKAderx(1,1,lll,kkk,1))
10416 cd write (2,*) 'lll=',lll
10417 cd write (2,*) 'iii=1'
10419 cd write (2,'(3(2f10.5),5x)')
10420 cd & (AKAderx(jjj,mmm,lll,kkk,1),mmm=1,2)
10423 call prodmat3(aa1(1,1),aa2tderx(1,1,lll,kkk),
10424 & KK(1,1),transp,AKAderx(1,1,lll,kkk,2))
10426 cd write (2,*) 'lll=',lll
10427 cd write (2,*) 'iii=2'
10429 cd write (2,'(3(2f10.5),5x)')
10430 cd & (AKAderx(jjj,mmm,lll,kkk,2),mmm=1,2)
10437 C---------------------------------------------------------------------------
10438 double precision function eello4(i,j,k,l,jj,kk)
10439 implicit real*8 (a-h,o-z)
10440 include 'DIMENSIONS'
10441 include 'COMMON.IOUNITS'
10442 include 'COMMON.CHAIN'
10443 include 'COMMON.DERIV'
10444 include 'COMMON.INTERACT'
10445 include 'COMMON.CONTACTS'
10446 include 'COMMON.CONTMAT'
10447 include 'COMMON.CORRMAT'
10448 include 'COMMON.TORSION'
10449 include 'COMMON.VAR'
10450 include 'COMMON.GEO'
10451 double precision pizda(2,2),ggg1(3),ggg2(3)
10452 cd if (i.ne.1 .or. j.ne.5 .or. k.ne.2 .or.l.ne.4) then
10456 cd print *,'eello4:',i,j,k,l,jj,kk
10457 cd write (2,*) 'i',i,' j',j,' k',k,' l',l
10458 cd call checkint4(i,j,k,l,jj,kk,eel4_num)
10459 cold eij=facont_hb(jj,i)
10460 cold ekl=facont_hb(kk,k)
10462 eel4=-EAEA(1,1,1)-EAEA(2,2,1)
10463 cd eel41=-EAEA(1,1,2)-EAEA(2,2,2)
10464 gcorr_loc(k-1)=gcorr_loc(k-1)
10465 & -ekont*(EAEAderg(1,1,1,1)+EAEAderg(2,2,1,1))
10467 gcorr_loc(l-1)=gcorr_loc(l-1)
10468 & -ekont*(EAEAderg(1,1,2,1)+EAEAderg(2,2,2,1))
10469 C Al 4/16/16: Derivatives in theta, to be added later.
10471 c gcorr_loc(nphi+l-1)=gcorr_loc(nphi+l-1)
10472 c & -ekont*(EAEAdert(1,1,2,1)+EAEAdert(2,2,2,1))
10475 gcorr_loc(j-1)=gcorr_loc(j-1)
10476 & -ekont*(EAEAderg(1,1,2,1)+EAEAderg(2,2,2,1))
10478 c gcorr_loc(nphi+j-1)=gcorr_loc(nphi+j-1)
10479 c & -ekont*(EAEAdert(1,1,2,1)+EAEAdert(2,2,2,1))
10485 derx(lll,kkk,iii)=-EAEAderx(1,1,lll,kkk,iii,1)
10486 & -EAEAderx(2,2,lll,kkk,iii,1)
10487 cd derx(lll,kkk,iii)=0.0d0
10491 cd gcorr_loc(l-1)=0.0d0
10492 cd gcorr_loc(j-1)=0.0d0
10493 cd gcorr_loc(k-1)=0.0d0
10495 cd write (iout,*)'Contacts have occurred for peptide groups',
10496 cd & i,j,' fcont:',eij,' eij',' and ',k,l,
10497 cd & ' fcont ',ekl,' eel4=',eel4,' eel4_num',16*eel4_num
10498 if (j.lt.nres-1) then
10505 if (l.lt.nres-1) then
10513 cgrad ggg1(ll)=eel4*g_contij(ll,1)
10514 cgrad ggg2(ll)=eel4*g_contij(ll,2)
10515 glongij=eel4*g_contij(ll,1)+ekont*derx(ll,1,1)
10516 glongkl=eel4*g_contij(ll,2)+ekont*derx(ll,1,2)
10517 cgrad ghalf=0.5d0*ggg1(ll)
10518 gradcorr(ll,i)=gradcorr(ll,i)+ekont*derx(ll,2,1)
10519 gradcorr(ll,i+1)=gradcorr(ll,i+1)+ekont*derx(ll,3,1)
10520 gradcorr(ll,j)=gradcorr(ll,j)+ekont*derx(ll,4,1)
10521 gradcorr(ll,j1)=gradcorr(ll,j1)+ekont*derx(ll,5,1)
10522 gradcorr_long(ll,j)=gradcorr_long(ll,j)+glongij
10523 gradcorr_long(ll,i)=gradcorr_long(ll,i)-glongij
10524 cgrad ghalf=0.5d0*ggg2(ll)
10525 gradcorr(ll,k)=gradcorr(ll,k)+ekont*derx(ll,2,2)
10526 gradcorr(ll,k+1)=gradcorr(ll,k+1)+ekont*derx(ll,3,2)
10527 gradcorr(ll,l)=gradcorr(ll,l)+ekont*derx(ll,4,2)
10528 gradcorr(ll,l1)=gradcorr(ll,l1)+ekont*derx(ll,5,2)
10529 gradcorr_long(ll,l)=gradcorr_long(ll,l)+glongkl
10530 gradcorr_long(ll,k)=gradcorr_long(ll,k)-glongkl
10534 cgrad gradcorr(ll,m)=gradcorr(ll,m)+ggg1(ll)
10539 cgrad gradcorr(ll,m)=gradcorr(ll,m)+ggg2(ll)
10544 cgrad gradcorr(ll,m)=gradcorr(ll,m)+ekont*derx(ll,1,1)
10549 cgrad gradcorr(ll,m)=gradcorr(ll,m)+ekont*derx(ll,1,2)
10553 cd write (2,*) iii,gcorr_loc(iii)
10556 cd write (2,*) 'ekont',ekont
10557 cd write (iout,*) 'eello4',ekont*eel4
10560 C---------------------------------------------------------------------------
10561 double precision function eello5(i,j,k,l,jj,kk)
10562 implicit real*8 (a-h,o-z)
10563 include 'DIMENSIONS'
10564 include 'COMMON.IOUNITS'
10565 include 'COMMON.CHAIN'
10566 include 'COMMON.DERIV'
10567 include 'COMMON.INTERACT'
10568 include 'COMMON.CONTACTS'
10569 include 'COMMON.CONTMAT'
10570 include 'COMMON.CORRMAT'
10571 include 'COMMON.TORSION'
10572 include 'COMMON.VAR'
10573 include 'COMMON.GEO'
10574 double precision pizda(2,2),auxmat(2,2),auxmat1(2,2),vv(2)
10575 double precision ggg1(3),ggg2(3)
10576 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
10578 C Parallel chains C
10581 C /l\ / \ \ / \ / \ / C
10582 C / \ / \ \ / \ / \ / C
10583 C j| o |l1 | o | o| o | | o |o C
10584 C \ |/k\| |/ \| / |/ \| |/ \| C
10585 C \i/ \ / \ / / \ / \ C
10587 C (I) (II) (III) (IV) C
10589 C eello5_1 eello5_2 eello5_3 eello5_4 C
10591 C Antiparallel chains C
10594 C /j\ / \ \ / \ / \ / C
10595 C / \ / \ \ / \ / \ / C
10596 C j1| o |l | o | o| o | | o |o C
10597 C \ |/k\| |/ \| / |/ \| |/ \| C
10598 C \i/ \ / \ / / \ / \ C
10600 C (I) (II) (III) (IV) C
10602 C eello5_1 eello5_2 eello5_3 eello5_4 C
10604 C o denotes a local interaction, vertical lines an electrostatic interaction. C
10606 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
10607 cd if (i.ne.2 .or. j.ne.6 .or. k.ne.3 .or. l.ne.5) then
10612 cd & 'EELLO5: Contacts have occurred for peptide groups',i,j,
10614 itk=itype2loc(itype(k))
10615 itl=itype2loc(itype(l))
10616 itj=itype2loc(itype(j))
10621 cd call checkint5(i,j,k,l,jj,kk,eel5_1_num,eel5_2_num,
10622 cd & eel5_3_num,eel5_4_num)
10626 derx(lll,kkk,iii)=0.0d0
10630 cd eij=facont_hb(jj,i)
10631 cd ekl=facont_hb(kk,k)
10633 cd write (iout,*)'Contacts have occurred for peptide groups',
10634 cd & i,j,' fcont:',eij,' eij',' and ',k,l
10636 C Contribution from the graph I.
10637 cd write (2,*) 'AEA ',AEA(1,1,1),AEA(2,1,1),AEA(1,2,1),AEA(2,2,1)
10638 cd write (2,*) 'AEAb2',AEAb2(1,1,1),AEAb2(2,1,1)
10639 call transpose2(EUg(1,1,k),auxmat(1,1))
10640 call matmat2(AEA(1,1,1),auxmat(1,1),pizda(1,1))
10641 vv(1)=pizda(1,1)-pizda(2,2)
10642 vv(2)=pizda(1,2)+pizda(2,1)
10643 eello5_1=scalar2(AEAb2(1,1,1),Ub2(1,k))
10644 & +0.5d0*scalar2(vv(1),Dtobr2(1,i))
10645 C Explicit gradient in virtual-dihedral angles.
10646 if (i.gt.1) g_corr5_loc(i-1)=g_corr5_loc(i-1)
10647 & +ekont*(scalar2(AEAb2derg(1,2,1,1),Ub2(1,k))
10648 & +0.5d0*scalar2(vv(1),Dtobr2der(1,i)))
10649 call transpose2(EUgder(1,1,k),auxmat1(1,1))
10650 call matmat2(AEA(1,1,1),auxmat1(1,1),pizda(1,1))
10651 vv(1)=pizda(1,1)-pizda(2,2)
10652 vv(2)=pizda(1,2)+pizda(2,1)
10653 g_corr5_loc(k-1)=g_corr5_loc(k-1)
10654 & +ekont*(scalar2(AEAb2(1,1,1),Ub2der(1,k))
10655 & +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
10656 call matmat2(AEAderg(1,1,1),auxmat(1,1),pizda(1,1))
10657 vv(1)=pizda(1,1)-pizda(2,2)
10658 vv(2)=pizda(1,2)+pizda(2,1)
10660 if (l.lt.nres-1) g_corr5_loc(l-1)=g_corr5_loc(l-1)
10661 & +ekont*(scalar2(AEAb2derg(1,1,1,1),Ub2(1,k))
10662 & +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
10664 if (j.lt.nres-1) g_corr5_loc(j-1)=g_corr5_loc(j-1)
10665 & +ekont*(scalar2(AEAb2derg(1,1,1,1),Ub2(1,k))
10666 & +0.5d0*scalar2(vv(1),Dtobr2(1,i)))
10668 C Cartesian gradient
10672 call matmat2(AEAderx(1,1,lll,kkk,iii,1),auxmat(1,1),
10674 vv(1)=pizda(1,1)-pizda(2,2)
10675 vv(2)=pizda(1,2)+pizda(2,1)
10676 derx(lll,kkk,iii)=derx(lll,kkk,iii)
10677 & +scalar2(AEAb2derx(1,lll,kkk,iii,1,1),Ub2(1,k))
10678 & +0.5d0*scalar2(vv(1),Dtobr2(1,i))
10684 C Contribution from graph II
10685 call transpose2(EE(1,1,k),auxmat(1,1))
10686 call matmat2(auxmat(1,1),AEA(1,1,1),pizda(1,1))
10687 vv(1)=pizda(1,1)+pizda(2,2)
10688 vv(2)=pizda(2,1)-pizda(1,2)
10689 eello5_2=scalar2(AEAb1(1,2,1),b1(1,k))
10690 & -0.5d0*scalar2(vv(1),Ctobr(1,k))
10691 C Explicit gradient in virtual-dihedral angles.
10692 g_corr5_loc(k-1)=g_corr5_loc(k-1)
10693 & -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,k))
10694 call matmat2(auxmat(1,1),AEAderg(1,1,1),pizda(1,1))
10695 vv(1)=pizda(1,1)+pizda(2,2)
10696 vv(2)=pizda(2,1)-pizda(1,2)
10698 g_corr5_loc(l-1)=g_corr5_loc(l-1)
10699 & +ekont*(scalar2(AEAb1derg(1,2,1),b1(1,k))
10700 & -0.5d0*scalar2(vv(1),Ctobr(1,k)))
10702 g_corr5_loc(j-1)=g_corr5_loc(j-1)
10703 & +ekont*(scalar2(AEAb1derg(1,2,1),b1(1,k))
10704 & -0.5d0*scalar2(vv(1),Ctobr(1,k)))
10706 C Cartesian gradient
10710 call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,1),
10712 vv(1)=pizda(1,1)+pizda(2,2)
10713 vv(2)=pizda(2,1)-pizda(1,2)
10714 derx(lll,kkk,iii)=derx(lll,kkk,iii)
10715 & +scalar2(AEAb1derx(1,lll,kkk,iii,2,1),b1(1,k))
10716 & -0.5d0*scalar2(vv(1),Ctobr(1,k))
10724 C Parallel orientation
10725 C Contribution from graph III
10726 call transpose2(EUg(1,1,l),auxmat(1,1))
10727 call matmat2(AEA(1,1,2),auxmat(1,1),pizda(1,1))
10728 vv(1)=pizda(1,1)-pizda(2,2)
10729 vv(2)=pizda(1,2)+pizda(2,1)
10730 eello5_3=scalar2(AEAb2(1,1,2),Ub2(1,l))
10731 & +0.5d0*scalar2(vv(1),Dtobr2(1,j))
10732 C Explicit gradient in virtual-dihedral angles.
10733 g_corr5_loc(j-1)=g_corr5_loc(j-1)
10734 & +ekont*(scalar2(AEAb2derg(1,2,1,2),Ub2(1,l))
10735 & +0.5d0*scalar2(vv(1),Dtobr2der(1,j)))
10736 call matmat2(AEAderg(1,1,2),auxmat(1,1),pizda(1,1))
10737 vv(1)=pizda(1,1)-pizda(2,2)
10738 vv(2)=pizda(1,2)+pizda(2,1)
10739 g_corr5_loc(k-1)=g_corr5_loc(k-1)
10740 & +ekont*(scalar2(AEAb2derg(1,1,1,2),Ub2(1,l))
10741 & +0.5d0*scalar2(vv(1),Dtobr2(1,j)))
10742 call transpose2(EUgder(1,1,l),auxmat1(1,1))
10743 call matmat2(AEA(1,1,2),auxmat1(1,1),pizda(1,1))
10744 vv(1)=pizda(1,1)-pizda(2,2)
10745 vv(2)=pizda(1,2)+pizda(2,1)
10746 g_corr5_loc(l-1)=g_corr5_loc(l-1)
10747 & +ekont*(scalar2(AEAb2(1,1,2),Ub2der(1,l))
10748 & +0.5d0*scalar2(vv(1),Dtobr2(1,j)))
10749 C Cartesian gradient
10753 call matmat2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1),
10755 vv(1)=pizda(1,1)-pizda(2,2)
10756 vv(2)=pizda(1,2)+pizda(2,1)
10757 derx(lll,kkk,iii)=derx(lll,kkk,iii)
10758 & +scalar2(AEAb2derx(1,lll,kkk,iii,1,2),Ub2(1,l))
10759 & +0.5d0*scalar2(vv(1),Dtobr2(1,j))
10764 C Contribution from graph IV
10766 call transpose2(EE(1,1,l),auxmat(1,1))
10767 call matmat2(auxmat(1,1),AEA(1,1,2),pizda(1,1))
10768 vv(1)=pizda(1,1)+pizda(2,2)
10769 vv(2)=pizda(2,1)-pizda(1,2)
10770 eello5_4=scalar2(AEAb1(1,2,2),b1(1,l))
10771 & -0.5d0*scalar2(vv(1),Ctobr(1,l))
10772 C Explicit gradient in virtual-dihedral angles.
10773 g_corr5_loc(l-1)=g_corr5_loc(l-1)
10774 & -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,l))
10775 call matmat2(auxmat(1,1),AEAderg(1,1,2),pizda(1,1))
10776 vv(1)=pizda(1,1)+pizda(2,2)
10777 vv(2)=pizda(2,1)-pizda(1,2)
10778 g_corr5_loc(k-1)=g_corr5_loc(k-1)
10779 & +ekont*(scalar2(AEAb1derg(1,2,2),b1(1,l))
10780 & -0.5d0*scalar2(vv(1),Ctobr(1,l)))
10781 C Cartesian gradient
10785 call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
10787 vv(1)=pizda(1,1)+pizda(2,2)
10788 vv(2)=pizda(2,1)-pizda(1,2)
10789 derx(lll,kkk,iii)=derx(lll,kkk,iii)
10790 & +scalar2(AEAb1derx(1,lll,kkk,iii,2,2),b1(1,l))
10791 & -0.5d0*scalar2(vv(1),Ctobr(1,l))
10796 C Antiparallel orientation
10797 C Contribution from graph III
10799 call transpose2(EUg(1,1,j),auxmat(1,1))
10800 call matmat2(AEA(1,1,2),auxmat(1,1),pizda(1,1))
10801 vv(1)=pizda(1,1)-pizda(2,2)
10802 vv(2)=pizda(1,2)+pizda(2,1)
10803 eello5_3=scalar2(AEAb2(1,1,2),Ub2(1,j))
10804 & +0.5d0*scalar2(vv(1),Dtobr2(1,l))
10805 C Explicit gradient in virtual-dihedral angles.
10806 g_corr5_loc(l-1)=g_corr5_loc(l-1)
10807 & +ekont*(scalar2(AEAb2derg(1,2,1,2),Ub2(1,j))
10808 & +0.5d0*scalar2(vv(1),Dtobr2der(1,l)))
10809 call matmat2(AEAderg(1,1,2),auxmat(1,1),pizda(1,1))
10810 vv(1)=pizda(1,1)-pizda(2,2)
10811 vv(2)=pizda(1,2)+pizda(2,1)
10812 g_corr5_loc(k-1)=g_corr5_loc(k-1)
10813 & +ekont*(scalar2(AEAb2derg(1,1,1,2),Ub2(1,j))
10814 & +0.5d0*scalar2(vv(1),Dtobr2(1,l)))
10815 call transpose2(EUgder(1,1,j),auxmat1(1,1))
10816 call matmat2(AEA(1,1,2),auxmat1(1,1),pizda(1,1))
10817 vv(1)=pizda(1,1)-pizda(2,2)
10818 vv(2)=pizda(1,2)+pizda(2,1)
10819 g_corr5_loc(j-1)=g_corr5_loc(j-1)
10820 & +ekont*(scalar2(AEAb2(1,1,2),Ub2der(1,j))
10821 & +0.5d0*scalar2(vv(1),Dtobr2(1,l)))
10822 C Cartesian gradient
10826 call matmat2(AEAderx(1,1,lll,kkk,iii,2),auxmat(1,1),
10828 vv(1)=pizda(1,1)-pizda(2,2)
10829 vv(2)=pizda(1,2)+pizda(2,1)
10830 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)
10831 & +scalar2(AEAb2derx(1,lll,kkk,iii,1,2),Ub2(1,j))
10832 & +0.5d0*scalar2(vv(1),Dtobr2(1,l))
10837 C Contribution from graph IV
10839 call transpose2(EE(1,1,j),auxmat(1,1))
10840 call matmat2(auxmat(1,1),AEA(1,1,2),pizda(1,1))
10841 vv(1)=pizda(1,1)+pizda(2,2)
10842 vv(2)=pizda(2,1)-pizda(1,2)
10843 eello5_4=scalar2(AEAb1(1,2,2),b1(1,j))
10844 & -0.5d0*scalar2(vv(1),Ctobr(1,j))
10845 C Explicit gradient in virtual-dihedral angles.
10846 g_corr5_loc(j-1)=g_corr5_loc(j-1)
10847 & -0.5d0*ekont*scalar2(vv(1),Ctobrder(1,j))
10848 call matmat2(auxmat(1,1),AEAderg(1,1,2),pizda(1,1))
10849 vv(1)=pizda(1,1)+pizda(2,2)
10850 vv(2)=pizda(2,1)-pizda(1,2)
10851 g_corr5_loc(k-1)=g_corr5_loc(k-1)
10852 & +ekont*(scalar2(AEAb1derg(1,2,2),b1(1,j))
10853 & -0.5d0*scalar2(vv(1),Ctobr(1,j)))
10854 C Cartesian gradient
10858 call matmat2(auxmat(1,1),AEAderx(1,1,lll,kkk,iii,2),
10860 vv(1)=pizda(1,1)+pizda(2,2)
10861 vv(2)=pizda(2,1)-pizda(1,2)
10862 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)
10863 & +scalar2(AEAb1derx(1,lll,kkk,iii,2,2),b1(1,j))
10864 & -0.5d0*scalar2(vv(1),Ctobr(1,j))
10870 eel5=eello5_1+eello5_2+eello5_3+eello5_4
10871 cd if (i.eq.2 .and. j.eq.8 .and. k.eq.3 .and. l.eq.7) then
10872 cd write (2,*) 'ijkl',i,j,k,l
10873 cd write (2,*) 'eello5_1',eello5_1,' eello5_2',eello5_2,
10874 cd & ' eello5_3',eello5_3,' eello5_4',eello5_4
10876 cd write(iout,*) 'eello5_1',eello5_1,' eel5_1_num',16*eel5_1_num
10877 cd write(iout,*) 'eello5_2',eello5_2,' eel5_2_num',16*eel5_2_num
10878 cd write(iout,*) 'eello5_3',eello5_3,' eel5_3_num',16*eel5_3_num
10879 cd write(iout,*) 'eello5_4',eello5_4,' eel5_4_num',16*eel5_4_num
10880 if (j.lt.nres-1) then
10887 if (l.lt.nres-1) then
10897 cd write (2,*) 'eij',eij,' ekl',ekl,' ekont',ekont
10898 C 2/11/08 AL Gradients over DC's connecting interacting sites will be
10899 C summed up outside the subrouine as for the other subroutines
10900 C handling long-range interactions. The old code is commented out
10901 C with "cgrad" to keep track of changes.
10903 cgrad ggg1(ll)=eel5*g_contij(ll,1)
10904 cgrad ggg2(ll)=eel5*g_contij(ll,2)
10905 gradcorr5ij=eel5*g_contij(ll,1)+ekont*derx(ll,1,1)
10906 gradcorr5kl=eel5*g_contij(ll,2)+ekont*derx(ll,1,2)
10907 c write (iout,'(a,3i3,a,5f8.3,2i3,a,5f8.3,a,f8.3)')
10908 c & "ecorr5",ll,i,j," derx",derx(ll,2,1),derx(ll,3,1),derx(ll,4,1),
10909 c & derx(ll,5,1),k,l," derx",derx(ll,2,2),derx(ll,3,2),
10910 c & derx(ll,4,2),derx(ll,5,2)," ekont",ekont
10911 c write (iout,'(a,3i3,a,3f8.3,2i3,a,3f8.3)')
10912 c & "ecorr5",ll,i,j," gradcorr5",g_contij(ll,1),derx(ll,1,1),
10914 c & k,l," gradcorr5",g_contij(ll,2),derx(ll,1,2),gradcorr5kl
10915 cold ghalf=0.5d0*eel5*ekl*gacont_hbr(ll,jj,i)
10916 cgrad ghalf=0.5d0*ggg1(ll)
10918 gradcorr5(ll,i)=gradcorr5(ll,i)+ekont*derx(ll,2,1)
10919 gradcorr5(ll,i+1)=gradcorr5(ll,i+1)+ekont*derx(ll,3,1)
10920 gradcorr5(ll,j)=gradcorr5(ll,j)+ekont*derx(ll,4,1)
10921 gradcorr5(ll,j1)=gradcorr5(ll,j1)+ekont*derx(ll,5,1)
10922 gradcorr5_long(ll,j)=gradcorr5_long(ll,j)+gradcorr5ij
10923 gradcorr5_long(ll,i)=gradcorr5_long(ll,i)-gradcorr5ij
10924 cold ghalf=0.5d0*eel5*eij*gacont_hbr(ll,kk,k)
10925 cgrad ghalf=0.5d0*ggg2(ll)
10927 gradcorr5(ll,k)=gradcorr5(ll,k)+ekont*derx(ll,2,2)
10928 gradcorr5(ll,k+1)=gradcorr5(ll,k+1)+ekont*derx(ll,3,2)
10929 gradcorr5(ll,l)=gradcorr5(ll,l)+ekont*derx(ll,4,2)
10930 gradcorr5(ll,l1)=gradcorr5(ll,l1)+ekont*derx(ll,5,2)
10931 gradcorr5_long(ll,l)=gradcorr5_long(ll,l)+gradcorr5kl
10932 gradcorr5_long(ll,k)=gradcorr5_long(ll,k)-gradcorr5kl
10937 cold gradcorr5(ll,m)=gradcorr5(ll,m)+eel5*ekl*gacont_hbr(ll,jj,i)
10938 cgrad gradcorr5(ll,m)=gradcorr5(ll,m)+ggg1(ll)
10943 cold gradcorr5(ll,m)=gradcorr5(ll,m)+eel5*eij*gacont_hbr(ll,kk,k)
10944 cgrad gradcorr5(ll,m)=gradcorr5(ll,m)+ggg2(ll)
10950 cgrad gradcorr5(ll,m)=gradcorr5(ll,m)+ekont*derx(ll,1,1)
10955 cgrad gradcorr5(ll,m)=gradcorr5(ll,m)+ekont*derx(ll,1,2)
10959 cd write (2,*) iii,g_corr5_loc(iii)
10962 cd write (2,*) 'ekont',ekont
10963 cd write (iout,*) 'eello5',ekont*eel5
10966 c--------------------------------------------------------------------------
10967 double precision function eello6(i,j,k,l,jj,kk)
10968 implicit real*8 (a-h,o-z)
10969 include 'DIMENSIONS'
10970 include 'COMMON.IOUNITS'
10971 include 'COMMON.CHAIN'
10972 include 'COMMON.DERIV'
10973 include 'COMMON.INTERACT'
10974 include 'COMMON.CONTACTS'
10975 include 'COMMON.CONTMAT'
10976 include 'COMMON.CORRMAT'
10977 include 'COMMON.TORSION'
10978 include 'COMMON.VAR'
10979 include 'COMMON.GEO'
10980 include 'COMMON.FFIELD'
10981 double precision ggg1(3),ggg2(3)
10982 cd if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
10987 cd & 'EELLO6: Contacts have occurred for peptide groups',i,j,
10995 cd call checkint6(i,j,k,l,jj,kk,eel6_1_num,eel6_2_num,
10996 cd & eel6_3_num,eel6_4_num,eel6_5_num,eel6_6_num)
11000 derx(lll,kkk,iii)=0.0d0
11004 cd eij=facont_hb(jj,i)
11005 cd ekl=facont_hb(kk,k)
11011 eello6_1=eello6_graph1(i,j,k,l,1,.false.)
11012 eello6_2=eello6_graph1(j,i,l,k,2,.false.)
11013 eello6_3=eello6_graph2(i,j,k,l,jj,kk,.false.)
11014 eello6_4=eello6_graph4(i,j,k,l,jj,kk,1,.false.)
11015 eello6_5=eello6_graph4(j,i,l,k,jj,kk,2,.false.)
11016 eello6_6=eello6_graph3(i,j,k,l,jj,kk,.false.)
11018 eello6_1=eello6_graph1(i,j,k,l,1,.false.)
11019 eello6_2=eello6_graph1(l,k,j,i,2,.true.)
11020 eello6_3=eello6_graph2(i,l,k,j,jj,kk,.true.)
11021 eello6_4=eello6_graph4(i,j,k,l,jj,kk,1,.false.)
11022 if (wturn6.eq.0.0d0 .or. j.ne.i+4) then
11023 eello6_5=eello6_graph4(l,k,j,i,kk,jj,2,.true.)
11027 eello6_6=eello6_graph3(i,l,k,j,jj,kk,.true.)
11029 C If turn contributions are considered, they will be handled separately.
11030 eel6=eello6_1+eello6_2+eello6_3+eello6_4+eello6_5+eello6_6
11031 cd write(iout,*) 'eello6_1',eello6_1!,' eel6_1_num',16*eel6_1_num
11032 cd write(iout,*) 'eello6_2',eello6_2!,' eel6_2_num',16*eel6_2_num
11033 cd write(iout,*) 'eello6_3',eello6_3!,' eel6_3_num',16*eel6_3_num
11034 cd write(iout,*) 'eello6_4',eello6_4!,' eel6_4_num',16*eel6_4_num
11035 cd write(iout,*) 'eello6_5',eello6_5!,' eel6_5_num',16*eel6_5_num
11036 cd write(iout,*) 'eello6_6',eello6_6!,' eel6_6_num',16*eel6_6_num
11038 if (j.lt.nres-1) then
11045 if (l.lt.nres-1) then
11053 cgrad ggg1(ll)=eel6*g_contij(ll,1)
11054 cgrad ggg2(ll)=eel6*g_contij(ll,2)
11055 cold ghalf=0.5d0*eel6*ekl*gacont_hbr(ll,jj,i)
11056 cgrad ghalf=0.5d0*ggg1(ll)
11058 gradcorr6ij=eel6*g_contij(ll,1)+ekont*derx(ll,1,1)
11059 gradcorr6kl=eel6*g_contij(ll,2)+ekont*derx(ll,1,2)
11060 gradcorr6(ll,i)=gradcorr6(ll,i)+ekont*derx(ll,2,1)
11061 gradcorr6(ll,i+1)=gradcorr6(ll,i+1)+ekont*derx(ll,3,1)
11062 gradcorr6(ll,j)=gradcorr6(ll,j)+ekont*derx(ll,4,1)
11063 gradcorr6(ll,j1)=gradcorr6(ll,j1)+ekont*derx(ll,5,1)
11064 gradcorr6_long(ll,j)=gradcorr6_long(ll,j)+gradcorr6ij
11065 gradcorr6_long(ll,i)=gradcorr6_long(ll,i)-gradcorr6ij
11066 cgrad ghalf=0.5d0*ggg2(ll)
11067 cold ghalf=0.5d0*eel6*eij*gacont_hbr(ll,kk,k)
11069 gradcorr6(ll,k)=gradcorr6(ll,k)+ekont*derx(ll,2,2)
11070 gradcorr6(ll,k+1)=gradcorr6(ll,k+1)+ekont*derx(ll,3,2)
11071 gradcorr6(ll,l)=gradcorr6(ll,l)+ekont*derx(ll,4,2)
11072 gradcorr6(ll,l1)=gradcorr6(ll,l1)+ekont*derx(ll,5,2)
11073 gradcorr6_long(ll,l)=gradcorr6_long(ll,l)+gradcorr6kl
11074 gradcorr6_long(ll,k)=gradcorr6_long(ll,k)-gradcorr6kl
11079 cold gradcorr6(ll,m)=gradcorr6(ll,m)+eel6*ekl*gacont_hbr(ll,jj,i)
11080 cgrad gradcorr6(ll,m)=gradcorr6(ll,m)+ggg1(ll)
11085 cold gradcorr6(ll,m)=gradcorr6(ll,m)+eel6*eij*gacont_hbr(ll,kk,k)
11086 cgrad gradcorr6(ll,m)=gradcorr6(ll,m)+ggg2(ll)
11092 cgrad gradcorr6(ll,m)=gradcorr6(ll,m)+ekont*derx(ll,1,1)
11097 cgrad gradcorr6(ll,m)=gradcorr6(ll,m)+ekont*derx(ll,1,2)
11101 cd write (2,*) iii,g_corr6_loc(iii)
11104 cd write (2,*) 'ekont',ekont
11105 cd write (iout,*) 'eello6',ekont*eel6
11108 c--------------------------------------------------------------------------
11109 double precision function eello6_graph1(i,j,k,l,imat,swap)
11110 implicit real*8 (a-h,o-z)
11111 include 'DIMENSIONS'
11112 include 'COMMON.IOUNITS'
11113 include 'COMMON.CHAIN'
11114 include 'COMMON.DERIV'
11115 include 'COMMON.INTERACT'
11116 include 'COMMON.CONTACTS'
11117 include 'COMMON.CONTMAT'
11118 include 'COMMON.CORRMAT'
11119 include 'COMMON.TORSION'
11120 include 'COMMON.VAR'
11121 include 'COMMON.GEO'
11122 double precision vv(2),vv1(2),pizda(2,2),auxmat(2,2),pizda1(2,2)
11125 common /kutas/ lprn
11126 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11128 C Parallel Antiparallel C
11134 C \ j|/k\| / \ |/k\|l / C
11135 C \ / \ / \ / \ / C
11139 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11140 itk=itype2loc(itype(k))
11141 s1= scalar2(AEAb1(1,2,imat),CUgb2(1,i))
11142 s2=-scalar2(AEAb2(1,1,imat),Ug2Db1t(1,k))
11143 s3= scalar2(AEAb2(1,1,imat),CUgb2(1,k))
11144 call transpose2(EUgC(1,1,k),auxmat(1,1))
11145 call matmat2(AEA(1,1,imat),auxmat(1,1),pizda1(1,1))
11146 vv1(1)=pizda1(1,1)-pizda1(2,2)
11147 vv1(2)=pizda1(1,2)+pizda1(2,1)
11148 s4=0.5d0*scalar2(vv1(1),Dtobr2(1,i))
11149 vv(1)=AEAb1(1,2,imat)*b1(1,k)-AEAb1(2,2,imat)*b1(2,k)
11150 vv(2)=AEAb1(1,2,imat)*b1(2,k)+AEAb1(2,2,imat)*b1(1,k)
11151 s5=scalar2(vv(1),Dtobr2(1,i))
11152 cd write (2,*) 's1',s1,' s2',s2,' s3',s3,' s4', s4,' s5',s5
11153 eello6_graph1=-0.5d0*(s1+s2+s3+s4+s5)
11154 if (i.gt.1) g_corr6_loc(i-1)=g_corr6_loc(i-1)
11155 & -0.5d0*ekont*(scalar2(AEAb1(1,2,imat),CUgb2der(1,i))
11156 & -scalar2(AEAb2derg(1,2,1,imat),Ug2Db1t(1,k))
11157 & +scalar2(AEAb2derg(1,2,1,imat),CUgb2(1,k))
11158 & +0.5d0*scalar2(vv1(1),Dtobr2der(1,i))
11159 & +scalar2(vv(1),Dtobr2der(1,i)))
11160 call matmat2(AEAderg(1,1,imat),auxmat(1,1),pizda1(1,1))
11161 vv1(1)=pizda1(1,1)-pizda1(2,2)
11162 vv1(2)=pizda1(1,2)+pizda1(2,1)
11163 vv(1)=AEAb1derg(1,2,imat)*b1(1,k)-AEAb1derg(2,2,imat)*b1(2,k)
11164 vv(2)=AEAb1derg(1,2,imat)*b1(2,k)+AEAb1derg(2,2,imat)*b1(1,k)
11166 g_corr6_loc(l-1)=g_corr6_loc(l-1)
11167 & +ekont*(-0.5d0*(scalar2(AEAb1derg(1,2,imat),CUgb2(1,i))
11168 & -scalar2(AEAb2derg(1,1,1,imat),Ug2Db1t(1,k))
11169 & +scalar2(AEAb2derg(1,1,1,imat),CUgb2(1,k))
11170 & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))+scalar2(vv(1),Dtobr2(1,i))))
11172 g_corr6_loc(j-1)=g_corr6_loc(j-1)
11173 & +ekont*(-0.5d0*(scalar2(AEAb1derg(1,2,imat),CUgb2(1,i))
11174 & -scalar2(AEAb2derg(1,1,1,imat),Ug2Db1t(1,k))
11175 & +scalar2(AEAb2derg(1,1,1,imat),CUgb2(1,k))
11176 & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))+scalar2(vv(1),Dtobr2(1,i))))
11178 call transpose2(EUgCder(1,1,k),auxmat(1,1))
11179 call matmat2(AEA(1,1,imat),auxmat(1,1),pizda1(1,1))
11180 vv1(1)=pizda1(1,1)-pizda1(2,2)
11181 vv1(2)=pizda1(1,2)+pizda1(2,1)
11182 if (k.gt.1) g_corr6_loc(k-1)=g_corr6_loc(k-1)
11183 & +ekont*(-0.5d0*(-scalar2(AEAb2(1,1,imat),Ug2Db1tder(1,k))
11184 & +scalar2(AEAb2(1,1,imat),CUgb2der(1,k))
11185 & +0.5d0*scalar2(vv1(1),Dtobr2(1,i))))
11194 s1= scalar2(AEAb1derx(1,lll,kkk,iii,2,imat),CUgb2(1,i))
11195 s2=-scalar2(AEAb2derx(1,lll,kkk,iii,1,imat),Ug2Db1t(1,k))
11196 s3= scalar2(AEAb2derx(1,lll,kkk,iii,1,imat),CUgb2(1,k))
11197 call transpose2(EUgC(1,1,k),auxmat(1,1))
11198 call matmat2(AEAderx(1,1,lll,kkk,iii,imat),auxmat(1,1),
11200 vv1(1)=pizda1(1,1)-pizda1(2,2)
11201 vv1(2)=pizda1(1,2)+pizda1(2,1)
11202 s4=0.5d0*scalar2(vv1(1),Dtobr2(1,i))
11203 vv(1)=AEAb1derx(1,lll,kkk,iii,2,imat)*b1(1,k)
11204 & -AEAb1derx(2,lll,kkk,iii,2,imat)*b1(2,k)
11205 vv(2)=AEAb1derx(1,lll,kkk,iii,2,imat)*b1(2,k)
11206 & +AEAb1derx(2,lll,kkk,iii,2,imat)*b1(1,k)
11207 s5=scalar2(vv(1),Dtobr2(1,i))
11208 derx(lll,kkk,ind)=derx(lll,kkk,ind)-0.5d0*(s1+s2+s3+s4+s5)
11214 c----------------------------------------------------------------------------
11215 double precision function eello6_graph2(i,j,k,l,jj,kk,swap)
11216 implicit real*8 (a-h,o-z)
11217 include 'DIMENSIONS'
11218 include 'COMMON.IOUNITS'
11219 include 'COMMON.CHAIN'
11220 include 'COMMON.DERIV'
11221 include 'COMMON.INTERACT'
11222 include 'COMMON.CONTACTS'
11223 include 'COMMON.CONTMAT'
11224 include 'COMMON.CORRMAT'
11225 include 'COMMON.TORSION'
11226 include 'COMMON.VAR'
11227 include 'COMMON.GEO'
11229 double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
11230 & auxvec1(2),auxvec2(2),auxmat1(2,2)
11232 common /kutas/ lprn
11233 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11235 C Parallel Antiparallel C
11241 C \ j|/k\| \ |/k\|l C
11246 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11247 cd write (2,*) 'eello6_graph2: i,',i,' j',j,' k',k,' l',l
11248 C AL 7/4/01 s1 would occur in the sixth-order moment,
11249 C but not in a cluster cumulant
11251 s1=dip(1,jj,i)*dip(1,kk,k)
11253 call matvec2(ADtEA1(1,1,1),Ub2(1,k),auxvec(1))
11254 s2=-0.5d0*scalar2(Ub2(1,i),auxvec(1))
11255 call matvec2(ADtEA(1,1,2),Ub2(1,l),auxvec1(1))
11256 s3=-0.5d0*scalar2(Ub2(1,j),auxvec1(1))
11257 call transpose2(EUg(1,1,k),auxmat(1,1))
11258 call matmat2(ADtEA1(1,1,1),auxmat(1,1),pizda(1,1))
11259 vv(1)=pizda(1,1)-pizda(2,2)
11260 vv(2)=pizda(1,2)+pizda(2,1)
11261 s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
11262 cd write (2,*) 'eello6_graph2:','s1',s1,' s2',s2,' s3',s3,' s4',s4
11264 eello6_graph2=-(s1+s2+s3+s4)
11266 eello6_graph2=-(s2+s3+s4)
11268 c eello6_graph2=-s3
11269 C Derivatives in gamma(i-1)
11272 s1=dipderg(1,jj,i)*dip(1,kk,k)
11274 s2=-0.5d0*scalar2(Ub2der(1,i),auxvec(1))
11275 call matvec2(ADtEAderg(1,1,1,2),Ub2(1,l),auxvec2(1))
11276 s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
11277 s4=-0.25d0*scalar2(vv(1),Dtobr2der(1,i))
11279 g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s1+s2+s3+s4)
11281 g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s2+s3+s4)
11283 c g_corr6_loc(i-1)=g_corr6_loc(i-1)-s3
11285 C Derivatives in gamma(k-1)
11287 s1=dip(1,jj,i)*dipderg(1,kk,k)
11289 call matvec2(ADtEA1(1,1,1),Ub2der(1,k),auxvec2(1))
11290 s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
11291 call matvec2(ADtEAderg(1,1,2,2),Ub2(1,l),auxvec2(1))
11292 s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
11293 call transpose2(EUgder(1,1,k),auxmat1(1,1))
11294 call matmat2(ADtEA1(1,1,1),auxmat1(1,1),pizda(1,1))
11295 vv(1)=pizda(1,1)-pizda(2,2)
11296 vv(2)=pizda(1,2)+pizda(2,1)
11297 s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
11299 g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s1+s2+s3+s4)
11301 g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s2+s3+s4)
11303 c g_corr6_loc(k-1)=g_corr6_loc(k-1)-s3
11304 C Derivatives in gamma(j-1) or gamma(l-1)
11307 s1=dipderg(3,jj,i)*dip(1,kk,k)
11309 call matvec2(ADtEA1derg(1,1,1,1),Ub2(1,k),auxvec2(1))
11310 s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
11311 s3=-0.5d0*scalar2(Ub2der(1,j),auxvec1(1))
11312 call matmat2(ADtEA1derg(1,1,1,1),auxmat(1,1),pizda(1,1))
11313 vv(1)=pizda(1,1)-pizda(2,2)
11314 vv(2)=pizda(1,2)+pizda(2,1)
11315 s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
11318 g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*s1
11320 g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*s1
11323 g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*(s2+s3+s4)
11324 c g_corr6_loc(j-1)=g_corr6_loc(j-1)-s3
11326 C Derivatives in gamma(l-1) or gamma(j-1)
11329 s1=dip(1,jj,i)*dipderg(3,kk,k)
11331 call matvec2(ADtEA1derg(1,1,2,1),Ub2(1,k),auxvec2(1))
11332 s2=-0.5d0*scalar2(Ub2(1,i),auxvec2(1))
11333 call matvec2(ADtEA(1,1,2),Ub2der(1,l),auxvec2(1))
11334 s3=-0.5d0*scalar2(Ub2(1,j),auxvec2(1))
11335 call matmat2(ADtEA1derg(1,1,2,1),auxmat(1,1),pizda(1,1))
11336 vv(1)=pizda(1,1)-pizda(2,2)
11337 vv(2)=pizda(1,2)+pizda(2,1)
11338 s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
11341 g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*s1
11343 g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*s1
11346 g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s3+s4)
11347 c g_corr6_loc(l-1)=g_corr6_loc(l-1)-s3
11349 C Cartesian derivatives.
11351 write (2,*) 'In eello6_graph2'
11353 write (2,*) 'iii=',iii
11355 write (2,*) 'kkk=',kkk
11357 write (2,'(3(2f10.5),5x)')
11358 & ((ADtEA1derx(jjj,mmm,lll,kkk,iii,1),mmm=1,2),lll=1,3)
11368 s1=dipderx(lll,kkk,1,jj,i)*dip(1,kk,k)
11370 s1=dip(1,jj,i)*dipderx(lll,kkk,1,kk,k)
11373 call matvec2(ADtEA1derx(1,1,lll,kkk,iii,1),Ub2(1,k),
11375 s2=-0.5d0*scalar2(Ub2(1,i),auxvec(1))
11376 call matvec2(ADtEAderx(1,1,lll,kkk,iii,2),Ub2(1,l),
11378 s3=-0.5d0*scalar2(Ub2(1,j),auxvec(1))
11379 call transpose2(EUg(1,1,k),auxmat(1,1))
11380 call matmat2(ADtEA1derx(1,1,lll,kkk,iii,1),auxmat(1,1),
11382 vv(1)=pizda(1,1)-pizda(2,2)
11383 vv(2)=pizda(1,2)+pizda(2,1)
11384 s4=-0.25d0*scalar2(vv(1),Dtobr2(1,i))
11385 cd write (2,*) 's1',s1,' s2',s2,' s3',s3,' s4',s4
11387 derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
11389 derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
11392 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
11394 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
11401 c----------------------------------------------------------------------------
11402 double precision function eello6_graph3(i,j,k,l,jj,kk,swap)
11403 implicit real*8 (a-h,o-z)
11404 include 'DIMENSIONS'
11405 include 'COMMON.IOUNITS'
11406 include 'COMMON.CHAIN'
11407 include 'COMMON.DERIV'
11408 include 'COMMON.INTERACT'
11409 include 'COMMON.CONTACTS'
11410 include 'COMMON.CONTMAT'
11411 include 'COMMON.CORRMAT'
11412 include 'COMMON.TORSION'
11413 include 'COMMON.VAR'
11414 include 'COMMON.GEO'
11415 double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2)
11417 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11419 C Parallel Antiparallel C
11424 C /| o |o o| o |\ C
11425 C j|/k\| / |/k\|l / C
11430 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11432 C 4/7/01 AL Component s1 was removed, because it pertains to the respective
11433 C energy moment and not to the cluster cumulant.
11434 iti=itortyp(itype(i))
11435 if (j.lt.nres-1) then
11436 itj1=itype2loc(itype(j+1))
11440 itk=itype2loc(itype(k))
11441 itk1=itype2loc(itype(k+1))
11442 if (l.lt.nres-1) then
11443 itl1=itype2loc(itype(l+1))
11448 s1=dip(4,jj,i)*dip(4,kk,k)
11450 call matvec2(AECA(1,1,1),b1(1,k+1),auxvec(1))
11451 s2=0.5d0*scalar2(b1(1,k),auxvec(1))
11452 call matvec2(AECA(1,1,2),b1(1,l+1),auxvec(1))
11453 s3=0.5d0*scalar2(b1(1,j+1),auxvec(1))
11454 call transpose2(EE(1,1,k),auxmat(1,1))
11455 call matmat2(auxmat(1,1),AECA(1,1,1),pizda(1,1))
11456 vv(1)=pizda(1,1)+pizda(2,2)
11457 vv(2)=pizda(2,1)-pizda(1,2)
11458 s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
11459 cd write (2,*) 'eello6_graph3:','s1',s1,' s2',s2,' s3',s3,' s4',s4,
11460 cd & "sum",-(s2+s3+s4)
11462 eello6_graph3=-(s1+s2+s3+s4)
11464 eello6_graph3=-(s2+s3+s4)
11466 c eello6_graph3=-s4
11467 C Derivatives in gamma(k-1)
11468 call matvec2(AECAderg(1,1,2),b1(1,l+1),auxvec(1))
11469 s3=0.5d0*scalar2(b1(1,j+1),auxvec(1))
11470 s4=-0.25d0*scalar2(vv(1),Ctobrder(1,k))
11471 g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s3+s4)
11472 C Derivatives in gamma(l-1)
11473 call matvec2(AECAderg(1,1,1),b1(1,k+1),auxvec(1))
11474 s2=0.5d0*scalar2(b1(1,k),auxvec(1))
11475 call matmat2(auxmat(1,1),AECAderg(1,1,1),pizda(1,1))
11476 vv(1)=pizda(1,1)+pizda(2,2)
11477 vv(2)=pizda(2,1)-pizda(1,2)
11478 s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
11479 g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s4)
11480 C Cartesian derivatives.
11486 s1=dipderx(lll,kkk,4,jj,i)*dip(4,kk,k)
11488 s1=dip(4,jj,i)*dipderx(lll,kkk,4,kk,k)
11491 call matvec2(AECAderx(1,1,lll,kkk,iii,1),b1(1,k+1),
11493 s2=0.5d0*scalar2(b1(1,k),auxvec(1))
11494 call matvec2(AECAderx(1,1,lll,kkk,iii,2),b1(1,l+1),
11496 s3=0.5d0*scalar2(b1(1,j+1),auxvec(1))
11497 call matmat2(auxmat(1,1),AECAderx(1,1,lll,kkk,iii,1),
11499 vv(1)=pizda(1,1)+pizda(2,2)
11500 vv(2)=pizda(2,1)-pizda(1,2)
11501 s4=-0.25d0*scalar2(vv(1),Ctobr(1,k))
11503 derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
11505 derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
11508 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
11510 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
11512 c derx(lll,kkk,iii)=derx(lll,kkk,iii)-s4
11518 c----------------------------------------------------------------------------
11519 double precision function eello6_graph4(i,j,k,l,jj,kk,imat,swap)
11520 implicit real*8 (a-h,o-z)
11521 include 'DIMENSIONS'
11522 include 'COMMON.IOUNITS'
11523 include 'COMMON.CHAIN'
11524 include 'COMMON.DERIV'
11525 include 'COMMON.INTERACT'
11526 include 'COMMON.CONTACTS'
11527 include 'COMMON.CONTMAT'
11528 include 'COMMON.CORRMAT'
11529 include 'COMMON.TORSION'
11530 include 'COMMON.VAR'
11531 include 'COMMON.GEO'
11532 include 'COMMON.FFIELD'
11533 double precision vv(2),pizda(2,2),auxmat(2,2),auxvec(2),
11534 & auxvec1(2),auxmat1(2,2)
11536 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11538 C Parallel Antiparallel C
11543 C /| o |o o| o |\ C
11544 C \ j|/k\| \ |/k\|l C
11549 CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
11551 C 4/7/01 AL Component s1 was removed, because it pertains to the respective
11552 C energy moment and not to the cluster cumulant.
11553 cd write (2,*) 'eello_graph4: wturn6',wturn6
11554 iti=itype2loc(itype(i))
11555 itj=itype2loc(itype(j))
11556 if (j.lt.nres-1) then
11557 itj1=itype2loc(itype(j+1))
11561 itk=itype2loc(itype(k))
11562 if (k.lt.nres-1) then
11563 itk1=itype2loc(itype(k+1))
11567 itl=itype2loc(itype(l))
11568 if (l.lt.nres-1) then
11569 itl1=itype2loc(itype(l+1))
11573 cd write (2,*) 'eello6_graph4:','i',i,' j',j,' k',k,' l',l
11574 cd write (2,*) 'iti',iti,' itj',itj,' itj1',itj1,' itk',itk,
11575 cd & ' itl',itl,' itl1',itl1
11577 if (imat.eq.1) then
11578 s1=dip(3,jj,i)*dip(3,kk,k)
11580 s1=dip(2,jj,j)*dip(2,kk,l)
11583 call matvec2(AECA(1,1,imat),Ub2(1,k),auxvec(1))
11584 s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
11586 call matvec2(ADtEA1(1,1,3-imat),b1(1,j+1),auxvec1(1))
11587 s3=-0.5d0*scalar2(b1(1,j),auxvec1(1))
11589 call matvec2(ADtEA1(1,1,3-imat),b1(1,l+1),auxvec1(1))
11590 s3=-0.5d0*scalar2(b1(1,l),auxvec1(1))
11592 call transpose2(EUg(1,1,k),auxmat(1,1))
11593 call matmat2(AECA(1,1,imat),auxmat(1,1),pizda(1,1))
11594 vv(1)=pizda(1,1)-pizda(2,2)
11595 vv(2)=pizda(2,1)+pizda(1,2)
11596 s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
11597 cd write (2,*) 'eello6_graph4:','s1',s1,' s2',s2,' s3',s3,' s4',s4
11599 eello6_graph4=-(s1+s2+s3+s4)
11601 eello6_graph4=-(s2+s3+s4)
11603 C Derivatives in gamma(i-1)
11606 if (imat.eq.1) then
11607 s1=dipderg(2,jj,i)*dip(3,kk,k)
11609 s1=dipderg(4,jj,j)*dip(2,kk,l)
11612 s2=0.5d0*scalar2(Ub2der(1,i),auxvec(1))
11614 call matvec2(ADtEA1derg(1,1,1,3-imat),b1(1,j+1),auxvec1(1))
11615 s3=-0.5d0*scalar2(b1(1,j),auxvec1(1))
11617 call matvec2(ADtEA1derg(1,1,1,3-imat),b1(1,l+1),auxvec1(1))
11618 s3=-0.5d0*scalar2(b1(1,l),auxvec1(1))
11620 s4=0.25d0*scalar2(vv(1),Dtobr2der(1,i))
11621 if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
11622 cd write (2,*) 'turn6 derivatives'
11624 gel_loc_turn6(i-1)=gel_loc_turn6(i-1)-ekont*(s1+s2+s3+s4)
11626 gel_loc_turn6(i-1)=gel_loc_turn6(i-1)-ekont*(s2+s3+s4)
11630 g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s1+s2+s3+s4)
11632 g_corr6_loc(i-1)=g_corr6_loc(i-1)-ekont*(s2+s3+s4)
11636 C Derivatives in gamma(k-1)
11638 if (imat.eq.1) then
11639 s1=dip(3,jj,i)*dipderg(2,kk,k)
11641 s1=dip(2,jj,j)*dipderg(4,kk,l)
11644 call matvec2(AECA(1,1,imat),Ub2der(1,k),auxvec1(1))
11645 s2=0.5d0*scalar2(Ub2(1,i),auxvec1(1))
11647 call matvec2(ADtEA1derg(1,1,2,3-imat),b1(1,j+1),auxvec1(1))
11648 s3=-0.5d0*scalar2(b1(1,j),auxvec1(1))
11650 call matvec2(ADtEA1derg(1,1,2,3-imat),b1(1,l+1),auxvec1(1))
11651 s3=-0.5d0*scalar2(b1(1,l),auxvec1(1))
11653 call transpose2(EUgder(1,1,k),auxmat1(1,1))
11654 call matmat2(AECA(1,1,imat),auxmat1(1,1),pizda(1,1))
11655 vv(1)=pizda(1,1)-pizda(2,2)
11656 vv(2)=pizda(2,1)+pizda(1,2)
11657 s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
11658 if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
11660 gel_loc_turn6(k-1)=gel_loc_turn6(k-1)-ekont*(s1+s2+s3+s4)
11662 gel_loc_turn6(k-1)=gel_loc_turn6(k-1)-ekont*(s2+s3+s4)
11666 g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s1+s2+s3+s4)
11668 g_corr6_loc(k-1)=g_corr6_loc(k-1)-ekont*(s2+s3+s4)
11671 C Derivatives in gamma(j-1) or gamma(l-1)
11672 if (l.eq.j+1 .and. l.gt.1) then
11673 call matvec2(AECAderg(1,1,imat),Ub2(1,k),auxvec(1))
11674 s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
11675 call matmat2(AECAderg(1,1,imat),auxmat(1,1),pizda(1,1))
11676 vv(1)=pizda(1,1)-pizda(2,2)
11677 vv(2)=pizda(2,1)+pizda(1,2)
11678 s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
11679 g_corr6_loc(l-1)=g_corr6_loc(l-1)-ekont*(s2+s4)
11680 else if (j.gt.1) then
11681 call matvec2(AECAderg(1,1,imat),Ub2(1,k),auxvec(1))
11682 s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
11683 call matmat2(AECAderg(1,1,imat),auxmat(1,1),pizda(1,1))
11684 vv(1)=pizda(1,1)-pizda(2,2)
11685 vv(2)=pizda(2,1)+pizda(1,2)
11686 s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
11687 if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
11688 gel_loc_turn6(j-1)=gel_loc_turn6(j-1)-ekont*(s2+s4)
11690 g_corr6_loc(j-1)=g_corr6_loc(j-1)-ekont*(s2+s4)
11693 C Cartesian derivatives.
11699 if (imat.eq.1) then
11700 s1=dipderx(lll,kkk,3,jj,i)*dip(3,kk,k)
11702 s1=dipderx(lll,kkk,2,jj,j)*dip(2,kk,l)
11705 if (imat.eq.1) then
11706 s1=dip(3,jj,i)*dipderx(lll,kkk,3,kk,k)
11708 s1=dip(2,jj,j)*dipderx(lll,kkk,2,kk,l)
11712 call matvec2(AECAderx(1,1,lll,kkk,iii,imat),Ub2(1,k),
11714 s2=0.5d0*scalar2(Ub2(1,i),auxvec(1))
11716 call matvec2(ADtEA1derx(1,1,lll,kkk,iii,3-imat),
11717 & b1(1,j+1),auxvec(1))
11718 s3=-0.5d0*scalar2(b1(1,j),auxvec(1))
11720 call matvec2(ADtEA1derx(1,1,lll,kkk,iii,3-imat),
11721 & b1(1,l+1),auxvec(1))
11722 s3=-0.5d0*scalar2(b1(1,l),auxvec(1))
11724 call matmat2(AECAderx(1,1,lll,kkk,iii,imat),auxmat(1,1),
11726 vv(1)=pizda(1,1)-pizda(2,2)
11727 vv(2)=pizda(2,1)+pizda(1,2)
11728 s4=0.25d0*scalar2(vv(1),Dtobr2(1,i))
11730 if (wturn6.gt.0.0d0 .and. k.eq.l+4 .and. i.eq.j+2) then
11732 derx_turn(lll,kkk,3-iii)=derx_turn(lll,kkk,3-iii)
11735 derx_turn(lll,kkk,3-iii)=derx_turn(lll,kkk,3-iii)
11738 derx_turn(lll,kkk,iii)=derx_turn(lll,kkk,iii)-s3
11741 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-(s1+s2+s4)
11743 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-(s2+s4)
11745 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
11749 derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s1+s2+s4)
11751 derx(lll,kkk,iii)=derx(lll,kkk,iii)-(s2+s4)
11754 derx(lll,kkk,iii)=derx(lll,kkk,iii)-s3
11756 derx(lll,kkk,3-iii)=derx(lll,kkk,3-iii)-s3
11764 c----------------------------------------------------------------------------
11765 double precision function eello_turn6(i,jj,kk)
11766 implicit real*8 (a-h,o-z)
11767 include 'DIMENSIONS'
11768 include 'COMMON.IOUNITS'
11769 include 'COMMON.CHAIN'
11770 include 'COMMON.DERIV'
11771 include 'COMMON.INTERACT'
11772 include 'COMMON.CONTACTS'
11773 include 'COMMON.CONTMAT'
11774 include 'COMMON.CORRMAT'
11775 include 'COMMON.TORSION'
11776 include 'COMMON.VAR'
11777 include 'COMMON.GEO'
11778 double precision vtemp1(2),vtemp2(2),vtemp3(2),vtemp4(2),
11779 & atemp(2,2),auxmat(2,2),achuj_temp(2,2),gtemp(2,2),gvec(2),
11781 double precision vtemp1d(2),vtemp2d(2),vtemp3d(2),vtemp4d(2),
11782 & atempd(2,2),auxmatd(2,2),achuj_tempd(2,2),gtempd(2,2),gvecd(2)
11783 C 4/7/01 AL Components s1, s8, and s13 were removed, because they pertain to
11784 C the respective energy moment and not to the cluster cumulant.
11793 iti=itype2loc(itype(i))
11794 itk=itype2loc(itype(k))
11795 itk1=itype2loc(itype(k+1))
11796 itl=itype2loc(itype(l))
11797 itj=itype2loc(itype(j))
11798 cd write (2,*) 'itk',itk,' itk1',itk1,' itl',itl,' itj',itj
11799 cd write (2,*) 'i',i,' k',k,' j',j,' l',l
11800 cd if (i.ne.1 .or. j.ne.3 .or. k.ne.2 .or. l.ne.4) then
11805 cd & 'EELLO6: Contacts have occurred for peptide groups',i,j,
11807 cd call checkint_turn6(i,jj,kk,eel_turn6_num)
11811 derx_turn(lll,kkk,iii)=0.0d0
11818 eello6_5=eello6_graph4(l,k,j,i,kk,jj,2,.true.)
11820 cd write (2,*) 'eello6_5',eello6_5
11822 call transpose2(AEA(1,1,1),auxmat(1,1))
11823 call matmat2(EUg(1,1,i+1),auxmat(1,1),auxmat(1,1))
11824 ss1=scalar2(Ub2(1,i+2),b1(1,l))
11825 s1 = (auxmat(1,1)+auxmat(2,2))*ss1
11827 call matvec2(EUg(1,1,i+2),b1(1,l),vtemp1(1))
11828 call matvec2(AEA(1,1,1),vtemp1(1),vtemp1(1))
11829 s2 = scalar2(b1(1,k),vtemp1(1))
11831 call transpose2(AEA(1,1,2),atemp(1,1))
11832 call matmat2(atemp(1,1),EUg(1,1,i+4),atemp(1,1))
11833 call matvec2(Ug2(1,1,i+2),dd(1,1,k+1),vtemp2(1))
11834 s8 = -(atemp(1,1)+atemp(2,2))*scalar2(cc(1,1,l),vtemp2(1))
11836 call matmat2(EUg(1,1,i+3),AEA(1,1,2),auxmat(1,1))
11837 call matvec2(auxmat(1,1),Ub2(1,i+4),vtemp3(1))
11838 s12 = scalar2(Ub2(1,i+2),vtemp3(1))
11840 call transpose2(a_chuj(1,1,kk,i+1),achuj_temp(1,1))
11841 call matmat2(achuj_temp(1,1),EUg(1,1,i+2),gtemp(1,1))
11842 call matmat2(gtemp(1,1),EUg(1,1,i+3),gtemp(1,1))
11843 call matvec2(a_chuj(1,1,jj,i),Ub2(1,i+4),vtemp4(1))
11844 ss13 = scalar2(b1(1,k),vtemp4(1))
11845 s13 = (gtemp(1,1)+gtemp(2,2))*ss13
11847 c write (2,*) 's1,s2,s8,s12,s13',s1,s2,s8,s12,s13
11853 eel_turn6 = eello6_5 - 0.5d0*(s1+s2+s12+s8+s13)
11854 C Derivatives in gamma(i+2)
11858 call transpose2(AEA(1,1,1),auxmatd(1,1))
11859 call matmat2(EUgder(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
11860 s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
11861 call transpose2(AEAderg(1,1,2),atempd(1,1))
11862 call matmat2(atempd(1,1),EUg(1,1,i+4),atempd(1,1))
11863 s8d = -(atempd(1,1)+atempd(2,2))*scalar2(cc(1,1,l),vtemp2(1))
11865 call matmat2(EUg(1,1,i+3),AEAderg(1,1,2),auxmatd(1,1))
11866 call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
11867 s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
11873 gel_loc_turn6(i)=gel_loc_turn6(i)-0.5d0*ekont*(s1d+s8d+s12d)
11874 C Derivatives in gamma(i+3)
11876 call transpose2(AEA(1,1,1),auxmatd(1,1))
11877 call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
11878 ss1d=scalar2(Ub2der(1,i+2),b1(1,l))
11879 s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1d
11881 call matvec2(EUgder(1,1,i+2),b1(1,l),vtemp1d(1))
11882 call matvec2(AEA(1,1,1),vtemp1d(1),vtemp1d(1))
11883 s2d = scalar2(b1(1,k),vtemp1d(1))
11885 call matvec2(Ug2der(1,1,i+2),dd(1,1,k+1),vtemp2d(1))
11886 s8d = -(atemp(1,1)+atemp(2,2))*scalar2(cc(1,1,l),vtemp2d(1))
11888 s12d = scalar2(Ub2der(1,i+2),vtemp3(1))
11890 call matmat2(achuj_temp(1,1),EUgder(1,1,i+2),gtempd(1,1))
11891 call matmat2(gtempd(1,1),EUg(1,1,i+3),gtempd(1,1))
11892 s13d = (gtempd(1,1)+gtempd(2,2))*ss13
11900 gel_loc_turn6(i+1)=gel_loc_turn6(i+1)
11901 & -0.5d0*ekont*(s1d+s2d+s8d+s12d+s13d)
11903 gel_loc_turn6(i+1)=gel_loc_turn6(i+1)
11904 & -0.5d0*ekont*(s2d+s12d)
11906 C Derivatives in gamma(i+4)
11907 call matmat2(EUgder(1,1,i+3),AEA(1,1,2),auxmatd(1,1))
11908 call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
11909 s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
11911 call matmat2(achuj_temp(1,1),EUg(1,1,i+2),gtempd(1,1))
11912 call matmat2(gtempd(1,1),EUgder(1,1,i+3),gtempd(1,1))
11913 s13d = (gtempd(1,1)+gtempd(2,2))*ss13
11921 gel_loc_turn6(i+2)=gel_loc_turn6(i+2)-0.5d0*ekont*(s12d+s13d)
11923 gel_loc_turn6(i+2)=gel_loc_turn6(i+2)-0.5d0*ekont*(s12d)
11925 C Derivatives in gamma(i+5)
11927 call transpose2(AEAderg(1,1,1),auxmatd(1,1))
11928 call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
11929 s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
11931 call matvec2(EUg(1,1,i+2),b1(1,l),vtemp1d(1))
11932 call matvec2(AEAderg(1,1,1),vtemp1d(1),vtemp1d(1))
11933 s2d = scalar2(b1(1,k),vtemp1d(1))
11935 call transpose2(AEA(1,1,2),atempd(1,1))
11936 call matmat2(atempd(1,1),EUgder(1,1,i+4),atempd(1,1))
11937 s8d = -(atempd(1,1)+atempd(2,2))*scalar2(cc(1,1,l),vtemp2(1))
11939 call matvec2(auxmat(1,1),Ub2der(1,i+4),vtemp3d(1))
11940 s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
11942 call matvec2(a_chuj(1,1,jj,i),Ub2der(1,i+4),vtemp4d(1))
11943 ss13d = scalar2(b1(1,k),vtemp4d(1))
11944 s13d = (gtemp(1,1)+gtemp(2,2))*ss13d
11952 gel_loc_turn6(i+3)=gel_loc_turn6(i+3)
11953 & -0.5d0*ekont*(s1d+s2d+s8d+s12d+s13d)
11955 gel_loc_turn6(i+3)=gel_loc_turn6(i+3)
11956 & -0.5d0*ekont*(s2d+s12d)
11958 C Cartesian derivatives
11963 call transpose2(AEAderx(1,1,lll,kkk,iii,1),auxmatd(1,1))
11964 call matmat2(EUg(1,1,i+1),auxmatd(1,1),auxmatd(1,1))
11965 s1d = (auxmatd(1,1)+auxmatd(2,2))*ss1
11967 call matvec2(EUg(1,1,i+2),b1(1,l),vtemp1(1))
11968 call matvec2(AEAderx(1,1,lll,kkk,iii,1),vtemp1(1),
11970 s2d = scalar2(b1(1,k),vtemp1d(1))
11972 call transpose2(AEAderx(1,1,lll,kkk,iii,2),atempd(1,1))
11973 call matmat2(atempd(1,1),EUg(1,1,i+4),atempd(1,1))
11974 s8d = -(atempd(1,1)+atempd(2,2))*
11975 & scalar2(cc(1,1,l),vtemp2(1))
11977 call matmat2(EUg(1,1,i+3),AEAderx(1,1,lll,kkk,iii,2),
11979 call matvec2(auxmatd(1,1),Ub2(1,i+4),vtemp3d(1))
11980 s12d = scalar2(Ub2(1,i+2),vtemp3d(1))
11987 derx_turn(lll,kkk,iii) = derx_turn(lll,kkk,iii)
11988 & - 0.5d0*(s1d+s2d)
11990 derx_turn(lll,kkk,iii) = derx_turn(lll,kkk,iii)
11994 derx_turn(lll,kkk,3-iii) = derx_turn(lll,kkk,3-iii)
11995 & - 0.5d0*(s8d+s12d)
11997 derx_turn(lll,kkk,3-iii) = derx_turn(lll,kkk,3-iii)
12006 call transpose2(a_chuj_der(1,1,lll,kkk,kk,i+1),
12007 & achuj_tempd(1,1))
12008 call matmat2(achuj_tempd(1,1),EUg(1,1,i+2),gtempd(1,1))
12009 call matmat2(gtempd(1,1),EUg(1,1,i+3),gtempd(1,1))
12010 s13d=(gtempd(1,1)+gtempd(2,2))*ss13
12011 derx_turn(lll,kkk,2) = derx_turn(lll,kkk,2)-0.5d0*s13d
12012 call matvec2(a_chuj_der(1,1,lll,kkk,jj,i),Ub2(1,i+4),
12014 ss13d = scalar2(b1(1,k),vtemp4d(1))
12015 s13d = (gtemp(1,1)+gtemp(2,2))*ss13d
12016 derx_turn(lll,kkk,1) = derx_turn(lll,kkk,1)-0.5d0*s13d
12020 cd write(iout,*) 'eel6_turn6',eel_turn6,' eel_turn6_num',
12021 cd & 16*eel_turn6_num
12023 if (j.lt.nres-1) then
12030 if (l.lt.nres-1) then
12038 cgrad ggg1(ll)=eel_turn6*g_contij(ll,1)
12039 cgrad ggg2(ll)=eel_turn6*g_contij(ll,2)
12040 cgrad ghalf=0.5d0*ggg1(ll)
12042 gturn6ij=eel_turn6*g_contij(ll,1)+ekont*derx_turn(ll,1,1)
12043 gturn6kl=eel_turn6*g_contij(ll,2)+ekont*derx_turn(ll,1,2)
12044 gcorr6_turn(ll,i)=gcorr6_turn(ll,i)!+ghalf
12045 & +ekont*derx_turn(ll,2,1)
12046 gcorr6_turn(ll,i+1)=gcorr6_turn(ll,i+1)+ekont*derx_turn(ll,3,1)
12047 gcorr6_turn(ll,j)=gcorr6_turn(ll,j)!+ghalf
12048 & +ekont*derx_turn(ll,4,1)
12049 gcorr6_turn(ll,j1)=gcorr6_turn(ll,j1)+ekont*derx_turn(ll,5,1)
12050 gcorr6_turn_long(ll,j)=gcorr6_turn_long(ll,j)+gturn6ij
12051 gcorr6_turn_long(ll,i)=gcorr6_turn_long(ll,i)-gturn6ij
12052 cgrad ghalf=0.5d0*ggg2(ll)
12054 gcorr6_turn(ll,k)=gcorr6_turn(ll,k)!+ghalf
12055 & +ekont*derx_turn(ll,2,2)
12056 gcorr6_turn(ll,k+1)=gcorr6_turn(ll,k+1)+ekont*derx_turn(ll,3,2)
12057 gcorr6_turn(ll,l)=gcorr6_turn(ll,l)!+ghalf
12058 & +ekont*derx_turn(ll,4,2)
12059 gcorr6_turn(ll,l1)=gcorr6_turn(ll,l1)+ekont*derx_turn(ll,5,2)
12060 gcorr6_turn_long(ll,l)=gcorr6_turn_long(ll,l)+gturn6kl
12061 gcorr6_turn_long(ll,k)=gcorr6_turn_long(ll,k)-gturn6kl
12066 cgrad gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ggg1(ll)
12071 cgrad gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ggg2(ll)
12077 cgrad gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ekont*derx_turn(ll,1,1)
12082 cgrad gcorr6_turn(ll,m)=gcorr6_turn(ll,m)+ekont*derx_turn(ll,1,2)
12086 cd write (2,*) iii,g_corr6_loc(iii)
12088 eello_turn6=ekont*eel_turn6
12089 cd write (2,*) 'ekont',ekont
12090 cd write (2,*) 'eel_turn6',ekont*eel_turn6
12093 C-----------------------------------------------------------------------------
12095 double precision function scalar(u,v)
12096 !DIR$ INLINEALWAYS scalar
12098 cDEC$ ATTRIBUTES FORCEINLINE::scalar
12101 double precision u(3),v(3)
12102 cd double precision sc
12110 scalar=u(1)*v(1)+u(2)*v(2)+u(3)*v(3)
12113 crc-------------------------------------------------
12114 SUBROUTINE MATVEC2(A1,V1,V2)
12115 !DIR$ INLINEALWAYS MATVEC2
12117 cDEC$ ATTRIBUTES FORCEINLINE::MATVEC2
12119 implicit real*8 (a-h,o-z)
12120 include 'DIMENSIONS'
12121 DIMENSION A1(2,2),V1(2),V2(2)
12125 c 3 VI=VI+A1(I,K)*V1(K)
12129 vaux1=a1(1,1)*v1(1)+a1(1,2)*v1(2)
12130 vaux2=a1(2,1)*v1(1)+a1(2,2)*v1(2)
12135 C---------------------------------------
12136 SUBROUTINE MATMAT2(A1,A2,A3)
12138 cDEC$ ATTRIBUTES FORCEINLINE::MATMAT2
12140 implicit real*8 (a-h,o-z)
12141 include 'DIMENSIONS'
12142 DIMENSION A1(2,2),A2(2,2),A3(2,2)
12143 c DIMENSION AI3(2,2)
12147 c A3IJ=A3IJ+A1(I,K)*A2(K,J)
12153 ai3_11=a1(1,1)*a2(1,1)+a1(1,2)*a2(2,1)
12154 ai3_12=a1(1,1)*a2(1,2)+a1(1,2)*a2(2,2)
12155 ai3_21=a1(2,1)*a2(1,1)+a1(2,2)*a2(2,1)
12156 ai3_22=a1(2,1)*a2(1,2)+a1(2,2)*a2(2,2)
12164 c-------------------------------------------------------------------------
12165 double precision function scalar2(u,v)
12166 !DIR$ INLINEALWAYS scalar2
12168 double precision u(2),v(2)
12169 double precision sc
12171 scalar2=u(1)*v(1)+u(2)*v(2)
12175 C-----------------------------------------------------------------------------
12177 subroutine transpose2(a,at)
12178 !DIR$ INLINEALWAYS transpose2
12180 cDEC$ ATTRIBUTES FORCEINLINE::transpose2
12183 double precision a(2,2),at(2,2)
12190 c--------------------------------------------------------------------------
12191 subroutine transpose(n,a,at)
12194 double precision a(n,n),at(n,n)
12202 C---------------------------------------------------------------------------
12203 subroutine prodmat3(a1,a2,kk,transp,prod)
12204 !DIR$ INLINEALWAYS prodmat3
12206 cDEC$ ATTRIBUTES FORCEINLINE::prodmat3
12210 double precision a1(2,2),a2(2,2),a2t(2,2),kk(2,2),prod(2,2)
12212 crc double precision auxmat(2,2),prod_(2,2)
12215 crc call transpose2(kk(1,1),auxmat(1,1))
12216 crc call matmat2(a1(1,1),auxmat(1,1),auxmat(1,1))
12217 crc call matmat2(auxmat(1,1),a2(1,1),prod_(1,1))
12219 prod(1,1)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(1,2))*a2(1,1)
12220 & +(a1(1,1)*kk(2,1)+a1(1,2)*kk(2,2))*a2(2,1)
12221 prod(1,2)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(1,2))*a2(1,2)
12222 & +(a1(1,1)*kk(2,1)+a1(1,2)*kk(2,2))*a2(2,2)
12223 prod(2,1)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(1,2))*a2(1,1)
12224 & +(a1(2,1)*kk(2,1)+a1(2,2)*kk(2,2))*a2(2,1)
12225 prod(2,2)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(1,2))*a2(1,2)
12226 & +(a1(2,1)*kk(2,1)+a1(2,2)*kk(2,2))*a2(2,2)
12229 crc call matmat2(a1(1,1),kk(1,1),auxmat(1,1))
12230 crc call matmat2(auxmat(1,1),a2(1,1),prod_(1,1))
12232 prod(1,1)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(2,1))*a2(1,1)
12233 & +(a1(1,1)*kk(1,2)+a1(1,2)*kk(2,2))*a2(2,1)
12234 prod(1,2)=(a1(1,1)*kk(1,1)+a1(1,2)*kk(2,1))*a2(1,2)
12235 & +(a1(1,1)*kk(1,2)+a1(1,2)*kk(2,2))*a2(2,2)
12236 prod(2,1)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(2,1))*a2(1,1)
12237 & +(a1(2,1)*kk(1,2)+a1(2,2)*kk(2,2))*a2(2,1)
12238 prod(2,2)=(a1(2,1)*kk(1,1)+a1(2,2)*kk(2,1))*a2(1,2)
12239 & +(a1(2,1)*kk(1,2)+a1(2,2)*kk(2,2))*a2(2,2)
12242 c call transpose2(a2(1,1),a2t(1,1))
12245 crc print *,((prod_(i,j),i=1,2),j=1,2)
12246 crc print *,((prod(i,j),i=1,2),j=1,2)
12250 CCC----------------------------------------------
12251 subroutine Eliptransfer(eliptran)
12252 implicit real*8 (a-h,o-z)
12253 include 'DIMENSIONS'
12254 include 'COMMON.GEO'
12255 include 'COMMON.VAR'
12256 include 'COMMON.LOCAL'
12257 include 'COMMON.CHAIN'
12258 include 'COMMON.DERIV'
12259 include 'COMMON.NAMES'
12260 include 'COMMON.INTERACT'
12261 include 'COMMON.IOUNITS'
12262 include 'COMMON.CALC'
12263 include 'COMMON.CONTROL'
12264 include 'COMMON.SPLITELE'
12265 include 'COMMON.SBRIDGE'
12266 C this is done by Adasko
12267 C print *,"wchodze"
12268 C structure of box:
12270 C--bordliptop-- buffore starts
12271 C--bufliptop--- here true lipid starts
12273 C--buflipbot--- lipid ends buffore starts
12274 C--bordlipbot--buffore ends
12276 do i=ilip_start,ilip_end
12278 if (itype(i).eq.ntyp1) cycle
12280 positi=(mod(((c(3,i)+c(3,i+1))/2.0d0),boxzsize))
12281 if (positi.le.0.0) positi=positi+boxzsize
12283 C first for peptide groups
12284 c for each residue check if it is in lipid or lipid water border area
12285 if ((positi.gt.bordlipbot)
12286 &.and.(positi.lt.bordliptop)) then
12287 C the energy transfer exist
12288 if (positi.lt.buflipbot) then
12289 C what fraction I am in
12291 & ((positi-bordlipbot)/lipbufthick)
12292 C lipbufthick is thickenes of lipid buffore
12293 sslip=sscalelip(fracinbuf)
12294 ssgradlip=-sscagradlip(fracinbuf)/lipbufthick
12295 eliptran=eliptran+sslip*pepliptran
12296 gliptranc(3,i)=gliptranc(3,i)+ssgradlip*pepliptran/2.0d0
12297 gliptranc(3,i-1)=gliptranc(3,i-1)+ssgradlip*pepliptran/2.0d0
12298 C gliptranc(3,i-2)=gliptranc(3,i)+ssgradlip*pepliptran
12300 C print *,"doing sccale for lower part"
12301 C print *,i,sslip,fracinbuf,ssgradlip
12302 elseif (positi.gt.bufliptop) then
12303 fracinbuf=1.0d0-((bordliptop-positi)/lipbufthick)
12304 sslip=sscalelip(fracinbuf)
12305 ssgradlip=sscagradlip(fracinbuf)/lipbufthick
12306 eliptran=eliptran+sslip*pepliptran
12307 gliptranc(3,i)=gliptranc(3,i)+ssgradlip*pepliptran/2.0d0
12308 gliptranc(3,i-1)=gliptranc(3,i-1)+ssgradlip*pepliptran/2.0d0
12309 C gliptranc(3,i-2)=gliptranc(3,i)+ssgradlip*pepliptran
12310 C print *, "doing sscalefor top part"
12311 C print *,i,sslip,fracinbuf,ssgradlip
12313 eliptran=eliptran+pepliptran
12314 C print *,"I am in true lipid"
12317 C eliptran=elpitran+0.0 ! I am in water
12320 C print *, "nic nie bylo w lipidzie?"
12321 C now multiply all by the peptide group transfer factor
12322 C eliptran=eliptran*pepliptran
12323 C now the same for side chains
12325 do i=ilip_start,ilip_end
12326 if (itype(i).eq.ntyp1) cycle
12327 positi=(mod(c(3,i+nres),boxzsize))
12328 if (positi.le.0) positi=positi+boxzsize
12329 C print *,mod(c(3,i+nres),boxzsize),bordlipbot,bordliptop
12330 c for each residue check if it is in lipid or lipid water border area
12331 C respos=mod(c(3,i+nres),boxzsize)
12332 C print *,positi,bordlipbot,buflipbot
12333 if ((positi.gt.bordlipbot)
12334 & .and.(positi.lt.bordliptop)) then
12335 C the energy transfer exist
12336 if (positi.lt.buflipbot) then
12338 & ((positi-bordlipbot)/lipbufthick)
12339 C lipbufthick is thickenes of lipid buffore
12340 sslip=sscalelip(fracinbuf)
12341 ssgradlip=-sscagradlip(fracinbuf)/lipbufthick
12342 eliptran=eliptran+sslip*liptranene(itype(i))
12343 gliptranx(3,i)=gliptranx(3,i)
12344 &+ssgradlip*liptranene(itype(i))
12345 gliptranc(3,i-1)= gliptranc(3,i-1)
12346 &+ssgradlip*liptranene(itype(i))
12347 C print *,"doing sccale for lower part"
12348 elseif (positi.gt.bufliptop) then
12350 &((bordliptop-positi)/lipbufthick)
12351 sslip=sscalelip(fracinbuf)
12352 ssgradlip=sscagradlip(fracinbuf)/lipbufthick
12353 eliptran=eliptran+sslip*liptranene(itype(i))
12354 gliptranx(3,i)=gliptranx(3,i)
12355 &+ssgradlip*liptranene(itype(i))
12356 gliptranc(3,i-1)= gliptranc(3,i-1)
12357 &+ssgradlip*liptranene(itype(i))
12358 C print *, "doing sscalefor top part",sslip,fracinbuf
12360 eliptran=eliptran+liptranene(itype(i))
12361 C print *,"I am in true lipid"
12363 endif ! if in lipid or buffor
12365 C eliptran=elpitran+0.0 ! I am in water
12369 C---------------------------------------------------------
12370 C AFM soubroutine for constant force
12371 subroutine AFMforce(Eafmforce)
12372 implicit real*8 (a-h,o-z)
12373 include 'DIMENSIONS'
12374 include 'COMMON.GEO'
12375 include 'COMMON.VAR'
12376 include 'COMMON.LOCAL'
12377 include 'COMMON.CHAIN'
12378 include 'COMMON.DERIV'
12379 include 'COMMON.NAMES'
12380 include 'COMMON.INTERACT'
12381 include 'COMMON.IOUNITS'
12382 include 'COMMON.CALC'
12383 include 'COMMON.CONTROL'
12384 include 'COMMON.SPLITELE'
12385 include 'COMMON.SBRIDGE'
12390 diffafm(i)=c(i,afmend)-c(i,afmbeg)
12391 dist=dist+diffafm(i)**2
12394 Eafmforce=-forceAFMconst*(dist-distafminit)
12396 gradafm(i,afmend-1)=-forceAFMconst*diffafm(i)/dist
12397 gradafm(i,afmbeg-1)=forceAFMconst*diffafm(i)/dist
12399 C print *,'AFM',Eafmforce
12402 C---------------------------------------------------------
12403 C AFM subroutine with pseudoconstant velocity
12404 subroutine AFMvel(Eafmforce)
12405 implicit real*8 (a-h,o-z)
12406 include 'DIMENSIONS'
12407 include 'COMMON.GEO'
12408 include 'COMMON.VAR'
12409 include 'COMMON.LOCAL'
12410 include 'COMMON.CHAIN'
12411 include 'COMMON.DERIV'
12412 include 'COMMON.NAMES'
12413 include 'COMMON.INTERACT'
12414 include 'COMMON.IOUNITS'
12415 include 'COMMON.CALC'
12416 include 'COMMON.CONTROL'
12417 include 'COMMON.SPLITELE'
12418 include 'COMMON.SBRIDGE'
12420 C Only for check grad COMMENT if not used for checkgrad
12422 C--------------------------------------------------------
12423 C print *,"wchodze"
12427 diffafm(i)=c(i,afmend)-c(i,afmbeg)
12428 dist=dist+diffafm(i)**2
12431 Eafmforce=0.5d0*forceAFMconst
12432 & *(distafminit+totTafm*velAFMconst-dist)**2
12433 C Eafmforce=-forceAFMconst*(dist-distafminit)
12435 gradafm(i,afmend-1)=-forceAFMconst*
12436 &(distafminit+totTafm*velAFMconst-dist)
12438 gradafm(i,afmbeg-1)=forceAFMconst*
12439 &(distafminit+totTafm*velAFMconst-dist)
12442 C print *,'AFM',Eafmforce,totTafm*velAFMconst,dist
12445 C-----------------------------------------------------------
12446 C first for shielding is setting of function of side-chains
12447 subroutine set_shield_fac
12448 implicit real*8 (a-h,o-z)
12449 include 'DIMENSIONS'
12450 include 'COMMON.CHAIN'
12451 include 'COMMON.DERIV'
12452 include 'COMMON.IOUNITS'
12453 include 'COMMON.SHIELD'
12454 include 'COMMON.INTERACT'
12455 C this is the squar root 77 devided by 81 the epislion in lipid (in protein)
12456 double precision div77_81/0.974996043d0/,
12457 &div4_81/0.2222222222d0/,sh_frac_dist_grad(3)
12459 C the vector between center of side_chain and peptide group
12460 double precision pep_side(3),long,side_calf(3),
12461 &pept_group(3),costhet_grad(3),cosphi_grad_long(3),
12462 &cosphi_grad_loc(3),pep_side_norm(3),side_calf_norm(3)
12463 C the line belowe needs to be changed for FGPROC>1
12465 if ((itype(i).eq.ntyp1).and.itype(i+1).eq.ntyp1) cycle
12467 Cif there two consequtive dummy atoms there is no peptide group between them
12468 C the line below has to be changed for FGPROC>1
12471 if ((itype(k).eq.ntyp1).or.(itype(k).eq.10)) cycle
12475 C first lets set vector conecting the ithe side-chain with kth side-chain
12476 pep_side(j)=c(j,k+nres)-(c(j,i)+c(j,i+1))/2.0d0
12477 C pep_side(j)=2.0d0
12478 C and vector conecting the side-chain with its proper calfa
12479 side_calf(j)=c(j,k+nres)-c(j,k)
12480 C side_calf(j)=2.0d0
12481 pept_group(j)=c(j,i)-c(j,i+1)
12482 C lets have their lenght
12483 dist_pep_side=pep_side(j)**2+dist_pep_side
12484 dist_side_calf=dist_side_calf+side_calf(j)**2
12485 dist_pept_group=dist_pept_group+pept_group(j)**2
12487 dist_pep_side=dsqrt(dist_pep_side)
12488 dist_pept_group=dsqrt(dist_pept_group)
12489 dist_side_calf=dsqrt(dist_side_calf)
12491 pep_side_norm(j)=pep_side(j)/dist_pep_side
12492 side_calf_norm(j)=dist_side_calf
12494 C now sscale fraction
12495 sh_frac_dist=-(dist_pep_side-rpp(1,1)-buff_shield)/buff_shield
12496 C print *,buff_shield,"buff"
12498 if (sh_frac_dist.le.0.0) cycle
12499 C If we reach here it means that this side chain reaches the shielding sphere
12500 C Lets add him to the list for gradient
12501 ishield_list(i)=ishield_list(i)+1
12502 C ishield_list is a list of non 0 side-chain that contribute to factor gradient
12503 C this list is essential otherwise problem would be O3
12504 shield_list(ishield_list(i),i)=k
12505 C Lets have the sscale value
12506 if (sh_frac_dist.gt.1.0) then
12507 scale_fac_dist=1.0d0
12509 sh_frac_dist_grad(j)=0.0d0
12512 scale_fac_dist=-sh_frac_dist*sh_frac_dist
12513 & *(2.0*sh_frac_dist-3.0d0)
12514 fac_help_scale=6.0*(sh_frac_dist-sh_frac_dist**2)
12515 & /dist_pep_side/buff_shield*0.5
12516 C remember for the final gradient multiply sh_frac_dist_grad(j)
12517 C for side_chain by factor -2 !
12519 sh_frac_dist_grad(j)=fac_help_scale*pep_side(j)
12520 C print *,"jestem",scale_fac_dist,fac_help_scale,
12521 C & sh_frac_dist_grad(j)
12524 C if ((i.eq.3).and.(k.eq.2)) then
12525 C print *,i,sh_frac_dist,dist_pep,fac_help_scale,scale_fac_dist
12529 C this is what is now we have the distance scaling now volume...
12530 short=short_r_sidechain(itype(k))
12531 long=long_r_sidechain(itype(k))
12532 costhet=1.0d0/dsqrt(1.0+short**2/dist_pep_side**2)
12535 costhet_fac=costhet**3*short**2*(-0.5)/dist_pep_side**4
12536 C costhet_fac=0.0d0
12538 costhet_grad(j)=costhet_fac*pep_side(j)
12540 C remember for the final gradient multiply costhet_grad(j)
12541 C for side_chain by factor -2 !
12542 C fac alfa is angle between CB_k,CA_k, CA_i,CA_i+1
12543 C pep_side0pept_group is vector multiplication
12544 pep_side0pept_group=0.0
12546 pep_side0pept_group=pep_side0pept_group+pep_side(j)*side_calf(j)
12548 cosalfa=(pep_side0pept_group/
12549 & (dist_pep_side*dist_side_calf))
12550 fac_alfa_sin=1.0-cosalfa**2
12551 fac_alfa_sin=dsqrt(fac_alfa_sin)
12552 rkprim=fac_alfa_sin*(long-short)+short
12554 cosphi=1.0d0/dsqrt(1.0+rkprim**2/dist_pep_side**2)
12555 cosphi_fac=cosphi**3*rkprim**2*(-0.5)/dist_pep_side**4
12558 cosphi_grad_long(j)=cosphi_fac*pep_side(j)
12559 &+cosphi**3*0.5/dist_pep_side**2*(-rkprim)
12560 &*(long-short)/fac_alfa_sin*cosalfa/
12561 &((dist_pep_side*dist_side_calf))*
12562 &((side_calf(j))-cosalfa*
12563 &((pep_side(j)/dist_pep_side)*dist_side_calf))
12565 cosphi_grad_loc(j)=cosphi**3*0.5/dist_pep_side**2*(-rkprim)
12566 &*(long-short)/fac_alfa_sin*cosalfa
12567 &/((dist_pep_side*dist_side_calf))*
12569 &cosalfa*side_calf(j)/dist_side_calf*dist_pep_side)
12572 VofOverlap=VSolvSphere/2.0d0*(1.0-costhet)*(1.0-cosphi)
12575 C now the gradient...
12576 C grad_shield is gradient of Calfa for peptide groups
12577 C write(iout,*) "shield_compon",i,k,VSolvSphere,scale_fac_dist,
12579 C write(iout,*) "cosphi_compon",i,k,pep_side0pept_group,
12580 C & dist_pep_side,dist_side_calf,c(1,k+nres),c(1,k),itype(k)
12582 grad_shield(j,i)=grad_shield(j,i)
12583 C gradient po skalowaniu
12584 & +(sh_frac_dist_grad(j)
12585 C gradient po costhet
12586 &-scale_fac_dist*costhet_grad(j)/(1.0-costhet)
12587 &-scale_fac_dist*(cosphi_grad_long(j))
12588 &/(1.0-cosphi) )*div77_81
12590 C grad_shield_side is Cbeta sidechain gradient
12591 grad_shield_side(j,ishield_list(i),i)=
12592 & (sh_frac_dist_grad(j)*(-2.0d0)
12593 & +scale_fac_dist*costhet_grad(j)*2.0d0/(1.0-costhet)
12594 & +scale_fac_dist*(cosphi_grad_long(j))
12595 & *2.0d0/(1.0-cosphi))
12596 & *div77_81*VofOverlap
12598 grad_shield_loc(j,ishield_list(i),i)=
12599 & scale_fac_dist*cosphi_grad_loc(j)
12600 & *2.0d0/(1.0-cosphi)
12601 & *div77_81*VofOverlap
12603 VolumeTotal=VolumeTotal+VofOverlap*scale_fac_dist
12605 fac_shield(i)=VolumeTotal*div77_81+div4_81
12606 c write(2,*) "TOTAL VOLUME",i,VolumeTotal,fac_shield(i)
12610 C--------------------------------------------------------------------------
12611 double precision function tschebyshev(m,n,x,y)
12613 include "DIMENSIONS"
12615 double precision x(n),y,yy(0:maxvar),aux
12616 c Tschebyshev polynomial. Note that the first term is omitted
12617 c m=0: the constant term is included
12618 c m=1: the constant term is not included
12622 yy(i)=2*yy(1)*yy(i-1)-yy(i-2)
12631 C--------------------------------------------------------------------------
12632 double precision function gradtschebyshev(m,n,x,y)
12634 include "DIMENSIONS"
12636 double precision x(n+1),y,yy(0:maxvar),aux
12637 c Tschebyshev polynomial. Note that the first term is omitted
12638 c m=0: the constant term is included
12639 c m=1: the constant term is not included
12643 yy(i)=2*y*yy(i-1)-yy(i-2)
12647 aux=aux+x(i+1)*yy(i)*(i+1)
12648 C print *, x(i+1),yy(i),i
12650 gradtschebyshev=aux
12653 C------------------------------------------------------------------------
12654 C first for shielding is setting of function of side-chains
12655 subroutine set_shield_fac2
12656 implicit real*8 (a-h,o-z)
12657 include 'DIMENSIONS'
12658 include 'COMMON.CHAIN'
12659 include 'COMMON.DERIV'
12660 include 'COMMON.IOUNITS'
12661 include 'COMMON.SHIELD'
12662 include 'COMMON.INTERACT'
12663 C this is the squar root 77 devided by 81 the epislion in lipid (in protein)
12664 double precision div77_81/0.974996043d0/,
12665 &div4_81/0.2222222222d0/,sh_frac_dist_grad(3)
12667 C the vector between center of side_chain and peptide group
12668 double precision pep_side(3),long,side_calf(3),
12669 &pept_group(3),costhet_grad(3),cosphi_grad_long(3),
12670 &cosphi_grad_loc(3),pep_side_norm(3),side_calf_norm(3)
12671 C the line belowe needs to be changed for FGPROC>1
12673 if ((itype(i).eq.ntyp1).and.itype(i+1).eq.ntyp1) cycle
12675 Cif there two consequtive dummy atoms there is no peptide group between them
12676 C the line below has to be changed for FGPROC>1
12679 if ((itype(k).eq.ntyp1).or.(itype(k).eq.10)) cycle
12683 C first lets set vector conecting the ithe side-chain with kth side-chain
12684 pep_side(j)=c(j,k+nres)-(c(j,i)+c(j,i+1))/2.0d0
12685 C pep_side(j)=2.0d0
12686 C and vector conecting the side-chain with its proper calfa
12687 side_calf(j)=c(j,k+nres)-c(j,k)
12688 C side_calf(j)=2.0d0
12689 pept_group(j)=c(j,i)-c(j,i+1)
12690 C lets have their lenght
12691 dist_pep_side=pep_side(j)**2+dist_pep_side
12692 dist_side_calf=dist_side_calf+side_calf(j)**2
12693 dist_pept_group=dist_pept_group+pept_group(j)**2
12695 dist_pep_side=dsqrt(dist_pep_side)
12696 dist_pept_group=dsqrt(dist_pept_group)
12697 dist_side_calf=dsqrt(dist_side_calf)
12699 pep_side_norm(j)=pep_side(j)/dist_pep_side
12700 side_calf_norm(j)=dist_side_calf
12702 C now sscale fraction
12703 sh_frac_dist=-(dist_pep_side-rpp(1,1)-buff_shield)/buff_shield
12704 C print *,buff_shield,"buff"
12706 if (sh_frac_dist.le.0.0) cycle
12707 C If we reach here it means that this side chain reaches the shielding sphere
12708 C Lets add him to the list for gradient
12709 ishield_list(i)=ishield_list(i)+1
12710 C ishield_list is a list of non 0 side-chain that contribute to factor gradient
12711 C this list is essential otherwise problem would be O3
12712 shield_list(ishield_list(i),i)=k
12713 C Lets have the sscale value
12714 if (sh_frac_dist.gt.1.0) then
12715 scale_fac_dist=1.0d0
12717 sh_frac_dist_grad(j)=0.0d0
12720 scale_fac_dist=-sh_frac_dist*sh_frac_dist
12721 & *(2.0d0*sh_frac_dist-3.0d0)
12722 fac_help_scale=6.0d0*(sh_frac_dist-sh_frac_dist**2)
12723 & /dist_pep_side/buff_shield*0.5d0
12724 C remember for the final gradient multiply sh_frac_dist_grad(j)
12725 C for side_chain by factor -2 !
12727 sh_frac_dist_grad(j)=fac_help_scale*pep_side(j)
12728 C sh_frac_dist_grad(j)=0.0d0
12729 C scale_fac_dist=1.0d0
12730 C print *,"jestem",scale_fac_dist,fac_help_scale,
12731 C & sh_frac_dist_grad(j)
12734 C this is what is now we have the distance scaling now volume...
12735 short=short_r_sidechain(itype(k))
12736 long=long_r_sidechain(itype(k))
12737 costhet=1.0d0/dsqrt(1.0d0+short**2/dist_pep_side**2)
12738 sinthet=short/dist_pep_side*costhet
12742 costhet_fac=costhet**3*short**2*(-0.5d0)/dist_pep_side**4
12743 C sinthet_fac=costhet**2*0.5d0*(short**3/dist_pep_side**4*costhet
12744 C & -short/dist_pep_side**2/costhet)
12745 C costhet_fac=0.0d0
12747 costhet_grad(j)=costhet_fac*pep_side(j)
12749 C remember for the final gradient multiply costhet_grad(j)
12750 C for side_chain by factor -2 !
12751 C fac alfa is angle between CB_k,CA_k, CA_i,CA_i+1
12752 C pep_side0pept_group is vector multiplication
12753 pep_side0pept_group=0.0d0
12755 pep_side0pept_group=pep_side0pept_group+pep_side(j)*side_calf(j)
12757 cosalfa=(pep_side0pept_group/
12758 & (dist_pep_side*dist_side_calf))
12759 fac_alfa_sin=1.0d0-cosalfa**2
12760 fac_alfa_sin=dsqrt(fac_alfa_sin)
12761 rkprim=fac_alfa_sin*(long-short)+short
12765 cosphi=1.0d0/dsqrt(1.0d0+rkprim**2/dist_pep_side**2)
12767 cosphi_fac=cosphi**3*rkprim**2*(-0.5d0)/dist_pep_side**4
12768 sinphi=rkprim/dist_pep_side/dsqrt(1.0d0+rkprim**2/
12769 & dist_pep_side**2)
12772 cosphi_grad_long(j)=cosphi_fac*pep_side(j)
12773 &+cosphi**3*0.5d0/dist_pep_side**2*(-rkprim)
12774 &*(long-short)/fac_alfa_sin*cosalfa/
12775 &((dist_pep_side*dist_side_calf))*
12776 &((side_calf(j))-cosalfa*
12777 &((pep_side(j)/dist_pep_side)*dist_side_calf))
12778 C cosphi_grad_long(j)=0.0d0
12779 cosphi_grad_loc(j)=cosphi**3*0.5d0/dist_pep_side**2*(-rkprim)
12780 &*(long-short)/fac_alfa_sin*cosalfa
12781 &/((dist_pep_side*dist_side_calf))*
12783 &cosalfa*side_calf(j)/dist_side_calf*dist_pep_side)
12784 C cosphi_grad_loc(j)=0.0d0
12786 C print *,sinphi,sinthet
12787 c write (iout,*) "VSolvSphere",VSolvSphere," VSolvSphere_div",
12788 c & VSolvSphere_div," sinphi",sinphi," sinthet",sinthet
12789 VofOverlap=VSolvSphere/2.0d0*(1.0d0-dsqrt(1.0d0-sinphi*sinthet))
12792 C now the gradient...
12794 grad_shield(j,i)=grad_shield(j,i)
12795 C gradient po skalowaniu
12796 & +(sh_frac_dist_grad(j)*VofOverlap
12797 C gradient po costhet
12798 & +scale_fac_dist*VSolvSphere/VSolvSphere_div/4.0d0*
12799 &(1.0d0/(-dsqrt(1.0d0-sinphi*sinthet))*(
12800 & sinphi/sinthet*costhet*costhet_grad(j)
12801 & +sinthet/sinphi*cosphi*cosphi_grad_long(j)))
12803 C grad_shield_side is Cbeta sidechain gradient
12804 grad_shield_side(j,ishield_list(i),i)=
12805 & (sh_frac_dist_grad(j)*(-2.0d0)
12807 & -scale_fac_dist*VSolvSphere/VSolvSphere_div/2.0d0*
12808 &(1.0d0/(-dsqrt(1.0d0-sinphi*sinthet))*(
12809 & sinphi/sinthet*costhet*costhet_grad(j)
12810 & +sinthet/sinphi*cosphi*cosphi_grad_long(j)))
12813 grad_shield_loc(j,ishield_list(i),i)=
12814 & scale_fac_dist*VSolvSphere/VSolvSphere_div/2.0d0*
12815 &(1.0d0/(dsqrt(1.0d0-sinphi*sinthet))*(
12816 & sinthet/sinphi*cosphi*cosphi_grad_loc(j)
12820 c write (iout,*) "VofOverlap",VofOverlap," scale_fac_dist",
12822 VolumeTotal=VolumeTotal+VofOverlap*scale_fac_dist
12824 fac_shield(i)=VolumeTotal*wshield+(1.0d0-wshield)
12825 c write(2,*) "TOTAL VOLUME",i,VolumeTotal,fac_shield(i),
12826 c & " wshield",wshield
12827 c write(2,*) "TU",rpp(1,1),short,long,buff_shield
12831 C-----------------------------------------------------------------------
12832 C-----------------------------------------------------------
12833 C This subroutine is to mimic the histone like structure but as well can be
12834 C utilizet to nanostructures (infinit) small modification has to be used to
12835 C make it finite (z gradient at the ends has to be changes as well as the x,y
12836 C gradient has to be modified at the ends
12837 C The energy function is Kihara potential
12838 C E=4esp*((sigma/(r-r0))^12 - (sigma/(r-r0))^6)
12839 C 4eps is depth of well sigma is r_minimum r is distance from center of tube
12840 C and r0 is the excluded size of nanotube (can be set to 0 if we want just a
12841 C simple Kihara potential
12842 subroutine calctube(Etube)
12843 implicit real*8 (a-h,o-z)
12844 include 'DIMENSIONS'
12845 include 'COMMON.GEO'
12846 include 'COMMON.VAR'
12847 include 'COMMON.LOCAL'
12848 include 'COMMON.CHAIN'
12849 include 'COMMON.DERIV'
12850 include 'COMMON.NAMES'
12851 include 'COMMON.INTERACT'
12852 include 'COMMON.IOUNITS'
12853 include 'COMMON.CALC'
12854 include 'COMMON.CONTROL'
12855 include 'COMMON.SPLITELE'
12856 include 'COMMON.SBRIDGE'
12857 double precision tub_r,vectube(3),enetube(maxres*2)
12862 C first we calculate the distance from tube center
12863 C first sugare-phosphate group for NARES this would be peptide group
12866 C lets ommit dummy atoms for now
12867 if ((itype(i).eq.ntyp1).or.(itype(i+1).eq.ntyp1)) cycle
12868 C now calculate distance from center of tube and direction vectors
12869 vectube(1)=mod((c(1,i)+c(1,i+1))/2.0d0,boxxsize)
12870 if (vectube(1).lt.0) vectube(1)=vectube(1)+boxxsize
12871 vectube(2)=mod((c(2,i)+c(2,i+1))/2.0d0,boxxsize)
12872 if (vectube(2).lt.0) vectube(2)=vectube(2)+boxxsize
12873 vectube(1)=vectube(1)-tubecenter(1)
12874 vectube(2)=vectube(2)-tubecenter(2)
12876 C print *,"x",(c(1,i)+c(1,i+1))/2.0d0,tubecenter(1)
12877 C print *,"y",(c(2,i)+c(2,i+1))/2.0d0,tubecenter(2)
12879 C as the tube is infinity we do not calculate the Z-vector use of Z
12882 C now calculte the distance
12883 tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
12884 C now normalize vector
12885 vectube(1)=vectube(1)/tub_r
12886 vectube(2)=vectube(2)/tub_r
12887 C calculte rdiffrence between r and r0
12890 rdiff6=rdiff**6.0d0
12891 C for vectorization reasons we will sumup at the end to avoid depenence of previous
12892 enetube(i)=pep_aa_tube/rdiff6**2.0d0-pep_bb_tube/rdiff6
12893 C write(iout,*) "TU13",i,rdiff6,enetube(i)
12894 C print *,rdiff,rdiff6,pep_aa_tube
12895 C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
12896 C now we calculate gradient
12897 fac=(-12.0d0*pep_aa_tube/rdiff6+
12898 & 6.0d0*pep_bb_tube)/rdiff6/rdiff
12899 C write(iout,'(a5,i4,f12.1,3f12.5)') "TU13",i,rdiff6,enetube(i),
12902 C now direction of gg_tube vector
12904 gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac/2.0d0
12905 gg_tube(j,i)=gg_tube(j,i)+vectube(j)*fac/2.0d0
12908 C basically thats all code now we split for side-chains (REMEMBER to sum up at the END)
12910 C Lets not jump over memory as we use many times iti
12912 C lets ommit dummy atoms for now
12914 C in UNRES uncomment the line below as GLY has no side-chain...
12917 vectube(1)=c(1,i+nres)
12918 vectube(1)=mod(vectube(1),boxxsize)
12919 if (vectube(1).lt.0) vectube(1)=vectube(1)+boxxsize
12920 vectube(2)=c(2,i+nres)
12921 vectube(2)=mod(vectube(2),boxxsize)
12922 if (vectube(2).lt.0) vectube(2)=vectube(2)+boxxsize
12924 vectube(1)=vectube(1)-tubecenter(1)
12925 vectube(2)=vectube(2)-tubecenter(2)
12927 C as the tube is infinity we do not calculate the Z-vector use of Z
12930 C now calculte the distance
12931 tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
12932 C now normalize vector
12933 vectube(1)=vectube(1)/tub_r
12934 vectube(2)=vectube(2)/tub_r
12935 C calculte rdiffrence between r and r0
12938 rdiff6=rdiff**6.0d0
12939 C for vectorization reasons we will sumup at the end to avoid depenence of previous
12940 sc_aa_tube=sc_aa_tube_par(iti)
12941 sc_bb_tube=sc_bb_tube_par(iti)
12942 enetube(i+nres)=sc_aa_tube/rdiff6**2.0d0-sc_bb_tube/rdiff6
12943 C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
12944 C now we calculate gradient
12945 fac=-12.0d0*sc_aa_tube/rdiff6**2.0d0/rdiff+
12946 & 6.0d0*sc_bb_tube/rdiff6/rdiff
12947 C now direction of gg_tube vector
12949 gg_tube_SC(j,i)=gg_tube_SC(j,i)+vectube(j)*fac
12950 gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac
12954 Etube=Etube+enetube(i)
12956 C print *,"ETUBE", etube
12959 C TO DO 1) add to total energy
12960 C 2) add to gradient summation
12961 C 3) add reading parameters (AND of course oppening of PARAM file)
12962 C 4) add reading the center of tube
12964 C 6) add to zerograd
12966 C-----------------------------------------------------------------------
12967 C-----------------------------------------------------------
12968 C This subroutine is to mimic the histone like structure but as well can be
12969 C utilizet to nanostructures (infinit) small modification has to be used to
12970 C make it finite (z gradient at the ends has to be changes as well as the x,y
12971 C gradient has to be modified at the ends
12972 C The energy function is Kihara potential
12973 C E=4esp*((sigma/(r-r0))^12 - (sigma/(r-r0))^6)
12974 C 4eps is depth of well sigma is r_minimum r is distance from center of tube
12975 C and r0 is the excluded size of nanotube (can be set to 0 if we want just a
12976 C simple Kihara potential
12977 subroutine calctube2(Etube)
12978 implicit real*8 (a-h,o-z)
12979 include 'DIMENSIONS'
12980 include 'COMMON.GEO'
12981 include 'COMMON.VAR'
12982 include 'COMMON.LOCAL'
12983 include 'COMMON.CHAIN'
12984 include 'COMMON.DERIV'
12985 include 'COMMON.NAMES'
12986 include 'COMMON.INTERACT'
12987 include 'COMMON.IOUNITS'
12988 include 'COMMON.CALC'
12989 include 'COMMON.CONTROL'
12990 include 'COMMON.SPLITELE'
12991 include 'COMMON.SBRIDGE'
12992 double precision tub_r,vectube(3),enetube(maxres*2)
12997 C first we calculate the distance from tube center
12998 C first sugare-phosphate group for NARES this would be peptide group
13001 C lets ommit dummy atoms for now
13002 if ((itype(i).eq.ntyp1).or.(itype(i+1).eq.ntyp1)) cycle
13003 C now calculate distance from center of tube and direction vectors
13004 vectube(1)=mod((c(1,i)+c(1,i+1))/2.0d0,boxxsize)
13005 if (vectube(1).lt.0) vectube(1)=vectube(1)+boxxsize
13006 vectube(2)=mod((c(2,i)+c(2,i+1))/2.0d0,boxxsize)
13007 if (vectube(2).lt.0) vectube(2)=vectube(2)+boxxsize
13008 vectube(1)=vectube(1)-tubecenter(1)
13009 vectube(2)=vectube(2)-tubecenter(2)
13011 C print *,"x",(c(1,i)+c(1,i+1))/2.0d0,tubecenter(1)
13012 C print *,"y",(c(2,i)+c(2,i+1))/2.0d0,tubecenter(2)
13014 C as the tube is infinity we do not calculate the Z-vector use of Z
13017 C now calculte the distance
13018 tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
13019 C now normalize vector
13020 vectube(1)=vectube(1)/tub_r
13021 vectube(2)=vectube(2)/tub_r
13022 C calculte rdiffrence between r and r0
13025 rdiff6=rdiff**6.0d0
13026 C for vectorization reasons we will sumup at the end to avoid depenence of previous
13027 enetube(i)=pep_aa_tube/rdiff6**2.0d0-pep_bb_tube/rdiff6
13028 C write(iout,*) "TU13",i,rdiff6,enetube(i)
13029 C print *,rdiff,rdiff6,pep_aa_tube
13030 C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
13031 C now we calculate gradient
13032 fac=(-12.0d0*pep_aa_tube/rdiff6+
13033 & 6.0d0*pep_bb_tube)/rdiff6/rdiff
13034 C write(iout,'(a5,i4,f12.1,3f12.5)') "TU13",i,rdiff6,enetube(i),
13037 C now direction of gg_tube vector
13039 gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac/2.0d0
13040 gg_tube(j,i)=gg_tube(j,i)+vectube(j)*fac/2.0d0
13043 C basically thats all code now we split for side-chains (REMEMBER to sum up at the END)
13045 C Lets not jump over memory as we use many times iti
13047 C lets ommit dummy atoms for now
13049 C in UNRES uncomment the line below as GLY has no side-chain...
13052 vectube(1)=c(1,i+nres)
13053 vectube(1)=mod(vectube(1),boxxsize)
13054 if (vectube(1).lt.0) vectube(1)=vectube(1)+boxxsize
13055 vectube(2)=c(2,i+nres)
13056 vectube(2)=mod(vectube(2),boxxsize)
13057 if (vectube(2).lt.0) vectube(2)=vectube(2)+boxxsize
13059 vectube(1)=vectube(1)-tubecenter(1)
13060 vectube(2)=vectube(2)-tubecenter(2)
13061 C THIS FRAGMENT MAKES TUBE FINITE
13062 positi=(mod(c(3,i+nres),boxzsize))
13063 if (positi.le.0) positi=positi+boxzsize
13064 C print *,mod(c(3,i+nres),boxzsize),bordlipbot,bordliptop
13065 c for each residue check if it is in lipid or lipid water border area
13066 C respos=mod(c(3,i+nres),boxzsize)
13067 print *,positi,bordtubebot,buftubebot,bordtubetop
13068 if ((positi.gt.bordtubebot)
13069 & .and.(positi.lt.bordtubetop)) then
13070 C the energy transfer exist
13071 if (positi.lt.buftubebot) then
13073 & ((positi-bordtubebot)/tubebufthick)
13074 C lipbufthick is thickenes of lipid buffore
13075 sstube=sscalelip(fracinbuf)
13076 ssgradtube=-sscagradlip(fracinbuf)/tubebufthick
13077 print *,ssgradtube, sstube,tubetranene(itype(i))
13078 enetube(i+nres)=enetube(i+nres)+sstube*tubetranene(itype(i))
13079 gg_tube_SC(3,i)=gg_tube_SC(3,i)
13080 &+ssgradtube*tubetranene(itype(i))
13081 gg_tube(3,i-1)= gg_tube(3,i-1)
13082 &+ssgradtube*tubetranene(itype(i))
13083 C print *,"doing sccale for lower part"
13084 elseif (positi.gt.buftubetop) then
13086 &((bordtubetop-positi)/tubebufthick)
13087 sstube=sscalelip(fracinbuf)
13088 ssgradtube=sscagradlip(fracinbuf)/tubebufthick
13089 enetube(i+nres)=enetube(i+nres)+sstube*tubetranene(itype(i))
13090 C gg_tube_SC(3,i)=gg_tube_SC(3,i)
13091 C &+ssgradtube*tubetranene(itype(i))
13092 C gg_tube(3,i-1)= gg_tube(3,i-1)
13093 C &+ssgradtube*tubetranene(itype(i))
13094 C print *, "doing sscalefor top part",sslip,fracinbuf
13098 enetube(i+nres)=enetube(i+nres)+sstube*tubetranene(itype(i))
13099 C print *,"I am in true lipid"
13105 endif ! if in lipid or buffor
13106 CEND OF FINITE FRAGMENT
13107 C as the tube is infinity we do not calculate the Z-vector use of Z
13110 C now calculte the distance
13111 tub_r=dsqrt(vectube(1)**2+vectube(2)**2+vectube(3)**2)
13112 C now normalize vector
13113 vectube(1)=vectube(1)/tub_r
13114 vectube(2)=vectube(2)/tub_r
13115 C calculte rdiffrence between r and r0
13118 rdiff6=rdiff**6.0d0
13119 C for vectorization reasons we will sumup at the end to avoid depenence of previous
13120 sc_aa_tube=sc_aa_tube_par(iti)
13121 sc_bb_tube=sc_bb_tube_par(iti)
13122 enetube(i+nres)=(sc_aa_tube/rdiff6**2.0d0-sc_bb_tube/rdiff6)
13123 & *sstube+enetube(i+nres)
13124 C pep_aa_tube and pep_bb_tube are precomputed values A=4eps*sigma^12 B=4eps*sigma^6
13125 C now we calculate gradient
13126 fac=(-12.0d0*sc_aa_tube/rdiff6**2.0d0/rdiff+
13127 & 6.0d0*sc_bb_tube/rdiff6/rdiff)*sstube
13128 C now direction of gg_tube vector
13130 gg_tube_SC(j,i)=gg_tube_SC(j,i)+vectube(j)*fac
13131 gg_tube(j,i-1)=gg_tube(j,i-1)+vectube(j)*fac
13133 gg_tube_SC(3,i)=gg_tube_SC(3,i)
13134 &+ssgradtube*enetube(i+nres)/sstube
13135 gg_tube(3,i-1)= gg_tube(3,i-1)
13136 &+ssgradtube*enetube(i+nres)/sstube
13140 Etube=Etube+enetube(i)
13142 C print *,"ETUBE", etube
13145 C TO DO 1) add to total energy
13146 C 2) add to gradient summation
13147 C 3) add reading parameters (AND of course oppening of PARAM file)
13148 C 4) add reading the center of tube
13150 C 6) add to zerograd
13151 c----------------------------------------------------------------------------
13152 subroutine e_saxs(Esaxs_constr)
13154 include 'DIMENSIONS'
13157 include "COMMON.SETUP"
13160 include 'COMMON.SBRIDGE'
13161 include 'COMMON.CHAIN'
13162 include 'COMMON.GEO'
13163 include 'COMMON.DERIV'
13164 include 'COMMON.LOCAL'
13165 include 'COMMON.INTERACT'
13166 include 'COMMON.VAR'
13167 include 'COMMON.IOUNITS'
13168 c include 'COMMON.MD'
13171 include 'COMMON.LANGEVIN.lang0.5diag'
13173 include 'COMMON.LANGEVIN.lang0'
13176 include 'COMMON.LANGEVIN'
13178 include 'COMMON.CONTROL'
13179 include 'COMMON.SAXS'
13180 include 'COMMON.NAMES'
13181 include 'COMMON.TIME1'
13182 include 'COMMON.FFIELD'
13184 double precision Esaxs_constr
13185 integer i,iint,j,k,l
13186 double precision PgradC(maxSAXS,3,maxres),
13187 & PgradX(maxSAXS,3,maxres),Pcalc(maxSAXS)
13189 double precision PgradC_(maxSAXS,3,maxres),
13190 & PgradX_(maxSAXS,3,maxres),Pcalc_(maxSAXS)
13192 double precision dk,dijCACA,dijCASC,dijSCCA,dijSCSC,
13193 & sigma2CACA,sigma2CASC,sigma2SCCA,sigma2SCSC,expCACA,expCASC,
13194 & expSCCA,expSCSC,CASCgrad,SCCAgrad,SCSCgrad,aux,auxC,auxC1,
13195 & auxX,auxX1,CACAgrad,Cnorm,sigmaCACA,threesig
13196 double precision sss2,ssgrad2,rrr,sscalgrad2,sscale2
13197 double precision dist,mygauss,mygaussder
13199 integer llicz,lllicz
13200 double precision time01
13201 c SAXS restraint penalty function
13203 write(iout,*) "------- SAXS penalty function start -------"
13204 write (iout,*) "nsaxs",nsaxs
13205 write (iout,*) "Esaxs: iatsc_s",iatsc_s," iatsc_e",iatsc_e
13206 write (iout,*) "Psaxs"
13208 write (iout,'(i5,e15.5)') i, Psaxs(i)
13214 Esaxs_constr = 0.0d0
13219 PgradC(k,l,j)=0.0d0
13220 PgradX(k,l,j)=0.0d0
13225 do i=iatsc_s,iatsc_e
13226 if (itype(i).eq.ntyp1) cycle
13227 do iint=1,nint_gr(i)
13228 do j=istart(i,iint),iend(i,iint)
13229 if (itype(j).eq.ntyp1) cycle
13232 dijCASC=dist(i,j+nres)
13233 dijSCCA=dist(i+nres,j)
13234 dijSCSC=dist(i+nres,j+nres)
13235 sigma2CACA=2.0d0/(pstok**2)
13236 sigma2CASC=4.0d0/(pstok**2+restok(itype(j))**2)
13237 sigma2SCCA=4.0d0/(pstok**2+restok(itype(i))**2)
13238 sigma2SCSC=4.0d0/(restok(itype(j))**2+restok(itype(i))**2)
13241 expCACA = dexp(-0.5d0*sigma2CACA*(dijCACA-dk)**2)
13242 if (itype(j).ne.10) then
13243 expCASC = dexp(-0.5d0*sigma2CASC*(dijCASC-dk)**2)
13247 if (itype(i).ne.10) then
13248 expSCCA = dexp(-0.5d0*sigma2SCCA*(dijSCCA-dk)**2)
13252 if (itype(i).ne.10 .and. itype(j).ne.10) then
13253 expSCSC = dexp(-0.5d0*sigma2SCSC*(dijSCSC-dk)**2)
13257 Pcalc(k) = Pcalc(k)+expCACA+expCASC+expSCCA+expSCSC
13259 write(iout,*) "i j k Pcalc",i,j,Pcalc(k)
13261 CACAgrad = sigma2CACA*(dijCACA-dk)*expCACA
13262 CASCgrad = sigma2CASC*(dijCASC-dk)*expCASC
13263 SCCAgrad = sigma2SCCA*(dijSCCA-dk)*expSCCA
13264 SCSCgrad = sigma2SCSC*(dijSCSC-dk)*expSCSC
13267 aux = CACAgrad*(C(l,j)-C(l,i))/dijCACA
13268 PgradC(k,l,i) = PgradC(k,l,i)-aux
13269 PgradC(k,l,j) = PgradC(k,l,j)+aux
13271 if (itype(j).ne.10) then
13272 aux = CASCgrad*(C(l,j+nres)-C(l,i))/dijCASC
13273 PgradC(k,l,i) = PgradC(k,l,i)-aux
13274 PgradC(k,l,j) = PgradC(k,l,j)+aux
13275 PgradX(k,l,j) = PgradX(k,l,j)+aux
13278 if (itype(i).ne.10) then
13279 aux = SCCAgrad*(C(l,j)-C(l,i+nres))/dijSCCA
13280 PgradX(k,l,i) = PgradX(k,l,i)-aux
13281 PgradC(k,l,i) = PgradC(k,l,i)-aux
13282 PgradC(k,l,j) = PgradC(k,l,j)+aux
13285 if (itype(i).ne.10 .and. itype(j).ne.10) then
13286 aux = SCSCgrad*(C(l,j+nres)-C(l,i+nres))/dijSCSC
13287 PgradC(k,l,i) = PgradC(k,l,i)-aux
13288 PgradC(k,l,j) = PgradC(k,l,j)+aux
13289 PgradX(k,l,i) = PgradX(k,l,i)-aux
13290 PgradX(k,l,j) = PgradX(k,l,j)+aux
13296 sigma2CACA=scal_rad**2*0.25d0/
13297 & (restok(itype(j))**2+restok(itype(i))**2)
13298 c write (iout,*) "scal_rad",scal_rad," restok",restok(itype(j))
13299 c & ,restok(itype(i)),"sigma",1.0d0/dsqrt(sigma2CACA)
13301 sigmaCACA=dsqrt(sigma2CACA)
13302 threesig=3.0d0/sigmaCACA
13306 if (dabs(dijCACA-dk).ge.threesig) cycle
13309 aux = sigmaCACA*(dijCACA-dk)
13310 expCACA = mygauss(aux)
13311 c if (expcaca.eq.0.0d0) cycle
13312 Pcalc(k) = Pcalc(k)+expCACA
13313 CACAgrad = -sigmaCACA*mygaussder(aux)
13314 c write (iout,*) "i,j,k,aux",i,j,k,CACAgrad
13316 aux = CACAgrad*(C(l,j)-C(l,i))/dijCACA
13317 PgradC(k,l,i) = PgradC(k,l,i)-aux
13318 PgradC(k,l,j) = PgradC(k,l,j)+aux
13321 c write (iout,*) "i",i," j",j," llicz",llicz
13323 IF (saxs_cutoff.eq.0) THEN
13326 expCACA = dexp(-0.5d0*sigma2CACA*(dijCACA-dk)**2)
13327 Pcalc(k) = Pcalc(k)+expCACA
13328 CACAgrad = sigma2CACA*(dijCACA-dk)*expCACA
13330 aux = CACAgrad*(C(l,j)-C(l,i))/dijCACA
13331 PgradC(k,l,i) = PgradC(k,l,i)-aux
13332 PgradC(k,l,j) = PgradC(k,l,j)+aux
13336 rrr = saxs_cutoff*2.0d0/dsqrt(sigma2CACA)
13339 c write (2,*) "ijk",i,j,k
13340 sss2 = sscale2(dijCACA,rrr,dk,0.3d0)
13341 if (sss2.eq.0.0d0) cycle
13342 ssgrad2 = sscalgrad2(dijCACA,rrr,dk,0.3d0)
13343 if (energy_dec) write(iout,'(a4,3i5,8f10.4)')
13344 & 'saxs',i,j,k,dijCACA,restok(itype(i)),restok(itype(j)),
13345 & 1.0d0/dsqrt(sigma2CACA),rrr,dk,
13347 expCACA = dexp(-0.5d0*sigma2CACA*(dijCACA-dk)**2)*sss2
13348 Pcalc(k) = Pcalc(k)+expCACA
13350 write(iout,*) "i j k Pcalc",i,j,Pcalc(k)
13352 CACAgrad = -sigma2CACA*(dijCACA-dk)*expCACA+
13353 & ssgrad2*expCACA/sss2
13356 aux = CACAgrad*(C(l,j)-C(l,i))/dijCACA
13357 PgradC(k,l,i) = PgradC(k,l,i)+aux
13358 PgradC(k,l,j) = PgradC(k,l,j)-aux
13368 c time_SAXS=time_SAXS+MPI_Wtime()-time01
13370 c write (iout,*) "lllicz",lllicz
13372 c time01=MPI_Wtime()
13375 if (nfgtasks.gt.1) then
13376 call MPI_AllReduce(Pcalc(1),Pcalc_(1),nsaxs,MPI_DOUBLE_PRECISION,
13377 & MPI_SUM,FG_COMM,IERR)
13378 c if (fg_rank.eq.king) then
13380 Pcalc(k) = Pcalc_(k)
13383 c call MPI_AllReduce(PgradC(k,1,1),PgradC_(k,1,1),3*maxsaxs*nres,
13384 c & MPI_DOUBLE_PRECISION,MPI_SUM,FG_COMM,IERR)
13385 c if (fg_rank.eq.king) then
13389 c PgradC(k,l,i) = PgradC_(k,l,i)
13395 c call MPI_AllReduce(PgradX(k,1,1),PgradX_(k,1,1),3*maxsaxs*nres,
13396 c & MPI_DOUBLE_PRECISION,MPI_SUM,FG_COMM,IERR)
13397 c if (fg_rank.eq.king) then
13401 c PgradX(k,l,i) = PgradX_(k,l,i)
13411 Cnorm = Cnorm + Pcalc(k)
13414 if (fg_rank.eq.king) then
13416 Esaxs_constr = dlog(Cnorm)-wsaxs0
13418 if (Pcalc(k).gt.0.0d0)
13419 & Esaxs_constr = Esaxs_constr - Psaxs(k)*dlog(Pcalc(k))
13421 write (iout,*) "k",k," Esaxs_constr",Esaxs_constr
13425 write (iout,*) "Cnorm",Cnorm," Esaxs_constr",Esaxs_constr
13440 & auxC = auxC +Psaxs(k)*PgradC(k,l,i)/Pcalc(k)
13441 auxC1 = auxC1+PgradC(k,l,i)
13443 auxX = auxX +Psaxs(k)*PgradX(k,l,i)/Pcalc(k)
13444 auxX1 = auxX1+PgradX(k,l,i)
13447 gsaxsC(l,i) = auxC - auxC1/Cnorm
13449 gsaxsX(l,i) = auxX - auxX1/Cnorm
13451 c write (iout,*) "l i",l,i," gradC",wsaxs*(auxC - auxC1/Cnorm),
13452 c * " gradX",wsaxs*(auxX - auxX1/Cnorm)
13453 c write (iout,*) "l i",l,i," gradC",wsaxs*gsaxsC(l,i),
13454 c * " gradX",wsaxs*gsaxsX(l,i)
13458 time_SAXS=time_SAXS+MPI_Wtime()-time01
13461 write (iout,*) "gsaxsc"
13463 write (iout,'(i5,3e15.5)') i,(gsaxsc(j,i),j=1,3)
13471 c----------------------------------------------------------------------------
13472 subroutine e_saxsC(Esaxs_constr)
13474 include 'DIMENSIONS'
13477 include "COMMON.SETUP"
13480 include 'COMMON.SBRIDGE'
13481 include 'COMMON.CHAIN'
13482 include 'COMMON.GEO'
13483 include 'COMMON.DERIV'
13484 include 'COMMON.LOCAL'
13485 include 'COMMON.INTERACT'
13486 include 'COMMON.VAR'
13487 include 'COMMON.IOUNITS'
13488 c include 'COMMON.MD'
13491 include 'COMMON.LANGEVIN.lang0.5diag'
13493 include 'COMMON.LANGEVIN.lang0'
13496 include 'COMMON.LANGEVIN'
13498 include 'COMMON.CONTROL'
13499 include 'COMMON.SAXS'
13500 include 'COMMON.NAMES'
13501 include 'COMMON.TIME1'
13502 include 'COMMON.FFIELD'
13504 double precision Esaxs_constr
13505 integer i,iint,j,k,l
13506 double precision PgradC(3,maxres),PgradX(3,maxres),Pcalc,logPtot
13508 double precision gsaxsc_(3,maxres),gsaxsx_(3,maxres),logPtot_
13510 double precision dk,dijCASPH,dijSCSPH,
13511 & sigma2CA,sigma2SC,expCASPH,expSCSPH,
13512 & CASPHgrad,SCSPHgrad,aux,auxC,auxC1,
13514 c SAXS restraint penalty function
13516 write(iout,*) "------- SAXS penalty function start -------"
13517 write (iout,*) "nsaxs",nsaxs
13520 print *,MyRank,"C",i,(C(j,i),j=1,3)
13523 print *,MyRank,"CSaxs",i,(Csaxs(j,i),j=1,3)
13526 Esaxs_constr = 0.0d0
13528 do j=isaxs_start,isaxs_end
13537 if (itype(i).eq.ntyp1) cycle
13541 dijCASPH=dijCASPH+(C(l,i)-Csaxs(l,j))**2
13543 if (itype(i).ne.10) then
13545 dijSCSPH=dijSCSPH+(C(l,i+nres)-Csaxs(l,j))**2
13548 sigma2CA=2.0d0/pstok**2
13549 sigma2SC=4.0d0/restok(itype(i))**2
13550 expCASPH = dexp(-0.5d0*sigma2CA*dijCASPH)
13551 expSCSPH = dexp(-0.5d0*sigma2SC*dijSCSPH)
13552 Pcalc = Pcalc+expCASPH+expSCSPH
13554 write(*,*) "processor i j Pcalc",
13555 & MyRank,i,j,dijCASPH,dijSCSPH, Pcalc
13557 CASPHgrad = sigma2CA*expCASPH
13558 SCSPHgrad = sigma2SC*expSCSPH
13560 aux = (C(l,i+nres)-Csaxs(l,j))*SCSPHgrad
13561 PgradX(l,i) = PgradX(l,i) + aux
13562 PgradC(l,i) = PgradC(l,i)+(C(l,i)-Csaxs(l,j))*CASPHgrad+aux
13567 gsaxsc(l,i)=gsaxsc(l,i)+PgradC(l,i)/Pcalc
13568 gsaxsx(l,i)=gsaxsx(l,i)+PgradX(l,i)/Pcalc
13571 logPtot = logPtot - dlog(Pcalc)
13572 c print *,"me",me,MyRank," j",j," logPcalc",-dlog(Pcalc),
13573 c & " logPtot",logPtot
13576 if (nfgtasks.gt.1) then
13577 c write (iout,*) "logPtot before reduction",logPtot
13578 call MPI_Reduce(logPtot,logPtot_,1,MPI_DOUBLE_PRECISION,
13579 & MPI_SUM,king,FG_COMM,IERR)
13581 c write (iout,*) "logPtot after reduction",logPtot
13582 call MPI_Reduce(gsaxsC(1,1),gsaxsC_(1,1),3*nres,
13583 & MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
13584 if (fg_rank.eq.king) then
13587 gsaxsC(l,i) = gsaxsC_(l,i)
13591 call MPI_Reduce(gsaxsX(1,1),gsaxsX_(1,1),3*nres,
13592 & MPI_DOUBLE_PRECISION,MPI_SUM,king,FG_COMM,IERR)
13593 if (fg_rank.eq.king) then
13596 gsaxsX(l,i) = gsaxsX_(l,i)
13602 Esaxs_constr = logPtot
13605 c----------------------------------------------------------------------------
13606 double precision function sscale2(r,r_cut,r0,rlamb)
13608 double precision r,gamm,r_cut,r0,rlamb,rr
13610 c write (2,*) "r",r," r_cut",r_cut," r0",r0," rlamb",rlamb
13611 c write (2,*) "rr",rr
13612 if(rr.lt.r_cut-rlamb) then
13614 else if(rr.le.r_cut.and.rr.ge.r_cut-rlamb) then
13615 gamm=(rr-(r_cut-rlamb))/rlamb
13616 sscale2=1.0d0+gamm*gamm*(2*gamm-3.0d0)
13622 C-----------------------------------------------------------------------
13623 double precision function sscalgrad2(r,r_cut,r0,rlamb)
13625 double precision r,gamm,r_cut,r0,rlamb,rr
13627 if(rr.lt.r_cut-rlamb) then
13629 else if(rr.le.r_cut.and.rr.ge.r_cut-rlamb) then
13630 gamm=(rr-(r_cut-rlamb))/rlamb
13632 sscalgrad2=gamm*(6*gamm-6.0d0)/rlamb
13634 sscalgrad2=-gamm*(6*gamm-6.0d0)/rlamb