Merge branch 'devel' into UCGM
[unres4.git] / source / unres / control.F90
1       module control
2 !-----------------------------------------------------------------------------
3       use io_units
4       use names
5       use MPI_data
6       use geometry_data
7       use energy_data
8       use control_data
9       use minim_data
10       use geometry, only:int_bounds
11 #ifndef CLUSTER
12       use csa_data
13 #ifdef WHAM_RUN
14       use wham_data
15 #endif
16 #endif
17       implicit none
18 !-----------------------------------------------------------------------------
19 ! commom.control
20 !      common /cntrl/
21 !      integer :: modecalc,iscode,indpdb,indback,indphi,iranconf,&
22 !       icheckgrad,iprint,i2ndstr,mucadyn,constr_dist,symetr
23 !      logical :: minim,refstr,pdbref,outpdb,outmol2,overlapsc,&
24 !       energy_dec,sideadd,lsecondary,read_cart,unres_pdb,&
25 !       vdisulf,searchsc,lmuca,dccart,extconf,out1file,&
26 !       gnorm_check,gradout,split_ene
27 !... minim = .true. means DO minimization.
28 !... energy_dec = .true. means print energy decomposition matrix
29 !-----------------------------------------------------------------------------
30 ! common.time1
31 !     FOUND_NAN - set by calcf to stop sumsl via stopx
32 !      COMMON/TIME1/
33       real(kind=8) :: STIME,BATIME,PREVTIM,RSTIME
34 !el      real(kind=8) :: TIMLIM,SAFETY
35 !el      real(kind=8) :: WALLTIME
36 !      COMMON/STOPTIM/
37       integer :: ISTOP
38 !      common /sumsl_flag/
39       logical :: FOUND_NAN
40 !      common /timing/
41       real(kind=8) :: t_init
42 !       time_bcast,time_reduce,time_gather,&
43 !       time_sendrecv,time_barrier_e,time_barrier_g,time_scatter,&
44        !t_eelecij,
45 !       time_allreduce,&
46 !       time_lagrangian,time_cartgrad,&
47 !       time_sumgradient,time_intcartderiv,time_inttocart,time_intfcart,&
48 !       time_mat,time_fricmatmult,&
49 !       time_scatter_fmat,time_scatter_ginv,&
50 !       time_scatter_fmatmult,time_scatter_ginvmult,&
51 !       t_eshort,t_elong,t_etotal
52 !-----------------------------------------------------------------------------
53 ! initialize_p.F
54 !-----------------------------------------------------------------------------
55 !      block data
56 !      integer,parameter :: MaxMoveType = 4
57 !      character(len=14),dimension(-1:MaxMoveType+1) :: MovTypID=(/'pool','chain regrow',&
58 !      character :: MovTypID(-1:MaxMoveType+1)=(/'pool','chain regrow',&
59 !       'multi-bond','phi','theta','side chain','total'/)
60 ! Conversion from poises to molecular unit and the gas constant
61 !el      real(kind=8) :: cPoise=2.9361d0, Rb=0.001986d0
62 !-----------------------------------------------------------------------------
63 !      common /przechowalnia/ subroutines: init_int_table,add_int,add_int_from
64       integer,dimension(:),allocatable :: iturn3_start_all,&
65         iturn3_end_all,iturn4_start_all,iturn4_end_all,iatel_s_all,&
66         iatel_e_all !(0:max_fg_procs)
67       integer,dimension(:,:),allocatable :: ielstart_all,&
68         ielend_all !(maxres,0:max_fg_procs-1)
69
70 !      common /przechowalnia/ subroutine: init_int_table
71       integer,dimension(:),allocatable :: ntask_cont_from_all,&
72         ntask_cont_to_all !(0:max_fg_procs-1)
73       integer,dimension(:,:),allocatable :: itask_cont_from_all,&
74         itask_cont_to_all !(0:max_fg_procs-1,0:max_fg_procs-1)
75 !-----------------------------------------------------------------------------
76 !
77 !
78 !-----------------------------------------------------------------------------
79       contains
80 !-----------------------------------------------------------------------------
81 ! initialize_p.F
82 !-----------------------------------------------------------------------------
83       subroutine initialize
84 !
85 ! Define constants and zero out tables.
86 !
87       use comm_iofile
88       use comm_machsw
89       use MCM_data, only: MovTypID
90 !      implicit real*8 (a-h,o-z)
91 !      include 'DIMENSIONS'
92 #ifdef MPI
93       include 'mpif.h'
94 #endif
95 #ifndef ISNAN
96       external proc_proc
97 #ifdef WINPGI
98 !MS$ATTRIBUTES C ::  proc_proc
99 #endif
100 #endif
101 !      include 'COMMON.IOUNITS'
102 !      include 'COMMON.CHAIN'
103 !      include 'COMMON.INTERACT'
104 !      include 'COMMON.GEO'
105 !      include 'COMMON.LOCAL'
106 !      include 'COMMON.TORSION'
107 !      include 'COMMON.FFIELD'
108 !      include 'COMMON.SBRIDGE'
109 !      include 'COMMON.MCM'
110 !      include 'COMMON.MINIM' 
111 !      include 'COMMON.DERIV'
112 !      include 'COMMON.SPLITELE'
113 !      implicit none
114 ! Common blocks from the diagonalization routines
115 !el      integer :: IR,IW,IP,IJK,IPK,IDAF,NAV,IODA(400)
116 !el      integer :: KDIAG,ICORFL,IXDR
117 !el      COMMON /IOFILE/ IR,IW,IP,IJK,IPK,IDAF,NAV,IODA
118 !el      COMMON /MACHSW/ KDIAG,ICORFL,IXDR
119       logical :: mask_r
120 !      real*8 text1 /'initial_i'/
121       real(kind=4) :: rr
122
123 !local variables el
124       integer :: i,j,k,l,ichir1,ichir2,iblock,m,maxit
125
126 #if .not. defined(WHAM_RUN) && .not. defined(CLUSTER)
127       mask_r=.false.
128 #ifndef ISNAN
129 ! NaNQ initialization
130       i=-1
131       rr=dacos(100.0d0)
132 #ifdef WINPGI
133       idumm=proc_proc(rr,i)
134 #elif defined(WHAM_RUN)
135       call proc_proc(rr,i)
136 #endif
137 #endif
138
139       kdiag=0
140       icorfl=0
141       iw=2
142       
143       allocate(MovTypID(-1:MaxMoveType+1))
144       MovTypID=(/'pool          ','chain regrow  ',&
145        'multi-bond    ','phi           ','theta         ',&
146        'side chain    ','total         '/)
147 #endif
148 !
149 ! The following is just to define auxiliary variables used in angle conversion
150 !
151       pi=4.0D0*datan(1.0D0)
152       dwapi=2.0D0*pi
153       dwapi3=dwapi/3.0D0
154       pipol=0.5D0*pi
155       deg2rad=pi/180.0D0
156       rad2deg=1.0D0/deg2rad
157       angmin=10.0D0*deg2rad
158 !el#ifdef CLUSTER
159 !el      Rgas = 1.987D-3
160 !el#endif
161 !
162 ! Define I/O units.
163 !
164       inp=    1
165       iout=   2
166       ipdbin= 3
167       ipdb=   7
168 #ifdef CLUSTER
169       imol2= 18
170       jplot= 19
171 !el      jstatin=10
172       imol2=  4
173       jrms=30
174 #else
175       icart = 30
176       imol2=  4
177       ithep_pdb=51
178       irotam_pdb=52
179       irest1=55
180       irest2=56
181       iifrag=57
182       ientin=18
183       ientout=19
184 !rc for write_rmsbank1  
185       izs1=21
186 !dr  include secondary structure prediction bias
187       isecpred=27
188 #endif
189       igeom=  8
190       intin=  9
191       ithep= 11
192       irotam=12
193       itorp= 13
194       itordp= 23
195       ielep= 14
196       isidep=15
197 #if defined(WHAM_RUN) || defined(CLUSTER)
198       isidep1=22 !wham
199 #else
200 !
201 ! CSA I/O units (separated from others especially for Jooyoung)
202 !
203       icsa_rbank=30
204       icsa_seed=31
205       icsa_history=32
206       icsa_bank=33
207       icsa_bank1=34
208       icsa_alpha=35
209       icsa_alpha1=36
210       icsa_bankt=37
211       icsa_int=39
212       icsa_bank_reminimized=38
213       icsa_native_int=41
214       icsa_in=40
215 !rc for ifc error 118
216       icsa_pdb=42
217 #endif
218       iscpp=25
219       icbase=16
220       ifourier=20
221       istat= 17
222       ibond = 28
223       isccor = 29
224 #ifdef WHAM_RUN
225 !
226 ! WHAM files
227 !
228       ihist=30
229       iweight=31
230       izsc=32
231 #endif
232       iliptranpar=60
233       itube=61
234 #if defined(WHAM_RUN) || defined(CLUSTER)
235 !
236 ! setting the mpi variables for WHAM
237 !
238       fgprocs=1
239       nfgtasks=1
240       nfgtasks1=1
241 #endif
242 !
243 ! Set default weights of the energy terms.
244 !
245       wsc=1.0D0 ! in wham:  wlong=1.0D0
246       welec=1.0D0
247       wtor =1.0D0
248       wang =1.0D0
249       wscloc=1.0D0
250       wstrain=1.0D0
251 !
252 ! Zero out tables.
253 !
254 !      print '(a,$)','Inside initialize'
255 !      call memmon_print_usage()
256       
257 !      do i=1,maxres2
258 !       do j=1,3
259 !         c(j,i)=0.0D0
260 !         dc(j,i)=0.0D0
261 !       enddo
262 !      enddo
263 !      do i=1,maxres
264 !       do j=1,3
265 !         xloc(j,i)=0.0D0
266 !        enddo
267 !      enddo
268 !      do i=1,ntyp
269 !       do j=1,ntyp
270 !         aa(i,j)=0.0D0
271 !         bb(i,j)=0.0D0
272 !         augm(i,j)=0.0D0
273 !         sigma(i,j)=0.0D0
274 !         r0(i,j)=0.0D0
275 !         chi(i,j)=0.0D0
276 !        enddo
277 !       do j=1,2
278 !         bad(i,j)=0.0D0
279 !        enddo
280 !       chip(i)=0.0D0
281 !       alp(i)=0.0D0
282 !       sigma0(i)=0.0D0
283 !       sigii(i)=0.0D0
284 !       rr0(i)=0.0D0
285 !       a0thet(i)=0.0D0
286 !       do j=1,2
287 !         do ichir1=-1,1
288 !          do ichir2=-1,1
289 !          athet(j,i,ichir1,ichir2)=0.0D0
290 !          bthet(j,i,ichir1,ichir2)=0.0D0
291 !          enddo
292 !         enddo
293 !        enddo
294 !        do j=0,3
295 !         polthet(j,i)=0.0D0
296 !        enddo
297 !       do j=1,3
298 !         gthet(j,i)=0.0D0
299 !        enddo
300 !       theta0(i)=0.0D0
301 !       sig0(i)=0.0D0
302 !       sigc0(i)=0.0D0
303 !       do j=1,maxlob
304 !         bsc(j,i)=0.0D0
305 !         do k=1,3
306 !           censc(k,j,i)=0.0D0
307 !          enddo
308 !          do k=1,3
309 !           do l=1,3
310 !             gaussc(l,k,j,i)=0.0D0
311 !            enddo
312 !          enddo
313 !         nlob(i)=0
314 !        enddo
315 !      enddo
316 !      nlob(ntyp1)=0
317 !      dsc(ntyp1)=0.0D0
318 !      do i=-maxtor,maxtor
319 !        itortyp(i)=0
320 !c      write (iout,*) "TU DOCHODZE",i,itortyp(i)
321 !       do iblock=1,2
322 !        do j=-maxtor,maxtor
323 !          do k=1,maxterm
324 !            v1(k,j,i,iblock)=0.0D0
325 !            v2(k,j,i,iblock)=0.0D0
326 !          enddo
327 !        enddo
328 !        enddo
329 !      enddo
330 !      do iblock=1,2
331 !       do i=-maxtor,maxtor
332 !        do j=-maxtor,maxtor
333 !         do k=-maxtor,maxtor
334 !          do l=1,maxtermd_1
335 !            v1c(1,l,i,j,k,iblock)=0.0D0
336 !            v1s(1,l,i,j,k,iblock)=0.0D0
337 !            v1c(2,l,i,j,k,iblock)=0.0D0
338 !            v1s(2,l,i,j,k,iblock)=0.0D0
339 !          enddo !l
340 !          do l=1,maxtermd_2
341 !           do m=1,maxtermd_2
342 !            v2c(m,l,i,j,k,iblock)=0.0D0
343 !            v2s(m,l,i,j,k,iblock)=0.0D0
344 !           enddo !m
345 !          enddo !l
346 !        enddo !k
347 !       enddo !j
348 !      enddo !i
349 !      enddo !iblock
350
351 !      do i=1,maxres
352 !       itype(i,1)=0
353 !       itel(i)=0
354 !      enddo
355 ! Initialize the bridge arrays
356       ns=0
357       nss=0 
358       nhpb=0
359 !      do i=1,maxss
360 !       iss(i)=0
361 !      enddo
362 !      do i=1,maxdim
363 !       dhpb(i)=0.0D0
364 !      enddo
365 !      do i=1,maxres
366 !       ihpb(i)=0
367 !       jhpb(i)=0
368 !      enddo
369 !
370 ! Initialize timing.
371 !
372       call set_timers
373 !
374 ! Initialize variables used in minimization.
375 !   
376 !c     maxfun=5000
377 !c     maxit=2000
378       maxfun=500
379       maxit=200
380       tolf=1.0D-2
381       rtolf=5.0D-4
382
383 ! Initialize the variables responsible for the mode of gradient storage.
384 !
385       nfl=0
386       icg=1
387       
388 #ifdef WHAM_RUN
389       allocate(iww(max_eneW))
390       do i=1,14
391         do j=1,14
392           if (print_order(i).eq.j) then
393             iww(print_order(i))=j
394             goto 1121
395           endif
396         enddo
397 1121    continue
398       enddo
399 #endif
400  
401 #if defined(WHAM_RUN) || defined(CLUSTER)
402       ndih_constr=0
403
404 !      allocate(ww0(max_eneW))
405 !      ww0 = reshape((/1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,&
406 !          1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,0.4d0,1.0d0,&
407 !          1.0d0,0.0d0,0.0/), shape(ww0))
408 !
409       calc_grad=.false.
410 ! Set timers and counters for the respective routines
411       t_func = 0.0d0
412       t_grad = 0.0d0
413       t_fhel = 0.0d0
414       t_fbet = 0.0d0
415       t_ghel = 0.0d0
416       t_gbet = 0.0d0
417       t_viol = 0.0d0
418       t_gviol = 0.0d0
419       n_func = 0
420       n_grad = 0
421       n_fhel = 0
422       n_fbet = 0
423       n_ghel = 0
424       n_gbet = 0
425       n_viol = 0
426       n_gviol = 0
427       n_map = 0
428 #endif
429 !
430 ! Initialize constants used to split the energy into long- and short-range
431 ! components
432 !
433       r_cut=2.0d0
434       rlamb=0.3d0
435 #ifndef SPLITELE
436       nprint_ene=nprint_ene-1
437 #endif
438       return
439       end subroutine initialize
440 !-----------------------------------------------------------------------------
441       subroutine init_int_table
442
443       use geometry, only:int_bounds1
444 !el      use MPI_data
445 !el      implicit none
446 !      implicit real*8 (a-h,o-z)
447 !      include 'DIMENSIONS'
448 #ifdef MPI
449       include 'mpif.h'
450       integer,dimension(15) :: blocklengths,displs
451 #endif
452 !      include 'COMMON.CONTROL'
453 !      include 'COMMON.SETUP'
454 !      include 'COMMON.CHAIN'
455 !      include 'COMMON.INTERACT'
456 !      include 'COMMON.LOCAL'
457 !      include 'COMMON.SBRIDGE'
458 !      include 'COMMON.TORCNSTR'
459 !      include 'COMMON.IOUNITS'
460 !      include 'COMMON.DERIV'
461 !      include 'COMMON.CONTACTS'
462 !el      integer,dimension(0:nfgtasks) :: iturn3_start_all,iturn3_end_all,&
463 !el        iturn4_start_all,iturn4_end_all,iatel_s_all,iatel_e_all  !(0:max_fg_procs)
464 !el      integer,dimension(nres,0:nfgtasks) :: ielstart_all,&
465 !el        ielend_all !(maxres,0:max_fg_procs-1)
466 !el      integer,dimension(0:nfgtasks-1) :: ntask_cont_from_all,&
467 !el        ntask_cont_to_all !(0:max_fg_procs-1),
468 !el      integer,dimension(0:nfgtasks-1,0:nfgtasks-1) :: itask_cont_from_all,&
469 !el        itask_cont_to_all !(0:max_fg_procs-1,0:max_fg_procs-1)
470
471 !el      common /przechowalnia/ iturn3_start_all,iturn3_end_all,&
472 !el        iturn4_start_all,iturn4_end_all,iatel_s_all,iatel_e_all,&
473 !el        ielstart_all,ielend_all,ntask_cont_from_all,itask_cont_from_all,&
474 !el        ntask_cont_to_all,itask_cont_to_all
475
476       integer :: FG_GROUP,CONT_FROM_GROUP,CONT_TO_GROUP
477       logical :: scheck,lprint,flag
478
479 !el local variables
480       integer :: ind_scint=0,ind_scint_old,ii,jj,i,j,iint
481
482 #ifdef MPI
483       integer :: my_sc_int(0:nfgtasks-1),my_ele_int(0:nfgtasks-1)
484       integer :: my_sc_intt(0:nfgtasks),my_ele_intt(0:nfgtasks)
485       integer :: n_sc_int_tot,my_sc_inde,my_sc_inds,ind_sctint,npept
486       integer :: nele_int_tot,my_ele_inds,my_ele_inde,ind_eleint_old,&
487             ind_eleint,ijunk,nele_int_tot_vdw,my_ele_inds_vdw,&
488             my_ele_inde_vdw,ind_eleint_vdw,ind_eleint_vdw_old,&
489             nscp_int_tot,my_scp_inds,my_scp_inde,ind_scpint,&
490             ind_scpint_old,nsumgrad,nlen,ngrad_start,ngrad_end,&
491             ierror,k,ierr,iaux,ncheck_to,ncheck_from,ind_typ,&
492             ichunk,int_index_old
493       integer,dimension(5) :: nct_molec
494 !el      allocate(itask_cont_from(0:nfgtasks-1)) !(0:max_fg_procs-1)
495 !el      allocate(itask_cont_to(0:nfgtasks-1)) !(0:max_fg_procs-1)
496
497 !... Determine the numbers of start and end SC-SC interaction
498 !... to deal with by current processor.
499 !write (iout,*) '******INIT_INT_TABLE nres=',nres,' nnt=',nnt,' nct=',nct
500       do i=0,nfgtasks-1
501         itask_cont_from(i)=fg_rank
502         itask_cont_to(i)=fg_rank
503       enddo
504       lprint=energy_dec
505 !      lprint=.true.
506       if (lprint) &
507        write (iout,*)'INIT_INT_TABLE nres=',nres,' nnt=',nnt,' nct=',nct
508       n_sc_int_tot=(nct-nnt+1)*(nct-nnt)/2-nss
509       call int_bounds(n_sc_int_tot,my_sc_inds,my_sc_inde)
510 !write (iout,*) 'INIT_INT_TABLE nres=',nres,' nnt=',nnt,' nct=',nct
511       if (lprint) &
512         write (iout,*) 'Processor',fg_rank,' CG group',kolor,&
513         ' absolute rank',MyRank,&
514         ' n_sc_int_tot',n_sc_int_tot,' my_sc_inds=',my_sc_inds,&
515         ' my_sc_inde',my_sc_inde
516       ind_sctint=0
517       iatsc_s=0
518       iatsc_e=0
519 #endif
520 !el       common /przechowalnia/
521       allocate(iturn3_start_all(0:nfgtasks))
522       allocate(iturn3_end_all(0:nfgtasks))
523       allocate(iturn4_start_all(0:nfgtasks))
524       allocate(iturn4_end_all(0:nfgtasks))
525       allocate(iatel_s_all(0:nfgtasks))
526       allocate(iatel_e_all(0:nfgtasks))
527       allocate(ielstart_all(nres,0:nfgtasks-1))
528       allocate(ielend_all(nres,0:nfgtasks-1))
529
530       allocate(ntask_cont_from_all(0:nfgtasks-1))
531       allocate(ntask_cont_to_all(0:nfgtasks-1))
532       allocate(itask_cont_from_all(0:nfgtasks-1,0:nfgtasks-1))
533       allocate(itask_cont_to_all(0:nfgtasks-1,0:nfgtasks-1))
534 !el----------
535 !      lprint=.false.
536       do i=1,nres !el   !maxres
537         nint_gr(i)=0
538         nscp_gr(i)=0
539         ielstart(i)=0
540         ielend(i)=0
541         do j=1,maxint_gr
542           istart(i,j)=0
543           iend(i,j)=0
544           iscpstart(i,j)=0
545           iscpend(i,j)=0    
546         enddo
547       enddo
548       ind_scint=0
549       ind_scint_old=0
550 !d    write (iout,*) 'ns=',ns,' nss=',nss,' ihpb,jhpb',
551 !d   &   (ihpb(i),jhpb(i),i=1,nss)
552       do i=nnt,nct-1
553         scheck=.false.
554         if (dyn_ss) goto 10
555         do ii=1,nss
556           if (ihpb(ii).eq.i+nres) then
557             scheck=.true.
558             jj=jhpb(ii)-nres
559             goto 10
560           endif
561         enddo
562    10   continue
563 !d      write (iout,*) 'i=',i,' scheck=',scheck,' jj=',jj
564         if (scheck) then
565           if (jj.eq.i+1) then
566 #ifdef MPI
567 !            write (iout,*) 'jj=i+1'
568             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,&
569        iatsc_s,iatsc_e,i+2,nct,nint_gr(i),istart(i,1),iend(i,1),*12)
570 #else
571             nint_gr(i)=1
572             istart(i,1)=i+2
573             iend(i,1)=nct
574 #endif
575           else if (jj.eq.nct) then
576 #ifdef MPI
577 !            write (iout,*) 'jj=nct'
578             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,&
579         iatsc_s,iatsc_e,i+1,nct-1,nint_gr(i),istart(i,1),iend(i,1),*12)
580 #else
581             nint_gr(i)=1
582             istart(i,1)=i+1
583             iend(i,1)=nct-1
584 #endif
585           else
586 #ifdef MPI
587             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,&
588        iatsc_s,iatsc_e,i+1,jj-1,nint_gr(i),istart(i,1),iend(i,1),*12)
589             ii=nint_gr(i)+1
590             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,&
591        iatsc_s,iatsc_e,jj+1,nct_molec(1),nint_gr(i),istart(i,ii),iend(i,ii),*12)
592 #else
593             nint_gr(i)=2
594             istart(i,1)=i+1
595             iend(i,1)=jj-1
596             istart(i,2)=jj+1
597             iend(i,2)=nct_molec(1)
598 #endif
599           endif
600         else
601 #ifdef MPI
602           call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,&
603           iatsc_s,iatsc_e,i+1,nct_molec(1),nint_gr(i),istart(i,1),iend(i,1),*12)
604 #else
605           nint_gr(i)=1
606           istart(i,1)=i+1
607           iend(i,1)=nct_molec(1)
608           ind_scint=ind_scint+nct_molec(1)-i
609 #endif
610         endif
611 #ifdef MPI
612         ind_scint_old=ind_scint
613 #endif
614       enddo
615    12 continue
616 #ifndef MPI
617       iatsc_s=nnt
618       iatsc_e=nct-1
619 #endif
620       if (iatsc_s.eq.0) iatsc_s=1
621 #ifdef MPI
622       if (lprint) write (*,*) 'Processor',fg_rank,' CG Group',kolor,&
623          ' absolute rank',myrank,' iatsc_s=',iatsc_s,' iatsc_e=',iatsc_e
624 #endif
625       if (lprint) then
626       write (iout,'(a)') 'Interaction array:'
627       do i=iatsc_s,iatsc_e
628         write (iout,'(i3,2(2x,2i3))') &
629        i,(istart(i,iint),iend(i,iint),iint=1,nint_gr(i))
630       enddo
631       endif
632       ispp=4 !?? wham ispp=2
633 #ifdef MPI
634 ! Now partition the electrostatic-interaction array
635       if (itype(nres_molec(1),1).eq.ntyp1_molec(1)) then
636       npept=nres_molec(1)-nnt-1
637       else
638       npept=nres_molec(1)-nnt
639       endif
640       nele_int_tot=(npept-ispp)*(npept-ispp+1)/2
641       call int_bounds(nele_int_tot,my_ele_inds,my_ele_inde)
642       if (lprint) &
643        write (*,*) 'Processor',fg_rank,' CG group',kolor,&
644         ' absolute rank',MyRank,&
645         ' nele_int_tot',nele_int_tot,' my_ele_inds=',my_ele_inds,&
646                     ' my_ele_inde',my_ele_inde
647       iatel_s=0
648       iatel_e=0
649       ind_eleint=0
650       ind_eleint_old=0
651       if (itype(nres_molec(1),1).eq.ntyp1_molec(1)) then
652       nct_molec(1)=nres_molec(1)-1
653       else
654       nct_molec(1)=nres_molec(1)
655       endif
656 !       print *,"nct",nct,nct_molec(1),itype(nres_molec(1),1),ntyp_molec(1)
657       do i=nnt,nct_molec(1)-3
658         ijunk=0
659         call int_partition(ind_eleint,my_ele_inds,my_ele_inde,i,&
660           iatel_s,iatel_e,i+ispp,nct_molec(1)-1,ijunk,ielstart(i),ielend(i),*13)
661       enddo ! i 
662    13 continue
663       if (iatel_s.eq.0) iatel_s=1
664       nele_int_tot_vdw=(npept-2)*(npept-2+1)/2
665 !      write (iout,*) "nele_int_tot_vdw",nele_int_tot_vdw
666       call int_bounds(nele_int_tot_vdw,my_ele_inds_vdw,my_ele_inde_vdw)
667 !      write (iout,*) "my_ele_inds_vdw",my_ele_inds_vdw,
668 !     & " my_ele_inde_vdw",my_ele_inde_vdw
669       ind_eleint_vdw=0
670       ind_eleint_vdw_old=0
671       iatel_s_vdw=0
672       iatel_e_vdw=0
673       do i=nnt,nct_molec(1)-3
674         ijunk=0
675         call int_partition(ind_eleint_vdw,my_ele_inds_vdw,&
676           my_ele_inde_vdw,i,&
677           iatel_s_vdw,iatel_e_vdw,i+2,nct_molec(1)-1,ijunk,ielstart_vdw(i),&
678           ielend_vdw(i),*15)
679 !        write (iout,*) i," ielstart_vdw",ielstart_vdw(i),
680 !     &   " ielend_vdw",ielend_vdw(i)
681       enddo ! i 
682       if (iatel_s_vdw.eq.0) iatel_s_vdw=1
683    15 continue
684 #else
685       iatel_s=nnt
686       iatel_e=nct_molec(1)-5 ! ?? wham iatel_e=nct-3
687       do i=iatel_s,iatel_e
688         ielstart(i)=i+4 ! ?? wham +2
689         ielend(i)=nct_molec(1)-1
690       enddo
691       iatel_s_vdw=nnt
692       iatel_e_vdw=nct_molec(1)-3
693       do i=iatel_s_vdw,iatel_e_vdw
694         ielstart_vdw(i)=i+2
695         ielend_vdw(i)=nct_molec(1)-1
696       enddo
697 #endif
698       if (lprint) then
699         write (*,'(a)') 'Processor',fg_rank,' CG group',kolor,&
700         ' absolute rank',MyRank
701         write (iout,*) 'Electrostatic interaction array:'
702         do i=iatel_s,iatel_e
703           write (iout,'(i3,2(2x,2i3))') i,ielstart(i),ielend(i)
704         enddo
705       endif ! lprint
706 !     iscp=3
707       iscp=2
708 ! Partition the SC-p interaction array
709 #ifdef MPI
710       nscp_int_tot=(npept-iscp+1)*(npept-iscp+1)
711       call int_bounds(nscp_int_tot,my_scp_inds,my_scp_inde)
712       if (lprint) write (iout,*) 'Processor',fg_rank,' CG group',kolor,&
713         ' absolute rank',myrank,&
714         ' nscp_int_tot',nscp_int_tot,' my_scp_inds=',my_scp_inds,&
715                     ' my_scp_inde',my_scp_inde
716       iatscp_s=0
717       iatscp_e=0
718       ind_scpint=0
719       ind_scpint_old=0
720       do i=nnt,nct_molec(1)-1
721         if (i.lt.nnt+iscp) then
722 !d        write (iout,*) 'i.le.nnt+iscp'
723           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,&
724             iatscp_s,iatscp_e,i+iscp,nct_molec(1),nscp_gr(i),iscpstart(i,1),&
725             iscpend(i,1),*14)
726         else if (i.gt.nct-iscp) then
727 !d        write (iout,*) 'i.gt.nct-iscp'
728           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,&
729             iatscp_s,iatscp_e,nnt,i-iscp,nscp_gr(i),iscpstart(i,1),&
730             iscpend(i,1),*14)
731         else
732           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,&
733             iatscp_s,iatscp_e,nnt,i-iscp,nscp_gr(i),iscpstart(i,1),&
734            iscpend(i,1),*14)
735           ii=nscp_gr(i)+1
736           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,&
737             iatscp_s,iatscp_e,i+iscp,nct_molec(1),nscp_gr(i),iscpstart(i,ii),&
738             iscpend(i,ii),*14)
739         endif
740       enddo ! i
741    14 continue
742 #else
743       iatscp_s=nnt
744       iatscp_e=nct_molec(1)-1
745       do i=nnt,nct_molec(1)-1
746         if (i.lt.nnt+iscp) then
747           nscp_gr(i)=1
748           iscpstart(i,1)=i+iscp
749           iscpend(i,1)=nct_molec(1)
750         elseif (i.gt.nct-iscp) then
751           nscp_gr(i)=1
752           iscpstart(i,1)=nnt
753           iscpend(i,1)=i-iscp
754         else
755           nscp_gr(i)=2
756           iscpstart(i,1)=nnt
757           iscpend(i,1)=i-iscp
758           iscpstart(i,2)=i+iscp
759           iscpend(i,2)=nct_molec(1)
760         endif 
761       enddo ! i
762 #endif
763       if (iatscp_s.eq.0) iatscp_s=1
764       if (lprint) then
765         write (iout,'(a)') 'SC-p interaction array:'
766         do i=iatscp_s,iatscp_e
767           write (iout,'(i3,2(2x,2i3))') &
768               i,(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
769         enddo
770       endif ! lprint
771 ! Partition local interactions
772 #ifdef MPI
773       call int_bounds(nres_molec(1)-2,loc_start,loc_end)
774       loc_start=loc_start+1
775       loc_end=loc_end+1
776       call int_bounds(nres_molec(1)-2,ithet_start,ithet_end)
777       ithet_start=ithet_start+2
778       ithet_end=ithet_end+2
779       call int_bounds(nct_molec(1)-nnt-2,iturn3_start,iturn3_end) 
780       iturn3_start=iturn3_start+nnt
781       iphi_start=iturn3_start+2
782       iturn3_end=iturn3_end+nnt
783       iphi_end=iturn3_end+2
784       iturn3_start=iturn3_start-1
785       iturn3_end=iturn3_end-1
786       call int_bounds(nres_molec(1)-3,itau_start,itau_end)
787       itau_start=itau_start+3
788       itau_end=itau_end+3
789       call int_bounds(nres_molec(1)-3,iphi1_start,iphi1_end)
790       iphi1_start=iphi1_start+3
791       iphi1_end=iphi1_end+3
792       call int_bounds(nct_molec(1)-nnt-3,iturn4_start,iturn4_end) 
793       iturn4_start=iturn4_start+nnt
794       iphid_start=iturn4_start+2
795       iturn4_end=iturn4_end+nnt
796       iphid_end=iturn4_end+2
797       iturn4_start=iturn4_start-1
798       iturn4_end=iturn4_end-1
799 !      print *,"TUTUTU",nres_molec(1),nres
800       call int_bounds(nres_molec(1)-2,ibond_start,ibond_end) 
801       ibond_start=ibond_start+1
802       ibond_end=ibond_end+1
803       print *,ibond_start,ibond_end
804       call int_bounds(nct_molec(1)-nnt,ibondp_start,ibondp_end) 
805       ibondp_start=ibondp_start+nnt
806       ibondp_end=ibondp_end+nnt
807       call int_bounds1(nres_molec(1)-1,ivec_start,ivec_end) 
808 !      print *,"Processor",myrank,fg_rank,fg_rank1,
809 !     &  " ivec_start",ivec_start," ivec_end",ivec_end
810       iset_start=loc_start+2
811       iset_end=loc_end+2
812       call int_bounds(nres_molec(1),ilip_start,ilip_end)
813       ilip_start=ilip_start
814       ilip_end=ilip_end
815       call int_bounds(nres_molec(1)-1,itube_start,itube_end)
816       itube_start=itube_start
817       itube_end=itube_end
818       if (ndih_constr.eq.0) then
819         idihconstr_start=1
820         idihconstr_end=0
821       else
822         call int_bounds(ndih_constr,idihconstr_start,idihconstr_end)
823       endif
824       if (ntheta_constr.eq.0) then
825         ithetaconstr_start=1
826         ithetaconstr_end=0
827       else
828         call int_bounds &
829        (ntheta_constr,ithetaconstr_start,ithetaconstr_end)
830       endif
831
832 !      nsumgrad=(nres-nnt)*(nres-nnt+1)/2
833 !      nlen=nres-nnt+1
834       nsumgrad=(nres-nnt)*(nres-nnt+1)/2
835       nlen=nres-nnt+1
836       call int_bounds(nsumgrad,ngrad_start,ngrad_end)
837       igrad_start=((2*nlen+1) &
838          -sqrt(float((2*nlen-1)**2-8*(ngrad_start-1))))/2
839       igrad_end=((2*nlen+1) &
840          -sqrt(float((2*nlen-1)**2-8*(ngrad_end-1))))/2
841 !el      allocate(jgrad_start(igrad_start:igrad_end))
842 !el      allocate(jgrad_end(igrad_start:igrad_end)) !(maxres)
843       jgrad_start(igrad_start)= &
844          ngrad_start-(2*nlen-igrad_start)*(igrad_start-1)/2 &
845          +igrad_start
846       jgrad_end(igrad_start)=nres
847       if (igrad_end.gt.igrad_start) jgrad_start(igrad_end)=igrad_end+1
848       jgrad_end(igrad_end)=ngrad_end-(2*nlen-igrad_end)*(igrad_end-1)/2 &
849           +igrad_end
850       do i=igrad_start+1,igrad_end-1
851         jgrad_start(i)=i+1
852         jgrad_end(i)=nres
853       enddo
854       if (lprint) then 
855         write (*,*) 'Processor:',fg_rank,' CG group',kolor,&
856        ' absolute rank',myrank,&
857        ' loc_start',loc_start,' loc_end',loc_end,&
858        ' ithet_start',ithet_start,' ithet_end',ithet_end,&
859        ' iphi_start',iphi_start,' iphi_end',iphi_end,&
860        ' iphid_start',iphid_start,' iphid_end',iphid_end,&
861        ' ibond_start',ibond_start,' ibond_end',ibond_end,&
862        ' ibondp_start',ibondp_start,' ibondp_end',ibondp_end,&
863        ' iturn3_start',iturn3_start,' iturn3_end',iturn3_end,&
864        ' iturn4_start',iturn4_start,' iturn4_end',iturn4_end,&
865        ' ivec_start',ivec_start,' ivec_end',ivec_end,&
866        ' iset_start',iset_start,' iset_end',iset_end,&
867        ' idihconstr_start',idihconstr_start,' idihconstr_end',&
868          idihconstr_end
869        write (*,*) 'Processor:',fg_rank,myrank,' igrad_start',&
870          igrad_start,' igrad_end',igrad_end,' ngrad_start',ngrad_start,&
871          ' ngrad_end',ngrad_end
872        do i=igrad_start,igrad_end
873          write(*,*) 'Processor:',fg_rank,myrank,i,&
874           jgrad_start(i),jgrad_end(i)
875        enddo
876       endif
877       if (nfgtasks.gt.1) then
878         call MPI_Allgather(ivec_start,1,MPI_INTEGER,ivec_displ(0),1,&
879           MPI_INTEGER,FG_COMM1,IERROR)
880         iaux=ivec_end-ivec_start+1
881         call MPI_Allgather(iaux,1,MPI_INTEGER,ivec_count(0),1,&
882           MPI_INTEGER,FG_COMM1,IERROR)
883         call MPI_Allgather(iset_start-2,1,MPI_INTEGER,iset_displ(0),1,&
884           MPI_INTEGER,FG_COMM,IERROR)
885         iaux=iset_end-iset_start+1
886         call MPI_Allgather(iaux,1,MPI_INTEGER,iset_count(0),1,&
887           MPI_INTEGER,FG_COMM,IERROR)
888         call MPI_Allgather(ibond_start,1,MPI_INTEGER,ibond_displ(0),1,&
889           MPI_INTEGER,FG_COMM,IERROR)
890         iaux=ibond_end-ibond_start+1
891         call MPI_Allgather(iaux,1,MPI_INTEGER,ibond_count(0),1,&
892           MPI_INTEGER,FG_COMM,IERROR)
893         call MPI_Allgather(ithet_start,1,MPI_INTEGER,ithet_displ(0),1,&
894           MPI_INTEGER,FG_COMM,IERROR)
895         iaux=ithet_end-ithet_start+1
896         call MPI_Allgather(iaux,1,MPI_INTEGER,ithet_count(0),1,&
897           MPI_INTEGER,FG_COMM,IERROR)
898         call MPI_Allgather(iphi_start,1,MPI_INTEGER,iphi_displ(0),1,&
899           MPI_INTEGER,FG_COMM,IERROR)
900         iaux=iphi_end-iphi_start+1
901         call MPI_Allgather(iaux,1,MPI_INTEGER,iphi_count(0),1,&
902           MPI_INTEGER,FG_COMM,IERROR)
903         call MPI_Allgather(iphi1_start,1,MPI_INTEGER,iphi1_displ(0),1,&
904           MPI_INTEGER,FG_COMM,IERROR)
905         iaux=iphi1_end-iphi1_start+1
906         call MPI_Allgather(iaux,1,MPI_INTEGER,iphi1_count(0),1,&
907           MPI_INTEGER,FG_COMM,IERROR)
908         do i=0,nfgtasks-1
909           do j=1,nres
910             ielstart_all(j,i)=0
911             ielend_all(j,i)=0
912           enddo
913         enddo
914         call MPI_Allgather(iturn3_start,1,MPI_INTEGER,&
915           iturn3_start_all(0),1,MPI_INTEGER,FG_COMM,IERROR)
916         call MPI_Allgather(iturn4_start,1,MPI_INTEGER,&
917           iturn4_start_all(0),1,MPI_INTEGER,FG_COMM,IERROR)
918         call MPI_Allgather(iturn3_end,1,MPI_INTEGER,&
919           iturn3_end_all(0),1,MPI_INTEGER,FG_COMM,IERROR)
920         call MPI_Allgather(iturn4_end,1,MPI_INTEGER,&
921           iturn4_end_all(0),1,MPI_INTEGER,FG_COMM,IERROR)
922         call MPI_Allgather(iatel_s,1,MPI_INTEGER,&
923           iatel_s_all(0),1,MPI_INTEGER,FG_COMM,IERROR)
924         call MPI_Allgather(iatel_e,1,MPI_INTEGER,&
925           iatel_e_all(0),1,MPI_INTEGER,FG_COMM,IERROR)
926         call MPI_Allgather(ielstart(1),nres,MPI_INTEGER,&
927           ielstart_all(1,0),nres,MPI_INTEGER,FG_COMM,IERROR)
928         call MPI_Allgather(ielend(1),nres,MPI_INTEGER,&
929           ielend_all(1,0),nres,MPI_INTEGER,FG_COMM,IERROR)
930         if (lprint) then
931         write (iout,*) "iatel_s_all",(iatel_s_all(i),i=0,nfgtasks)
932         write (iout,*) "iatel_e_all",(iatel_e_all(i),i=0,nfgtasks)
933         write (iout,*) "iturn3_start_all",&
934           (iturn3_start_all(i),i=0,nfgtasks-1)
935         write (iout,*) "iturn3_end_all",&
936           (iturn3_end_all(i),i=0,nfgtasks-1)
937         write (iout,*) "iturn4_start_all",&
938           (iturn4_start_all(i),i=0,nfgtasks-1)
939         write (iout,*) "iturn4_end_all",&
940           (iturn4_end_all(i),i=0,nfgtasks-1)
941         write (iout,*) "The ielstart_all array"
942         do i=nnt,nct
943           write (iout,'(20i4)') i,(ielstart_all(i,j),j=0,nfgtasks-1)
944         enddo
945         write (iout,*) "The ielend_all array"
946         do i=nnt,nct
947           write (iout,'(20i4)') i,(ielend_all(i,j),j=0,nfgtasks-1)
948         enddo
949         call flush(iout)
950         endif
951         ntask_cont_from=0
952         ntask_cont_to=0
953         itask_cont_from(0)=fg_rank
954         itask_cont_to(0)=fg_rank
955         flag=.false.
956 !el        allocate(iturn3_sent(4,iturn3_start:iturn3_end))
957 !el        allocate(iturn4_sent(4,iturn4_start:iturn4_end)) !(4,maxres)
958         do ii=iturn3_start,iturn3_end
959           call add_int(ii,ii+2,iturn3_sent(1,ii),&
960                       ntask_cont_to,itask_cont_to,flag)
961         enddo
962         do ii=iturn4_start,iturn4_end
963           call add_int(ii,ii+3,iturn4_sent(1,ii),&
964                       ntask_cont_to,itask_cont_to,flag)
965         enddo
966         do ii=iturn3_start,iturn3_end
967           call add_int_from(ii,ii+2,ntask_cont_from,itask_cont_from)
968         enddo
969         do ii=iturn4_start,iturn4_end
970           call add_int_from(ii,ii+3,ntask_cont_from,itask_cont_from)
971         enddo
972         if (lprint) then
973         write (iout,*) "After turn3 ntask_cont_from",ntask_cont_from,&
974          " ntask_cont_to",ntask_cont_to
975         write (iout,*) "itask_cont_from",&
976           (itask_cont_from(i),i=1,ntask_cont_from)
977         write (iout,*) "itask_cont_to",&
978           (itask_cont_to(i),i=1,ntask_cont_to)
979         call flush(iout)
980         endif
981 !        write (iout,*) "Loop forward"
982 !        call flush(iout)
983         do i=iatel_s,iatel_e
984 !          write (iout,*) "from loop i=",i
985 !          call flush(iout)
986           do j=ielstart(i),ielend(i)
987             call add_int_from(i,j,ntask_cont_from,itask_cont_from)
988           enddo
989         enddo
990 !        write (iout,*) "Loop backward iatel_e-1",iatel_e-1,
991 !     &     " iatel_e",iatel_e
992 !        call flush(iout)
993         nat_sent=0
994         do i=iatel_s,iatel_e
995 !          write (iout,*) "i",i," ielstart",ielstart(i),
996 !     &      " ielend",ielend(i)
997 !          call flush(iout)
998           flag=.false.
999           do j=ielstart(i),ielend(i)
1000             call add_int(i,j,iint_sent(1,j,nat_sent+1),ntask_cont_to,&
1001                         itask_cont_to,flag)
1002           enddo
1003           if (flag) then
1004             nat_sent=nat_sent+1
1005             iat_sent(nat_sent)=i
1006           endif
1007         enddo
1008         if (lprint) then
1009         write (iout,*)"After longrange ntask_cont_from",ntask_cont_from,&
1010          " ntask_cont_to",ntask_cont_to
1011         write (iout,*) "itask_cont_from",&
1012           (itask_cont_from(i),i=1,ntask_cont_from)
1013         write (iout,*) "itask_cont_to",&
1014           (itask_cont_to(i),i=1,ntask_cont_to)
1015         call flush(iout)
1016         write (iout,*) "iint_sent"
1017         do i=1,nat_sent
1018           ii=iat_sent(i)
1019           write (iout,'(20i4)') ii,(j,(iint_sent(k,j,i),k=1,4),&
1020             j=ielstart(ii),ielend(ii))
1021         enddo
1022         write (iout,*) "iturn3_sent iturn3_start",iturn3_start,&
1023           " iturn3_end",iturn3_end
1024         write (iout,'(20i4)') (i,(iturn3_sent(j,i),j=1,4),&
1025            i=iturn3_start,iturn3_end)
1026         write (iout,*) "iturn4_sent iturn4_start",iturn4_start,&
1027           " iturn4_end",iturn4_end
1028         write (iout,'(20i4)') (i,(iturn4_sent(j,i),j=1,4),&
1029            i=iturn4_start,iturn4_end)
1030         call flush(iout)
1031         endif
1032         call MPI_Gather(ntask_cont_from,1,MPI_INTEGER,&
1033          ntask_cont_from_all,1,MPI_INTEGER,king,FG_COMM,IERR)
1034 !        write (iout,*) "Gather ntask_cont_from ended"
1035 !        call flush(iout)
1036         call MPI_Gather(itask_cont_from(0),nfgtasks,MPI_INTEGER,&
1037          itask_cont_from_all(0,0),nfgtasks,MPI_INTEGER,king,&
1038          FG_COMM,IERR)
1039 !        write (iout,*) "Gather itask_cont_from ended"
1040 !        call flush(iout)
1041         call MPI_Gather(ntask_cont_to,1,MPI_INTEGER,ntask_cont_to_all,&
1042          1,MPI_INTEGER,king,FG_COMM,IERR)
1043 !        write (iout,*) "Gather ntask_cont_to ended"
1044 !        call flush(iout)
1045         call MPI_Gather(itask_cont_to,nfgtasks,MPI_INTEGER,&
1046          itask_cont_to_all,nfgtasks,MPI_INTEGER,king,FG_COMM,IERR)
1047 !        write (iout,*) "Gather itask_cont_to ended"
1048 !        call flush(iout)
1049         if (fg_rank.eq.king) then
1050           write (iout,*)"Contact receive task map (proc, #tasks, tasks)"
1051           do i=0,nfgtasks-1
1052             write (iout,'(20i4)') i,ntask_cont_from_all(i),&
1053               (itask_cont_from_all(j,i),j=1,ntask_cont_from_all(i)) 
1054           enddo
1055           write (iout,*)
1056           call flush(iout)
1057           write (iout,*) "Contact send task map (proc, #tasks, tasks)"
1058           do i=0,nfgtasks-1
1059             write (iout,'(20i4)') i,ntask_cont_to_all(i),&
1060              (itask_cont_to_all(j,i),j=1,ntask_cont_to_all(i)) 
1061           enddo
1062           write (iout,*)
1063           call flush(iout)
1064 ! Check if every send will have a matching receive
1065           ncheck_to=0
1066           ncheck_from=0
1067           do i=0,nfgtasks-1
1068             ncheck_to=ncheck_to+ntask_cont_to_all(i)
1069             ncheck_from=ncheck_from+ntask_cont_from_all(i)
1070           enddo
1071           write (iout,*) "Control sums",ncheck_from,ncheck_to
1072           if (ncheck_from.ne.ncheck_to) then
1073             write (iout,*) "Error: #receive differs from #send."
1074             write (iout,*) "Terminating program...!"
1075             call flush(iout)
1076             flag=.false.
1077           else
1078             flag=.true.
1079             do i=0,nfgtasks-1
1080               do j=1,ntask_cont_to_all(i)
1081                 ii=itask_cont_to_all(j,i)
1082                 do k=1,ntask_cont_from_all(ii)
1083                   if (itask_cont_from_all(k,ii).eq.i) then
1084                     if(lprint)write(iout,*)"Matching send/receive",i,ii
1085                     exit
1086                   endif
1087                 enddo
1088                 if (k.eq.ntask_cont_from_all(ii)+1) then
1089                   flag=.false.
1090                   write (iout,*) "Error: send by",j," to",ii,&
1091                     " would have no matching receive"
1092                 endif
1093               enddo
1094             enddo
1095           endif
1096           if (.not.flag) then
1097             write (iout,*) "Unmatched sends; terminating program"
1098             call flush(iout)
1099           endif
1100         endif
1101         call MPI_Bcast(flag,1,MPI_LOGICAL,king,FG_COMM,IERROR)
1102 !        write (iout,*) "flag broadcast ended flag=",flag
1103 !        call flush(iout)
1104         if (.not.flag) then
1105           call MPI_Finalize(IERROR)
1106           stop "Error in INIT_INT_TABLE: unmatched send/receive."
1107         endif
1108         call MPI_Comm_group(FG_COMM,fg_group,IERR)
1109 !        write (iout,*) "MPI_Comm_group ended"
1110 !        call flush(iout)
1111         call MPI_Group_incl(fg_group,ntask_cont_from+1,&
1112           itask_cont_from(0),CONT_FROM_GROUP,IERR)
1113         call MPI_Group_incl(fg_group,ntask_cont_to+1,itask_cont_to(0),&
1114           CONT_TO_GROUP,IERR)
1115         do i=1,nat_sent
1116           ii=iat_sent(i)
1117           iaux=4*(ielend(ii)-ielstart(ii)+1)
1118           call MPI_Group_translate_ranks(fg_group,iaux,&
1119             iint_sent(1,ielstart(ii),i),CONT_TO_GROUP,&
1120             iint_sent_local(1,ielstart(ii),i),IERR )
1121 !          write (iout,*) "Ranks translated i=",i
1122 !          call flush(iout)
1123         enddo
1124         iaux=4*(iturn3_end-iturn3_start+1)
1125         call MPI_Group_translate_ranks(fg_group,iaux,&
1126            iturn3_sent(1,iturn3_start),CONT_TO_GROUP,&
1127            iturn3_sent_local(1,iturn3_start),IERR)
1128         iaux=4*(iturn4_end-iturn4_start+1)
1129         call MPI_Group_translate_ranks(fg_group,iaux,&
1130            iturn4_sent(1,iturn4_start),CONT_TO_GROUP,&
1131            iturn4_sent_local(1,iturn4_start),IERR)
1132         if (lprint) then
1133         write (iout,*) "iint_sent_local"
1134         do i=1,nat_sent
1135           ii=iat_sent(i)
1136           write (iout,'(20i4)') ii,(j,(iint_sent_local(k,j,i),k=1,4),&
1137             j=ielstart(ii),ielend(ii))
1138           call flush(iout)
1139         enddo
1140         write (iout,*) "iturn3_sent_local iturn3_start",iturn3_start,&
1141           " iturn3_end",iturn3_end
1142         write (iout,'(20i4)') (i,(iturn3_sent_local(j,i),j=1,4),&
1143            i=iturn3_start,iturn3_end)
1144         write (iout,*) "iturn4_sent_local iturn4_start",iturn4_start,&
1145           " iturn4_end",iturn4_end
1146         write (iout,'(20i4)') (i,(iturn4_sent_local(j,i),j=1,4),&
1147            i=iturn4_start,iturn4_end)
1148         call flush(iout)
1149         endif
1150         call MPI_Group_free(fg_group,ierr)
1151         call MPI_Group_free(cont_from_group,ierr)
1152         call MPI_Group_free(cont_to_group,ierr)
1153         call MPI_Type_contiguous(3,MPI_DOUBLE_PRECISION,MPI_UYZ,IERROR)
1154         call MPI_Type_commit(MPI_UYZ,IERROR)
1155         call MPI_Type_contiguous(18,MPI_DOUBLE_PRECISION,MPI_UYZGRAD,&
1156           IERROR)
1157         call MPI_Type_commit(MPI_UYZGRAD,IERROR)
1158         call MPI_Type_contiguous(2,MPI_DOUBLE_PRECISION,MPI_MU,IERROR)
1159         call MPI_Type_commit(MPI_MU,IERROR)
1160         call MPI_Type_contiguous(4,MPI_DOUBLE_PRECISION,MPI_MAT1,IERROR)
1161         call MPI_Type_commit(MPI_MAT1,IERROR)
1162         call MPI_Type_contiguous(8,MPI_DOUBLE_PRECISION,MPI_MAT2,IERROR)
1163         call MPI_Type_commit(MPI_MAT2,IERROR)
1164         call MPI_Type_contiguous(6,MPI_DOUBLE_PRECISION,MPI_THET,IERROR)
1165         call MPI_Type_commit(MPI_THET,IERROR)
1166         call MPI_Type_contiguous(9,MPI_DOUBLE_PRECISION,MPI_GAM,IERROR)
1167         call MPI_Type_commit(MPI_GAM,IERROR)
1168
1169 !el        allocate(lentyp(0:nfgtasks-1))
1170 #ifndef MATGATHER
1171 ! 9/22/08 Derived types to send matrices which appear in correlation terms
1172         do i=0,nfgtasks-1
1173           if (ivec_count(i).eq.ivec_count(0)) then
1174             lentyp(i)=0
1175           else
1176             lentyp(i)=1
1177           endif
1178         enddo
1179         do ind_typ=lentyp(0),lentyp(nfgtasks-1)
1180         if (ind_typ.eq.0) then
1181           ichunk=ivec_count(0)
1182         else
1183           ichunk=ivec_count(1)
1184         endif
1185 !        do i=1,4
1186 !          blocklengths(i)=4
1187 !        enddo
1188 !        displs(1)=0
1189 !        do i=2,4
1190 !          displs(i)=displs(i-1)+blocklengths(i-1)*maxres
1191 !        enddo
1192 !        do i=1,4
1193 !          blocklengths(i)=blocklengths(i)*ichunk
1194 !        enddo
1195 !        write (iout,*) "blocklengths and displs"
1196 !        do i=1,4
1197 !          write (iout,*) i,blocklengths(i),displs(i)
1198 !        enddo
1199 !        call flush(iout)
1200 !        call MPI_Type_indexed(4,blocklengths(1),displs(1),
1201 !     &    MPI_DOUBLE_PRECISION,MPI_ROTAT1(ind_typ),IERROR)
1202 !        call MPI_Type_commit(MPI_ROTAT1(ind_typ),IERROR)
1203 !        write (iout,*) "MPI_ROTAT1",MPI_ROTAT1 
1204 !        do i=1,4
1205 !          blocklengths(i)=2
1206 !        enddo
1207 !        displs(1)=0
1208 !        do i=2,4
1209 !          displs(i)=displs(i-1)+blocklengths(i-1)*maxres
1210 !        enddo
1211 !        do i=1,4
1212 !          blocklengths(i)=blocklengths(i)*ichunk
1213 !        enddo
1214 !        write (iout,*) "blocklengths and displs"
1215 !        do i=1,4
1216 !          write (iout,*) i,blocklengths(i),displs(i)
1217 !        enddo
1218 !        call flush(iout)
1219 !        call MPI_Type_indexed(4,blocklengths(1),displs(1),
1220 !     &    MPI_DOUBLE_PRECISION,MPI_ROTAT2(ind_typ),IERROR)
1221 !        call MPI_Type_commit(MPI_ROTAT2(ind_typ),IERROR)
1222 !        write (iout,*) "MPI_ROTAT2",MPI_ROTAT2 
1223         do i=1,8
1224           blocklengths(i)=2
1225         enddo
1226         displs(1)=0
1227         do i=2,8
1228           displs(i)=displs(i-1)+blocklengths(i-1)*nres !maxres
1229         enddo
1230         do i=1,15
1231           blocklengths(i)=blocklengths(i)*ichunk
1232         enddo
1233         call MPI_Type_indexed(8,blocklengths,displs,&
1234           MPI_DOUBLE_PRECISION,MPI_PRECOMP11(ind_typ),IERROR)
1235         call MPI_Type_commit(MPI_PRECOMP11(ind_typ),IERROR)
1236         do i=1,8
1237           blocklengths(i)=4
1238         enddo
1239         displs(1)=0
1240         do i=2,8
1241           displs(i)=displs(i-1)+blocklengths(i-1)*nres !maxres
1242         enddo
1243         do i=1,15
1244           blocklengths(i)=blocklengths(i)*ichunk
1245         enddo
1246         call MPI_Type_indexed(8,blocklengths,displs,&
1247           MPI_DOUBLE_PRECISION,MPI_PRECOMP12(ind_typ),IERROR)
1248         call MPI_Type_commit(MPI_PRECOMP12(ind_typ),IERROR)
1249         do i=1,6
1250           blocklengths(i)=4
1251         enddo
1252         displs(1)=0
1253         do i=2,6
1254           displs(i)=displs(i-1)+blocklengths(i-1)*nres !maxres
1255         enddo
1256         do i=1,6
1257           blocklengths(i)=blocklengths(i)*ichunk
1258         enddo
1259         call MPI_Type_indexed(6,blocklengths,displs,&
1260           MPI_DOUBLE_PRECISION,MPI_PRECOMP22(ind_typ),IERROR)
1261         call MPI_Type_commit(MPI_PRECOMP22(ind_typ),IERROR)
1262         do i=1,2
1263           blocklengths(i)=8
1264         enddo
1265         displs(1)=0
1266         do i=2,2
1267           displs(i)=displs(i-1)+blocklengths(i-1)*nres !maxres
1268         enddo
1269         do i=1,2
1270           blocklengths(i)=blocklengths(i)*ichunk
1271         enddo
1272         call MPI_Type_indexed(2,blocklengths,displs,&
1273           MPI_DOUBLE_PRECISION,MPI_PRECOMP23(ind_typ),IERROR)
1274         call MPI_Type_commit(MPI_PRECOMP23(ind_typ),IERROR)
1275         do i=1,4
1276           blocklengths(i)=1
1277         enddo
1278         displs(1)=0
1279         do i=2,4
1280           displs(i)=displs(i-1)+blocklengths(i-1)*nres !maxres
1281         enddo
1282         do i=1,4
1283           blocklengths(i)=blocklengths(i)*ichunk
1284         enddo
1285         call MPI_Type_indexed(4,blocklengths,displs,&
1286           MPI_DOUBLE_PRECISION,MPI_ROTAT_OLD(ind_typ),IERROR)
1287         call MPI_Type_commit(MPI_ROTAT_OLD(ind_typ),IERROR)
1288         enddo
1289 #endif
1290       endif
1291       iint_start=ivec_start+1
1292       iint_end=ivec_end+1
1293       do i=0,nfgtasks-1
1294           iint_count(i)=ivec_count(i)
1295           iint_displ(i)=ivec_displ(i)
1296           ivec_displ(i)=ivec_displ(i)-1
1297           iset_displ(i)=iset_displ(i)-1
1298           ithet_displ(i)=ithet_displ(i)-1
1299           iphi_displ(i)=iphi_displ(i)-1
1300           iphi1_displ(i)=iphi1_displ(i)-1
1301           ibond_displ(i)=ibond_displ(i)-1
1302       enddo
1303       if (nfgtasks.gt.1 .and. fg_rank.eq.king &
1304           .and. (me.eq.0 .or. .not. out1file)) then
1305         write (iout,*) "IVEC_DISPL, IVEC_COUNT, ISET_START, ISET_COUNT"
1306         do i=0,nfgtasks-1
1307           write (iout,*) i,ivec_displ(i),ivec_count(i),iset_displ(i),&
1308             iset_count(i)
1309         enddo
1310         write (iout,*) "iphi_start",iphi_start," iphi_end",iphi_end,&
1311           " iphi1_start",iphi1_start," iphi1_end",iphi1_end
1312         write (iout,*)"IPHI_COUNT, IPHI_DISPL, IPHI1_COUNT, IPHI1_DISPL"
1313         do i=0,nfgtasks-1
1314           write (iout,*) i,iphi_count(i),iphi_displ(i),iphi1_count(i),&
1315             iphi1_displ(i)
1316         enddo
1317         write(iout,'(i10,a,i10,a,i10,a/a,i3,a)') n_sc_int_tot,' SC-SC ',&
1318           nele_int_tot,' electrostatic and ',nscp_int_tot,&
1319           ' SC-p interactions','were distributed among',nfgtasks,&
1320           ' fine-grain processors.'
1321       endif
1322 #else
1323       loc_start=2
1324       loc_end=nres_molec(1)-1
1325       ithet_start=3 
1326       ithet_end=nres_molec(1)
1327       iturn3_start=nnt
1328       iturn3_end=nct_molec(1)-3
1329       iturn4_start=nnt
1330       iturn4_end=nct_molec(1)-4
1331       iphi_start=nnt+3
1332       iphi_end=nct_molec(1)
1333       iphi1_start=4
1334       iphi1_end=nres_molec(1)
1335       idihconstr_start=1
1336       idihconstr_end=ndih_constr
1337       ithetaconstr_start=1
1338       ithetaconstr_end=ntheta_constr
1339       iphid_start=iphi_start
1340       iphid_end=iphi_end-1
1341       itau_start=4
1342       itau_end=nres_molec(1)
1343       ibond_start=2
1344       ibond_end=nres_molec(1)-1
1345       ibondp_start=nnt
1346       ibondp_end=nct_molec(1)-1
1347       ivec_start=1
1348       ivec_end=nres_molec(1)-1
1349       iset_start=3
1350       iset_end=nres_molec(1)+1
1351       iint_start=2
1352       iint_end=nres_molec(1)-1
1353       ilip_start=1
1354       ilip_end=nres_molec(1)
1355       itube_start=1
1356       itube_end=nres_molec(1)
1357 #endif
1358 !el       common /przechowalnia/
1359 !      deallocate(iturn3_start_all)
1360 !      deallocate(iturn3_end_all)
1361 !      deallocate(iturn4_start_all)
1362 !      deallocate(iturn4_end_all)
1363 !      deallocate(iatel_s_all)
1364 !      deallocate(iatel_e_all)
1365 !      deallocate(ielstart_all)
1366 !      deallocate(ielend_all)
1367
1368 !      deallocate(ntask_cont_from_all)
1369 !      deallocate(ntask_cont_to_all)
1370 !      deallocate(itask_cont_from_all)
1371 !      deallocate(itask_cont_to_all)
1372 !el----------
1373       return
1374       end subroutine init_int_table
1375 #ifdef MPI
1376 !-----------------------------------------------------------------------------
1377       subroutine add_int(ii,jj,itask,ntask_cont_to,itask_cont_to,flag)
1378
1379 !el      implicit none
1380 !      include "DIMENSIONS"
1381 !      include "COMMON.INTERACT"
1382 !      include "COMMON.SETUP"
1383 !      include "COMMON.IOUNITS"
1384       integer :: ii,jj,ntask_cont_to
1385       integer,dimension(4) :: itask
1386       integer :: itask_cont_to(0:nfgtasks-1)    !(0:max_fg_procs-1)
1387       logical :: flag
1388 !el      integer,dimension(0:nfgtasks) :: iturn3_start_all,iturn3_end_all,iturn4_start_all,&
1389 !el       iturn4_end_all,iatel_s_all,iatel_e_all        !(0:max_fg_procs)
1390 !el      integer,dimension(nres,0:nfgtasks-1) :: ielstart_all,ielend_all        !(maxres,0:max_fg_procs-1)
1391 !el      common /przechowalnia/ iturn3_start_all,iturn3_end_all,iturn4_start_all,&
1392 !el       iturn4_end_all,iatel_s_all,iatel_e_all,ielstart_all,ielend_all
1393       integer :: iproc,isent,k,l
1394 ! Determines whether to send interaction ii,jj to other processors; a given
1395 ! interaction can be sent to at most 2 processors.
1396 ! Sets flag=.true. if interaction ii,jj needs to be sent to at least 
1397 ! one processor, otherwise flag is unchanged from the input value.
1398       isent=0
1399       itask(1)=fg_rank
1400       itask(2)=fg_rank
1401       itask(3)=fg_rank
1402       itask(4)=fg_rank
1403 !      write (iout,*) "ii",ii," jj",jj
1404 ! Loop over processors to check if anybody could need interaction ii,jj
1405       do iproc=0,fg_rank-1
1406 ! Check if the interaction matches any turn3 at iproc
1407         do k=iturn3_start_all(iproc),iturn3_end_all(iproc)
1408           l=k+2
1409           if (k.eq.ii-1 .and. l.eq.jj-1 .or. k.eq.ii-1 .and. l.eq.jj+1 &
1410          .or. k.eq.ii+1 .and. l.eq.jj+1 .or. k.eq.ii+1 .and. l.eq.jj-1) &
1411           then 
1412 !            write (iout,*) "turn3 to iproc",iproc," ij",ii,jj,"kl",k,l
1413 !            call flush(iout)
1414             flag=.true.
1415             if (iproc.ne.itask(1).and.iproc.ne.itask(2) &
1416               .and.iproc.ne.itask(3).and.iproc.ne.itask(4)) then
1417               isent=isent+1
1418               itask(isent)=iproc
1419               call add_task(iproc,ntask_cont_to,itask_cont_to)
1420             endif
1421           endif
1422         enddo
1423 ! Check if the interaction matches any turn4 at iproc
1424         do k=iturn4_start_all(iproc),iturn4_end_all(iproc)
1425           l=k+3
1426           if (k.eq.ii-1 .and. l.eq.jj-1 .or. k.eq.ii-1 .and. l.eq.jj+1 &
1427          .or. k.eq.ii+1 .and. l.eq.jj+1 .or. k.eq.ii+1 .and. l.eq.jj-1) &
1428           then 
1429 !            write (iout,*) "turn3 to iproc",iproc," ij",ii,jj," kl",k,l
1430 !            call flush(iout)
1431             flag=.true.
1432             if (iproc.ne.itask(1).and.iproc.ne.itask(2) &
1433               .and.iproc.ne.itask(3).and.iproc.ne.itask(4)) then
1434               isent=isent+1
1435               itask(isent)=iproc
1436               call add_task(iproc,ntask_cont_to,itask_cont_to)
1437             endif
1438           endif
1439         enddo
1440         if (iatel_s_all(iproc).gt.0 .and. iatel_e_all(iproc).gt.0 .and. &
1441         iatel_s_all(iproc).le.ii-1 .and. iatel_e_all(iproc).ge.ii-1)then
1442           if (ielstart_all(ii-1,iproc).le.jj-1.and. &
1443               ielend_all(ii-1,iproc).ge.jj-1) then
1444             flag=.true.
1445             if (iproc.ne.itask(1).and.iproc.ne.itask(2) &
1446               .and.iproc.ne.itask(3).and.iproc.ne.itask(4)) then
1447               isent=isent+1
1448               itask(isent)=iproc
1449               call add_task(iproc,ntask_cont_to,itask_cont_to)
1450             endif
1451           endif
1452           if (ielstart_all(ii-1,iproc).le.jj+1.and. &
1453               ielend_all(ii-1,iproc).ge.jj+1) then
1454             flag=.true.
1455             if (iproc.ne.itask(1).and.iproc.ne.itask(2) &
1456               .and.iproc.ne.itask(3).and.iproc.ne.itask(4)) then
1457               isent=isent+1
1458               itask(isent)=iproc
1459               call add_task(iproc,ntask_cont_to,itask_cont_to)
1460             endif
1461           endif
1462         endif
1463       enddo
1464       return
1465       end subroutine add_int
1466 !-----------------------------------------------------------------------------
1467       subroutine add_int_from(ii,jj,ntask_cont_from,itask_cont_from)
1468
1469 !el      use MPI_data
1470 !el      implicit none
1471 !      include "DIMENSIONS"
1472 !      include "COMMON.INTERACT"
1473 !      include "COMMON.SETUP"
1474 !      include "COMMON.IOUNITS"
1475       integer :: ii,jj,itask(2),ntask_cont_from,&
1476        itask_cont_from(0:nfgtasks-1)    !(0:max_fg_procs)
1477       logical :: flag
1478 !el      integer,dimension(0:nfgtasks) :: iturn3_start_all,iturn3_end_all,&
1479 !el       iturn4_start_all,iturn4_end_all,iatel_s_all,iatel_e_all       !(0:max_fg_procs)
1480 !el      integer,dimension(nres,0:nfgtasks-1) :: ielstart_all,ielend_all        !(maxres,0:max_fg_procs-1)
1481 !el      common /przechowalnia/ iturn3_start_all,iturn3_end_all,iturn4_start_all,&
1482 !el       iturn4_end_all,iatel_s_all,iatel_e_all,ielstart_all,ielend_all
1483       integer :: iproc,k,l
1484       do iproc=fg_rank+1,nfgtasks-1
1485         do k=iturn3_start_all(iproc),iturn3_end_all(iproc)
1486           l=k+2
1487           if (k.eq.ii+1 .and. l.eq.jj+1 .or. k.eq.ii+1.and.l.eq.jj-1 &
1488          .or. k.eq.ii-1 .and. l.eq.jj-1 .or. k.eq.ii-1 .and. l.eq.jj+1) &
1489           then
1490 !            write (iout,*)"turn3 from iproc",iproc," ij",ii,jj," kl",k,l
1491             call add_task(iproc,ntask_cont_from,itask_cont_from)
1492           endif
1493         enddo 
1494         do k=iturn4_start_all(iproc),iturn4_end_all(iproc)
1495           l=k+3
1496           if (k.eq.ii+1 .and. l.eq.jj+1 .or. k.eq.ii+1.and.l.eq.jj-1 &
1497          .or. k.eq.ii-1 .and. l.eq.jj-1 .or. k.eq.ii-1 .and. l.eq.jj+1) &
1498           then
1499 !            write (iout,*)"turn4 from iproc",iproc," ij",ii,jj," kl",k,l
1500             call add_task(iproc,ntask_cont_from,itask_cont_from)
1501           endif
1502         enddo 
1503         if (iatel_s_all(iproc).gt.0 .and. iatel_e_all(iproc).gt.0) then
1504           if (ii+1.ge.iatel_s_all(iproc).and.ii+1.le.iatel_e_all(iproc)) &
1505           then
1506             if (jj+1.ge.ielstart_all(ii+1,iproc).and. &
1507                 jj+1.le.ielend_all(ii+1,iproc)) then
1508               call add_task(iproc,ntask_cont_from,itask_cont_from)
1509             endif            
1510             if (jj-1.ge.ielstart_all(ii+1,iproc).and. &
1511                 jj-1.le.ielend_all(ii+1,iproc)) then
1512               call add_task(iproc,ntask_cont_from,itask_cont_from)
1513             endif
1514           endif
1515           if (ii-1.ge.iatel_s_all(iproc).and.ii-1.le.iatel_e_all(iproc)) &
1516           then
1517             if (jj-1.ge.ielstart_all(ii-1,iproc).and. &
1518                 jj-1.le.ielend_all(ii-1,iproc)) then
1519               call add_task(iproc,ntask_cont_from,itask_cont_from)
1520             endif
1521             if (jj+1.ge.ielstart_all(ii-1,iproc).and. &
1522                 jj+1.le.ielend_all(ii-1,iproc)) then
1523                call add_task(iproc,ntask_cont_from,itask_cont_from)
1524             endif
1525           endif
1526         endif
1527       enddo
1528       return
1529       end subroutine add_int_from
1530 !-----------------------------------------------------------------------------
1531       subroutine add_task(iproc,ntask_cont,itask_cont)
1532
1533 !el      use MPI_data
1534 !el      implicit none
1535 !      include "DIMENSIONS"
1536       integer :: iproc,ntask_cont,itask_cont(0:nfgtasks-1)      !(0:max_fg_procs-1)
1537       integer :: ii
1538       do ii=1,ntask_cont
1539         if (itask_cont(ii).eq.iproc) return
1540       enddo
1541       ntask_cont=ntask_cont+1
1542       itask_cont(ntask_cont)=iproc
1543       return
1544       end subroutine add_task
1545 #endif
1546 !-----------------------------------------------------------------------------
1547 #if defined MPI || defined WHAM_RUN
1548       subroutine int_partition(int_index,lower_index,upper_index,atom,&
1549        at_start,at_end,first_atom,last_atom,int_gr,jat_start,jat_end,*)
1550
1551 !      implicit real*8 (a-h,o-z)
1552 !      include 'DIMENSIONS'
1553 !      include 'COMMON.IOUNITS'
1554       integer :: int_index,lower_index,upper_index,atom,at_start,at_end,&
1555        first_atom,last_atom,int_gr,jat_start,jat_end,int_index_old
1556       logical :: lprn
1557       lprn=.false.
1558       if (lprn) write (iout,*) 'int_index=',int_index
1559       int_index_old=int_index
1560       int_index=int_index+last_atom-first_atom+1
1561       if (lprn) &
1562          write (iout,*) 'int_index=',int_index,&
1563                      ' int_index_old',int_index_old,&
1564                      ' lower_index=',lower_index,&
1565                      ' upper_index=',upper_index,&
1566                      ' atom=',atom,' first_atom=',first_atom,&
1567                      ' last_atom=',last_atom
1568       if (int_index.ge.lower_index) then
1569         int_gr=int_gr+1
1570         if (at_start.eq.0) then
1571           at_start=atom
1572           jat_start=first_atom-1+lower_index-int_index_old
1573         else
1574           jat_start=first_atom
1575         endif
1576         if (lprn) write (iout,*) 'jat_start',jat_start
1577         if (int_index.ge.upper_index) then
1578           at_end=atom
1579           jat_end=first_atom-1+upper_index-int_index_old
1580           return 1
1581         else
1582           jat_end=last_atom
1583         endif
1584         if (lprn) write (iout,*) 'jat_end',jat_end
1585       endif
1586       return
1587       end subroutine int_partition
1588 #endif
1589 !-----------------------------------------------------------------------------
1590 #ifndef CLUSTER
1591       subroutine hpb_partition
1592
1593 !      implicit real*8 (a-h,o-z)
1594 !      include 'DIMENSIONS'
1595 #ifdef MPI
1596       include 'mpif.h'
1597 #endif
1598 !      include 'COMMON.SBRIDGE'
1599 !      include 'COMMON.IOUNITS'
1600 !      include 'COMMON.SETUP'
1601 #ifdef MPI
1602       call int_bounds(nhpb,link_start,link_end)
1603       write (iout,*) 'Processor',fg_rank,' CG group',kolor,&
1604         ' absolute rank',MyRank,&
1605         ' nhpb',nhpb,' link_start=',link_start,&
1606         ' link_end',link_end
1607 #else
1608       link_start=1
1609       link_end=nhpb
1610 #endif
1611       return
1612       end subroutine hpb_partition
1613 #endif
1614 !-----------------------------------------------------------------------------
1615 ! misc.f in module io_base
1616 !-----------------------------------------------------------------------------
1617 !-----------------------------------------------------------------------------
1618 ! parmread.F
1619 !-----------------------------------------------------------------------------
1620       subroutine getenv_loc(var, val)
1621
1622       character(*) :: var, val
1623
1624 #ifdef WINIFL
1625       character(len=2000) :: line
1626 !el      external ilen
1627
1628       open (196,file='env',status='old',readonly,shared)
1629       iread=0
1630 !      write(*,*)'looking for ',var
1631 10    read(196,*,err=11,end=11)line
1632       iread=index(line,var)
1633 !      write(*,*)iread,' ',var,' ',line
1634       if (iread.eq.0) go to 10 
1635 !      write(*,*)'---> ',line
1636 11    continue
1637       if(iread.eq.0) then
1638 !       write(*,*)'CHUJ'
1639        val=''
1640       else
1641        iread=iread+ilen(var)+1
1642        read (line(iread:),*,err=12,end=12) val
1643 !       write(*,*)'OK: ',var,' = ',val
1644       endif
1645       close(196)
1646       return
1647 12    val=''
1648       close(196)
1649 #elif (defined CRAY)
1650       integer :: lennam,lenval,ierror
1651 !
1652 !        getenv using a POSIX call, useful on the T3D
1653 !        Sept 1996, comment out error check on advice of H. Pritchard
1654 !
1655       lennam = len(var)
1656       if(lennam.le.0) stop '--error calling getenv--'
1657       call pxfgetenv(var,lennam,val,lenval,ierror)
1658 !-HP- if(ierror.ne.0) stop '--error returned by pxfgetenv--'
1659 #else
1660       call getenv(var,val)
1661 #endif
1662
1663       return
1664       end subroutine getenv_loc
1665 !-----------------------------------------------------------------------------
1666 ! readrtns_CSA.F
1667 !-----------------------------------------------------------------------------
1668       subroutine setup_var
1669
1670       integer :: i
1671 !      implicit real*8 (a-h,o-z)
1672 !      include 'DIMENSIONS'
1673 !      include 'COMMON.IOUNITS'
1674 !      include 'COMMON.GEO'
1675 !      include 'COMMON.VAR'
1676 !      include 'COMMON.INTERACT'
1677 !      include 'COMMON.LOCAL'
1678 !      include 'COMMON.NAMES'
1679 !      include 'COMMON.CHAIN'
1680 !      include 'COMMON.FFIELD'
1681 !      include 'COMMON.SBRIDGE'
1682 !      include 'COMMON.HEADER'
1683 !      include 'COMMON.CONTROL'
1684 !      include 'COMMON.DBASE'
1685 !      include 'COMMON.THREAD'
1686 !      include 'COMMON.TIME1'
1687 ! Set up variable list.
1688       ntheta=nres-2
1689       nphi=nres-3
1690       nvar=ntheta+nphi
1691       nside=0
1692       do i=2,nres-1
1693 #ifdef WHAM_RUN
1694         if (itype(i,1).ne.10) then
1695 #else
1696         if (itype(i,1).ne.10 .and. itype(i,1).ne.ntyp1) then
1697 #endif
1698           nside=nside+1
1699           ialph(i,1)=nvar+nside
1700           ialph(nside,2)=i
1701         endif
1702       enddo
1703       if (indphi.gt.0) then
1704         nvar=nphi
1705       else if (indback.gt.0) then
1706         nvar=nphi+ntheta
1707       else
1708         nvar=nvar+2*nside
1709       endif
1710 !d    write (iout,'(3i4)') (i,ialph(i,1),ialph(i,2),i=2,nres-1)
1711       return
1712       end subroutine setup_var
1713 !-----------------------------------------------------------------------------
1714 ! rescode.f
1715 !-----------------------------------------------------------------------------
1716       integer function rescode(iseq,nam,itype,molecule)
1717
1718       use io_base, only: ucase
1719 !      implicit real*8 (a-h,o-z)
1720 !      include 'DIMENSIONS'
1721 !      include 'COMMON.NAMES'
1722 !      include 'COMMON.IOUNITS'
1723       character(len=3) :: nam   !,ucase
1724       integer :: iseq,itype,i
1725       integer :: molecule
1726       print *,molecule,nam
1727       if (molecule.eq.1) then 
1728       if (itype.eq.0) then
1729
1730       do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
1731         if (ucase(nam).eq.restyp(i,molecule)) then
1732           rescode=i
1733           return
1734         endif
1735       enddo
1736
1737       else
1738
1739       do i=-ntyp1_molec(molecule),ntyp1_molec(molecule)
1740         if (nam(1:1).eq.onelet(i)) then
1741           rescode=i
1742           return  
1743         endif  
1744       enddo
1745
1746       endif
1747       else if (molecule.eq.2) then
1748       do i=1,ntyp1_molec(molecule)
1749          print *,nam(1:1),restyp(i,molecule)(1:1) 
1750         if (nam(1:1).eq.restyp(i,molecule)(1:1)) then
1751           rescode=i
1752           return
1753         endif
1754       enddo
1755       else if (molecule.eq.3) then
1756        write(iout,*) "SUGAR not yet implemented"
1757        stop
1758       else if (molecule.eq.4) then
1759        write(iout,*) "Explicit LIPID not yet implemented"
1760        stop
1761       else if (molecule.eq.5) then
1762       do i=1,ntyp1_molec(molecule)
1763         print *,i,restyp(i,molecule)
1764         if (ucase(nam).eq.restyp(i,molecule)) then
1765           rescode=i
1766           return
1767         endif
1768       enddo
1769       else   
1770        write(iout,*) "molecule not defined"
1771       endif
1772       write (iout,10) iseq,nam
1773       stop
1774    10 format ('**** Error - residue',i4,' has an unresolved name ',a3)
1775       end function rescode
1776       integer function sugarcode(sugar,ires)
1777       character sugar
1778       integer ires
1779       if (sugar.eq.'D') then
1780         sugarcode=1
1781       else if (sugar.eq.' ') then
1782         sugarcode=2
1783       else
1784         write (iout,*) 'UNKNOWN sugar type for residue',ires,' ',sugar
1785         stop
1786       endif
1787       return
1788       end function sugarcode
1789
1790 !-----------------------------------------------------------------------------
1791 ! timing.F
1792 !-----------------------------------------------------------------------------
1793 ! $Date: 1994/10/05 16:41:52 $
1794 ! $Revision: 2.2 $
1795 !
1796       subroutine set_timers
1797 !
1798 !el      implicit none
1799 !el      real(kind=8) :: tcpu
1800 !      include 'COMMON.TIME1'
1801 !#ifdef MP
1802 #ifdef MPI
1803       include 'mpif.h'
1804 #endif
1805 ! Diminish the assigned time limit a little so that there is some time to
1806 ! end a batch job
1807 !     timlim=batime-150.0
1808 ! Calculate the initial time, if it is not zero (e.g. for the SUN).
1809       stime=tcpu()
1810 #if .not. defined(WHAM_RUN) && .not. defined(CLUSTER)
1811 #ifdef MPI
1812       walltime=MPI_WTIME()
1813       time_reduce=0.0d0
1814       time_allreduce=0.0d0
1815       time_bcast=0.0d0
1816       time_gather=0.0d0
1817       time_sendrecv=0.0d0
1818       time_scatter=0.0d0
1819       time_scatter_fmat=0.0d0
1820       time_scatter_ginv=0.0d0
1821       time_scatter_fmatmult=0.0d0
1822       time_scatter_ginvmult=0.0d0
1823       time_barrier_e=0.0d0
1824       time_barrier_g=0.0d0
1825       time_enecalc=0.0d0
1826       time_sumene=0.0d0
1827       time_lagrangian=0.0d0
1828       time_sumgradient=0.0d0
1829       time_intcartderiv=0.0d0
1830       time_inttocart=0.0d0
1831       time_ginvmult=0.0d0
1832       time_fricmatmult=0.0d0
1833       time_cartgrad=0.0d0
1834       time_bcastc=0.0d0
1835       time_bcast7=0.0d0
1836       time_bcastw=0.0d0
1837       time_intfcart=0.0d0
1838       time_vec=0.0d0
1839       time_mat=0.0d0
1840       time_fric=0.0d0
1841       time_stoch=0.0d0
1842       time_fricmatmult=0.0d0
1843       time_fsample=0.0d0
1844 #endif
1845 #endif
1846 !d    print *,' in SET_TIMERS stime=',stime
1847       return
1848       end subroutine set_timers
1849 !-----------------------------------------------------------------------------
1850 #ifndef CLUSTER
1851       logical function stopx(nf)
1852 ! This function returns .true. if one of the following reasons to exit SUMSL
1853 ! occurs. The "reason" code is stored in WHATSUP passed thru a COMMON block:
1854 !
1855 !... WHATSUP = 0 - go on, no reason to stop. Stopx will return .false.
1856 !...           1 - Time up in current node;
1857 !...           2 - STOP signal was received from another node because the
1858 !...               node's task was accomplished (parallel only);
1859 !...          -1 - STOP signal was received from another node because of error;
1860 !...          -2 - STOP signal was received from another node, because 
1861 !...               the node's time was up.
1862 !      implicit real*8 (a-h,o-z)
1863 !      include 'DIMENSIONS'
1864 !el#ifdef WHAM_RUN
1865 !el      use control_data, only:WhatsUp
1866 !el#endif
1867 #ifdef MP
1868 !el      use MPI_data   !include 'COMMON.INFO'
1869       include 'mpif.h'
1870 #endif
1871       integer :: nf
1872 !el      logical :: ovrtim
1873
1874 !      include 'COMMON.IOUNITS'
1875 !      include 'COMMON.TIME1'
1876       integer :: Kwita
1877
1878 !d    print *,'Processor',MyID,' NF=',nf
1879 !d      write (iout,*) "stopx: ",nf
1880 #ifndef WHAM_RUN
1881 #ifndef MPI
1882       if (ovrtim()) then
1883 ! Finish if time is up.
1884          stopx = .true.
1885          WhatsUp=1
1886 #ifdef MPL
1887       else if (mod(nf,100).eq.0) then
1888 ! Other processors might have finished. Check this every 100th function 
1889 ! evaluation.
1890 ! Master checks if any other processor has sent accepted conformation(s) to it. 
1891          if (MyID.ne.MasterID) call receive_mcm_info
1892          if (MyID.eq.MasterID) call receive_conf
1893 !d       print *,'Processor ',MyID,' is checking STOP: nf=',nf
1894          call recv_stop_sig(Kwita)
1895          if (Kwita.eq.-1) then
1896            write (iout,'(a,i4,a,i5)') 'Processor',&
1897            MyID,' has received STOP signal in STOPX; NF=',nf
1898            write (*,'(a,i4,a,i5)') 'Processor',&
1899            MyID,' has received STOP signal in STOPX; NF=',nf
1900            stopx=.true.
1901            WhatsUp=2
1902          elseif (Kwita.eq.-2) then
1903            write (iout,*) &
1904           'Processor',MyID,' received TIMEUP-STOP signal in SUMSL.'
1905            write (*,*) &
1906           'Processor',MyID,' received TIMEUP-STOP signal in SUMSL.'
1907            WhatsUp=-2
1908            stopx=.true.  
1909          else if (Kwita.eq.-3) then
1910            write (iout,*) &
1911           'Processor',MyID,' received ERROR-STOP signal in SUMSL.'
1912            write (*,*) &
1913           'Processor',MyID,' received ERROR-STOP signal in SUMSL.'
1914            WhatsUp=-1
1915            stopx=.true.
1916          else
1917            stopx=.false.
1918            WhatsUp=0
1919          endif
1920 #endif
1921       else
1922          stopx = .false.
1923          WhatsUp=0
1924       endif
1925 #else
1926       stopx=.false.
1927 !d      write (iout,*) "stopx set at .false."
1928 #endif
1929
1930 #ifdef OSF
1931 ! Check for FOUND_NAN flag
1932       if (FOUND_NAN) then
1933         write(iout,*)"   ***   stopx : Found a NaN"
1934         stopx=.true.
1935       endif
1936 #endif
1937 #else
1938       if (ovrtim()) then
1939 ! Finish if time is up.
1940          stopx = .true.
1941          WhatsUp=1
1942       else if (cutoffviol) then
1943         stopx = .true.
1944         WhatsUp=2
1945       else
1946         stopx=.false.
1947       endif
1948 #endif
1949       return
1950       end function stopx
1951 !-----------------------------------------------------------------------------
1952 #else
1953       logical function stopx(nf)
1954 !
1955 !     ..................................................................
1956 !
1957 !     *****PURPOSE...
1958 !     THIS FUNCTION MAY SERVE AS THE STOPX (ASYNCHRONOUS INTERRUPTION)
1959 !     FUNCTION FOR THE NL2SOL (NONLINEAR LEAST-SQUARES) PACKAGE AT
1960 !     THOSE INSTALLATIONS WHICH DO NOT WISH TO IMPLEMENT A
1961 !     DYNAMIC STOPX.
1962 !
1963 !     *****ALGORITHM NOTES...
1964 !     AT INSTALLATIONS WHERE THE NL2SOL SYSTEM IS USED
1965 !     INTERACTIVELY, THIS DUMMY STOPX SHOULD BE REPLACED BY A
1966 !     FUNCTION THAT RETURNS .TRUE. IF AND ONLY IF THE INTERRUPT
1967 !     (BREAK) KEY HAS BEEN PRESSED SINCE THE LAST CALL ON STOPX.
1968 !
1969 !     $$$ MODIFIED FOR USE AS  THE TIMER ROUTINE.
1970 !     $$$                              WHEN THE TIME LIMIT HAS BEEN
1971 !     $$$ REACHED     STOPX IS SET TO .TRUE  AND INITIATES (IN ITSUM)
1972 !     $$$ AND ORDERLY EXIT OUT OF SUMSL.  IF ARRAYS IV AND V ARE
1973 !     $$$ SAVED, THE SUMSL ROUTINES CAN BE RESTARTED AT THE SAME
1974 !     $$$ POINT AT WHICH THEY WERE INTERRUPTED.
1975 !
1976 !     ..................................................................
1977 !
1978 !      include 'DIMENSIONS'
1979       integer :: nf
1980 !      logical ovrtim
1981 !      include 'COMMON.IOUNITS'
1982 !      include 'COMMON.TIME1'
1983 #ifdef MPL
1984 !     include 'COMMON.INFO'
1985       integer :: Kwita
1986
1987 !d    print *,'Processor',MyID,' NF=',nf
1988 #endif
1989       if (ovrtim()) then
1990 ! Finish if time is up.
1991          stopx = .true.
1992 #ifdef MPL
1993       else if (mod(nf,100).eq.0) then
1994 ! Other processors might have finished. Check this every 100th function 
1995 ! evaluation.
1996 !d       print *,'Processor ',MyID,' is checking STOP: nf=',nf
1997          call recv_stop_sig(Kwita)
1998          if (Kwita.eq.-1) then
1999            write (iout,'(a,i4,a,i5)') 'Processor',&
2000            MyID,' has received STOP signal in STOPX; NF=',nf
2001            write (*,'(a,i4,a,i5)') 'Processor',&
2002            MyID,' has received STOP signal in STOPX; NF=',nf
2003            stopx=.true.
2004          else
2005            stopx=.false.
2006          endif
2007 #endif
2008       else
2009          stopx = .false.
2010       endif
2011       return
2012       end function stopx
2013 #endif
2014 !-----------------------------------------------------------------------------
2015       logical function ovrtim()
2016
2017 !      include 'DIMENSIONS'
2018 !      include 'COMMON.IOUNITS'
2019 !      include 'COMMON.TIME1'
2020 !el      real(kind=8) :: tcpu
2021       real(kind=8) :: curtim
2022 #ifdef MPI
2023       include "mpif.h"
2024       curtim = MPI_Wtime()-walltime
2025 #else
2026       curtim= tcpu()
2027 #endif
2028 !  curtim is the current time in seconds.
2029 !      write (iout,*) "curtim",curtim," timlim",timlim," safety",safety
2030 #ifndef WHAM_RUN
2031       if (curtim .ge. timlim - safety) then
2032         write (iout,'(a,f10.2,a,f10.2,a,f10.2,a)') &
2033         "***************** Elapsed time (",curtim,&
2034         " s) is within the safety limit (",safety,&
2035         " s) of the allocated time (",timlim," s). Terminating."
2036         ovrtim=.true.
2037       else
2038         ovrtim=.false.
2039       endif
2040 #else
2041       ovrtim=.false.
2042 #endif
2043 !elwrite (iout,*) "ovrtim",ovrtim
2044       return
2045       end function ovrtim
2046 !-----------------------------------------------------------------------------
2047       real(kind=8) function tcpu()
2048
2049 !      include 'COMMON.TIME1'
2050       real(kind=8) :: seconds
2051 #ifdef ES9000
2052 !***************************
2053 ! Next definition for EAGLE (ibm-es9000)
2054       real(kind=8) :: micseconds
2055       integer :: rcode
2056       tcpu=cputime(micseconds,rcode)
2057       tcpu=(micseconds/1.0E6) - stime
2058 !***************************
2059 #endif
2060 #ifdef SUN
2061 !***************************
2062 ! Next definitions for sun
2063       REAL(kind=8) ::  ECPU,ETIME,ETCPU
2064       real(kind=8),dimension(2) :: tarray
2065       tcpu=etime(tarray)
2066       tcpu=tarray(1)
2067 !***************************
2068 #endif
2069 #ifdef KSR
2070 !***************************
2071 ! Next definitions for ksr
2072 ! this function uses the ksr timer ALL_SECONDS from the PMON library to
2073 ! return the elapsed time in seconds
2074       tcpu= all_seconds() - stime
2075 !***************************
2076 #endif
2077 #ifdef SGI
2078 !***************************
2079 ! Next definitions for sgi
2080       real(kind=4) :: timar(2), etime
2081       seconds = etime(timar)
2082 !d    print *,'seconds=',seconds,' stime=',stime
2083 !      usrsec = timar(1)
2084 !      syssec = timar(2)
2085       tcpu=seconds - stime
2086 !***************************
2087 #endif
2088
2089 #ifdef LINUX
2090 !***************************
2091 ! Next definitions for sgi
2092       real(kind=4) :: timar(2), etime
2093       seconds = etime(timar)
2094 !d    print *,'seconds=',seconds,' stime=',stime
2095 !      usrsec = timar(1)
2096 !      syssec = timar(2)
2097       tcpu=seconds - stime
2098 !***************************
2099 #endif
2100
2101
2102 #ifdef CRAY
2103 !***************************
2104 ! Next definitions for Cray
2105 !     call date(curdat)
2106 !     curdat=curdat(1:9)
2107 !     call clock(curtim)
2108 !     curtim=curtim(1:8)
2109       cpusec = second()
2110       tcpu=cpusec - stime
2111 !***************************
2112 #endif
2113 #ifdef AIX
2114 !***************************
2115 ! Next definitions for RS6000
2116        integer(kind=4) :: i1,mclock
2117        i1 = mclock()
2118        tcpu = (i1+0.0D0)/100.0D0
2119 #endif
2120 #ifdef WINPGI
2121 !***************************
2122 ! next definitions for windows NT Digital fortran
2123        real(kind=4) :: time_real
2124        call cpu_time(time_real)
2125        tcpu = time_real
2126 #endif
2127 #ifdef WINIFL
2128 !***************************
2129 ! next definitions for windows NT Digital fortran
2130        real(kind=4) :: time_real
2131        call cpu_time(time_real)
2132        tcpu = time_real
2133 #endif
2134       tcpu = 0d0 !el
2135       return
2136       end function tcpu
2137 !-----------------------------------------------------------------------------
2138 #ifndef CLUSTER
2139       subroutine dajczas(rntime,hrtime,mintime,sectime)
2140
2141 !      include 'COMMON.IOUNITS'
2142       integer :: ihr,imn,isc
2143       real(kind=8) :: rntime,hrtime,mintime,sectime 
2144       hrtime=rntime/3600.0D0 
2145       hrtime=aint(hrtime)
2146       mintime=aint((rntime-3600.0D0*hrtime)/60.0D0)
2147       sectime=aint((rntime-3600.0D0*hrtime-60.0D0*mintime)+0.5D0)
2148       if (sectime.eq.60.0D0) then
2149         sectime=0.0D0
2150         mintime=mintime+1.0D0
2151       endif
2152       ihr=hrtime
2153       imn=mintime
2154       isc=sectime
2155       write (iout,328) ihr,imn,isc
2156   328 FORMAT(//'***** Computation time: ',I4  ,' hours ',I2  ,&
2157                ' minutes ', I2  ,' seconds *****')       
2158       return
2159       end subroutine dajczas
2160 !-----------------------------------------------------------------------------
2161       subroutine print_detailed_timing
2162
2163 !el      use MPI_data
2164 !      implicit real*8 (a-h,o-z)
2165 !      include 'DIMENSIONS'
2166 #ifdef MPI
2167       include 'mpif.h'
2168 #endif
2169 !      include 'COMMON.IOUNITS'
2170 !      include 'COMMON.TIME1'
2171 !      include 'COMMON.SETUP'
2172       real(kind=8) :: time1,time_barrier
2173       time_barrier = 0.0d0
2174 #ifdef MPI !el
2175       time1=MPI_WTIME()
2176 #endif !el
2177          write (iout,'(80(1h=)/a/(80(1h=)))') &
2178           "Details of FG communication time"
2179          write (*,'(7(a40,1pe15.5/),40(1h-)/a40,1pe15.5/80(1h=))') &
2180           "BROADCAST:",time_bcast,"REDUCE:",time_reduce,&
2181           "GATHER:",time_gather,&
2182           "SCATTER:",time_scatter,"SENDRECV:",time_sendrecv,&
2183           "BARRIER ene",time_barrier_e,&
2184           "BARRIER grad",time_barrier_g,&
2185           "TOTAL:",&
2186           time_bcast+time_reduce+time_gather+time_scatter+time_sendrecv
2187          write (*,*) fg_rank,myrank,&
2188            ': Total wall clock time',time1-walltime,' sec'
2189          write (*,*) "Processor",fg_rank,myrank,&
2190            ": BROADCAST time",time_bcast," REDUCE time",&
2191             time_reduce," GATHER time",time_gather," SCATTER time",&
2192             time_scatter,&
2193            " SCATTER fmatmult",time_scatter_fmatmult,&
2194            " SCATTER ginvmult",time_scatter_ginvmult,&
2195            " SCATTER fmat",time_scatter_fmat,&
2196            " SCATTER ginv",time_scatter_ginv,&
2197             " SENDRECV",time_sendrecv,&
2198             " BARRIER ene",time_barrier_e,&
2199             " BARRIER GRAD",time_barrier_g,&
2200             " BCAST7",time_bcast7," BCASTC",time_bcastc,&
2201             " BCASTW",time_bcastw," ALLREDUCE",time_allreduce,&
2202             " TOTAL",&
2203             time_bcast+time_reduce+time_gather+time_scatter+ &
2204             time_sendrecv+time_barrier+time_bcastc
2205 !el#endif
2206          write (*,*) "Processor",fg_rank,myrank," enecalc",time_enecalc
2207          write (*,*) "Processor",fg_rank,myrank," sumene",time_sumene
2208          write (*,*) "Processor",fg_rank,myrank," intfromcart",&
2209            time_intfcart
2210          write (*,*) "Processor",fg_rank,myrank," vecandderiv",&
2211            time_vec
2212          write (*,*) "Processor",fg_rank,myrank," setmatrices",&
2213            time_mat
2214          write (*,*) "Processor",fg_rank,myrank," ginvmult",&
2215            time_ginvmult
2216          write (*,*) "Processor",fg_rank,myrank," fricmatmult",&
2217            time_fricmatmult
2218          write (*,*) "Processor",fg_rank,myrank," inttocart",&
2219            time_inttocart
2220          write (*,*) "Processor",fg_rank,myrank," sumgradient",&
2221            time_sumgradient
2222          write (*,*) "Processor",fg_rank,myrank," intcartderiv",&
2223            time_intcartderiv
2224          if (fg_rank.eq.0) then
2225            write (*,*) "Processor",fg_rank,myrank," lagrangian",&
2226              time_lagrangian
2227            write (*,*) "Processor",fg_rank,myrank," cartgrad",&
2228              time_cartgrad
2229          endif
2230       return
2231       end subroutine print_detailed_timing
2232 #endif
2233 !-----------------------------------------------------------------------------
2234 !-----------------------------------------------------------------------------
2235       end module control