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.ntyp1) 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.ntyp1) 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'
127 include 'COMMON.CONTROL'
129 include 'COMMON.CHAIN'
130 include 'COMMON.DERIV'
132 include 'COMMON.LOCAL'
133 include 'COMMON.INTERACT'
136 include 'COMMON.LANGEVIN'
138 include 'COMMON.LANGEVIN.lang0'
140 include 'COMMON.IOUNITS'
141 include 'COMMON.TIME1'
143 logical lprn /.false./
145 double precision dtdi,massvec(maxres2),Gcopy(maxres2,maxres2),
146 & Ghalf(mmaxres2),sqreig(maxres2)
147 double precision work(8*maxres6)
148 integer iwork(maxres6)
149 common /przechowalnia/ Gcopy,Ghalf
151 c Set up the matrix of the (dC,dX)-->(C,X) transformation (A), the
152 c inertia matrix (Gmat) and the inverse of the inertia matrix (Ginv)
154 c Determine the number of degrees of freedom (dimen) and the number of
156 dimen=(nct-nnt+1)+nside
157 dimen1=(nct-nnt)+(nct-nnt+1)
160 if (nfgtasks.gt.1) then
162 call MPI_Bcast(5,1,MPI_INTEGER,king,FG_COMM,IERROR)
163 time_Bcast=time_Bcast+MPI_Wtime()-time00
164 call int_bounds(dimen,igmult_start,igmult_end)
165 igmult_start=igmult_start-1
166 call MPI_Allgather(3*igmult_start,1,MPI_INTEGER,
167 & ng_start(0),1,MPI_INTEGER,FG_COMM,IERROR)
168 my_ng_count=igmult_end-igmult_start
169 call MPI_Allgather(3*my_ng_count,1,MPI_INTEGER,ng_counts(0),1,
170 & MPI_INTEGER,FG_COMM,IERROR)
171 if (me.eq.king .or. .not. out1file) then
172 write (iout,*) 'Processor:',fg_rank,' CG group',kolor,
173 & ' absolute rank',myrank,' igmult_start',igmult_start,
174 & ' igmult_end',igmult_end,' count',my_ng_count
175 write (iout,*) "ng_start",(ng_start(i),i=0,nfgtasks-1)
176 write (iout,*) "ng_counts",(ng_counts(i),i=0,nfgtasks-1)
187 c write (iout,*) "dimen",dimen," dimen1",dimen1," dimen3",dimen3
188 c Zeroing out A and fricmat
194 c Diagonal elements of the dC part of A and the respective friction coefficients
206 c Off-diagonal elements of the dC part of A
213 c Diagonal elements of the dX part of A and the respective friction coefficients
223 massvec(ii)=msc(iabs(iti))
224 if (iti.ne.10 .and. iti.ne.ntyp1) then
228 Gmat(ii1,ii1)=ISC(iabs(iti))
231 c Off-diagonal elements of the dX part of A
245 write (iout,*) "Vector massvec"
247 write (iout,*) i,massvec(i)
249 write (iout,'(//a)') "A"
250 call matout(dimen,dimen1,maxres2,maxres2,A)
253 c Calculate the G matrix (store in Gmat)
258 dtdi=dtdi+A(j,k)*A(j,i)*massvec(j)
260 Gmat(k,i)=Gmat(k,i)+dtdi
265 write (iout,'(//a)') "Gmat"
266 call matout(dimen,dimen,maxres2,maxres2,Gmat)
275 c Invert the G matrix
276 call MATINVERT(dimen,maxres2,Gcopy,Ginv,osob)
278 write (iout,'(//a)') "Ginv"
279 call matout(dimen,dimen,maxres2,maxres2,Ginv)
282 if (nfgtasks.gt.1) then
283 myginv_ng_count=maxres2*my_ng_count
284 call MPI_Allgather(maxres2*igmult_start,1,MPI_INTEGER,
285 & nginv_start(0),1,MPI_INTEGER,FG_COMM,IERROR)
286 call MPI_Allgather(myginv_ng_count,1,MPI_INTEGER,
287 & nginv_counts(0),1,MPI_INTEGER,FG_COMM,IERROR)
288 if (lprn .and. (me.eq.king .or. .not. out1file) ) then
289 write (iout,*) "nginv_start",(nginv_start(i),i=0,nfgtasks-1)
290 write (iout,*) "nginv_counts",(nginv_counts(i),i=0,nfgtasks-1)
293 c call MPI_Scatterv(ginv(1,1),nginv_counts(0),
294 c & nginv_start(0),MPI_DOUBLE_PRECISION,ginv,
295 c & myginv_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
296 c call MPI_Barrier(FG_COMM,IERR)
298 call MPI_Scatterv(ginv(1,1),nginv_counts(0),
299 & nginv_start(0),MPI_DOUBLE_PRECISION,gcopy(1,1),
300 & myginv_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
302 time_scatter_ginv=time_scatter_ginv+MPI_Wtime()-time00
309 c write (iout,*) "Master's chunk of ginv"
310 c call MATOUT2(my_ng_count,dimen,maxres2,maxres2,ginv)
314 write (iout,*) "The G matrix is singular."
317 c Compute G**(-1/2) and G**(1/2)
325 call gldiag(maxres2,dimen,dimen,Ghalf,work,Geigen,Gvec,
329 & "Eigenvectors and eigenvalues of the G matrix"
330 call eigout(dimen,dimen,maxres2,maxres2,Gvec,Geigen)
333 sqreig(i)=dsqrt(Geigen(i))
341 Gsqrp(i,j)=Gsqrp(i,j)+Gvec(i,k)*Gvec(j,k)*sqreig(k)
342 Gsqrm(i,j)=Gsqrm(i,j)+Gvec(i,k)*Gvec(j,k)/sqreig(k)
343 Gcopy(i,j)=Gcopy(i,j)+Gvec(i,k)*Gvec(j,k)*Geigen(k)
348 write (iout,*) "Comparison of original and restored G"
351 write (iout,'(2i5,5f10.5)') i,j,Gmat(i,j),Gcopy(i,j),
352 & Gmat(i,j)-Gcopy(i,j),Gsqrp(i,j),Gsqrm(i,j)
358 c-------------------------------------------------------------------------------
359 SUBROUTINE EIGOUT(NC,NR,LM2,LM3,A,B)
360 implicit real*8 (a-h,o-z)
362 include 'COMMON.IOUNITS'
363 double precision A(LM2,LM3),B(LM2)
367 WRITE(IOUT,600) (I,I=KA,KB)
368 WRITE(IOUT,601) (B(I),I=KA,KB)
372 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
378 4 IF (KB.EQ.NC) RETURN
382 600 FORMAT (// 9H ROOT NO.,I4,9I11)
383 601 FORMAT (/5X,10(1PE11.4))
385 603 FORMAT (I5,10F11.5)
388 c-------------------------------------------------------------------------------
389 SUBROUTINE MATOUT(NC,NR,LM2,LM3,A)
390 implicit real*8 (a-h,o-z)
392 include 'COMMON.IOUNITS'
393 double precision A(LM2,LM3)
397 WRITE(IOUT,600) (I,I=KA,KB)
401 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
407 4 IF (KB.EQ.NC) RETURN
411 600 FORMAT (//5x,9I11)
413 603 FORMAT (I5,10F11.3)
416 c-------------------------------------------------------------------------------
417 SUBROUTINE MATOUT1(NC,NR,LM2,LM3,A)
418 implicit real*8 (a-h,o-z)
420 include 'COMMON.IOUNITS'
421 double precision A(LM2,LM3)
425 WRITE(IOUT,600) (I,I=KA,KB)
429 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
435 4 IF (KB.EQ.NC) RETURN
439 600 FORMAT (//5x,7(3I5,2x))
441 603 FORMAT (I5,7(3F5.1,2x))
444 c-------------------------------------------------------------------------------
445 SUBROUTINE MATOUT2(NC,NR,LM2,LM3,A)
446 implicit real*8 (a-h,o-z)
448 include 'COMMON.IOUNITS'
449 double precision A(LM2,LM3)
453 WRITE(IOUT,600) (I,I=KA,KB)
457 WRITE(IOUT,603) I,(A(I,J),J=KA,KB)
463 4 IF (KB.EQ.NC) RETURN
467 600 FORMAT (//5x,4(3I9,2x))
469 603 FORMAT (I5,4(3F9.3,2x))
472 c---------------------------------------------------------------------------
473 SUBROUTINE ginv_mult(z,d_a_tmp)
474 implicit real*8 (a-h,o-z)
480 include 'COMMON.SETUP'
481 include 'COMMON.TIME1'
483 double precision z(dimen3),d_a_tmp(dimen3),temp(maxres6),time00
484 &,time01,zcopy(dimen3)
486 if (nfgtasks.gt.1) then
487 if (fg_rank.eq.0) then
488 c The matching BROADCAST for fg processors is called in ERGASTULUM
490 call MPI_Bcast(4,1,MPI_INTEGER,king,FG_COMM,IERROR)
491 time_Bcast=time_Bcast+MPI_Wtime()-time00
492 c print *,"Processor",myrank," BROADCAST iorder in GINV_MULT"
494 c write (2,*) "time00",time00
495 c write (2,*) "Before Scatterv"
497 c write (2,*) "Whole z (for FG master)"
501 c call MPI_Barrier(FG_COMM,IERROR)
503 call MPI_Scatterv(z,ng_counts(0),ng_start(0),
504 & MPI_DOUBLE_PRECISION,
505 & zcopy,3*my_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
509 c write (2,*) "My chunk of z"
510 c do i=1,3*my_ng_count
513 c write (2,*) "After SCATTERV"
515 c write (2,*) "MPI_Wtime",MPI_Wtime()
516 time_scatter=time_scatter+MPI_Wtime()-time00
518 time_scatter_ginvmult=time_scatter_ginvmult+MPI_Wtime()-time00
520 c write (2,*) "time_scatter",time_scatter
521 c write (2,*) "dimen",dimen," dimen3",dimen3," my_ng_count",
530 c write (2,*) "k,i,j,ind",k,i,j,ind,(j-1)*3+k+1,
531 c & Ginv(i,j),z((j-1)*3+k+1),
532 c & Ginv(i,j)*z((j-1)*3+k+1)
533 c temp(ind)=temp(ind)+Ginv(i,j)*z((j-1)*3+k+1)
534 temp(ind)=temp(ind)+Ginv(j,i)*z((j-1)*3+k+1)
538 time_ginvmult=time_ginvmult+MPI_Wtime()-time01
539 c write (2,*) "Before REDUCE"
541 c write (2,*) "z before reduce"
543 c write (2,*) i,temp(i)
546 call MPI_Reduce(temp(1),d_a_tmp(1),dimen3,MPI_DOUBLE_PRECISION,
547 & MPI_SUM,king,FG_COMM,IERR)
548 time_reduce=time_reduce+MPI_Wtime()-time00
549 c write (2,*) "After REDUCE"
561 c write (2,*) "k,i,j,ind",k,i,j,ind,(j-1)*3+k+1
563 c & Ginv(i,j),z((j-1)*3+k+1),
564 c & Ginv(i,j)*z((j-1)*3+k+1)
565 d_a_tmp(ind)=d_a_tmp(ind)
566 & +Ginv(j,i)*z((j-1)*3+k+1)
567 c d_a_tmp(ind)=d_a_tmp(ind)
568 c & +Ginv(i,j)*z((j-1)*3+k+1)
573 time_ginvmult=time_ginvmult+MPI_Wtime()-time01
580 c---------------------------------------------------------------------------
582 SUBROUTINE ginv_mult_test(z,d_a_tmp)
585 c include 'COMMON.MD'
586 double precision z(dimen),d_a_tmp(dimen)
587 double precision ztmp(dimen/3),dtmp(dimen/3)
592 c d_a_tmp(i)=d_a_tmp(i)+Ginv(i,j)*z(j)
601 ztmp(j)=z((j-1)*3+k+1)
604 call alignx(16,ztmp(1))
605 call alignx(16,dtmp(1))
606 call alignx(16,Ginv(1,1))
611 dtmp(i)=dtmp(i)+Ginv(i,j)*ztmp(j)
622 c---------------------------------------------------------------------------
623 SUBROUTINE fricmat_mult(z,d_a_tmp)
630 include 'COMMON.IOUNITS'
631 include 'COMMON.SETUP'
632 include 'COMMON.TIME1'
634 include 'COMMON.LANGEVIN'
636 include 'COMMON.LANGEVIN.lang0'
638 double precision z(dimen3),d_a_tmp(dimen3),temp(maxres6),time00
639 &,time01,zcopy(dimen3)
641 if (nfgtasks.gt.1) then
642 if (fg_rank.eq.0) then
643 c The matching BROADCAST for fg processors is called in ERGASTULUM
645 call MPI_Bcast(9,1,MPI_INTEGER,king,FG_COMM,IERROR)
646 time_Bcast=time_Bcast+MPI_Wtime()-time00
647 c print *,"Processor",myrank," BROADCAST iorder in FRICMAT_MULT"
649 c call MPI_Barrier(FG_COMM,IERROR)
651 call MPI_Scatterv(z,ng_counts(0),ng_start(0),
652 & MPI_DOUBLE_PRECISION,
653 & zcopy,3*my_ng_count,MPI_DOUBLE_PRECISION,king,FG_COMM,IERR)
658 c write (2,*) "My chunk of z"
659 c do i=1,3*my_ng_count
662 time_scatter=time_scatter+MPI_Wtime()-time00
664 time_scatter_fmatmult=time_scatter_fmatmult+MPI_Wtime()-time00
672 temp(ind)=temp(ind)-fricmat(j,i)*z((j-1)*3+k+1)
676 time_fricmatmult=time_fricmatmult+MPI_Wtime()-time01
677 c write (2,*) "Before REDUCE"
678 c write (2,*) "d_a_tmp before reduce"
680 c write (2,*) i,temp(i)
684 call MPI_Reduce(temp(1),d_a_tmp(1),dimen3,MPI_DOUBLE_PRECISION,
685 & MPI_SUM,king,FG_COMM,IERR)
686 time_reduce=time_reduce+MPI_Wtime()-time00
687 c write (2,*) "After REDUCE"
699 d_a_tmp(ind)=d_a_tmp(ind)
700 & -fricmat(j,i)*z((j-1)*3+k+1)
705 time_fricmatmult=time_fricmatmult+MPI_Wtime()-time01
710 c write (iout,*) "Vector d_a"
712 c write (2,*) i,d_a_tmp(i)