introdaction of homology into UNICORN
[unres4.git] / source / unres / io.F90
1       module io
2 !-----------------------------------------------------------------------
3       use io_units
4       use names
5       use io_base
6       use io_config
7       implicit none
8 !-----------------------------------------------------------------------------
9 !
10 !
11 !-----------------------------------------------------------------------------
12       contains
13 !-----------------------------------------------------------------------------
14 ! bank.F    io_csa
15 !-----------------------------------------------------------------------------
16       subroutine write_csa_pdb(var,ene,nft,ik,iw_pdb)
17
18       use csa_data
19       use geometry_data, only:nres,nvar
20       use geometry, only:var_to_geom,chainbuild
21       use compare, only:secondary2
22 !      implicit real*8 (a-h,o-z)
23 !      include 'DIMENSIONS'
24 !      include 'COMMON.CSA'
25 !      include 'COMMON.BANK'
26 !      include 'COMMON.VAR'
27 !      include 'COMMON.IOUNITS'
28 !      include 'COMMON.MINIM'
29 !      include 'COMMON.SETUP'
30 !      include 'COMMON.GEO'
31 !      include 'COMMON.CHAIN'
32 !      include 'COMMON.LOCAL'
33 !      include 'COMMON.INTERACT'
34 !      include 'COMMON.NAMES'
35 !      include 'COMMON.SBRIDGE'
36       integer :: lenpre,lenpot  !,ilen
37 !el      external ilen
38       real(kind=8),dimension(nvar) :: var       !(maxvar)       (maxvar=6*maxres)
39       character(len=50) :: titelloc
40       character(len=3) :: zahl
41       real(kind=8),dimension(mxch*(mxch+1)/2+1) :: ene
42 !el local variables
43       integer :: nft,ik,iw_pdb
44
45       nmin_csa=nmin_csa+1
46       if(ene(1).lt.eglob_csa) then
47         eglob_csa=ene(1)
48         nglob_csa=nglob_csa+1
49         call numstr(nglob_csa,zahl)
50
51         call var_to_geom(nvar,var)
52         call chainbuild
53         call secondary2(.false.)
54
55         lenpre=ilen(prefix)
56         open(icsa_pdb,file=prefix(:lenpre)//'@'//zahl//'.pdb')
57
58         if (iw_pdb.eq.1) then 
59           write(titelloc,'(a2,i3,a3,i9,a3,i6)') &
60           'GM',nglob_csa,' e ',nft,' m ',nmin_csa
61         else
62           write(titelloc,'(a2,i3,a3,i9,a3,i6,a5,f5.2,a5,f5.1)') &
63          'GM',nglob_csa,' e ',nft,' m ',nmin_csa,' rms ',&
64                rmsn(ik),' %NC ',pncn(ik)*100          
65         endif
66         call pdbout(eglob_csa,titelloc,icsa_pdb)
67         close(icsa_pdb)
68       endif
69
70       return
71       end subroutine write_csa_pdb
72 !-----------------------------------------------------------------------------
73 ! csa.f         io_csa
74 !-----------------------------------------------------------------------------
75       subroutine from_pdb(n,idum)
76 ! This subroutine stores the UNRES int variables generated from 
77 ! subroutine readpdb into the 1st conformation of in dihang_in.
78 ! Subsequent n-1 conformations of dihang_in have identical values
79 ! of theta and phi as the 1st conformation but random values for
80 ! alph and omeg.
81 ! The array cref (also generated from subroutine readpdb) is stored
82 ! to crefjlee to be used for rmsd calculation in CSA, if necessary.
83
84       use csa_data
85       use geometry_data
86       use random, only: ran1
87 !      implicit real*8 (a-h,o-z)
88 !      include 'DIMENSIONS'
89 !      include 'COMMON.IOUNITS'
90 !      include 'COMMON.CHAIN'
91 !      include 'COMMON.VAR'
92 !      include 'COMMON.BANK'
93 !      include 'COMMON.GEO'
94 !el local variables
95       integer :: n,idum,m,i,j,k,kk,kkk
96       real(kind=8) :: e
97
98       m=1
99       do j=2,nres-1
100         dihang_in(1,j,1,m)=theta(j+1)
101         dihang_in(2,j,1,m)=phi(j+2)
102         dihang_in(3,j,1,m)=alph(j)
103         dihang_in(4,j,1,m)=omeg(j)
104       enddo
105       dihang_in(2,nres-1,1,k)=0.0d0
106
107       do m=2,n
108        do k=2,nres-1
109         dihang_in(1,k,1,m)=dihang_in(1,k,1,1)
110         dihang_in(2,k,1,m)=dihang_in(2,k,1,1)
111         if(dabs(dihang_in(3,k,1,1)).gt.1.d-6) then
112          dihang_in(3,k,1,m)=90.d0*ran1(idum)+90.d0
113          dihang_in(3,k,1,m)=dihang_in(3,k,1,m)*deg2rad
114         endif
115         if(dabs(dihang_in(4,k,1,1)).gt.1.d-6) then
116          dihang_in(4,k,1,m)=360.d0*ran1(idum)-180.d0
117          dihang_in(4,k,1,m)=dihang_in(4,k,1,m)*deg2rad
118         endif
119        enddo
120       enddo
121
122 ! Store cref to crefjlee (they are in COMMON.CHAIN).
123       do k=1,2*nres
124        do kk=1,3
125         kkk=1
126         crefjlee(kk,k)=cref(kk,k,kkk)
127        enddo
128       enddo
129
130       open(icsa_native_int,file=csa_native_int,status="old")
131       do m=1,n
132          write(icsa_native_int,*) m,e
133          write(icsa_native_int,200) &
134           (dihang_in(1,k,1,m)*rad2deg,k=2,nres-1)
135          write(icsa_native_int,200) &
136           (dihang_in(2,k,1,m)*rad2deg,k=2,nres-2)
137          write(icsa_native_int,200) &
138           (dihang_in(3,k,1,m)*rad2deg,k=2,nres-1)
139          write(icsa_native_int,200) &
140           (dihang_in(4,k,1,m)*rad2deg,k=2,nres-1)
141       enddo
142
143       do k=1,nres
144        write(icsa_native_int,200) (crefjlee(i,k),i=1,3)
145       enddo
146       close(icsa_native_int)
147
148   200 format (8f10.4)
149
150       return
151       end subroutine from_pdb
152 !-----------------------------------------------------------------------------
153       subroutine from_int(n,mm,idum)
154
155       use csa_data
156       use geometry_data
157       use energy_data
158       use geometry, only:chainbuild,gen_side
159       use energy, only:etotal
160       use compare
161 !      implicit real*8 (a-h,o-z)
162 !      include 'DIMENSIONS'
163 !      include 'COMMON.IOUNITS'
164 !      include 'COMMON.CHAIN'
165 !      include 'COMMON.VAR'
166 !      include 'COMMON.INTERACT'
167 !      include 'COMMON.BANK'
168 !      include 'COMMON.GEO'
169 !      include 'COMMON.CONTACTS'
170 !      integer ilen
171 !el      external ilen
172       logical :: fail
173       real(kind=8),dimension(0:n_ene) :: energia
174 !el local variables
175       integer :: n,mm,idum,i,ii,j,m,k,kk,maxcount_fail,icount_fail,maxsi
176       real(kind=8) :: co
177
178       open(icsa_native_int,file=csa_native_int,status="old")
179       read (icsa_native_int,*)
180       call read_angles(icsa_native_int,*10)
181       goto 11
182    10 write (iout,'(2a)') "CHUJ NASTAPIL - error in ",&
183         csa_native_int(:ilen(csa_native_int))
184    11 continue
185       call intout
186       do j=2,nres-1
187         dihang_in(1,j,1,1)=theta(j+1)
188         dihang_in(2,j,1,1)=phi(j+2)
189         dihang_in(3,j,1,1)=alph(j)
190         dihang_in(4,j,1,1)=omeg(j)
191       enddo
192       dihang_in(2,nres-1,1,1)=0.0d0
193
194 !         read(icsa_native_int,*) ind,e
195 !         read(icsa_native_int,200) (dihang_in(1,k,1,1),k=2,nres-1)
196 !         read(icsa_native_int,200) (dihang_in(2,k,1,1),k=2,nres-2)
197 !         read(icsa_native_int,200) (dihang_in(3,k,1,1),k=2,nres-1)
198 !         read(icsa_native_int,200) (dihang_in(4,k,1,1),k=2,nres-1)
199 !         dihang_in(2,nres-1,1,1)=0.d0
200
201          maxsi=100
202          maxcount_fail=100
203
204          do m=mm+2,n
205 !          do k=2,nres-1
206 !           dihang_in(1,k,1,m)=dihang_in(1,k,1,1)
207 !           dihang_in(2,k,1,m)=dihang_in(2,k,1,1)
208 !           if(abs(dihang_in(3,k,1,1)).gt.1.d-3) then
209 !            dihang_in(3,k,1,m)=90.d0*ran1(idum)+90.d0
210 !           endif
211 !           if(abs(dihang_in(4,k,1,1)).gt.1.d-3) then
212 !            dihang_in(4,k,1,m)=360.d0*ran1(idum)-180.d0
213 !           endif
214 !          enddo
215 !           call intout
216            fail=.true.
217
218            icount_fail=0
219
220            DO WHILE (FAIL .AND. ICOUNT_FAIL .LE. MAXCOUNT_FAIL)
221
222            do i=nnt,nct
223              if (itype(i,1).ne.10) then
224 !d             print *,'i=',i,' itype=',itype(i,1),' theta=',theta(i+1)
225                fail=.true.
226                ii=0
227                do while (fail .and. ii .le. maxsi)
228                  call gen_side(itype(i,1),theta(i+1),alph(i),omeg(i),fail,molnum(i))
229                  ii = ii+1
230                enddo
231              endif
232            enddo
233            call chainbuild
234            call etotal(energia)
235            fail = (energia(0).ge.1.0d20)
236            icount_fail=icount_fail+1
237
238            ENDDO
239
240            if (icount_fail.gt.maxcount_fail) then
241              write (iout,*) &
242              'Failed to generate non-overlaping near-native conf.',&
243              m
244            endif
245
246            do j=2,nres-1
247              dihang_in(1,j,1,m)=theta(j+1)
248              dihang_in(2,j,1,m)=phi(j+2)
249              dihang_in(3,j,1,m)=alph(j)
250              dihang_in(4,j,1,m)=omeg(j)
251            enddo
252            dihang_in(2,nres-1,1,m)=0.0d0
253          enddo
254
255 !      do m=1,n
256 !        write(icsa_native_int,*) m,e
257 !         write(icsa_native_int,200) (dihang_in(1,k,1,m),k=2,nres-1)
258 !         write(icsa_native_int,200) (dihang_in(2,k,1,m),k=2,nres-2)
259 !         write(icsa_native_int,200) (dihang_in(3,k,1,m),k=2,nres-1)
260 !         write(icsa_native_int,200) (dihang_in(4,k,1,m),k=2,nres-1)
261 !      enddo
262 !     close(icsa_native_int)
263
264 !      do m=mm+2,n
265 !       do i=1,4
266 !        do j=2,nres-1
267 !         dihang_in(i,j,1,m)=dihang_in(i,j,1,m)*deg2rad
268 !        enddo
269 !       enddo
270 !      enddo
271
272       call dihang_to_c(dihang_in(1,1,1,1))
273
274 ! Store c to cref (they are in COMMON.CHAIN).
275       do k=1,2*nres
276        do kk=1,3
277         crefjlee(kk,k)=c(kk,k)
278        enddo
279       enddo
280
281       call contact(.true.,ncont_ref,icont_ref,co)
282
283 !      do k=1,nres
284 !       write(icsa_native_int,200) (crefjlee(i,k),i=1,3)
285 !      enddo
286       close(icsa_native_int)
287
288   200 format (8f10.4)
289
290       return
291       end subroutine from_int
292 !-----------------------------------------------------------------------------
293       subroutine dihang_to_c(aarray)
294
295       use geometry_data
296       use csa_data
297       use geometry, only:chainbuild
298 !      implicit real*8 (a-h,o-z)
299 !      include 'DIMENSIONS'
300 !      include 'COMMON.CSA'
301 !      include 'COMMON.BANK'
302 !      include 'COMMON.CHAIN'
303 !      include 'COMMON.GEO'
304 !      include 'COMMON.VAR'
305       integer :: i
306       real(kind=8),dimension(mxang,nres,mxch) :: aarray !(mxang,maxres,mxch)
307
308 !     do i=4,nres
309 !      phi(i)=dihang_in(1,i-2,1,1)
310 !     enddo
311       do i=2,nres-1
312        theta(i+1)=aarray(1,i,1)
313        phi(i+2)=aarray(2,i,1)
314        alph(i)=aarray(3,i,1)
315        omeg(i)=aarray(4,i,1)
316       enddo
317
318       call chainbuild
319
320       return
321       end subroutine dihang_to_c
322 !-----------------------------------------------------------------------------
323 ! geomout.F
324 !-----------------------------------------------------------------------------
325 #ifdef NOXDR
326       subroutine cartout(time)
327 #else
328       subroutine cartoutx(time)
329 #endif
330       use geometry_data, only: c,nres
331       use energy_data
332       use MD_data, only: potE,t_bath
333 !      implicit real*8 (a-h,o-z)
334 !      include 'DIMENSIONS'
335 !      include 'COMMON.CHAIN'
336 !      include 'COMMON.INTERACT'
337 !      include 'COMMON.NAMES'
338 !      include 'COMMON.IOUNITS'
339 !      include 'COMMON.HEADER'
340 !      include 'COMMON.SBRIDGE'
341 !      include 'COMMON.DISTFIT'
342 !      include 'COMMON.MD'
343       real(kind=8) :: time
344 !el  local variables
345       integer :: j,k,i
346
347 #if defined(AIX) || defined(PGI)
348       open(icart,file=cartname,position="append")
349 #else
350       open(icart,file=cartname,access="append")
351 #endif
352       write (icart,'(e15.8,2e15.5,f12.5,$)') time,potE,uconst,t_bath
353       if (dyn_ss) then
354        write (icart,'(i4,$)') &
355          nss,(idssb(j)+nres,jdssb(j)+nres,j=1,nss)       
356       else
357        write (icart,'(i4,$)') &
358          nss,(ihpb(j),jhpb(j),j=1,nss)
359        endif
360        write (icart,'(i4,20f7.4)') nfrag+npair+3*nfrag_back,&
361        (qfrag(i),i=1,nfrag),(qpair(i),i=1,npair),&
362        (utheta(i),ugamma(i),uscdiff(i),i=1,nfrag_back)
363       write (icart,'(8f10.5)') &
364        ((c(k,j),k=1,3),j=1,nres),&
365        ((c(k,j+nres),k=1,3),j=nnt,nct)
366       close(icart)
367       return
368
369 #ifdef NOXDR
370       end subroutine cartout
371 #else
372       end subroutine cartoutx
373 #endif
374 !-----------------------------------------------------------------------------
375 #ifndef NOXDR
376       subroutine cartout(time)
377 !      implicit real*8 (a-h,o-z)
378 !      include 'DIMENSIONS'
379       use geometry_data, only: c,nres
380       use energy_data
381       use MD_data, only: potE,t_bath
382 #ifdef MPI
383       use MPI_data
384       include 'mpif.h'
385 !      include 'COMMON.SETUP'
386 #else
387       integer,parameter :: me=0
388 #endif
389 !      include 'COMMON.CHAIN'
390 !      include 'COMMON.INTERACT'
391 !      include 'COMMON.NAMES'
392 !      include 'COMMON.IOUNITS'
393 !      include 'COMMON.HEADER'
394 !      include 'COMMON.SBRIDGE'
395 !      include 'COMMON.DISTFIT'
396 !      include 'COMMON.MD'
397       real(kind=8) :: time
398       integer :: iret,itmp
399       real(kind=4) :: prec
400       real(kind=4),dimension(3,2*nres+2) :: xcoord      !(3,maxres2+2)  (maxres2=2*maxres
401 !el  local variables
402       integer :: j,i,ixdrf
403
404 #ifdef AIX
405       call xdrfopen_(ixdrf,cartname, "a", iret)
406       call xdrffloat_(ixdrf, real(time), iret)
407       call xdrffloat_(ixdrf, real(potE), iret)
408       call xdrffloat_(ixdrf, real(uconst), iret)
409       call xdrffloat_(ixdrf, real(uconst_back), iret)
410       call xdrffloat_(ixdrf, real(t_bath), iret)
411       call xdrfint_(ixdrf, nss, iret) 
412       do j=1,nss
413        if (dyn_ss) then
414         call xdrfint_(ixdrf, idssb(j)+nres, iret)
415         call xdrfint_(ixdrf, jdssb(j)+nres, iret)
416        else
417         call xdrfint_(ixdrf, ihpb(j), iret)
418         call xdrfint_(ixdrf, jhpb(j), iret)
419        endif
420       enddo
421       call xdrfint_(ixdrf, nfrag+npair+3*nfrag_back, iret)
422       do i=1,nfrag
423         call xdrffloat_(ixdrf, real(qfrag(i)), iret)
424       enddo
425       do i=1,npair
426         call xdrffloat_(ixdrf, real(qpair(i)), iret)
427       enddo
428       do i=1,nfrag_back
429         call xdrffloat_(ixdrf, real(utheta(i)), iret)
430         call xdrffloat_(ixdrf, real(ugamma(i)), iret)
431         call xdrffloat_(ixdrf, real(uscdiff(i)), iret)
432       enddo
433 #else
434       call xdrfopen(ixdrf,cartname, "a", iret)
435       call xdrffloat(ixdrf, real(time), iret)
436       call xdrffloat(ixdrf, real(potE), iret)
437       call xdrffloat(ixdrf, real(uconst), iret)
438       call xdrffloat(ixdrf, real(uconst_back), iret)
439       call xdrffloat(ixdrf, real(t_bath), iret)
440       call xdrfint(ixdrf, nss, iret) 
441       do j=1,nss
442        if (dyn_ss) then
443         call xdrfint(ixdrf, idssb(j)+nres, iret)
444         call xdrfint(ixdrf, jdssb(j)+nres, iret)
445        else
446         call xdrfint(ixdrf, ihpb(j), iret)
447         call xdrfint(ixdrf, jhpb(j), iret)
448        endif
449       enddo
450       call xdrfint(ixdrf, nfrag+npair+3*nfrag_back, iret)
451       do i=1,nfrag
452         call xdrffloat(ixdrf, real(qfrag(i)), iret)
453       enddo
454       do i=1,npair
455         call xdrffloat(ixdrf, real(qpair(i)), iret)
456       enddo
457       do i=1,nfrag_back
458         call xdrffloat(ixdrf, real(utheta(i)), iret)
459         call xdrffloat(ixdrf, real(ugamma(i)), iret)
460         call xdrffloat(ixdrf, real(uscdiff(i)), iret)
461       enddo
462 #endif
463       prec=10000.0
464       do i=1,nres
465        do j=1,3
466         xcoord(j,i)=c(j,i)
467        enddo
468       enddo
469       do i=nnt,nct
470        do j=1,3
471         xcoord(j,nres+i-nnt+1)=c(j,i+nres)
472        enddo
473       enddo
474
475       itmp=nres+nct-nnt+1
476 #ifdef AIX
477       call xdrf3dfcoord_(ixdrf, xcoord, itmp, prec, iret)
478       call xdrfclose_(ixdrf, iret)
479 #else
480       call xdrf3dfcoord(ixdrf, xcoord, itmp, prec, iret)
481       call xdrfclose(ixdrf, iret)
482 #endif
483       return
484       end subroutine cartout
485 #endif
486 !-----------------------------------------------------------------------------
487       subroutine statout(itime)
488
489       use energy_data
490       use control_data
491       use MD_data
492       use MPI_data
493       use compare, only:rms_nac_nnc
494 !      implicit real*8 (a-h,o-z)
495 !      include 'DIMENSIONS'
496 !      include 'COMMON.CONTROL'
497 !      include 'COMMON.CHAIN'
498 !      include 'COMMON.INTERACT'
499 !      include 'COMMON.NAMES'
500 !      include 'COMMON.IOUNITS'
501 !      include 'COMMON.HEADER'
502 !      include 'COMMON.SBRIDGE'
503 !      include 'COMMON.DISTFIT'
504 !      include 'COMMON.MD'
505 !      include 'COMMON.REMD'
506 !      include 'COMMON.SETUP'
507       integer :: itime
508       real(kind=8),dimension(0:n_ene) :: energia
509 !      double precision gyrate
510 !el      external gyrate
511 !el      common /gucio/ cm
512       character(len=256) :: line1,line2
513       character(len=4) :: format1,format2
514       character(len=30) :: format
515 !el  local variables
516       integer :: i,ii1,ii2,j
517       real(kind=8) :: rms,frac,frac_nn,co,distance
518
519 #ifdef AIX
520       if(itime.eq.0) then
521        open(istat,file=statname,position="append")
522       endif
523 #else
524 #ifdef PGI
525       open(istat,file=statname,position="append")
526 #else
527       open(istat,file=statname,access="append")
528 #endif
529 #endif
530        if (AFMlog.gt.0) then
531        if (refstr) then
532          call rms_nac_nnc(rms,frac,frac_nn,co,.false.)
533           write (line1,'(i10,f15.2,3f12.3,f7.2,2f6.3,4f12.3,i5,$)')&
534                itime,totT,EK,potE,totE,&
535                rms,frac,frac_nn,kinetic_T,t_bath,gyrate(),&
536                potEcomp(23),me
537           format1="a133"
538          else
539 !C          print *,'A CHUJ',potEcomp(23)
540           write (line1,'(i10,f15.2,7f12.3,i5,$)') &
541                 itime,totT,EK,potE,totE,&
542                 kinetic_T,t_bath,gyrate(),&
543                 potEcomp(23),me
544           format1="a114"
545         endif
546        else if (selfguide.gt.0) then
547        distance=0.0
548        do j=1,3
549        distance=distance+(c(j,afmend)-c(j,afmbeg))**2
550        enddo
551        distance=dsqrt(distance)
552        if (refstr) then
553          call rms_nac_nnc(rms,frac,frac_nn,co,.false.)
554           write (line1,'(i10,f15.2,3f12.3,f7.2,2f6.3,f12.3,f10.1,2f8.2, &
555          f9.3,i5,$)') &
556                itime,totT,EK,potE,totE,&
557                rms,frac,frac_nn,kinetic_T,t_bath,gyrate(),&
558                distance,potEcomp(23),me
559           format1="a133"
560 !C          print *,"CHUJOWO"
561          else
562 !C          print *,'A CHUJ',potEcomp(23)
563           write (line1,'(i10,f15.2,8f12.3,i5,$)')&
564                 itime,totT,EK,potE,totE, &
565                 kinetic_T,t_bath,gyrate(),&
566                 distance,potEcomp(23),me
567           format1="a114"
568         endif
569        else
570        if (refstr) then
571          call rms_nac_nnc(rms,frac,frac_nn,co,.false.)
572           write (line1,'(i10,f15.2,3f12.3,f7.2,4f6.3,3f12.3,i5,$)') &
573                 itime,totT,EK,potE,totE,&
574                 rms,frac,frac_nn,co,amax,kinetic_T,t_bath,gyrate(),me
575           format1="a133"
576         else
577           write (line1,'(i10,f15.2,7f12.3,i5,$)') &
578                  itime,totT,EK,potE,totE,&
579                  amax,kinetic_T,t_bath,gyrate(),me
580           format1="a114"
581         endif
582         ENDIF
583         if(usampl.and.totT.gt.eq_time) then
584            write(line2,'(i5,2f9.4,300f7.4)') iset,uconst,uconst_back,&
585             (qfrag(ii1),ii1=1,nfrag),(qpair(ii2),ii2=1,npair),&
586             (utheta(i),ugamma(i),uscdiff(i),i=1,nfrag_back)
587            write(format2,'(a1,i3.3)') "a",23+7*nfrag+7*npair &
588                    +21*nfrag_back
589         else
590            format2="a001"
591            line2=' '
592         endif
593         if (print_compon) then
594           if(itime.eq.0) then
595            write(format,'(a1,a4,a1,a4,a10)') "(",format1,",",format2,&
596                                                            ",20a12)"
597            write (istat,format) "#","",&
598             (ename(print_order(i)),i=1,nprint_ene)
599           endif
600           write(format,'(a1,a4,a1,a4,a10)') "(",format1,",",format2,&
601                                                            ",20f12.3)"
602           write (istat,format) line1,line2,&
603             (potEcomp(print_order(i)),i=1,nprint_ene)
604         else
605           write(format,'(a1,a4,a1,a4,a1)') "(",format1,",",format2,")"
606           write (istat,format) line1,line2
607         endif
608 #if defined(AIX)
609         call flush(istat)
610 #else
611         close(istat)
612 #endif
613       return
614       end subroutine  statout
615 !-----------------------------------------------------------------------------
616 ! readrtns_CSA.F
617 !-----------------------------------------------------------------------------
618       subroutine readrtns
619
620       use control_data
621       use energy_data
622       use MPI_data
623       use muca_md, only:read_muca
624 !      implicit real*8 (a-h,o-z)
625 !      include 'DIMENSIONS'
626 #ifdef MPI
627       include 'mpif.h'
628 #endif
629 !      include 'COMMON.SETUP'
630 !      include 'COMMON.CONTROL'
631 !      include 'COMMON.SBRIDGE'
632 !      include 'COMMON.IOUNITS'
633       logical :: file_exist
634       integer :: i
635 ! Read force-field parameters except weights
636 !      call parmread
637 ! Read job setup parameters
638       call read_control
639 ! Read force-field parameters except weights
640       call parmread
641
642 ! Read control parameters for energy minimzation if required
643       if (minim) call read_minim
644 ! Read MCM control parameters if required
645       if (modecalc.eq.3 .or. modecalc.eq.6) call mcmread
646 ! Read MD control parameters if reqjuired
647       if (modecalc.eq.12) call read_MDpar
648 ! Read MREMD control parameters if required
649       if (modecalc.eq.14) then 
650          call read_MDpar
651          call read_REMDpar
652       endif
653 ! Read MUCA control parameters if required
654       if (lmuca) call read_muca
655 ! Read CSA control parameters if required (from fort.40 if exists
656 ! otherwise from general input file)
657       if (modecalc.eq.8) then
658        inquire (file="fort.40",exist=file_exist)
659        if (.not.file_exist) call csaread
660       endif 
661 !fmc      if (modecalc.eq.10) call mcmfread
662 ! Read molecule information, molecule geometry, energy-term weights, and
663 ! restraints if requested
664       call molread
665 ! Print restraint information
666 #ifdef MPI
667       if (.not. out1file .or. me.eq.king) then
668 #endif
669       if (nhpb.gt.nss) &
670       write (iout,'(a,i5,a)') "The following",nhpb-nss,&
671        " distance constraints have been imposed"
672       do i=nss+1,nhpb
673         write (iout,'(3i6,f10.5)') i-nss,ihpb(i),jhpb(i),forcon(i)
674       enddo
675 #ifdef MPI
676       endif
677 #endif
678 !      print *,"Processor",myrank," leaves READRTNS"
679 !      write(iout,*) "end readrtns"
680       return
681       end subroutine readrtns
682 !-----------------------------------------------------------------------------
683       subroutine molread
684 !
685 ! Read molecular data.
686 !
687 !      use control, only: ilen
688       use control_data
689       use geometry_data
690       use energy_data
691       use energy
692       use compare_data
693       use MD_data, only: t_bath
694       use MPI_data
695       use compare, only:seq_comp,contact
696       use control
697 !      implicit real*8 (a-h,o-z)
698 !      include 'DIMENSIONS'
699 #ifdef MPI
700       include 'mpif.h'
701       integer :: error_msg,ierror,ierr,ierrcode
702 #endif
703 !      include 'COMMON.IOUNITS'
704 !      include 'COMMON.GEO'
705 !      include 'COMMON.VAR'
706 !      include 'COMMON.INTERACT'
707 !      include 'COMMON.LOCAL'
708 !      include 'COMMON.NAMES'
709 !      include 'COMMON.CHAIN'
710 !      include 'COMMON.FFIELD'
711 !      include 'COMMON.SBRIDGE'
712 !      include 'COMMON.HEADER'
713 !      include 'COMMON.CONTROL'
714 !      include 'COMMON.DBASE'
715 !      include 'COMMON.THREAD'
716 !      include 'COMMON.CONTACTS'
717 !      include 'COMMON.TORCNSTR'
718 !      include 'COMMON.TIME1'
719 !      include 'COMMON.BOUNDS'
720 !      include 'COMMON.MD'
721 !      include 'COMMON.SETUP'
722       character(len=4),dimension(:,:),allocatable :: sequence   !(maxres,maxmolecules)
723 !      integer :: rescode
724 !      double precision x(maxvar)
725       character(len=256) :: pdbfile
726       character(len=800) :: weightcard
727       character(len=80) :: weightcard_t!,ucase
728 !      integer,dimension(:),allocatable :: itype_pdb    !(maxres)
729 !      common /pizda/ itype_pdb
730       logical :: fail   !seq_comp,
731       real(kind=8) :: energia(0:n_ene)
732 !      integer ilen
733 !el      external ilen
734 !el local varables
735       integer :: i,j,l,k,kkk,ii,i1,i2,it1,it2
736
737       real(kind=8),dimension(3,maxres2+2) :: c_alloc
738       real(kind=8),dimension(3,0:maxres2) :: dc_alloc
739       real(kind=8),dimension(:,:), allocatable :: secprob
740       integer,dimension(maxres) :: itype_alloc
741
742       integer :: iti,nsi,maxsi,itrial,itmp
743       real(kind=8) :: wlong,scalscp,co,ssscale,phihel,phibet,sigmahel,&
744       sigmabet,sumv,nres_temp
745       allocate(weights(n_ene))
746 !-----------------------------
747       allocate(c(3,2*maxres+2)) !(3,maxres2+2) maxres2=2*maxres
748       allocate(dc(3,0:2*maxres)) !(3,0:maxres2)
749       allocate(itype(maxres,5)) !(maxres)
750       allocate(istype(maxres))
751 !
752 ! Zero out tables.
753 !
754       c(:,:)=0.0D0
755       dc(:,:)=0.0D0
756       itype(:,:)=0
757 !-----------------------------
758 !
759 ! Body
760 !
761 ! Read weights of the subsequent energy terms.
762       call card_concat(weightcard,.true.)
763       call reada(weightcard,'WLONG',wlong,1.0D0)
764       call reada(weightcard,'WSC',wsc,wlong)
765       call reada(weightcard,'WSCP',wscp,wlong)
766       call reada(weightcard,'WELEC',welec,1.0D0)
767       call reada(weightcard,'WVDWPP',wvdwpp,welec)
768       call reada(weightcard,'WEL_LOC',wel_loc,1.0D0)
769       call reada(weightcard,'WCORR4',wcorr4,0.0D0)
770       call reada(weightcard,'WCORR5',wcorr5,0.0D0)
771       call reada(weightcard,'WCORR6',wcorr6,0.0D0)
772       call reada(weightcard,'WTURN3',wturn3,1.0D0)
773       call reada(weightcard,'WTURN4',wturn4,1.0D0)
774       call reada(weightcard,'WTURN6',wturn6,1.0D0)
775       call reada(weightcard,'WSCCOR',wsccor,1.0D0)
776       call reada(weightcard,'WSTRAIN',wstrain,1.0D0)
777       call reada(weightcard,'WVDWPP_NUCL',wvdwpp_nucl,0.0D0)
778       call reada(weightcard,'WELPP',welpp,0.0d0)
779       call reada(weightcard,'WVDWPSB',wvdwpsb,0.0d0)
780       call reada(weightcard,'WELPSB',welpsb,0.0D0)
781       call reada(weightcard,'WVDWSB',wvdwsb,0.0d0)
782       call reada(weightcard,'WELSB',welsb,0.0D0)
783       call reada(weightcard,'WBOND_NUCL',wbond_nucl,0.0D0)
784       call reada(weightcard,'WANG_NUCL',wang_nucl,0.0D0)
785       call reada(weightcard,'WSBLOC',wsbloc,0.0D0)
786       call reada(weightcard,'WTOR_NUCL',wtor_nucl,0.0D0)
787 !      print *,"KUR..",wtor_nucl
788       call reada(weightcard,'WTORD_NUCL',wtor_d_nucl,0.0D0)
789       call reada(weightcard,'WCORR_NUCL',wcorr_nucl,0.0D0)
790       call reada(weightcard,'WCORR3_NUC',wcorr3_nucl,0.0D0)
791       call reada(weightcard,'WBOND',wbond,1.0D0)
792       call reada(weightcard,'WTOR',wtor,1.0D0)
793       call reada(weightcard,'WTORD',wtor_d,1.0D0)
794       call reada(weightcard,'WSHIELD',wshield,0.05D0)
795       call reada(weightcard,'LIPSCALE',lipscale,1.0D0)
796       call reada(weightcard,'WLT',wliptran,1.0D0)
797       call reada(weightcard,'WTUBE',wtube,1.0d0)
798       call reada(weightcard,'WANG',wang,1.0D0)
799       call reada(weightcard,'WSCLOC',wscloc,1.0D0)
800       call reada(weightcard,'SCAL14',scal14,0.4D0)
801       call reada(weightcard,'SCALSCP',scalscp,1.0d0)
802       call reada(weightcard,'CUTOFF',cutoff_corr,7.0d0)
803       call reada(weightcard,'DELT_CORR',delt_corr,0.5d0)
804       call reada(weightcard,'TEMP0',temp0,300.0d0)
805       call reada(weightcard,'WSCBASE',wscbase,0.0D0)
806       if (index(weightcard,'SOFT').gt.0) ipot=6
807       call reada(weightcard,'WBOND_NUCL',wbond_nucl,0.0D0)
808       call reada(weightcard,'WCATCAT',wcatcat,0.0d0)
809       call reada(weightcard,'WCATPROT',wcatprot,0.0d0)
810       call reada(weightcard,'WCATNUCL',wcatnucl,0.0d0)
811       call reada(weightcard,'WPEPBASE',wpepbase,1.0d0)
812       call reada(weightcard,'WSCPHO',wscpho,0.0d0)
813       call reada(weightcard,'WPEPPHO',wpeppho,0.0d0)
814
815 ! 12/1/95 Added weight for the multi-body term WCORR
816       call reada(weightcard,'WCORRH',wcorr,1.0D0)
817       if (wcorr4.gt.0.0d0) wcorr=wcorr4
818       weights(1)=wsc
819       weights(2)=wscp
820       weights(3)=welec
821       weights(4)=wcorr
822       weights(5)=wcorr5
823       weights(6)=wcorr6
824       weights(7)=wel_loc
825       weights(8)=wturn3
826       weights(9)=wturn4
827       weights(10)=wturn6
828       weights(11)=wang
829       weights(12)=wscloc
830       weights(13)=wtor
831       weights(14)=wtor_d
832       weights(15)=wstrain
833       weights(16)=wvdwpp
834       weights(17)=wbond
835       weights(18)=scal14
836       weights(21)=wsccor
837           weights(26)=wvdwpp_nucl
838           weights(27)=welpp
839           weights(28)=wvdwpsb
840           weights(29)=welpsb
841           weights(30)=wvdwsb
842           weights(31)=welsb
843           weights(32)=wbond_nucl
844           weights(33)=wang_nucl
845           weights(34)=wsbloc
846           weights(35)=wtor_nucl
847           weights(36)=wtor_d_nucl
848           weights(37)=wcorr_nucl
849           weights(38)=wcorr3_nucl
850           weights(41)=wcatcat
851           weights(42)=wcatprot
852           weights(46)=wscbase
853           weights(47)=wpepbase
854           weights(48)=wscpho
855           weights(49)=wpeppho
856           weights(50)=wcatnucl
857
858       if(me.eq.king.or..not.out1file) &
859        write (iout,10) wsc,wscp,welec,wvdwpp,wbond,wang,wscloc,wtor,&
860         wtor_d,wstrain,wel_loc,wcorr,wcorr5,wcorr6,wsccor,wturn3,&
861         wturn4,wturn6
862    10 format (/'Energy-term weights (unscaled):'// &
863        'WSCC=   ',f10.6,' (SC-SC)'/ &
864        'WSCP=   ',f10.6,' (SC-p)'/ &
865        'WELEC=  ',f10.6,' (p-p electr)'/ &
866        'WVDWPP= ',f10.6,' (p-p VDW)'/ &
867        'WBOND=  ',f10.6,' (stretching)'/ &
868        'WANG=   ',f10.6,' (bending)'/ &
869        'WSCLOC= ',f10.6,' (SC local)'/ &
870        'WTOR=   ',f10.6,' (torsional)'/ &
871        'WTORD=  ',f10.6,' (double torsional)'/ &
872        'WSTRAIN=',f10.6,' (SS bridges & dist. cnstr.)'/ &
873        'WEL_LOC=',f10.6,' (multi-body 3-rd order)'/ &
874        'WCORR4= ',f10.6,' (multi-body 4th order)'/ &
875        'WCORR5= ',f10.6,' (multi-body 5th order)'/ &
876        'WCORR6= ',f10.6,' (multi-body 6th order)'/ &
877        'WSCCOR= ',f10.6,' (back-scloc correlation)'/ &
878        'WTURN3= ',f10.6,' (turns, 3rd order)'/ &
879        'WTURN4= ',f10.6,' (turns, 4th order)'/ &
880        'WTURN6= ',f10.6,' (turns, 6th order)')
881       if(me.eq.king.or..not.out1file)then
882        if (wcorr4.gt.0.0d0) then
883         write (iout,'(/2a/)') 'Local-electrostatic type correlation ',&
884          'between contact pairs of peptide groups'
885         write (iout,'(2(a,f5.3/))') &
886         'Cutoff on 4-6th order correlation terms: ',cutoff_corr,&
887         'Range of quenching the correlation terms:',2*delt_corr 
888        else if (wcorr.gt.0.0d0) then
889         write (iout,'(/2a/)') 'Hydrogen-bonding correlation ',&
890          'between contact pairs of peptide groups'
891        endif
892        write (iout,'(a,f8.3)') &
893         'Scaling factor of 1,4 SC-p interactions:',scal14
894        write (iout,'(a,f8.3)') &
895         'General scaling factor of SC-p interactions:',scalscp
896       endif
897       r0_corr=cutoff_corr-delt_corr
898       do i=1,ntyp
899         aad(i,1)=scalscp*aad(i,1)
900         aad(i,2)=scalscp*aad(i,2)
901         bad(i,1)=scalscp*bad(i,1)
902         bad(i,2)=scalscp*bad(i,2)
903       enddo
904       call rescale_weights(t_bath)
905       if(me.eq.king.or..not.out1file) &
906        write (iout,22) wsc,wscp,welec,wvdwpp,wbond,wang,wscloc,wtor,&
907         wtor_d,wstrain,wel_loc,wcorr,wcorr5,wcorr6,wsccor,wturn3,&
908         wturn4,wturn6
909    22 format (/'Energy-term weights (scaled):'// &
910        'WSCC=   ',f10.6,' (SC-SC)'/ &
911        'WSCP=   ',f10.6,' (SC-p)'/ &
912        'WELEC=  ',f10.6,' (p-p electr)'/ &
913        'WVDWPP= ',f10.6,' (p-p VDW)'/ &
914        'WBOND=  ',f10.6,' (stretching)'/ &
915        'WANG=   ',f10.6,' (bending)'/ &
916        'WSCLOC= ',f10.6,' (SC local)'/ &
917        'WTOR=   ',f10.6,' (torsional)'/ &
918        'WTORD=  ',f10.6,' (double torsional)'/ &
919        'WSTRAIN=',f10.6,' (SS bridges & dist. cnstr.)'/ &
920        'WEL_LOC=',f10.6,' (multi-body 3-rd order)'/ &
921        'WCORR4= ',f10.6,' (multi-body 4th order)'/ &
922        'WCORR5= ',f10.6,' (multi-body 5th order)'/ &
923        'WCORR6= ',f10.6,' (multi-body 6th order)'/ &
924        'WSCCOR= ',f10.6,' (back-scloc correlatkion)'/ &
925        'WTURN3= ',f10.6,' (turns, 3rd order)'/ &
926        'WTURN4= ',f10.6,' (turns, 4th order)'/ &
927        'WTURN6= ',f10.6,' (turns, 6th order)')
928       if(me.eq.king.or..not.out1file) &
929        write (iout,*) "Reference temperature for weights calculation:",&
930         temp0
931       call reada(weightcard,"D0CM",d0cm,3.78d0)
932       call reada(weightcard,"AKCM",akcm,15.1d0)
933       call reada(weightcard,"AKTH",akth,11.0d0)
934       call reada(weightcard,"AKCT",akct,12.0d0)
935       call reada(weightcard,"V1SS",v1ss,-1.08d0)
936       call reada(weightcard,"V2SS",v2ss,7.61d0)
937       call reada(weightcard,"V3SS",v3ss,13.7d0)
938       call reada(weightcard,"EBR",ebr,-5.50D0)
939       call reada(weightcard,"ATRISS",atriss,0.301D0)
940       call reada(weightcard,"BTRISS",btriss,0.021D0)
941       call reada(weightcard,"CTRISS",ctriss,1.001D0)
942       call reada(weightcard,"DTRISS",dtriss,1.001D0)
943       call reada(weightcard,"SSSCALE",ssscale,1.0D0)
944       dyn_ss=(index(weightcard,'DYN_SS').gt.0)
945
946       call reada(weightcard,"HT",Ht,0.0D0)
947       if (dyn_ss) then
948        ss_depth=(ebr/wsc-0.25*eps(1,1))*ssscale
949         Ht=(Ht/wsc-0.25*eps(1,1))*ssscale
950         akcm=akcm/wsc*ssscale
951         akth=akth/wsc*ssscale
952         akct=akct/wsc*ssscale
953         v1ss=v1ss/wsc*ssscale
954         v2ss=v2ss/wsc*ssscale
955         v3ss=v3ss/wsc*ssscale
956       else
957         ss_depth=ebr/wstrain-0.25*eps(1,1)*wsc/wstrain
958       endif
959
960       if(me.eq.king.or..not.out1file) then
961        write (iout,*) "Parameters of the SS-bond potential:"
962        write (iout,*) "D0CM",d0cm," AKCM",akcm," AKTH",akth,&
963        " AKCT",akct
964        write (iout,*) "V1SS",v1ss," V2SS",v2ss," V3SS",v3ss
965        write (iout,*) "EBR",ebr," SS_DEPTH",ss_depth
966        write (iout,*)" HT",Ht
967        print *,'indpdb=',indpdb,' pdbref=',pdbref
968       endif
969       if (indpdb.gt.0 .or. pdbref) then
970         read(inp,'(a)') pdbfile
971         if(me.eq.king.or..not.out1file) &
972          write (iout,'(2a)') 'PDB data will be read from file ',&
973          pdbfile(:ilen(pdbfile))
974         open(ipdbin,file=pdbfile,status='old',err=33)
975         goto 34 
976   33    write (iout,'(a)') 'Error opening PDB file.'
977         stop
978   34    continue
979 !        print *,'Begin reading pdb data'
980         call readpdb
981         if (.not.allocated(crefjlee)) allocate (crefjlee(3,2*nres+2))
982         do i=1,2*nres
983           do j=1,3
984             crefjlee(j,i)=c(j,i)
985           enddo
986         enddo
987 #ifdef DEBUG
988         do i=1,nres
989           write (iout,'(i5,3f8.3,5x,3f8.3)') i,(crefjlee(j,i),j=1,3),
990      &      (crefjlee(j,i+nres),j=1,3)
991         enddo
992 #endif
993
994 !        call int_from_cart1(.true.)
995
996 !        print *,'Finished reading pdb data'
997         if(me.eq.king.or..not.out1file) &
998          write (iout,'(a,i3,a,i3)')'nsup=',nsup,&
999          ' nstart_sup=',nstart_sup !,"ergwergewrgae"
1000 !el        if(.not.allocated(itype_pdb)) 
1001         allocate(itype_pdb(nres))
1002         do i=1,nres
1003           itype_pdb(i)=itype(i,1)
1004         enddo
1005         close (ipdbin)
1006         nnt=nstart_sup
1007         nct=nstart_sup+nsup-1
1008 !el        if(.not.allocated(icont_ref))
1009         allocate(icont_ref(2,(nres/2)*nres)) ! maxcont=12*maxres
1010         call contact(.false.,ncont_ref,icont_ref,co)
1011
1012         if (sideadd) then 
1013          if(me.eq.king.or..not.out1file) &
1014           write(iout,*)'Adding sidechains'
1015          maxsi=1000
1016          do i=2,nres-1
1017           iti=itype(i,1)
1018           if (iti.ne.10 .and. itype(i,1).ne.ntyp1) then
1019             nsi=0
1020             fail=.true.
1021             do while (fail.and.nsi.le.maxsi)
1022               call gen_side(iti,theta(i+1),alph(i),omeg(i),fail,molnum(i))
1023               nsi=nsi+1
1024             enddo
1025             if(fail) write(iout,*)'Adding sidechain failed for res ',&
1026                     i,' after ',nsi,' trials'
1027           endif
1028          enddo
1029         endif  
1030       endif
1031       
1032       if (indpdb.eq.0) then
1033       nres_molec(:)=0
1034         allocate(sequence(maxres,5))
1035 !      itype(:,:)=0
1036       itmp=0
1037       if (protein) then
1038 ! Read sequence if not taken from the pdb file.
1039         molec=1
1040         read (inp,*) nres_molec(molec)
1041         print *,'nres=',nres
1042         if (iscode.gt.0) then
1043           read (inp,'(80a1)') (sequence(i,molec)(1:1),i=1,nres_molec(molec))
1044         else
1045           read (inp,'(20(1x,a3))') (sequence(i,molec),i=1,nres_molec(molec))
1046         endif
1047 !        read(inp,*) weightcard_t
1048 !        print *,"po seq" weightcard_t
1049 ! Convert sequence to numeric code
1050         
1051         do i=1,nres_molec(molec)
1052           itmp=itmp+1
1053           itype(i,1)=rescode(i,sequence(i,molec),iscode,molec)
1054           print *,itype(i,1)
1055           
1056         enddo
1057        endif
1058 !        read(inp,*) weightcard_t
1059 !        print *,"po seq", weightcard_t
1060
1061        if (nucleic) then
1062 ! Read sequence if not taken from the pdb file.
1063         molec=2
1064         read (inp,*) nres_molec(molec)
1065 !        print *,'nres=',nres
1066 !        allocate(sequence(maxres,5))
1067 !        if (iscode.gt.0) then
1068           read (inp,'(20a4)') (sequence(i,molec),i=1,nres_molec(molec))
1069 ! Convert sequence to numeric code
1070
1071         do i=1,nres_molec(molec)
1072           itmp=itmp+1
1073           istype(itmp)=sugarcode(sequence(i,molec)(1:1),i)
1074           sequence(i,molec)=sequence(i,molec)(1:2)
1075           itype(itmp,molec)=rescode(i,sequence(i,molec),iscode,molec)
1076         enddo
1077        endif
1078
1079        if (ions) then
1080 ! Read sequence if not taken from the pdb file.
1081         molec=5
1082         read (inp,*) nres_molec(molec)
1083 !        print *,'nres=',nres
1084           read (inp,'(20(1x,a3))') (sequence(i,molec),i=1,nres_molec(molec))
1085 ! Convert sequence to numeric code
1086         print *,nres_molec(molec) 
1087         do i=1,nres_molec(molec)
1088           itmp=itmp+1
1089           print *,itmp,"itmp"
1090           itype(itmp,molec)=rescode(i,sequence(i,molec),iscode,molec)
1091         enddo
1092        endif
1093        nres=0
1094        do i=1,5
1095         nres=nres+nres_molec(i)
1096         print *,"nres_molec",nres,nres_molec(i)
1097        enddo
1098        
1099 ! Assign initial virtual bond lengths
1100         if(.not.allocated(molnum)) then
1101          allocate(molnum(nres+1))
1102          itmp=0
1103         do i=1,5
1104                do j=1,nres_molec(i)
1105                itmp=itmp+1
1106               molnum(itmp)=i
1107                enddo
1108          enddo
1109 !        print *,nres_molec(i)
1110         endif
1111         print *,nres,"nres"
1112         if(.not.allocated(vbld)) then
1113            print *, "I DO ENTER" 
1114            allocate(vbld(2*nres))
1115         endif
1116         if(.not.allocated(vbld_inv)) allocate(vbld_inv(2*nres))
1117         do i=2,nres
1118           if (molnum(i).eq.1) then
1119           vbld(i)=vbl
1120           vbld_inv(i)=vblinv
1121
1122           else
1123           vbld(i)=7.0
1124           vbld_inv(i)=1.0/7.0
1125           endif
1126         enddo
1127         do i=2,nres-1
1128            if (molnum(i).eq.1) then
1129 !          print *, "molnum",molnum(i),itype(i,molnum(i)),nres,i 
1130           vbld(i+nres)=dsc(iabs(itype(i,molnum(i))))
1131           vbld_inv(i+nres)=dsc_inv(iabs(itype(i,molnum(i))))
1132            else
1133           vbld(i+nres)=vbldsc0_nucl(1,iabs(itype(i,molnum(i))))
1134           vbld_inv(i+nres)=1.0/vbldsc0_nucl(1,iabs(itype(i,molnum(i))))
1135            endif
1136 !          write (iout,*) "i",i," itype",itype(i,1),
1137 !     &      " dsc",dsc(itype(i,1))," vbld",vbld(i),vbld(i+nres)
1138         enddo
1139       endif 
1140 !      print *,nres
1141 !      print '(20i4)',(itype(i,1),i=1,nres)
1142 !----------------------------
1143 !el reallocate tables
1144 !      do i=1,maxres2
1145 !        do j=1,3
1146 !          c_alloc(j,i)=c(j,i)
1147 !          dc_alloc(j,i)=dc(j,i)
1148 !        enddo
1149 !      enddo
1150 !      do i=1,maxres
1151 !elwrite(iout,*) "itype",i,itype(i,1)
1152 !        itype_alloc(i)=itype(i,1)
1153 !      enddo
1154
1155 !      deallocate(c)
1156 !      deallocate(dc)
1157 !      deallocate(itype)
1158 !      allocate(c(3,2*nres+4))
1159 !      allocate(dc(3,0:2*nres+2))
1160 !      allocate(itype(nres+2))
1161       allocate(itel(nres+2))
1162       itel(:)=0
1163
1164 !      do i=1,2*nres+2
1165 !        do j=1,3
1166 !          c(j,i)=c_alloc(j,i)
1167 !          dc(j,i)=dc_alloc(j,i)
1168 !        enddo
1169 !      enddo
1170 !      do i=1,nres+2
1171 !        itype(i,1)=itype_alloc(i)
1172 !        itel(i)=0
1173 !      enddo
1174 !--------------------------
1175       do i=1,nres
1176 #ifdef PROCOR
1177         if (itype(i,1).eq.ntyp1 .or. itype(i+1,1).eq.ntyp1) then
1178 #else
1179         if (itype(i,1).eq.ntyp1) then
1180 #endif
1181           itel(i)=0
1182 #ifdef PROCOR
1183         else if (iabs(itype(i+1,1)).ne.20) then
1184 #else
1185         else if (iabs(itype(i,1)).ne.20) then
1186 #endif
1187           itel(i)=1
1188         else
1189           itel(i)=2
1190         endif  
1191       enddo
1192       if(me.eq.king.or..not.out1file)then
1193        write (iout,*) "ITEL"
1194        print *,nres,"nres"
1195        do i=1,nres-1
1196          write (iout,*) i,itype(i,1),itel(i)
1197        enddo
1198        print *,'Call Read_Bridge.'
1199       endif
1200       call read_bridge
1201 !--------------------------------
1202 !       print *,"tu dochodze"
1203 ! znamy nres oraz nss można zaalokowac potrzebne tablice
1204       call alloc_geo_arrays
1205       call alloc_ener_arrays
1206 !--------------------------------
1207 ! 8/13/98 Set limits to generating the dihedral angles
1208       do i=1,nres
1209         phibound(1,i)=-pi
1210         phibound(2,i)=pi
1211       enddo
1212       read (inp,*) ndih_constr
1213       if (ndih_constr.gt.0) then
1214         raw_psipred=.false.
1215         allocate(idih_constr(ndih_constr),idih_nconstr(ndih_constr)) !(maxdih_constr)
1216         allocate(phi0(ndih_constr),drange(ndih_constr)) !(maxdih_constr)
1217         allocate(ftors(ndih_constr)) !(maxdih_constr)
1218         
1219 !        read (inp,*) ftors
1220         read (inp,*) (idih_constr(i),phi0(i),drange(i),ftors(i), &
1221         i=1,ndih_constr)
1222         if(me.eq.king.or..not.out1file)then
1223          write (iout,*) &
1224          'There are',ndih_constr,' constraints on phi angles.'
1225          do i=1,ndih_constr
1226           write (iout,'(i5,3f8.3)') idih_constr(i),phi0(i),drange(i), &
1227           ftors(i)
1228          enddo
1229         endif
1230         do i=1,ndih_constr
1231           phi0(i)=deg2rad*phi0(i)
1232           drange(i)=deg2rad*drange(i)
1233         enddo
1234 !        if(me.eq.king.or..not.out1file) &
1235 !         write (iout,*) 'FTORS',ftors
1236         do i=1,ndih_constr
1237           ii = idih_constr(i)
1238           phibound(1,ii) = phi0(i)-drange(i)
1239           phibound(2,ii) = phi0(i)+drange(i)
1240         enddo 
1241       else if (ndih_constr.lt.0) then
1242         raw_psipred=.true.
1243         allocate(secprob(3,nres))
1244         allocate(vpsipred(3,nres))
1245         allocate(sdihed(2,nres))
1246         call card_concat(weightcard,.true.)
1247         call reada(weightcard,"PHIHEL",phihel,50.0D0)
1248         call reada(weightcard,"PHIBET",phibet,180.0D0)
1249         call reada(weightcard,"SIGMAHEL",sigmahel,30.0d0)
1250         call reada(weightcard,"SIGMABET",sigmabet,40.0d0)
1251         call reada(weightcard,"WDIHC",wdihc,0.591D0)
1252         write (iout,*) "Weight of dihedral angle restraints",wdihc
1253         read(inp,'(9x,3f7.3)') &
1254           (secprob(1,i),secprob(2,i),secprob(3,i),i=nnt,nct)
1255         write (iout,*) "The secprob array"
1256         do i=nnt,nct
1257           write (iout,'(i5,3f8.3)') i,(secprob(j,i),j=1,3)
1258         enddo
1259         ndih_constr=0
1260         do i=nnt+3,nct
1261           if (itype(i-3,1).ne.ntyp1 .and. itype(i-2,1).ne.ntyp1 &
1262           .and. itype(i-1,1).ne.ntyp1 .and. itype(i,1).ne.ntyp1) then
1263             ndih_constr=ndih_constr+1
1264             idih_constr(ndih_constr)=i
1265             sumv=0.0d0
1266             do j=1,3
1267               vpsipred(j,ndih_constr)=secprob(j,i-1)*secprob(j,i-2)
1268               sumv=sumv+vpsipred(j,ndih_constr)
1269             enddo
1270             do j=1,3
1271               vpsipred(j,ndih_constr)=vpsipred(j,ndih_constr)/sumv
1272             enddo
1273             phibound(1,ndih_constr)=phihel*deg2rad
1274             phibound(2,ndih_constr)=phibet*deg2rad
1275             sdihed(1,ndih_constr)=sigmahel*deg2rad
1276             sdihed(2,ndih_constr)=sigmabet*deg2rad
1277           endif
1278         enddo
1279
1280       endif
1281       if (with_theta_constr) then
1282 !C with_theta_constr is keyword allowing for occurance of theta constrains
1283       read (inp,*) ntheta_constr
1284 !C ntheta_constr is the number of theta constrains
1285       if (ntheta_constr.gt.0) then
1286 !C        read (inp,*) ftors
1287         allocate(itheta_constr(ntheta_constr))
1288         allocate(theta_constr0(ntheta_constr))
1289         allocate(theta_drange(ntheta_constr),for_thet_constr(ntheta_constr))
1290         read (inp,*) (itheta_constr(i),theta_constr0(i), &
1291        theta_drange(i),for_thet_constr(i), &
1292        i=1,ntheta_constr)
1293 !C the above code reads from 1 to ntheta_constr 
1294 !C itheta_constr(i) residue i for which is theta_constr
1295 !C theta_constr0 the global minimum value
1296 !C theta_drange is range for which there is no energy penalty
1297 !C for_thet_constr is the force constant for quartic energy penalty
1298 !C E=k*x**4 
1299         if(me.eq.king.or..not.out1file)then
1300          write (iout,*) &
1301         'There are',ntheta_constr,' constraints on phi angles.'
1302          do i=1,ntheta_constr
1303           write (iout,'(i5,3f8.3)') itheta_constr(i),theta_constr0(i), &
1304          theta_drange(i), &
1305          for_thet_constr(i)
1306          enddo
1307         endif
1308         do i=1,ntheta_constr
1309           theta_constr0(i)=deg2rad*theta_constr0(i)
1310           theta_drange(i)=deg2rad*theta_drange(i)
1311         enddo
1312 !C        if(me.eq.king.or..not.out1file)
1313 !C     &   write (iout,*) 'FTORS',ftors
1314 !C        do i=1,ntheta_constr
1315 !C          ii = itheta_constr(i)
1316 !C          thetabound(1,ii) = phi0(i)-drange(i)
1317 !C          thetabound(2,ii) = phi0(i)+drange(i)
1318 !C        enddo
1319       endif ! ntheta_constr.gt.0
1320       endif! with_theta_constr
1321
1322       nnt=1
1323 #ifdef MPI
1324       if (me.eq.king) then
1325 #endif
1326        write (iout,'(a)') 'Boundaries in phi angle sampling:'
1327        do i=1,nres
1328          write (iout,'(a3,i5,2f10.1)') &
1329          restyp(itype(i,1),1),i,phibound(1,i)*rad2deg,phibound(2,i)*rad2deg
1330        enddo
1331 #ifdef MP
1332       endif
1333 #endif
1334       nct=nres
1335       print *,'NNT=',NNT,' NCT=',NCT
1336       if (itype(1,molnum(1)).eq.ntyp1_molec(molnum(1))) nnt=2
1337       if (itype(nres,molnum(nres)).eq.ntyp1_molec(molnum(nres))) nct=nct-1
1338       if (pdbref) then
1339         if(me.eq.king.or..not.out1file) &
1340          write (iout,'(a,i3)') 'nsup=',nsup
1341         nstart_seq=nnt
1342         if (nsup.le.(nct-nnt+1)) then
1343           do i=0,nct-nnt+1-nsup
1344             if (seq_comp(itype(nnt+i,1),itype_pdb(nstart_sup),nsup)) then
1345               nstart_seq=nnt+i
1346               goto 111
1347             endif
1348           enddo
1349           write (iout,'(a)') &
1350                   'Error - sequences to be superposed do not match.'
1351           stop
1352         else
1353           do i=0,nsup-(nct-nnt+1)
1354             if (seq_comp(itype(nnt,1),itype_pdb(nstart_sup+i),nct-nnt+1)) &
1355             then
1356               nstart_sup=nstart_sup+i
1357               nsup=nct-nnt+1
1358               goto 111
1359             endif
1360           enddo 
1361           write (iout,'(a)') &
1362                   'Error - sequences to be superposed do not match.'
1363         endif
1364   111   continue
1365         if (nsup.eq.0) nsup=nct-nnt
1366         if (nstart_sup.eq.0) nstart_sup=nnt
1367         if (nstart_seq.eq.0) nstart_seq=nnt
1368         if(me.eq.king.or..not.out1file) &
1369          write (iout,*) 'nsup=',nsup,' nstart_sup=',nstart_sup,&
1370                        ' nstart_seq=',nstart_seq !,"242343453254"
1371       endif
1372 !--- Zscore rms -------
1373       if (nz_start.eq.0) nz_start=nnt
1374       if (nz_end.eq.0 .and. nsup.gt.0) then
1375         nz_end=nnt+nsup-1
1376       else if (nz_end.eq.0) then
1377         nz_end=nct
1378       endif
1379       if(me.eq.king.or..not.out1file)then
1380        write (iout,*) 'NZ_START=',nz_start,' NZ_END=',nz_end
1381        write (iout,*) 'IZ_SC=',iz_sc
1382       endif
1383 !----------------------
1384       call init_int_table
1385       if (refstr) then
1386         if (.not.pdbref) then
1387           call read_angles(inp,*38)
1388           goto 39
1389    38     write (iout,'(a)') 'Error reading reference structure.'
1390 #ifdef MPI
1391           call MPI_Finalize(MPI_COMM_WORLD,IERROR)
1392           stop 'Error reading reference structure'
1393 #endif
1394    39     call chainbuild
1395           call setup_var
1396 !zscore          call geom_to_var(nvar,coord_exp_zs(1,1))
1397           nstart_sup=nnt
1398           nstart_seq=nnt
1399           nsup=nct-nnt+1
1400           kkk=1
1401           do i=1,2*nres
1402             do j=1,3
1403               cref(j,i,kkk)=c(j,i)
1404             enddo
1405           enddo
1406           call contact(.true.,ncont_ref,icont_ref,co)
1407         endif
1408 !        write (iout,*) "constr_dist",constr_dist,nstart_sup,nsup
1409 !        call flush(iout)
1410 !EL        if (constr_dist.gt.0) call read_dist_constr
1411 !EL        write (iout,*) "After read_dist_constr nhpb",nhpb
1412 !EL        if ((AFMlog.gt.0).or.(selfguide.gt.0)) call read_afminp
1413 !EL        call hpb_partition
1414         if(me.eq.king.or..not.out1file) &
1415          write (iout,*) 'Contact order:',co
1416         if (pdbref) then
1417         if(me.eq.king.or..not.out1file) &
1418          write (2,*) 'Shifting contacts:',nstart_seq,nstart_sup
1419         do i=1,ncont_ref
1420           do j=1,2
1421             icont_ref(j,i)=icont_ref(j,i)+nstart_seq-nstart_sup
1422           enddo
1423           if(me.eq.king.or..not.out1file) &
1424            write (2,*) i,' ',restyp(itype(icont_ref(1,i),1),1),' ',&
1425            icont_ref(1,i),' ',&
1426            restyp(itype(icont_ref(2,i),1),1),' ',icont_ref(2,i)
1427         enddo
1428         endif
1429       if (constr_homology.gt.0) then
1430 !        write (iout,*) "Calling read_constr_homology"
1431 !        call flush(iout)
1432         call read_constr_homology
1433         if (indpdb.gt.0 .or. pdbref) then
1434           do i=1,2*nres
1435             do j=1,3
1436               c(j,i)=crefjlee(j,i)
1437               cref(j,i,1)=crefjlee(j,i)
1438             enddo
1439           enddo
1440         endif
1441 #define DEBUG
1442 #ifdef DEBUG
1443         write (iout,*) "sc_loc_geom: Array C"
1444         do i=1,nres
1445           write (iout,'(i5,3f8.3,5x,3f8.3)') i,(c(j,i),j=1,3),&
1446            (c(j,i+nres),j=1,3)
1447         enddo
1448         write (iout,*) "Array Cref"
1449         do i=1,nres
1450           write (iout,'(i5,3f8.3,5x,3f8.3)') i,(cref(j,i,1),j=1,3),&
1451            (cref(j,i+nres,1),j=1,3)
1452         enddo
1453 #endif
1454        call int_from_cart1(.false.)
1455        call sc_loc_geom(.false.)
1456        do i=1,nres
1457          thetaref(i)=theta(i)
1458          phiref(i)=phi(i)
1459        enddo
1460        do i=1,nres-1
1461          do j=1,3
1462            dc(j,i)=c(j,i+1)-c(j,i)
1463            dc_norm(j,i)=dc(j,i)*vbld_inv(i+1)
1464          enddo
1465        enddo
1466        do i=2,nres-1
1467          do j=1,3
1468            dc(j,i+nres)=c(j,i+nres)-c(j,i)
1469            dc_norm(j,i+nres)=dc(j,i+nres)*vbld_inv(i+nres)
1470          enddo
1471        enddo
1472       else
1473         homol_nset=0
1474         if (start_from_model) then
1475           nmodel_start=0
1476           do
1477             read(inp,'(a)',end=332,err=332) pdbfile
1478             if (me.eq.king .or. .not. out1file)&
1479              write (iout,'(a,5x,a)') 'Opening PDB file',&
1480              pdbfile(:ilen(pdbfile))
1481             open(ipdbin,file=pdbfile,status='old',err=336)
1482             goto 335
1483  336        write (iout,'(a,5x,a)') 'Error opening PDB file',&
1484            pdbfile(:ilen(pdbfile))
1485             call flush(iout)
1486             stop
1487  335        continue
1488             unres_pdb=.false.
1489             nres_temp=nres
1490 !            call readpdb
1491             call readpdb_template(nmodel_start+1)
1492             close(ipdbin)
1493             if (nres.ge.nres_temp) then
1494               nmodel_start=nmodel_start+1
1495               pdbfiles_chomo(nmodel_start)=pdbfile
1496               do i=1,2*nres
1497                 do j=1,3
1498                   chomo(j,i,nmodel_start)=c(j,i)
1499                 enddo
1500               enddo
1501             else
1502               if (me.eq.king .or. .not. out1file) &
1503                write (iout,'(a,2i7,1x,a)') &
1504                 "Different number of residues",nres_temp,nres, &
1505                 " model skipped."
1506             endif
1507             nres=nres_temp
1508           enddo
1509   332     continue
1510           if (nmodel_start.eq.0) then
1511             if (me.eq.king .or. .not. out1file) &
1512              write (iout,'(a)') &
1513              "No valid starting model found START_FROM_MODELS is OFF"
1514               start_from_model=.false.
1515           endif
1516           write (iout,*) "nmodel_start",nmodel_start
1517         endif
1518       endif
1519
1520       endif
1521         if (constr_dist.gt.0) call read_dist_constr
1522         write (iout,*) "After read_dist_constr nhpb",nhpb
1523         if ((AFMlog.gt.0).or.(selfguide.gt.0)) call read_afminp
1524         call hpb_partition
1525
1526       if (indpdb.eq.0 .and. modecalc.ne.2 .and. modecalc.ne.4 &
1527           .and. modecalc.ne.8 .and. modecalc.ne.9 .and. &
1528           modecalc.ne.10) then
1529 ! If input structure hasn't been supplied from the PDB file read or generate
1530 ! initial geometry.
1531         if (iranconf.eq.0 .and. .not. extconf) then
1532           if(me.eq.king.or..not.out1file .and.fg_rank.eq.0) &
1533            write (iout,'(a)') 'Initial geometry will be read in.'
1534           if (read_cart) then
1535             read(inp,'(8f10.5)',end=36,err=36) &
1536              ((c(l,k),l=1,3),k=1,nres),&
1537              ((c(l,k+nres),l=1,3),k=nnt,nct)
1538             write (iout,*) "Exit READ_CART"
1539             write (iout,'(8f10.5)') &
1540              ((c(l,k),l=1,3),k=1,nres)
1541             write (iout,'(8f10.5)') &
1542              ((c(l,k+nres),l=1,3),k=nnt,nct)
1543             call int_from_cart1(.true.)
1544             write (iout,*) "Finish INT_TO_CART"
1545             do i=1,nres-1
1546               do j=1,3
1547                 dc(j,i)=c(j,i+1)-c(j,i)
1548                 dc_norm(j,i)=dc_norm(j,i)*vbld_inv(i+1)
1549               enddo
1550             enddo
1551             do i=nnt,nct
1552               if (itype(i,1).ne.10 .and. itype(i,1).ne.ntyp1) then
1553                 do j=1,3
1554                   dc(j,i+nres)=c(j,i+nres)-c(j,i) 
1555                   dc_norm(j,i+nres)=dc_norm(j,i+nres)*vbld_inv(i+nres)
1556                 enddo
1557               endif
1558             enddo
1559             return
1560           else
1561            write(iout,*) "read angles from input" 
1562            call read_angles(inp,*36)
1563             call chainbuild
1564
1565           endif
1566           goto 37
1567    36     write (iout,'(a)') 'Error reading angle file.'
1568 #ifdef MPI
1569           call mpi_finalize( MPI_COMM_WORLD,IERR )
1570 #endif
1571           stop 'Error reading angle file.'
1572    37     continue 
1573         else if (extconf) then
1574          if(me.eq.king.or..not.out1file .and. fg_rank.eq.0) &
1575           write (iout,'(a)') 'Extended chain initial geometry.'
1576          do i=3,nres
1577           theta(i)=90d0*deg2rad
1578          enddo
1579          do i=4,nres
1580           phi(i)=180d0*deg2rad
1581          enddo
1582          do i=2,nres-1
1583           alph(i)=110d0*deg2rad
1584          enddo
1585          do i=2,nres-1
1586           omeg(i)=-120d0*deg2rad
1587           if (itype(i,1).le.0) omeg(i)=-omeg(i)
1588          enddo
1589          call chainbuild
1590         else
1591           if(me.eq.king.or..not.out1file) &
1592            write (iout,'(a)') 'Random-generated initial geometry.'
1593
1594
1595 #ifdef MPI
1596           if (me.eq.king  .or. fg_rank.eq.0 .and. &
1597                  ( modecalc.eq.12 .or. modecalc.eq.14) ) then  
1598 #endif
1599             do itrial=1,100
1600               itmp=1
1601               call gen_rand_conf(itmp,*30)
1602               goto 40
1603    30         write (iout,*) 'Failed to generate random conformation',&
1604                 ', itrial=',itrial
1605               write (*,*) 'Processor:',me,&
1606                 ' Failed to generate random conformation',&
1607                 ' itrial=',itrial
1608               call intout
1609
1610 #ifdef AIX
1611               call flush_(iout)
1612 #else
1613               call flush(iout)
1614 #endif
1615             enddo
1616             write (iout,'(a,i3,a)') 'Processor:',me,&
1617               ' error in generating random conformation.'
1618             write (*,'(a,i3,a)') 'Processor:',me,&
1619               ' error in generating random conformation.'
1620             call flush(iout)
1621 #ifdef MPI
1622             call MPI_Abort(mpi_comm_world,error_msg,ierrcode)            
1623    40       continue
1624           endif
1625 #else
1626           do itrial=1,100
1627             itmp=1
1628             call gen_rand_conf(itmp,*335)
1629             goto 40
1630   335       write (iout,*) 'Failed to generate random conformation',&
1631               ', itrial=',itrial
1632             write (*,*) 'Failed to generate random conformation',&
1633               ', itrial=',itrial
1634           enddo
1635           write (iout,'(a,i3,a)') 'Processor:',me,&
1636             ' error in generating random conformation.'
1637           write (*,'(a,i3,a)') 'Processor:',me,&
1638             ' error in generating random conformation.'
1639           stop
1640    40     continue
1641 #endif
1642         endif
1643       elseif (modecalc.eq.4) then
1644         read (inp,'(a)') intinname
1645         open (intin,file=intinname,status='old',err=333)
1646         if (me.eq.king .or. .not.out1file.and.fg_rank.eq.0) &
1647         write (iout,'(a)') 'intinname',intinname
1648         write (*,'(a)') 'Processor',myrank,' intinname',intinname
1649         goto 334
1650   333   write (iout,'(2a)') 'Error opening angle file ',intinname
1651 #ifdef MPI 
1652         call MPI_Finalize(MPI_COMM_WORLD,IERR)
1653 #endif   
1654         stop 'Error opening angle file.' 
1655   334   continue
1656
1657       endif 
1658 ! Generate distance constraints, if the PDB structure is to be regularized. 
1659       if (nthread.gt.0) then
1660         call read_threadbase
1661       endif
1662       call setup_var
1663       if (me.eq.king .or. .not. out1file) &
1664        call intout
1665       if (ns.gt.0 .and. (me.eq.king .or. .not.out1file) ) then
1666         write (iout,'(/a,i3,a)') &
1667         'The chain contains',ns,' disulfide-bridging cysteines.'
1668         write (iout,'(20i4)') (iss(i),i=1,ns)
1669        if (dyn_ss) then
1670           write(iout,*)"Running with dynamic disulfide-bond formation"
1671        else
1672         write (iout,'(/a/)') 'Pre-formed links are:' 
1673         do i=1,nss
1674           i1=ihpb(i)-nres
1675           i2=jhpb(i)-nres
1676           it1=itype(i1,1)
1677           it2=itype(i2,1)
1678           if (me.eq.king.or..not.out1file) &
1679           write (iout,'(2a,i3,3a,i3,a,3f10.3)') &
1680           restyp(it1,1),'(',i1,') -- ',restyp(it2,1),'(',i2,')',dhpb(i),&
1681           ebr,forcon(i)
1682         enddo
1683         write (iout,'(a)')
1684        endif
1685       endif
1686       if (ns.gt.0.and.dyn_ss) then
1687           do i=nss+1,nhpb
1688             ihpb(i-nss)=ihpb(i)
1689             jhpb(i-nss)=jhpb(i)
1690             forcon(i-nss)=forcon(i)
1691             dhpb(i-nss)=dhpb(i)
1692           enddo
1693           nhpb=nhpb-nss
1694           nss=0
1695           call hpb_partition
1696           do i=1,ns
1697             dyn_ss_mask(iss(i))=.true.
1698           enddo
1699       endif
1700       if (i2ndstr.gt.0) call secstrp2dihc
1701       if (indpdb.gt.0) then 
1702           write(iout,*) "WCHODZE TU!!"
1703           call int_from_cart1(.true.)
1704       endif
1705 !      call geom_to_var(nvar,x)
1706 !      call etotal(energia(0))
1707 !      call enerprint(energia(0))
1708 !      call briefout(0,etot)
1709 !      stop
1710 !d    write (iout,'(2(a,i3))') 'NNT',NNT,' NCT',NCT
1711 !d    write (iout,'(a)') 'Variable list:'
1712 !d    write (iout,'(i4,f10.5)') (i,rad2deg*x(i),i=1,nvar)
1713 #ifdef MPI
1714       if (me.eq.king .or. (fg_rank.eq.0 .and. .not.out1file)) &
1715         write (iout,'(//80(1h*)/20x,a,i4,a/80(1h*)//)') &
1716         'Processor',myrank,': end reading molecular data.'
1717 #endif
1718       return
1719       end subroutine molread
1720 !-----------------------------------------------------------------------------
1721       subroutine read_constr_homology
1722       use control, only:init_int_table,homology_partition
1723       use MD_data, only:iset
1724 !      implicit none
1725 !      include 'DIMENSIONS'
1726 !#ifdef MPI
1727 !      include 'mpif.h'
1728 !#endif
1729 !      include 'COMMON.SETUP'
1730 !      include 'COMMON.CONTROL'
1731 !      include 'COMMON.HOMOLOGY'
1732 !      include 'COMMON.CHAIN'
1733 !      include 'COMMON.IOUNITS'
1734 !      include 'COMMON.MD'
1735 !      include 'COMMON.QRESTR'
1736 !      include 'COMMON.GEO'
1737 !      include 'COMMON.INTERACT'
1738 !      include 'COMMON.NAMES'
1739 !      include 'COMMON.VAR'
1740 !
1741
1742 !     double precision odl_temp,sigma_odl_temp,waga_theta,waga_d,
1743 !    &                 dist_cut
1744 !     common /przechowalnia/ odl_temp(maxres,maxres,max_template),
1745 !    &    sigma_odl_temp(maxres,maxres,max_template)
1746       character*2 kic2
1747       character*24 model_ki_dist, model_ki_angle
1748       character*500 controlcard
1749       integer :: ki,i,ii,j,k,l
1750       integer, dimension (:), allocatable :: ii_in_use
1751       integer :: i_tmp,idomain_tmp,&
1752       irec,ik,iistart,nres_temp
1753 !      integer :: iset
1754 !      external :: ilen
1755       logical :: liiflag,lfirst
1756       integer :: i01,i10
1757 !
1758 !     FP - Nov. 2014 Temporary specifications for new vars
1759 !
1760       real(kind=8) :: rescore_tmp,x12,y12,z12,rescore2_tmp,&
1761                        rescore3_tmp, dist_cut
1762       real(kind=8), dimension (:,:),allocatable :: rescore
1763       real(kind=8), dimension (:,:),allocatable :: rescore2
1764       real(kind=8), dimension (:,:),allocatable :: rescore3
1765       real(kind=8) :: distal
1766       character*24 tpl_k_rescore
1767       character*256 pdbfile
1768
1769 ! -----------------------------------------------------------------
1770 ! Reading multiple PDB ref structures and calculation of retraints
1771 ! not using pre-computed ones stored in files model_ki_{dist,angle}
1772 ! FP (Nov., 2014)
1773 ! -----------------------------------------------------------------
1774 !
1775 !
1776 ! Alternative: reading from input
1777       call card_concat(controlcard,.true.)
1778       call reada(controlcard,"HOMOL_DIST",waga_dist,1.0d0)
1779       call reada(controlcard,"HOMOL_ANGLE",waga_angle,1.0d0)
1780       call reada(controlcard,"HOMOL_THETA",waga_theta,1.0d0) ! new
1781       call reada(controlcard,"HOMOL_SCD",waga_d,1.0d0) ! new
1782       call reada(controlcard,'DIST_CUT',dist_cut,5.0d0) ! for diff ways of calc sigma
1783       call reada(controlcard,'DIST2_CUT',dist2_cut,9999.0d0)
1784       call readi(controlcard,"HOMOL_NSET",homol_nset,1)
1785       read2sigma=(index(controlcard,'READ2SIGMA').gt.0)
1786       start_from_model=(index(controlcard,'START_FROM_MODELS').gt.0)
1787       if(.not.read2sigma.and.start_from_model) then
1788           if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0)&
1789            write(iout,*) 'START_FROM_MODELS works only with READ2SIGMA'
1790           start_from_model=.false.
1791           iranconf=(indpdb.le.0)
1792       endif
1793       if(start_from_model .and. (me.eq.king .or. .not. out1file))&
1794          write(iout,*) 'START_FROM_MODELS is ON'
1795 !      if(start_from_model .and. rest) then 
1796 !        if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) then
1797 !         write(iout,*) 'START_FROM_MODELS is OFF'
1798 !         write(iout,*) 'remove restart keyword from input'
1799 !        endif
1800 !      endif
1801       if (start_from_model) nmodel_start=constr_homology
1802       if(.not.allocated(waga_homology)) allocate (waga_homology(homol_nset))
1803       if (homol_nset.gt.1)then
1804          call card_concat(controlcard,.true.)
1805          read(controlcard,*) (waga_homology(i),i=1,homol_nset)
1806          if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) then
1807 !          write(iout,*) "iset homology_weight "
1808           do i=1,homol_nset
1809            write(iout,*) i,waga_homology(i)
1810           enddo
1811          endif
1812          iset=mod(kolor,homol_nset)+1
1813       else
1814        iset=1
1815        waga_homology(1)=1.0
1816       endif
1817
1818 !d      write (iout,*) "nnt",nnt," nct",nct
1819 !d      call flush(iout)
1820
1821       if (read_homol_frag) then
1822         call read_klapaucjusz
1823       else
1824
1825       lim_odl=0
1826       lim_dih=0
1827 !
1828 !      write(iout,*) 'nnt=',nnt,'nct=',nct
1829 !
1830 !      do i = nnt,nct
1831 !        do k=1,constr_homology
1832 !         idomain(k,i)=0
1833 !        enddo
1834 !      enddo
1835        idomain=0
1836
1837 !      ii=0
1838 !      do i = nnt,nct-2 
1839 !        do j=i+2,nct 
1840 !        ii=ii+1
1841 !        ii_in_use(ii)=0
1842 !        enddo
1843 !      enddo
1844       ii_in_use=0
1845       if(.not.allocated(pdbfiles_chomo)) allocate(pdbfiles_chomo(constr_homology)) 
1846       if(.not.allocated(chomo)) allocate(chomo(3,nres,constr_homology)) 
1847
1848       do k=1,constr_homology
1849
1850         read(inp,'(a)') pdbfile
1851         pdbfiles_chomo(k)=pdbfile
1852         if(me.eq.king .or. .not. out1file) &
1853          write (iout,'(a,5x,a)') 'HOMOL: Opening PDB file',&
1854         pdbfile(:ilen(pdbfile))
1855         open(ipdbin,file=pdbfile,status='old',err=33)
1856         goto 34
1857   33    write (iout,'(a,5x,a)') 'Error opening PDB file',&
1858         pdbfile(:ilen(pdbfile))
1859         stop
1860   34    continue
1861 !        print *,'Begin reading pdb data'
1862 !
1863 ! Files containing res sim or local scores (former containing sigmas)
1864 !
1865
1866         write(kic2,'(bz,i2.2)') k
1867
1868         tpl_k_rescore="template"//kic2//".sco"
1869         write(iout,*) "tpl_k_rescore=",tpl_k_rescore
1870         unres_pdb=.false.
1871         nres_temp=nres
1872         write(iout,*) "read2sigma",read2sigma
1873        
1874         if (read2sigma) then
1875           call readpdb_template(k)
1876         else
1877           call readpdb
1878         endif
1879         write(iout,*) "after readpdb"
1880         if(.not.allocated(nres_chomo)) allocate(nres_chomo(constr_homology))
1881         nres_chomo(k)=nres
1882         nres=nres_temp
1883         if(.not.allocated(rescore)) allocate(rescore(constr_homology,nres))
1884         if(.not.allocated(rescore2)) allocate(rescore2(constr_homology,nres))
1885         if(.not.allocated(rescore3)) allocate(rescore3(constr_homology,nres))
1886         if(.not.allocated(ii_in_use)) allocate(ii_in_use(nres*(nres-1)))
1887         if(.not.allocated(idomain)) allocate(idomain(constr_homology,nres))
1888         if(.not.allocated(l_homo)) allocate(l_homo(constr_homology,1000*nres))
1889         if(.not.allocated(ires_homo)) allocate(ires_homo(nres*200))
1890         if(.not.allocated(jres_homo)) allocate(jres_homo(nres*200))
1891         if(.not.allocated(odl)) allocate(odl(constr_homology,nres*200))
1892         if(.not.allocated(sigma_odl)) allocate(sigma_odl(constr_homology,nres*200))
1893         if(.not.allocated(dih)) allocate(dih(constr_homology,nres))
1894         if(.not.allocated(sigma_dih)) allocate(sigma_dih(constr_homology,nres))
1895         if(.not.allocated(thetatpl)) allocate(thetatpl(constr_homology,nres))
1896         if(.not.allocated(sigma_theta)) allocate(sigma_theta(constr_homology,nres))
1897 !        if(.not.allocated(thetatpl)) allocate(thetatpl(constr_homology,nres))
1898         if(.not.allocated(sigma_d)) allocate(sigma_d(constr_homology,nres))
1899         if(.not.allocated(xxtpl)) allocate(xxtpl(constr_homology,nres))
1900         if(.not.allocated(yytpl)) allocate(yytpl(constr_homology,nres))
1901         if(.not.allocated(zztpl)) allocate(zztpl(constr_homology,nres))
1902 !        if(.not.allocated(distance)) allocate(distance(constr_homology))
1903 !        if(.not.allocated(distancek)) allocate(distancek(constr_homology))
1904
1905
1906 !
1907 !     Distance restraints
1908 !
1909 !          ... --> odl(k,ii)
1910 ! Copy the coordinates from reference coordinates (?)
1911         do i=1,2*nres_chomo(k)
1912           do j=1,3
1913             c(j,i)=cref(j,i,1)
1914 !           write (iout,*) "c(",j,i,") =",c(j,i)
1915           enddo
1916         enddo
1917 !
1918 ! From read_dist_constr (commented out 25/11/2014 <-> res sim)
1919 !
1920 !         write(iout,*) "tpl_k_rescore - ",tpl_k_rescore
1921           open (ientin,file=tpl_k_rescore,status='old')
1922           if (nnt.gt.1) rescore(k,1)=0.0d0
1923           do irec=nnt,nct ! loop for reading res sim 
1924             if (read2sigma) then
1925              read (ientin,*,end=1401) i_tmp,rescore2_tmp,rescore_tmp,&
1926                                      rescore3_tmp,idomain_tmp
1927              i_tmp=i_tmp+nnt-1
1928              idomain(k,i_tmp)=idomain_tmp
1929              rescore(k,i_tmp)=rescore_tmp
1930              rescore2(k,i_tmp)=rescore2_tmp
1931              rescore3(k,i_tmp)=rescore3_tmp
1932              if (.not. out1file .or. me.eq.king)&
1933              write(iout,'(a7,i5,3f10.5,i5)') "rescore",&
1934                            i_tmp,rescore2_tmp,rescore_tmp,&
1935                                      rescore3_tmp,idomain_tmp
1936             else
1937              idomain(k,irec)=1
1938              read (ientin,*,end=1401) rescore_tmp
1939
1940 !           rescore(k,irec)=rescore_tmp+1.0d0 ! to avoid 0 values
1941              rescore(k,irec)=0.5d0*(rescore_tmp+0.5d0) ! alt transf to reduce scores
1942 !           write(iout,*) "rescore(",k,irec,") =",rescore(k,irec)
1943             endif
1944           enddo
1945  1401   continue
1946         close (ientin)
1947         if (waga_dist.ne.0.0d0) then
1948           ii=0
1949           do i = nnt,nct-2
1950             do j=i+2,nct
1951
1952               x12=c(1,i)-c(1,j)
1953               y12=c(2,i)-c(2,j)
1954               z12=c(3,i)-c(3,j)
1955               distal=dsqrt(x12*x12+y12*y12+z12*z12)
1956 !              write (iout,*) k,i,j,distal,dist2_cut
1957
1958             if (idomain(k,i).eq.idomain(k,j).and.idomain(k,i).ne.0 &
1959                  .and. distal.le.dist2_cut ) then
1960
1961               ii=ii+1
1962               ii_in_use(ii)=1
1963               l_homo(k,ii)=.true.
1964
1965 !             write (iout,*) "k",k
1966 !             write (iout,*) "i",i," j",j," constr_homology",
1967 !    &                       constr_homology
1968               ires_homo(ii)=i
1969               jres_homo(ii)=j
1970               odl(k,ii)=distal
1971               if (read2sigma) then
1972                 sigma_odl(k,ii)=0
1973                 do ik=i,j
1974                  sigma_odl(k,ii)=sigma_odl(k,ii)+rescore2(k,ik)
1975                 enddo
1976                 sigma_odl(k,ii)=sigma_odl(k,ii)/(j-i+1)
1977                 if (odl(k,ii).gt.dist_cut) sigma_odl(k,ii) = &
1978               sigma_odl(k,ii)*dexp(0.5d0*(odl(k,ii)/dist_cut)**2-0.5d0)
1979               else
1980                 if (odl(k,ii).le.dist_cut) then
1981                  sigma_odl(k,ii)=rescore(k,i)+rescore(k,j)
1982                 else
1983 #ifdef OLDSIGMA
1984                  sigma_odl(k,ii)=(rescore(k,i)+rescore(k,j))* &
1985                            dexp(0.5d0*(odl(k,ii)/dist_cut)**2)
1986 #else
1987                  sigma_odl(k,ii)=(rescore(k,i)+rescore(k,j))* &
1988                            dexp(0.5d0*(odl(k,ii)/dist_cut)**2-0.5d0)
1989 #endif
1990                 endif
1991               endif
1992               sigma_odl(k,ii)=1.0d0/(sigma_odl(k,ii)*sigma_odl(k,ii))
1993             else
1994 !              ii=ii+1
1995 !              l_homo(k,ii)=.false.
1996             endif
1997             enddo
1998           enddo
1999         lim_odl=ii
2000         endif
2001 !        write (iout,*) "Distance restraints set"
2002 !        call flush(iout)
2003 !
2004 !     Theta, dihedral and SC retraints
2005 !
2006         if (waga_angle.gt.0.0d0) then
2007 !         open (ientin,file=tpl_k_sigma_dih,status='old')
2008 !         do irec=1,maxres-3 ! loop for reading sigma_dih
2009 !            read (ientin,*,end=1402) i,j,ki,l,sigma_dih(k,i+nnt-1) ! j,ki,l what for?
2010 !            if (i+nnt-1.gt.lim_dih) lim_dih=i+nnt-1 ! right?
2011 !            sigma_dih(k,i+nnt-1)=sigma_dih(k,i+nnt-1)* ! not inverse because of use of res. similarity
2012 !    &                            sigma_dih(k,i+nnt-1)
2013 !         enddo
2014 !1402   continue
2015 !         close (ientin)
2016           do i = nnt+3,nct
2017             if (idomain(k,i).eq.0) then
2018                sigma_dih(k,i)=0.0
2019                cycle
2020             endif
2021             dih(k,i)=phiref(i) ! right?
2022 !           read (ientin,*) sigma_dih(k,i) ! original variant
2023 !             write (iout,*) "dih(",k,i,") =",dih(k,i)
2024 !             write(iout,*) "rescore(",k,i,") =",rescore(k,i),
2025 !    &                      "rescore(",k,i-1,") =",rescore(k,i-1),
2026 !    &                      "rescore(",k,i-2,") =",rescore(k,i-2),
2027 !    &                      "rescore(",k,i-3,") =",rescore(k,i-3)
2028
2029             sigma_dih(k,i)=(rescore(k,i)+rescore(k,i-1)+ &
2030                           rescore(k,i-2)+rescore(k,i-3))/4.0
2031 !            if (read2sigma) sigma_dih(k,i)=sigma_dih(k,i)/4.0
2032 !           write (iout,*) "Raw sigmas for dihedral angle restraints"
2033 !           write (iout,'(i5,10(2f8.2,4x))') i,sigma_dih(k,i)
2034 !           sigma_dih(k,i)=hmscore(k)*rescore(k,i)*rescore(k,i-1)*
2035 !                          rescore(k,i-2)*rescore(k,i-3)  !  right expression ?
2036 !   Instead of res sim other local measure of b/b str reliability possible
2037             if (sigma_dih(k,i).ne.0) &
2038             sigma_dih(k,i)=1.0d0/(sigma_dih(k,i)*sigma_dih(k,i))
2039 !           sigma_dih(k,i)=sigma_dih(k,i)*sigma_dih(k,i)
2040           enddo
2041           lim_dih=nct-nnt-2
2042         endif
2043 !        write (iout,*) "Dihedral angle restraints set"
2044 !        call flush(iout)
2045
2046         if (waga_theta.gt.0.0d0) then
2047 !         open (ientin,file=tpl_k_sigma_theta,status='old')
2048 !         do irec=1,maxres-2 ! loop for reading sigma_theta, right bounds?
2049 !            read (ientin,*,end=1403) i,j,ki,sigma_theta(k,i+nnt-1) ! j,ki what for?
2050 !            sigma_theta(k,i+nnt-1)=sigma_theta(k,i+nnt-1)* ! not inverse because of use of res. similarity
2051 !    &                              sigma_theta(k,i+nnt-1)
2052 !         enddo
2053 !1403   continue
2054 !         close (ientin)
2055
2056           do i = nnt+2,nct ! right? without parallel.
2057 !         do i = i=1,nres ! alternative for bounds acc to readpdb?
2058 !         do i=ithet_start,ithet_end ! with FG parallel.
2059              if (idomain(k,i).eq.0) then
2060               sigma_theta(k,i)=0.0
2061               cycle
2062              endif
2063              thetatpl(k,i)=thetaref(i)
2064 !            write (iout,*) "thetatpl(",k,i,") =",thetatpl(k,i)
2065 !            write(iout,*)  "rescore(",k,i,") =",rescore(k,i),
2066 !    &                      "rescore(",k,i-1,") =",rescore(k,i-1),
2067 !    &                      "rescore(",k,i-2,") =",rescore(k,i-2)
2068 !            read (ientin,*) sigma_theta(k,i) ! 1st variant
2069              sigma_theta(k,i)=(rescore(k,i)+rescore(k,i-1)+ &
2070                              rescore(k,i-2))/3.0
2071 !             if (read2sigma) sigma_theta(k,i)=sigma_theta(k,i)/3.0
2072              if (sigma_theta(k,i).ne.0) &
2073              sigma_theta(k,i)=1.0d0/(sigma_theta(k,i)*sigma_theta(k,i))
2074
2075 !            sigma_theta(k,i)=hmscore(k)*rescore(k,i)*rescore(k,i-1)*
2076 !                             rescore(k,i-2) !  right expression ?
2077 !            sigma_theta(k,i)=sigma_theta(k,i)*sigma_theta(k,i)
2078           enddo
2079         endif
2080 !        write (iout,*) "Angle restraints set"
2081 !        call flush(iout)
2082
2083         if (waga_d.gt.0.0d0) then
2084 !       open (ientin,file=tpl_k_sigma_d,status='old')
2085 !         do irec=1,maxres-1 ! loop for reading sigma_theta, right bounds?
2086 !            read (ientin,*,end=1404) i,j,sigma_d(k,i+nnt-1) ! j,ki what for?
2087 !            sigma_d(k,i+nnt-1)=sigma_d(k,i+nnt-1)* ! not inverse because of use of res. similarity
2088 !    &                          sigma_d(k,i+nnt-1)
2089 !         enddo
2090 !1404   continue
2091
2092           do i = nnt,nct ! right? without parallel.
2093 !         do i=2,nres-1 ! alternative for bounds acc to readpdb?
2094 !         do i=loc_start,loc_end ! with FG parallel.
2095                if (itype(i,1).eq.10) cycle
2096                if (idomain(k,i).eq.0 ) then
2097                   sigma_d(k,i)=0.0
2098                   cycle
2099                endif
2100                xxtpl(k,i)=xxref(i)
2101                yytpl(k,i)=yyref(i)
2102                zztpl(k,i)=zzref(i)
2103 !              write (iout,*) "xxtpl(",k,i,") =",xxtpl(k,i)
2104 !              write (iout,*) "yytpl(",k,i,") =",yytpl(k,i)
2105 !              write (iout,*) "zztpl(",k,i,") =",zztpl(k,i)
2106 !              write(iout,*)  "rescore(",k,i,") =",rescore(k,i)
2107                sigma_d(k,i)=rescore3(k,i) !  right expression ?
2108                if (sigma_d(k,i).ne.0) &
2109                sigma_d(k,i)=1.0d0/(sigma_d(k,i)*sigma_d(k,i))
2110
2111 !              sigma_d(k,i)=hmscore(k)*rescore(k,i) !  right expression ?
2112 !              sigma_d(k,i)=sigma_d(k,i)*sigma_d(k,i)
2113 !              read (ientin,*) sigma_d(k,i) ! 1st variant
2114           enddo
2115         endif
2116       enddo
2117 !      write (iout,*) "SC restraints set"
2118 !      call flush(iout)
2119 !
2120 ! remove distance restraints not used in any model from the list
2121 ! shift data in all arrays
2122 !
2123 !      write (iout,*) "waga_dist",waga_dist," nnt",nnt," nct",nct
2124       if (waga_dist.ne.0.0d0) then
2125         ii=0
2126         liiflag=.true.
2127         lfirst=.true.
2128         do i=nnt,nct-2
2129          do j=i+2,nct
2130           ii=ii+1
2131 !          if (idomain(k,i).eq.idomain(k,j).and.idomain(k,i).ne.0
2132 !     &            .and. distal.le.dist2_cut ) then
2133 !          write (iout,*) "i",i," j",j," ii",ii
2134 !          call flush(iout)
2135           if (ii_in_use(ii).eq.0.and.liiflag.or. &
2136           ii_in_use(ii).eq.1.and.liiflag.and.ii.eq.lim_odl) then
2137             liiflag=.false.
2138             i10=ii
2139             if (lfirst) then
2140               lfirst=.false.
2141               iistart=ii
2142             else
2143               if(i10.eq.lim_odl) i10=i10+1
2144               do ki=0,i10-i01-1
2145                ires_homo(iistart+ki)=ires_homo(ki+i01)
2146                jres_homo(iistart+ki)=jres_homo(ki+i01)
2147                ii_in_use(iistart+ki)=ii_in_use(ki+i01)
2148                do k=1,constr_homology
2149                 odl(k,iistart+ki)=odl(k,ki+i01)
2150                 sigma_odl(k,iistart+ki)=sigma_odl(k,ki+i01)
2151                 l_homo(k,iistart+ki)=l_homo(k,ki+i01)
2152                enddo
2153               enddo
2154               iistart=iistart+i10-i01
2155             endif
2156           endif
2157           if (ii_in_use(ii).ne.0.and..not.liiflag) then
2158              i01=ii
2159              liiflag=.true.
2160           endif
2161          enddo
2162         enddo
2163         lim_odl=iistart-1
2164       endif
2165 !      write (iout,*) "Removing distances completed"
2166 !      call flush(iout)
2167       endif ! .not. klapaucjusz
2168
2169       if (constr_homology.gt.0) call homology_partition
2170       write (iout,*) "After homology_partition"
2171       call flush(iout)
2172       if (constr_homology.gt.0) call init_int_table
2173       write (iout,*) "After init_int_table"
2174       call flush(iout)
2175 !      endif ! .not. klapaucjusz
2176 !      endif
2177 !      if (constr_homology.gt.0) call homology_partition
2178 !      write (iout,*) "After homology_partition"
2179 !      call flush(iout)
2180 !      if (constr_homology.gt.0) call init_int_table
2181 !      write (iout,*) "After init_int_table"
2182 !      call flush(iout)
2183 !      write (iout,*) "ithet_start =",ithet_start,"ithet_end =",ithet_end
2184 !      write (iout,*) "loc_start =",loc_start,"loc_end =",loc_end
2185 !
2186 ! Print restraints
2187 !
2188       if (.not.out_template_restr) return
2189 !d      write(iout,*) "waga_theta",waga_theta,"waga_d",waga_d
2190       if(me.eq.king .or. .not. out1file .and. fg_rank.eq.0) then
2191        write (iout,*) "Distance restraints from templates"
2192        do ii=1,lim_odl
2193        write(iout,'(3i7,100(2f8.2,1x,l1,4x))') &
2194         ii,ires_homo(ii),jres_homo(ii),&
2195         (odl(ki,ii),1.0d0/dsqrt(sigma_odl(ki,ii)),l_homo(ki,ii),&
2196         ki=1,constr_homology)
2197        enddo
2198        write (iout,*) "Dihedral angle restraints from templates"
2199        do i=nnt+3,nct
2200         write (iout,'(i7,a4,100(2f8.2,4x))') i,restyp(itype(i,1),1),&
2201             (rad2deg*dih(ki,i),&
2202             rad2deg/dsqrt(sigma_dih(ki,i)),ki=1,constr_homology)
2203        enddo
2204        write (iout,*) "Virtual-bond angle restraints from templates"
2205        do i=nnt+2,nct
2206         write (iout,'(i7,a4,100(2f8.2,4x))') i,restyp(itype(i,1),1),&
2207             (rad2deg*thetatpl(ki,i),&
2208             rad2deg/dsqrt(sigma_theta(ki,i)),ki=1,constr_homology)
2209        enddo
2210        write (iout,*) "SC restraints from templates"
2211        do i=nnt,nct
2212         write(iout,'(i7,100(4f8.2,4x))') i,&
2213         (xxtpl(ki,i),yytpl(ki,i),zztpl(ki,i), &
2214          1.0d0/dsqrt(sigma_d(ki,i)),ki=1,constr_homology)
2215        enddo
2216       endif
2217       return
2218       end subroutine read_constr_homology
2219 !-----------------------------------------------------------------------------
2220       subroutine read_klapaucjusz
2221 !     implicit none
2222 !     include 'DIMENSIONS'
2223 !#ifdef MPI
2224 !     include 'mpif.h'
2225 !#endif
2226 !     include 'COMMON.SETUP'
2227 !     include 'COMMON.CONTROL'
2228 !     include 'COMMON.HOMOLOGY'
2229 !     include 'COMMON.CHAIN'
2230 !     include 'COMMON.IOUNITS'
2231 !     include 'COMMON.MD'
2232 !     include 'COMMON.GEO'
2233 !     include 'COMMON.INTERACT'
2234 !     include 'COMMON.NAMES'
2235       character(len=256) fragfile
2236       integer, dimension(:), allocatable :: ninclust,nresclust,itype_temp,&
2237                          ii_in_use
2238       integer, dimension(:,:), allocatable :: iresclust,inclust
2239       integer :: nclust
2240
2241       character(len=2) :: kic2
2242       character(len=24) :: model_ki_dist, model_ki_angle
2243       character(len=500) :: controlcard
2244       integer :: ki, i, j, jj,k, l, i_tmp,&
2245       idomain_tmp,&
2246       ik,ll,lll,ii_old,ii,iii,ichain,kk,iistart,iishift,lim_xx,igr,&
2247       i01,i10,nnt_chain,nct_chain
2248       real(kind=8) :: distal
2249       logical :: lprn = .true.
2250       integer :: nres_temp
2251 !      integer :: ilen
2252 !      external :: ilen
2253       logical :: liiflag,lfirst
2254
2255       real(kind=8) rescore_tmp,x12,y12,z12,rescore2_tmp,dist_cut
2256       real(kind=8), dimension (:,:), allocatable  :: rescore
2257       real(kind=8), dimension (:,:), allocatable :: rescore2
2258       character(len=24) :: tpl_k_rescore
2259       character(len=256) :: pdbfile
2260
2261 !
2262 ! For new homol impl
2263 !
2264 !     include 'COMMON.VAR'
2265 !
2266 !      write (iout,*) "READ_KLAPAUCJUSZ"
2267 !      print *,"READ_KLAPAUCJUSZ"
2268 !      call flush(iout)
2269       call getenv("FRAGFILE",fragfile)
2270       write (iout,*) "Opening", fragfile
2271       call flush(iout)
2272       open(ientin,file=fragfile,status="old",err=10)
2273 !      write (iout,*) " opened"
2274 !      call flush(iout)
2275
2276       sigma_theta=0.0
2277       sigma_d=0.0
2278       sigma_dih=0.0
2279       l_homo = .false.
2280
2281       nres_temp=nres
2282       itype_temp(:)=itype(:,1)
2283       ii=0
2284       lim_odl=0
2285
2286 !      write (iout,*) "Entering loop"
2287 !      call flush(iout)
2288
2289       DO IGR = 1,NCHAIN_GROUP
2290
2291 !      write (iout,*) "igr",igr
2292       call flush(iout)
2293       read(ientin,*) constr_homology,nclust
2294       if (start_from_model) then
2295         nmodel_start=constr_homology
2296       else
2297         nmodel_start=0
2298       endif
2299
2300       ii_old=lim_odl
2301
2302       ichain=iequiv(1,igr)
2303       nnt_chain=chain_border(1,ichain)-chain_border1(1,ichain)+1
2304       nct_chain=chain_border(2,ichain)-chain_border1(1,ichain)+1
2305 !      write (iout,*) "nnt_chain",nnt_chain," nct_chain",nct_chain
2306
2307 ! Read pdb files
2308       if(.not.allocated(pdbfiles_chomo)) allocate(pdbfiles_chomo(constr_homology)) 
2309       if(.not.allocated(nres_chomo)) allocate(nres_chomo(constr_homology))
2310       do k=1,constr_homology
2311         read(ientin,'(a)') pdbfile
2312         write (iout,'(a,5x,a)') 'KLAPAUCJUSZ: Opening PDB file', &
2313         pdbfile(:ilen(pdbfile))
2314         pdbfiles_chomo(k)=pdbfile
2315         open(ipdbin,file=pdbfile,status='old',err=33)
2316         goto 34
2317   33    write (iout,'(a,5x,a)') 'Error opening PDB file',&
2318         pdbfile(:ilen(pdbfile))
2319         stop
2320   34    continue
2321         unres_pdb=.false.
2322 !        nres_temp=nres
2323         call readpdb_template(k)
2324         nres_chomo(k)=nres
2325 !        nres=nres_temp
2326         do i=1,nres
2327           rescore(k,i)=0.2d0
2328           rescore2(k,i)=1.0d0
2329         enddo
2330       enddo
2331 ! Read clusters
2332       do i=1,nclust
2333         read(ientin,*) ninclust(i),nresclust(i)
2334         read(ientin,*) (inclust(k,i),k=1,ninclust(i))
2335         read(ientin,*) (iresclust(k,i),k=1,nresclust(i))
2336       enddo
2337 !
2338 ! Loop over clusters
2339 !
2340       do l=1,nclust
2341         do ll = 1,ninclust(l)
2342
2343         k = inclust(ll,l)
2344 !        write (iout,*) "l",l," ll",ll," k",k
2345         do i=1,nres
2346           idomain(k,i)=0
2347         enddo
2348         do i=1,nresclust(l)
2349           if (nnt.gt.1)  then
2350             idomain(k,iresclust(i,l)+1) = 1
2351           else
2352             idomain(k,iresclust(i,l)) = 1
2353           endif
2354         enddo
2355 !
2356 !     Distance restraints
2357 !
2358 !          ... --> odl(k,ii)
2359 ! Copy the coordinates from reference coordinates (?)
2360 !        nres_temp=nres
2361         nres=nres_chomo(k)
2362         do i=1,2*nres
2363           do j=1,3
2364             c(j,i)=chomo(j,i,k)
2365 !           write (iout,*) "c(",j,i,") =",c(j,i)
2366           enddo
2367         enddo
2368         call int_from_cart(.true.,.false.)
2369         call sc_loc_geom(.false.)
2370         do i=1,nres
2371           thetaref(i)=theta(i)
2372           phiref(i)=phi(i)
2373         enddo
2374 !        nres=nres_temp
2375         if (waga_dist.ne.0.0d0) then
2376           ii=ii_old
2377 !          do i = nnt,nct-2 
2378           do i = nnt_chain,nct_chain-2
2379 !            do j=i+2,nct 
2380             do j=i+2,nct_chain
2381
2382               x12=c(1,i)-c(1,j)
2383               y12=c(2,i)-c(2,j)
2384               z12=c(3,i)-c(3,j)
2385               distal=dsqrt(x12*x12+y12*y12+z12*z12)
2386 !              write (iout,*) k,i,j,distal,dist2_cut
2387
2388             if (idomain(k,i).eq.idomain(k,j).and.idomain(k,i).ne.0 &
2389                  .and. distal.le.dist2_cut ) then
2390
2391               ii=ii+1
2392               ii_in_use(ii)=1
2393               l_homo(k,ii)=.true.
2394
2395 !             write (iout,*) "k",k
2396 !             write (iout,*) "i",i," j",j," constr_homology",
2397 !     &                       constr_homology
2398               ires_homo(ii)=i+chain_border1(1,igr)-1
2399               jres_homo(ii)=j+chain_border1(1,igr)-1
2400               odl(k,ii)=distal
2401               if (read2sigma) then
2402                 sigma_odl(k,ii)=0
2403                 do ik=i,j
2404                  sigma_odl(k,ii)=sigma_odl(k,ii)+rescore2(k,ik)
2405                 enddo
2406                 sigma_odl(k,ii)=sigma_odl(k,ii)/(j-i+1)
2407                 if (odl(k,ii).gt.dist_cut) sigma_odl(k,ii) = &
2408              sigma_odl(k,ii)*dexp(0.5d0*(odl(k,ii)/dist_cut)**2-0.5d0)
2409               else
2410                 if (odl(k,ii).le.dist_cut) then
2411                  sigma_odl(k,ii)=rescore(k,i)+rescore(k,j)
2412                 else
2413 #ifdef OLDSIGMA
2414                  sigma_odl(k,ii)=(rescore(k,i)+rescore(k,j))* &
2415                            dexp(0.5d0*(odl(k,ii)/dist_cut)**2)
2416 #else
2417                  sigma_odl(k,ii)=(rescore(k,i)+rescore(k,j))* &
2418                            dexp(0.5d0*(odl(k,ii)/dist_cut)**2-0.5d0)
2419 #endif
2420                 endif
2421               endif
2422               sigma_odl(k,ii)=1.0d0/(sigma_odl(k,ii)*sigma_odl(k,ii))
2423             else
2424               ii=ii+1
2425 !              l_homo(k,ii)=.false.
2426             endif
2427             enddo
2428           enddo
2429         lim_odl=ii
2430         endif
2431 !
2432 !     Theta, dihedral and SC retraints
2433 !
2434         if (waga_angle.gt.0.0d0) then
2435           do i = nnt_chain+3,nct_chain
2436             iii=i+chain_border1(1,igr)-1
2437             if (idomain(k,i).eq.0) then
2438 !               sigma_dih(k,i)=0.0
2439                cycle
2440             endif
2441             dih(k,iii)=phiref(i)
2442             sigma_dih(k,iii)= &
2443                (rescore(k,i)+rescore(k,i-1)+ &
2444                            rescore(k,i-2)+rescore(k,i-3))/4.0
2445 !            write (iout,*) "k",k," l",l," i",i," rescore",rescore(k,i),
2446 !     &       " sigma_dihed",sigma_dih(k,i)
2447             if (sigma_dih(k,iii).ne.0) &
2448              sigma_dih(k,iii)=1.0d0/(sigma_dih(k,iii)*sigma_dih(k,iii))
2449           enddo
2450 !          lim_dih=nct-nnt-2 
2451         endif
2452
2453         if (waga_theta.gt.0.0d0) then
2454           do i = nnt_chain+2,nct_chain
2455              iii=i+chain_border1(1,igr)-1
2456              if (idomain(k,i).eq.0) then
2457 !              sigma_theta(k,i)=0.0
2458               cycle
2459              endif
2460              thetatpl(k,iii)=thetaref(i)
2461              sigma_theta(k,iii)=(rescore(k,i)+rescore(k,i-1)+ &
2462                               rescore(k,i-2))/3.0
2463              if (sigma_theta(k,iii).ne.0) &
2464              sigma_theta(k,iii)=1.0d0/ &
2465              (sigma_theta(k,iii)*sigma_theta(k,iii))
2466           enddo
2467         endif
2468
2469         if (waga_d.gt.0.0d0) then
2470           do i = nnt_chain,nct_chain
2471              iii=i+chain_border1(1,igr)-1
2472                if (itype(i,1).eq.10) cycle
2473                if (idomain(k,i).eq.0 ) then
2474 !                  sigma_d(k,i)=0.0
2475                   cycle
2476                endif
2477                xxtpl(k,iii)=xxref(i)
2478                yytpl(k,iii)=yyref(i)
2479                zztpl(k,iii)=zzref(i)
2480                sigma_d(k,iii)=rescore(k,i)
2481                if (sigma_d(k,iii).ne.0) &
2482                 sigma_d(k,iii)=1.0d0/(sigma_d(k,iii)*sigma_d(k,iii))
2483 !               if (i-nnt+1.gt.lim_xx) lim_xx=i-nnt+1
2484           enddo
2485         endif
2486       enddo ! l
2487       enddo ! ll
2488 !
2489 ! remove distance restraints not used in any model from the list
2490 ! shift data in all arrays
2491 !
2492 !      write (iout,*) "ii_old",ii_old
2493       if (waga_dist.ne.0.0d0) then
2494 #ifdef DEBUG
2495        write (iout,*) "Distance restraints from templates"
2496        do iii=1,lim_odl
2497        write(iout,'(4i5,100(2f8.2,1x,l1,4x))') &
2498         iii,ii_in_use(iii),ires_homo(iii),jres_homo(iii), &
2499         (odl(ki,iii),1.0d0/dsqrt(sigma_odl(ki,iii)),l_homo(ki,iii), &
2500         ki=1,constr_homology)
2501        enddo
2502 #endif
2503         ii=ii_old
2504         liiflag=.true.
2505         lfirst=.true.
2506         do i=nnt_chain,nct_chain-2
2507          do j=i+2,nct_chain
2508           ii=ii+1
2509 !          if (idomain(k,i).eq.idomain(k,j).and.idomain(k,i).ne.0
2510 !     &            .and. distal.le.dist2_cut ) then
2511 !          write (iout,*) "i",i," j",j," ii",ii," i_in_use",ii_in_use(ii)
2512 !          call flush(iout)
2513           if (ii_in_use(ii).eq.0.and.liiflag.or. &
2514           ii_in_use(ii).eq.1.and.liiflag.and.ii.eq.lim_odl) then
2515             liiflag=.false.
2516             i10=ii
2517             if (lfirst) then
2518               lfirst=.false.
2519               iistart=ii
2520             else
2521               if(i10.eq.lim_odl) i10=i10+1
2522               do ki=0,i10-i01-1
2523                ires_homo(iistart+ki)=ires_homo(ki+i01)
2524                jres_homo(iistart+ki)=jres_homo(ki+i01)
2525                ii_in_use(iistart+ki)=ii_in_use(ki+i01)
2526                do k=1,constr_homology
2527                 odl(k,iistart+ki)=odl(k,ki+i01)
2528                 sigma_odl(k,iistart+ki)=sigma_odl(k,ki+i01)
2529                 l_homo(k,iistart+ki)=l_homo(k,ki+i01)
2530                enddo
2531               enddo
2532               iistart=iistart+i10-i01
2533             endif
2534           endif
2535           if (ii_in_use(ii).ne.0.and..not.liiflag) then
2536              i01=ii
2537              liiflag=.true.
2538           endif
2539          enddo
2540         enddo
2541         lim_odl=iistart-1
2542       endif
2543
2544       lll=lim_odl-ii_old
2545
2546       do i=2,nequiv(igr)
2547
2548         ichain=iequiv(i,igr)
2549
2550         do j=nnt_chain,nct_chain
2551           jj=j+chain_border1(1,ichain)-chain_border1(1,iequiv(1,igr))
2552           do k=1,constr_homology
2553             dih(k,jj)=dih(k,j)
2554             sigma_dih(k,jj)=sigma_dih(k,j)
2555             thetatpl(k,jj)=thetatpl(k,j)
2556             sigma_theta(k,jj)=sigma_theta(k,j)
2557             xxtpl(k,jj)=xxtpl(k,j)
2558             yytpl(k,jj)=yytpl(k,j)
2559             zztpl(k,jj)=zztpl(k,j)
2560             sigma_d(k,jj)=sigma_d(k,j)
2561           enddo
2562         enddo
2563
2564         jj=chain_border1(1,ichain)-chain_border1(1,iequiv(i-1,igr))
2565 !        write (iout,*) "igr",igr," i",i," ichain",ichain," jj",jj
2566         do j=ii_old+1,lim_odl
2567           ires_homo(j+lll)=ires_homo(j)+jj
2568           jres_homo(j+lll)=jres_homo(j)+jj
2569           do k=1,constr_homology
2570             odl(k,j+lll)=odl(k,j)
2571             sigma_odl(k,j+lll)=sigma_odl(k,j)
2572             l_homo(k,j+lll)=l_homo(k,j)
2573           enddo
2574         enddo
2575
2576         ii_old=ii_old+lll
2577         lim_odl=lim_odl+lll
2578
2579       enddo
2580
2581       ENDDO ! IGR
2582
2583       if (waga_angle.gt.0.0d0) lim_dih=nct-nnt-2
2584       nres=nres_temp
2585       itype(:,1)=itype_temp(:)
2586
2587       return
2588    10 stop "Error in fragment file"
2589       end subroutine read_klapaucjusz
2590 !-----------------------------------------------------------------------------
2591       end module io