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