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