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