update new files
[unres.git] / source / wham / src-M-homology / initialize_p.F
1       subroutine initialize
2
3 C Define constants and zero out tables.
4 C
5       implicit real*8 (a-h,o-z)
6       include 'DIMENSIONS'
7       include 'DIMENSIONS.ZSCOPT'
8 #ifdef MPI
9       include 'mpif.h'
10 #endif
11       include 'COMMON.IOUNITS'
12       include 'COMMON.CHAIN'
13       include 'COMMON.INTERACT'
14       include 'COMMON.GEO'
15       include 'COMMON.LOCAL'
16       include 'COMMON.TORSION'
17       include 'COMMON.FFIELD'
18       include 'COMMON.SBRIDGE'
19       include 'COMMON.MINIM' 
20       include 'COMMON.DERIV'
21       include "COMMON.WEIGHTS"
22       include "COMMON.NAMES"
23       include "COMMON.TIME1"
24 C
25 C The following is just to define auxiliary variables used in angle conversion
26 C
27       pi=4.0D0*datan(1.0D0)
28       dwapi=2.0D0*pi
29       dwapi3=dwapi/3.0D0
30       pipol=0.5D0*pi
31       deg2rad=pi/180.0D0
32       rad2deg=1.0D0/deg2rad
33       angmin=10.0D0*deg2rad
34 C
35 C Define I/O units.
36 C
37       inp=    1
38       iout=   2
39       ipdbin= 3
40       ipdb=   7
41       imol2=  4
42       igeom=  8
43       intin=  9
44       ithep= 11
45       irotam=12
46       itorp= 13
47       itordp= 23
48       ielep= 14
49       isidep=15 
50       isidep1=22
51       iscpp=25
52       icbase=16
53       ifourier=20
54       istat= 17
55       ientin=18
56       ientout=19
57       ibond=28
58       isccor=29
59 C
60 C WHAM files
61 C
62       ihist=30
63       iweight=31
64       izsc=32
65 C Lipidic input file for parameters range 60-79
66       iliptranpar=60
67 C
68 C Set default weights of the energy terms.
69 C
70       wlong=1.0D0
71       welec=1.0D0
72       wtor =1.0D0
73       wang =1.0D0
74       wscloc=1.0D0
75       wstrain=1.0D0
76 C
77 C Zero out tables.
78 C
79       ndih_constr=0
80       do i=1,maxres2
81         do j=1,3
82           c(j,i)=0.0D0
83           dc(j,i)=0.0D0
84         enddo
85       enddo
86       do i=1,maxres
87         do j=1,3
88           xloc(j,i)=0.0D0
89         enddo
90       enddo
91       do i=1,ntyp
92         do j=1,ntyp
93           aa_lip(i,j)=0.0D0
94           bb_lip(i,j)=0.0D0
95           aa_aq(i,j)=0.0D0
96           bb_aq(i,j)=0.0D0
97           augm(i,j)=0.0D0
98           sigma(i,j)=0.0D0
99           r0(i,j)=0.0D0
100           chi(i,j)=0.0D0
101         enddo
102         do j=1,2
103           bad(i,j)=0.0D0
104         enddo
105         chip(i)=0.0D0
106         alp(i)=0.0D0
107         sigma0(i)=0.0D0
108         sigii(i)=0.0D0
109         rr0(i)=0.0D0
110         a0thet(i)=0.0D0
111         do j=1,2
112          do ichir1=-1,1
113           do ichir2=-1,1
114           athet(j,i,ichir1,ichir2)=0.0D0
115           bthet(j,i,ichir1,ichir2)=0.0D0
116           enddo
117          enddo
118         enddo
119         do j=0,3
120           polthet(j,i)=0.0D0
121         enddo
122         do j=1,3
123           gthet(j,i)=0.0D0
124         enddo
125         theta0(i)=0.0D0
126         sig0(i)=0.0D0
127         sigc0(i)=0.0D0
128         do j=1,maxlob
129           bsc(j,i)=0.0D0
130           do k=1,3
131             censc(k,j,i)=0.0D0
132           enddo
133           do k=1,3
134             do l=1,3
135               gaussc(l,k,j,i)=0.0D0
136             enddo
137           enddo
138           nlob(i)=0
139         enddo
140       enddo
141       nlob(ntyp1)=0
142       dsc(ntyp1)=0.0D0
143       do i=-maxtor,maxtor
144         itortyp(i)=0
145        do iblock=1,2
146         do j=-maxtor,maxtor
147           do k=1,maxterm
148             v1(k,j,i,iblock)=0.0D0
149             v2(k,j,i,iblock)=0.0D0
150           enddo
151         enddo
152         enddo
153       enddo
154       do iblock=1,2
155        do i=-maxtor,maxtor
156         do j=-maxtor,maxtor
157          do k=-maxtor,maxtor
158           do l=1,maxtermd_1
159             v1c(1,l,i,j,k,iblock)=0.0D0
160             v1s(1,l,i,j,k,iblock)=0.0D0
161             v1c(2,l,i,j,k,iblock)=0.0D0
162             v1s(2,l,i,j,k,iblock)=0.0D0
163           enddo !l
164           do l=1,maxtermd_2
165            do m=1,maxtermd_2
166             v2c(m,l,i,j,k,iblock)=0.0D0
167             v2s(m,l,i,j,k,iblock)=0.0D0
168            enddo !m
169           enddo !l
170         enddo !k
171        enddo !j
172       enddo !i
173       enddo !iblock
174       do i=1,maxres
175         itype(i)=0
176         itel(i)=0
177       enddo
178 C Initialize the bridge arrays
179       ns=0
180       nss=0 
181       nhpb=0
182       do i=1,maxss
183         iss(i)=0
184       enddo
185       do i=1,maxdim
186         dhpb(i)=0.0D0
187       enddo
188       do i=1,maxres
189         ihpb(i)=0
190         jhpb(i)=0
191         dyn_ss_mask(i)=.false.
192       enddo
193 C
194 C Initialize timing.
195 C
196       call set_timers
197 C
198 C Initialize variables used in minimization.
199 C   
200 c     maxfun=5000
201 c     maxit=2000
202       maxfun=500
203       maxit=200
204       tolf=1.0D-2
205       rtolf=5.0D-4
206
207 C Initialize the variables responsible for the mode of gradient storage.
208 C
209       nfl=0
210       icg=1
211       do i=1,14
212         do j=1,14
213           if (print_order(i).eq.j) then
214             iw(print_order(i))=j
215             goto 1121
216           endif
217         enddo
218 1121    continue
219       enddo
220       calc_grad=.false.
221 C Set timers and counters for the respective routines
222       t_func = 0.0d0
223       t_grad = 0.0d0
224       t_fhel = 0.0d0
225       t_fbet = 0.0d0
226       t_ghel = 0.0d0
227       t_gbet = 0.0d0
228       t_viol = 0.0d0
229       t_gviol = 0.0d0
230       n_func = 0
231       n_grad = 0
232       n_fhel = 0
233       n_fbet = 0
234       n_ghel = 0
235       n_gbet = 0
236       n_viol = 0
237       n_gviol = 0
238       n_map = 0
239 #ifndef SPLITELE
240       nprint_ene=nprint_ene-1
241 #endif
242       return
243       end
244 c-------------------------------------------------------------------------
245       block data nazwy
246       implicit real*8 (a-h,o-z)
247       include 'DIMENSIONS'
248       include 'DIMENSIONS.ZSCOPT'
249       include 'COMMON.NAMES'
250       include 'COMMON.WEIGHTS'
251       include 'COMMON.FFIELD'
252       data restyp /
253      &'DD','DAU','DAI','DDB','DSM','DPR','DLY','DAR','DHI','DAS','DGL',
254      & 'DSG','DGN','DSN','DTH',
255      &'DYY','DAL','DTY','DTR','DVA','DLE','DIL','DPN','MED','DCY','ZER',
256      &'CYS','MET','PHE','ILE','LEU','VAL','TRP','TYR','ALA','GLY','THR',
257      &'SER','GLN','ASN','GLU','ASP','HIS','ARG','LYS','PRO','SME','DBZ',
258      &'AIB','ABU','D'/
259       data onelet /
260      &'z','z','z','z','z','p','k','r','h','d','e','n','q','s','t','g',
261      &'a','y','w','v','l','i','f','m','c','x',
262      &'C','M','F','I','L','V','W','Y','A','G','T',
263      &'S','Q','N','E','D','H','R','K','P','z','z','z','z','X'/
264       data potname /'LJ','LJK','BP','GB','GBV'/
265       data ename / 
266      &   "EVDW SC-SC","EVDW2 SC-p","EES p-p","ECORR4 ","ECORR5 ",
267      &   "ECORR6 ","EELLO ","ETURN3 ","ETURN4 ","ETURN6 ",
268      &   "EBE bend","ESC SCloc","ETORS ","ETORSD ","EHPB","EVDWPP",
269      &   "EVDW2_14","ESTR","ESCCOR","EDIHC","EVDW_T","ELIPTRAN",
270      &   "EAFM","ETHETC","ESHIELD","ESAXS"/
271       data wname /
272      &   "WSC","WSCP","WELEC","WCORR","WCORR5","WCORR6","WEL_LOC",
273      &   "WTURN3","WTURN4","WTURN6","WANG","WSCLOC","WTOR","WTORD",
274      &   "WHPB","WVDWPP","WSCP14","WBOND","WSCCOR","WDIHC","WSC",
275      &   "WLIPTRAN","WAFM","WTHETC","WSHIELD","WSAXS"/
276       data ww0 /1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,
277      &    1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,1.0d0,0.4d0,1.0d0,1.0d0,
278      &    0.0d0,0.0,0.0d0,0.0d0,0.0d0,0.0d0,0.0d0/
279       data nprint_ene /22/
280       data print_order /1,2,3,18,11,12,13,14,4,5,6,7,8,9,10,19,
281      &  16,15,17,20,21,24,22,23,26,0/
282       end 
283 c---------------------------------------------------------------------------
284       subroutine init_int_table
285       implicit real*8 (a-h,o-z)
286       include 'DIMENSIONS'
287       include 'DIMENSIONS.ZSCOPT'
288       include 'DIMENSIONS.FREE'
289 #ifdef MPI
290       include 'mpif.h'
291 #endif
292 #ifdef MP
293       include 'COMMON.INFO'
294 #endif
295       include 'COMMON.CONTROL'
296       include 'COMMON.CHAIN'
297       include 'COMMON.INTERACT'
298       include 'COMMON.LOCAL'
299       include 'COMMON.SBRIDGE'
300       include 'COMMON.IOUNITS'
301       logical scheck,lprint
302 #ifdef MPL
303       integer my_sc_int(0:max_fg_Procs-1),my_sc_intt(0:max_fg_Procs),
304      & my_ele_int(0:max_fg_Procs-1),my_ele_intt(0:max_fg_Procs)
305 C... Determine the numbers of start and end SC-SC interaction 
306 C... to deal with by current processor.
307       lprint=.false.
308       if (lprint)
309      &write (iout,*) 'INIT_INT_TABLE nres=',nres,' nnt=',nnt,' nct=',nct
310       n_sc_int_tot=(nct-nnt+1)*(nct-nnt)/2-nss
311       MyRank=MyID-(MyGroup-1)*fgProcs
312       call int_bounds(n_sc_int_tot,my_sc_inds,my_sc_inde)
313       if (lprint)
314      &  write (iout,*) 'Processor',MyID,' MyRank',MyRank,
315      &  ' n_sc_int_tot',n_sc_int_tot,' my_sc_inds=',my_sc_inds,
316      &  ' my_sc_inde',my_sc_inde
317       ind_sctint=0
318       iatsc_s=0
319       iatsc_e=0
320 #endif
321       lprint=.false.
322       do i=1,maxres
323         nint_gr(i)=0
324         nscp_gr(i)=0
325         do j=1,maxint_gr
326           istart(i,1)=0
327           iend(i,1)=0
328           ielstart(i)=0
329           ielend(i)=0
330           iscpstart(i,1)=0
331           iscpend(i,1)=0    
332         enddo
333       enddo
334       ind_scint=0
335       ind_scint_old=0
336 cd    write (iout,*) 'ns=',ns,' nss=',nss,' ihpb,jhpb',
337 cd   &   (ihpb(i),jhpb(i),i=1,nss)
338       do i=nnt,nct-1
339         scheck=.false.
340         if (dyn_ss) goto 10
341         do ii=1,nss
342           if (ihpb(ii).eq.i+nres) then
343             scheck=.true.
344             jj=jhpb(ii)-nres
345             goto 10
346           endif
347         enddo
348    10   continue
349 cd      write (iout,*) 'i=',i,' scheck=',scheck,' jj=',jj
350         if (scheck) then
351           if (jj.eq.i+1) then
352 #ifdef MPL
353             write (iout,*) 'jj=i+1'
354             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
355      & iatsc_s,iatsc_e,i+2,nct,nint_gr(i),istart(i,1),iend(i,1),*12)
356 #else
357             nint_gr(i)=1
358             istart(i,1)=i+2
359             iend(i,1)=nct
360 #endif
361           else if (jj.eq.nct) then
362 #ifdef MPL
363             write (iout,*) 'jj=nct'
364             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
365      &  iatsc_s,iatsc_e,i+1,nct-1,nint_gr(i),istart(i,1),iend(i,1),*12)
366 #else
367             nint_gr(i)=1
368             istart(i,1)=i+1
369             iend(i,1)=nct-1
370 #endif
371           else
372 #ifdef MPL
373             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
374      & iatsc_s,iatsc_e,i+1,jj-1,nint_gr(i),istart(i,1),iend(i,1),*12)
375             ii=nint_gr(i)+1
376             call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
377      & iatsc_s,iatsc_e,jj+1,nct,nint_gr(i),istart(i,ii),iend(i,ii),*12)
378 #else
379             nint_gr(i)=2
380             istart(i,1)=i+1
381             iend(i,1)=jj-1
382             istart(i,2)=jj+1
383             iend(i,2)=nct
384 #endif
385           endif
386         else
387 #ifdef MPL
388           call int_partition(ind_scint,my_sc_inds,my_sc_inde,i,
389      &    iatsc_s,iatsc_e,i+1,nct,nint_gr(i),istart(i,1),iend(i,1),*12)
390 #else
391           nint_gr(i)=1
392           istart(i,1)=i+1
393           iend(i,1)=nct
394           ind_scint=int_scint+nct-i
395 #endif
396         endif
397 #ifdef MPL
398         ind_scint_old=ind_scint
399 #endif
400       enddo
401    12 continue
402 #ifndef MPL
403       iatsc_s=nnt
404       iatsc_e=nct-1
405 #endif
406 #ifdef MPL
407       if (lprint) then
408         write (iout,*) 'Processor',MyID,' Group',MyGroup
409         write (iout,*) 'iatsc_s=',iatsc_s,' iatsc_e=',iatsc_e
410       endif
411 #endif
412       if (lprint) then
413       write (iout,'(a)') 'Interaction array:'
414       do i=iatsc_s,iatsc_e
415         write (iout,'(i3,2(2x,2i3))') 
416      & i,(istart(i,iint),iend(i,iint),iint=1,nint_gr(i))
417       enddo
418       endif
419       ispp=2
420 #ifdef MPL
421 C Now partition the electrostatic-interaction array
422       npept=nct-nnt
423       nele_int_tot=(npept-ispp)*(npept-ispp+1)/2
424       call int_bounds(nele_int_tot,my_ele_inds,my_ele_inde)
425       if (lprint)
426      & write (iout,*) 'Processor',MyID,' MyRank',MyRank,
427      &  ' nele_int_tot',nele_int_tot,' my_ele_inds=',my_ele_inds,
428      &               ' my_ele_inde',my_ele_inde
429       iatel_s=0
430       iatel_e=0
431       ind_eleint=0
432       ind_eleint_old=0
433       do i=nnt,nct-3
434         ijunk=0
435         call int_partition(ind_eleint,my_ele_inds,my_ele_inde,i,
436      &    iatel_s,iatel_e,i+ispp,nct-1,ijunk,ielstart(i),ielend(i),*13)
437       enddo ! i 
438    13 continue
439 #else
440       iatel_s=nnt
441       iatel_e=nct-3
442       do i=iatel_s,iatel_e
443         ielstart(i)=i+2
444         ielend(i)=nct-1
445       enddo
446 #endif
447       if (lprint) then
448         write (iout,'(a)') 'Electrostatic interaction array:'
449         do i=iatel_s,iatel_e
450           write (iout,'(i3,2(2x,2i3))') i,ielstart(i),ielend(i)
451         enddo
452       endif ! lprint
453 c     iscp=3
454       iscp=2
455 C Partition the SC-p interaction array
456 #ifdef MPL
457       nscp_int_tot=(npept-iscp+1)*(npept-iscp+1)
458       call int_bounds(nscp_int_tot,my_scp_inds,my_scp_inde)
459       if (lprint)
460      & write (iout,*) 'Processor',MyID,' MyRank',MyRank,
461      &  ' nscp_int_tot',nscp_int_tot,' my_scp_inds=',my_scp_inds,
462      &               ' my_scp_inde',my_scp_inde
463       iatscp_s=0
464       iatscp_e=0
465       ind_scpint=0
466       ind_scpint_old=0
467       do i=nnt,nct-1
468         if (i.lt.nnt+iscp) then
469 cd        write (iout,*) 'i.le.nnt+iscp'
470           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
471      &      iatscp_s,iatscp_e,i+iscp,nct,nscp_gr(i),iscpstart(i,1),
472      &      iscpend(i,1),*14)
473         else if (i.gt.nct-iscp) then
474 cd        write (iout,*) 'i.gt.nct-iscp'
475           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
476      &      iatscp_s,iatscp_e,nnt,i-iscp,nscp_gr(i),iscpstart(i,1),
477      &      iscpend(i,1),*14)
478         else
479           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
480      &      iatscp_s,iatscp_e,nnt,i-iscp,nscp_gr(i),iscpstart(i,1),
481      &      iscpend(i,1),*14)
482           ii=nscp_gr(i)+1
483           call int_partition(ind_scpint,my_scp_inds,my_scp_inde,i,
484      &      iatscp_s,iatscp_e,i+iscp,nct,nscp_gr(i),iscpstart(i,ii),
485      &      iscpend(i,ii),*14)
486         endif
487       enddo ! i
488    14 continue
489 #else
490       iatscp_s=nnt
491       iatscp_e=nct-1
492       do i=nnt,nct-1
493         if (i.lt.nnt+iscp) then
494           nscp_gr(i)=1
495           iscpstart(i,1)=i+iscp
496           iscpend(i,1)=nct
497         elseif (i.gt.nct-iscp) then
498           nscp_gr(i)=1
499           iscpstart(i,1)=nnt
500           iscpend(i,1)=i-iscp
501         else
502           nscp_gr(i)=2
503           iscpstart(i,1)=nnt
504           iscpend(i,1)=i-iscp
505           iscpstart(i,2)=i+iscp
506           iscpend(i,2)=nct
507         endif 
508       enddo ! i
509 #endif
510       if (lprint) then
511         write (iout,'(a)') 'SC-p interaction array:'
512         do i=iatscp_s,iatscp_e
513           write (iout,'(i3,2(2x,2i3))') 
514      &         i,(iscpstart(i,j),iscpend(i,j),j=1,nscp_gr(i))
515         enddo
516       endif ! lprint
517 C Partition local interactions
518 #ifdef MPL
519       call int_bounds(nres-2,loc_start,loc_end)
520       loc_start=loc_start+1
521       loc_end=loc_end+1
522       call int_bounds(nres-2,ithet_start,ithet_end)
523       ithet_start=ithet_start+2
524       ithet_end=ithet_end+2
525       call int_bounds(nct-nnt-2,iphi_start,iphi_end) 
526       iphi_start=iphi_start+nnt+2
527       iphi_end=iphi_end+nnt+2
528       call int_bounds(nres-3,itau_start,itau_end)
529       itau_start=itau_start+3
530       itau_end=itau_end+3
531       call int_bounds(nsaxs,isaxs_start,isaxs_end)
532       if (lprint) then 
533         write (iout,*) 'Processor:',MyID,
534      & ' loc_start',loc_start,' loc_end',loc_end,
535      & ' ithet_start',ithet_start,' ithet_end',ithet_end,
536      & ' iphi_start',iphi_start,' iphi_end',iphi_end
537         write (*,*) 'Processor:',MyID,
538      & ' loc_start',loc_start,' loc_end',loc_end,
539      & ' ithet_start',ithet_start,' ithet_end',ithet_end,
540      & ' iphi_start',iphi_start,' iphi_end',iphi_end
541       endif
542       if (fgprocs.gt.1 .and. MyID.eq.BossID) then
543         write(iout,'(i10,a,i10,a,i10,a/a,i3,a)') n_sc_int_tot,' SC-SC ',
544      & nele_int_tot,' electrostatic and ',nscp_int_tot,
545      & ' SC-p interactions','were distributed among',fgprocs,
546      & ' fine-grain processors.'
547       endif
548 #else
549       loc_start=2
550       loc_end=nres-1
551       ithet_start=3
552       ithet_end=nres
553       iphi_start=nnt+3
554       iphi_end=nct
555       itau_start=4
556       itau_end=nres
557       isaxs_start=1
558       isaxs_end=nsaxs
559 #endif
560       return
561       end 
562 c---------------------------------------------------------------------------
563       subroutine int_partition(int_index,lower_index,upper_index,atom,
564      & at_start,at_end,first_atom,last_atom,int_gr,jat_start,jat_end,*)
565       implicit real*8 (a-h,o-z)
566       include 'DIMENSIONS'
567       include 'COMMON.IOUNITS'
568       integer int_index,lower_index,upper_index,atom,at_start,at_end,
569      & first_atom,last_atom,int_gr,jat_start,jat_end
570       logical lprn
571       lprn=.false.
572       if (lprn) write (iout,*) 'int_index=',int_index
573       int_index_old=int_index
574       int_index=int_index+last_atom-first_atom+1
575       if (lprn) 
576      &   write (iout,*) 'int_index=',int_index,
577      &               ' int_index_old',int_index_old,
578      &               ' lower_index=',lower_index,
579      &               ' upper_index=',upper_index,
580      &               ' atom=',atom,' first_atom=',first_atom,
581      &               ' last_atom=',last_atom
582       if (int_index.ge.lower_index) then
583         int_gr=int_gr+1
584         if (at_start.eq.0) then
585           at_start=atom
586           jat_start=first_atom-1+lower_index-int_index_old
587         else
588           jat_start=first_atom
589         endif
590         if (lprn) write (iout,*) 'jat_start',jat_start
591         if (int_index.ge.upper_index) then
592           at_end=atom
593           jat_end=first_atom-1+upper_index-int_index_old
594           return1
595         else
596           jat_end=last_atom
597         endif
598         if (lprn) write (iout,*) 'jat_end',jat_end
599       endif
600       return
601       end
602 c------------------------------------------------------------------------------
603       subroutine hpb_partition
604       implicit real*8 (a-h,o-z)
605       include 'DIMENSIONS'
606       include 'COMMON.SBRIDGE'
607       include 'COMMON.IOUNITS'
608       link_start=1
609       link_end=nhpb
610       link_start_peak=1
611       link_end_peak=npeak
612       write (iout,*) 'HPB_PARTITION',
613      &  ' nhpb',nhpb,' link_start=',link_start,
614      &  ' link_end',link_end,' link_start_peak',link_start_peak,
615      &  ' link_end_peak',link_end_peak
616       return
617       end
618 c------------------------------------------------------------------------------
619       subroutine homology_partition
620       implicit real*8 (a-h,o-z)
621       include 'DIMENSIONS'
622       include 'DIMENSIONS.ZSCOPT'
623       include 'DIMENSIONS.FREE'
624 #ifdef MPI
625       include 'mpif.h'
626 #endif
627       include 'COMMON.SBRIDGE'
628       include 'COMMON.IOUNITS'
629 c      include 'COMMON.SETUP'
630       include 'COMMON.CONTROL'
631       include 'COMMON.CHAIN'
632       include 'COMMON.INTERACT'
633       include 'COMMON.HOMRESTR'
634       write(iout,*)"homology_partition: lim_odl=",lim_odl,
635      &   " lim_dih",lim_dih
636 #ifdef MPL
637       call int_bounds(lim_odl,link_start_homo,link_end_homo)
638       call int_bounds(lim_dih,idihconstr_start_homo,
639      &  idihconstr_end_homo)
640       idihconstr_start_homo=idihconstr_start_homo+nnt-1+3
641       idihconstr_end_homo=idihconstr_end_homo+nnt-1+3
642       if (me.eq.king .or. .not. out1file)
643      &  write (iout,*) 'Processor',fg_rank,' CG group',kolor,
644      &  ' absolute rank',MyRank,
645      &  ' lim_odl',lim_odl,' link_start=',link_start_homo,
646      &  ' link_end',link_end_homo,' lim_dih',lim_dih,
647      &  ' idihconstr_start_homo',idihconstr_start_homo,
648      &  ' idihconstr_end_homo',idihconstr_end_homo
649 #else
650       link_start_homo=1
651       link_end_homo=lim_odl
652       idihconstr_start_homo=nnt+3
653       idihconstr_end_homo=lim_dih+nnt-1+3
654       write (iout,*)
655      &  ' lim_odl',lim_odl,' link_start=',link_start_homo,
656      &  ' link_end',link_end_homo,' lim_dih',lim_dih,
657      &  ' idihconstr_start_homo',idihconstr_start_homo,
658      &  ' idihconstr_end_homo',idihconstr_end_homo
659 #endif
660       return
661       end