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