2 c-------------------------------------------------------------------------
3 c This subroutine contains the total lagrangain from which the accelerations
4 c are obtained. For numerical gradient checking, the derivetive of the
5 c lagrangian in the velocities and coordinates are calculated seperately
6 c-------------------------------------------------------------------------
7 implicit real*8 (a-h,o-z)
13 include 'COMMON.CHAIN'
14 include 'COMMON.DERIV'
16 include 'COMMON.LOCAL'
17 include 'COMMON.INTERACT'
19 include 'COMMON.IOUNITS'
20 include 'COMMON.CONTROL'
22 include 'COMMON.TIME1'
25 double precision zapas(MAXRES6),muca_factor
26 logical lprn /.false./
27 common /cipiszcze/ itime
37 write (iout,*) "Potential forces backbone"
40 if (lprn) write (iout,'(i5,3e15.5,5x,3e15.5)')
41 & i,(-gcart(j,i),j=1,3)
44 zapas(ind)=-gcart(j,i)
47 if (lprn) write (iout,*) "Potential forces sidechain"
49 if (itype(i).ne.10 .and. itype(i).ne.21) then
50 if (lprn) write (iout,'(i5,3e15.5,5x,3e15.5)')
51 & i,(-gcart(j,i),j=1,3)
54 zapas(ind)=-gxcart(j,i)
59 call ginv_mult(zapas,d_a_work)
68 d_a(j,i)=d_a_work(ind)
72 if (itype(i).ne.10 .and. itype(i).ne.21) then
75 d_a(j,i+nres)=d_a_work(ind)
82 if(mucadyn.gt.0) call muca_update(potE)
83 factor=muca_factor(potE)*t_bath*Rb
85 cd print *,'lmuca ',factor,potE
87 d_a(j,0)=d_a(j,0)*factor
91 d_a(j,i)=d_a(j,i)*factor
96 d_a(j,i+nres)=d_a(j,i+nres)*factor
103 write(iout,*) 'acceleration 3D'
104 write (iout,'(i3,3f10.5,3x,3f10.5)') 0,(d_a(j,0),j=1,3)
106 write (iout,'(i3,3f10.5,3x,3f10.5)') i,(d_a(j,i),j=1,3)
109 write (iout,'(i3,3f10.5,3x,3f10.5)')
110 & i+nres,(d_a(j,i+nres),j=1,3)
114 time_lagrangian=time_lagrangian+MPI_Wtime()-time00
118 c------------------------------------------------------------------
119 subroutine setup_MD_matrices
120 implicit real*8 (a-h,o-z)
126 include 'COMMON.SETUP'
128 include 'COMMON.CHAIN'
129 include 'COMMON.DERIV'
131 include 'COMMON.LOCAL'
132 include 'COMMON.INTERACT'
135 include 'COMMON.LANGEVIN'
137 include 'COMMON.LANGEVIN.lang0'
139 include 'COMMON.IOUNITS'
140 include 'COMMON.TIME1'
142 logical lprn /.false./
144 double precision dtdi,massvec(maxres2),Gcopy(maxres2,maxres2),
145 & Ghalf(mmaxres2),sqreig(maxres2)
146 double precision work(8*maxres6)
147 integer iwork(maxres6)
148 common /przechowalnia/ Gcopy,Ghalf
150 c Set up the matrix of the (dC,dX)-->(C,X) transformation (A), the
151 c inertia matrix (Gmat) and the inverse of the inertia matrix (Ginv)
153 c Determine the number of degrees of freedom (dimen) and the number of
155 dimen=(nct-nnt+1)+nside
156 dimen1=(nct-nnt)+(nct-nnt+1)
159 if (nfgtasks.gt.1) then
161 call MPI_Bcast(5,1,MPI_INTEGER,king,FG_COMM,IERROR)
162 time_Bcast=time_Bcast+MPI_Wtime()-time00
163 call int_bounds(dimen,igmult_start,igmult_end)
164 igmult_start=igmult_start-1
165 call MPI_Allgather(3*igmult_start,1,MPI_INTEGER,
166 & ng_start(0),1,MPI_INTEGER,FG_COMM,IERROR)
167 my_ng_count=igmult_end-igmult_start
168 call MPI_Allgather(3*my_ng_count,1,MPI_INTEGER,ng_counts(0),1,
169 & MPI_INTEGER,FG_COMM,IERROR)
170 write (iout,*) 'Processor:',fg_rank,' CG group',kolor,
171 & ' absolute rank',myrank,' igmult_start',igmult_start,
172 & ' igmult_end',igmult_end,' count',my_ng_count
173 write (iout,*) "ng_start",(ng_start(i),i=0,nfgtasks-1)
174 write (iout,*) "ng_counts",(ng_counts(i),i=0,nfgtasks-1)
184 c write (iout,*) "dimen",dimen," dimen1",dimen1," dimen3",dimen3
185 write (iout,*) "The number of degrees of freedom ",dimen3
186 c Zeroing out A and fricmat
192 c Diagonal elements of the dC part of A and the respective friction coefficients
204 c Off-diagonal elements of the dC part of A
211 c Diagonal elements of the dX part of A and the respective friction coefficients
221 massvec(ii)=msc(iabs(iti))
222 if (iti.ne.10 .and. iti.ne.ntyp1) then
226 Gmat(ii1,ii1)=ISC(iabs(iti))
229 c Off-diagonal elements of the dX part of A
243 write (iout,*) "Vector massvec"
245 write (iout,*) i,massvec(i)
247 write (iout,'(//a)') "A"
248 call matout(dimen,dimen1,maxres2,maxres2,A)
251 c Calculate the G matrix (store in Gmat)
256 dtdi=dtdi+A(j,k)*A(j,i)*massvec(j)
258 Gmat(k,i)=Gmat(k,i)+dtdi
263 write (iout,'(//a)') "Gmat"
264 call matout(dimen,dimen,maxres2,maxres2,Gmat)
273 c Invert the G matrix
274 call MATINVERT(dimen,maxres2,Gcopy,Ginv,osob)
276 write (iout,'(//a)') "Ginv"
277 call matout(dimen,dimen,maxres2,maxres2,Ginv)
280 if (nfgtasks.gt.1) then
281 myginv_ng_count=maxres2*my_ng_count
282 call MPI_Allgather(maxres2*igmult_start,1,MPI_INTEGER,
283 & nginv_start(0),1,MPI_INTEGER,FG_COMM,IERROR)
284 call MPI_Allgather(myginv_ng_count,1,MPI_INTEGER,
285 & nginv_counts(0),1,MPI_INTEGER,FG_COMM,IERROR)
286 write (iout,*) "nginv_start",(nginv_start(i),i=0,nfgtasks-1)
287 write (iout,*) "nginv_counts",(nginv_counts(i),i=0,nfgtasks-1)
289 c call MPI_Scatterv(ginv(1,1),nginv_counts(0),
290 c & nginv_start(0),MPI_DOUBLE_PRECISION,ginv,
291 c & myginv_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
292 c call MPI_Barrier(FG_COMM,IERR)
294 call MPI_Scatterv(ginv(1,1),nginv_counts(0),
295 & nginv_start(0),MPI_DOUBLE_PRECISION,gcopy(1,1),
296 & myginv_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
298 time_scatter_ginv=time_scatter_ginv+MPI_Wtime()-time00
305 c write (iout,*) "Master's chunk of ginv"
306 c call MATOUT2(my_ng_count,dimen,maxres2,maxres2,ginv)
310 write (iout,*) "The G matrix is singular."
313 c Compute G**(-1/2) and G**(1/2)
321 call gldiag(maxres2,dimen,dimen,Ghalf,work,Geigen,Gvec,
325 & "Eigenvectors and eigenvalues of the G matrix"
326 call eigout(dimen,dimen,maxres2,maxres2,Gvec,Geigen)
329 sqreig(i)=dsqrt(Geigen(i))
337 Gsqrp(i,j)=Gsqrp(i,j)+Gvec(i,k)*Gvec(j,k)*sqreig(k)
338 Gsqrm(i,j)=Gsqrm(i,j)+Gvec(i,k)*Gvec(j,k)/sqreig(k)
339 Gcopy(i,j)=Gcopy(i,j)+Gvec(i,k)*Gvec(j,k)*Geigen(k)
344 write (iout,*) "Comparison of original and restored G"
347 write (iout,'(2i5,5f10.5)') i,j,Gmat(i,j),Gcopy(i,j),
348 & Gmat(i,j)-Gcopy(i,j),Gsqrp(i,j),Gsqrm(i,j)
354 c-------------------------------------------------------------------------------
355 SUBROUTINE EIGOUT(NC,NR,LM2,LM3,A,B)
356 implicit real*8 (a-h,o-z)
358 include 'COMMON.IOUNITS'
359 double precision A(LM2,LM3),B(LM2)
363 WRITE(IOUT,600) (I,I=KA,KB)
364 WRITE(IOUT,601) (B(I),I=KA,KB)
368 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
374 4 IF (KB.EQ.NC) RETURN
378 600 FORMAT (// 9H ROOT NO.,I4,9I11)
379 601 FORMAT (/5X,10(1PE11.4))
381 603 FORMAT (I5,10F11.5)
384 c-------------------------------------------------------------------------------
385 SUBROUTINE MATOUT(NC,NR,LM2,LM3,A)
386 implicit real*8 (a-h,o-z)
388 include 'COMMON.IOUNITS'
389 double precision A(LM2,LM3)
393 WRITE(IOUT,600) (I,I=KA,KB)
397 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
403 4 IF (KB.EQ.NC) RETURN
407 600 FORMAT (//5x,9I11)
409 603 FORMAT (I5,10F11.3)
412 c-------------------------------------------------------------------------------
413 SUBROUTINE MATOUT1(NC,NR,LM2,LM3,A)
414 implicit real*8 (a-h,o-z)
416 include 'COMMON.IOUNITS'
417 double precision A(LM2,LM3)
421 WRITE(IOUT,600) (I,I=KA,KB)
425 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
431 4 IF (KB.EQ.NC) RETURN
435 600 FORMAT (//5x,7(3I5,2x))
437 603 FORMAT (I5,7(3F5.1,2x))
440 c-------------------------------------------------------------------------------
441 SUBROUTINE MATOUT2(NC,NR,LM2,LM3,A)
442 implicit real*8 (a-h,o-z)
444 include 'COMMON.IOUNITS'
445 double precision A(LM2,LM3)
449 WRITE(IOUT,600) (I,I=KA,KB)
453 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
459 4 IF (KB.EQ.NC) RETURN
463 600 FORMAT (//5x,4(3I9,2x))
465 603 FORMAT (I5,4(3F9.3,2x))
468 c---------------------------------------------------------------------------
469 SUBROUTINE ginv_mult(z,d_a_tmp)
470 implicit real*8 (a-h,o-z)
476 include 'COMMON.SETUP'
477 include 'COMMON.TIME1'
479 double precision z(dimen3),d_a_tmp(dimen3),temp(maxres6),time00
480 &,time01,zcopy(dimen3)
482 if (nfgtasks.gt.1) then
483 if (fg_rank.eq.0) then
484 c The matching BROADCAST for fg processors is called in ERGASTULUM
486 call MPI_Bcast(4,1,MPI_INTEGER,king,FG_COMM,IERROR)
487 time_Bcast=time_Bcast+MPI_Wtime()-time00
488 c print *,"Processor",myrank," BROADCAST iorder in GINV_MULT"
490 c write (2,*) "time00",time00
491 c write (2,*) "Before Scatterv"
493 c write (2,*) "Whole z (for FG master)"
497 c call MPI_Barrier(FG_COMM,IERROR)
499 call MPI_Scatterv(z,ng_counts(0),ng_start(0),
500 & MPI_DOUBLE_PRECISION,
501 & zcopy,3*my_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
505 c write (2,*) "My chunk of z"
506 c do i=1,3*my_ng_count
509 c write (2,*) "After SCATTERV"
511 c write (2,*) "MPI_Wtime",MPI_Wtime()
512 time_scatter=time_scatter+MPI_Wtime()-time00
514 time_scatter_ginvmult=time_scatter_ginvmult+MPI_Wtime()-time00
516 c write (2,*) "time_scatter",time_scatter
517 c write (2,*) "dimen",dimen," dimen3",dimen3," my_ng_count",
526 c write (2,*) "k,i,j,ind",k,i,j,ind,(j-1)*3+k+1,
527 c & Ginv(i,j),z((j-1)*3+k+1),
528 c & Ginv(i,j)*z((j-1)*3+k+1)
529 c temp(ind)=temp(ind)+Ginv(i,j)*z((j-1)*3+k+1)
530 temp(ind)=temp(ind)+Ginv(j,i)*z((j-1)*3+k+1)
534 time_ginvmult=time_ginvmult+MPI_Wtime()-time01
535 c write (2,*) "Before REDUCE"
537 c write (2,*) "z before reduce"
539 c write (2,*) i,temp(i)
542 call MPI_Reduce(temp(1),d_a_tmp(1),dimen3,MPI_DOUBLE_PRECISION,
543 & MPI_SUM,king,FG_COMM,IERR)
544 time_reduce=time_reduce+MPI_Wtime()-time00
545 c write (2,*) "After REDUCE"
557 c write (2,*) "k,i,j,ind",k,i,j,ind,(j-1)*3+k+1
559 c & Ginv(i,j),z((j-1)*3+k+1),
560 c & Ginv(i,j)*z((j-1)*3+k+1)
561 d_a_tmp(ind)=d_a_tmp(ind)
562 & +Ginv(j,i)*z((j-1)*3+k+1)
563 c d_a_tmp(ind)=d_a_tmp(ind)
564 c & +Ginv(i,j)*z((j-1)*3+k+1)
569 time_ginvmult=time_ginvmult+MPI_Wtime()-time01
576 c---------------------------------------------------------------------------
578 SUBROUTINE ginv_mult_test(z,d_a_tmp)
581 c include 'COMMON.MD'
582 double precision z(dimen),d_a_tmp(dimen)
583 double precision ztmp(dimen/3),dtmp(dimen/3)
588 c d_a_tmp(i)=d_a_tmp(i)+Ginv(i,j)*z(j)
597 ztmp(j)=z((j-1)*3+k+1)
600 call alignx(16,ztmp(1))
601 call alignx(16,dtmp(1))
602 call alignx(16,Ginv(1,1))
607 dtmp(i)=dtmp(i)+Ginv(i,j)*ztmp(j)
618 c---------------------------------------------------------------------------
619 SUBROUTINE fricmat_mult(z,d_a_tmp)
626 include 'COMMON.IOUNITS'
627 include 'COMMON.SETUP'
628 include 'COMMON.TIME1'
630 include 'COMMON.LANGEVIN'
632 include 'COMMON.LANGEVIN.lang0'
634 double precision z(dimen3),d_a_tmp(dimen3),temp(maxres6),time00
635 &,time01,zcopy(dimen3)
637 if (nfgtasks.gt.1) then
638 if (fg_rank.eq.0) then
639 c The matching BROADCAST for fg processors is called in ERGASTULUM
641 call MPI_Bcast(9,1,MPI_INTEGER,king,FG_COMM,IERROR)
642 time_Bcast=time_Bcast+MPI_Wtime()-time00
643 c print *,"Processor",myrank," BROADCAST iorder in FRICMAT_MULT"
645 c call MPI_Barrier(FG_COMM,IERROR)
647 call MPI_Scatterv(z,ng_counts(0),ng_start(0),
648 & MPI_DOUBLE_PRECISION,
649 & zcopy,3*my_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
654 c write (2,*) "My chunk of z"
655 c do i=1,3*my_ng_count
658 time_scatter=time_scatter+MPI_Wtime()-time00
660 time_scatter_fmatmult=time_scatter_fmatmult+MPI_Wtime()-time00
668 temp(ind)=temp(ind)-fricmat(j,i)*z((j-1)*3+k+1)
672 time_fricmatmult=time_fricmatmult+MPI_Wtime()-time01
673 c write (2,*) "Before REDUCE"
674 c write (2,*) "d_a_tmp before reduce"
676 c write (2,*) i,temp(i)
680 call MPI_Reduce(temp(1),d_a_tmp(1),dimen3,MPI_DOUBLE_PRECISION,
681 & MPI_SUM,king,FG_COMM,IERR)
682 time_reduce=time_reduce+MPI_Wtime()-time00
683 c write (2,*) "After REDUCE"
695 d_a_tmp(ind)=d_a_tmp(ind)
696 & -fricmat(j,i)*z((j-1)*3+k+1)
701 time_fricmatmult=time_fricmatmult+MPI_Wtime()-time01
706 c write (iout,*) "Vector d_a"
708 c write (2,*) i,d_a_tmp(i)