7964cdd3c53a593df9e699a9b1d698489cf9073c
[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).ne.10) then
224 !d             print *,'i=',i,' itype=',itype(i),' theta=',theta(i+1)
225                fail=.true.
226                ii=0
227                do while (fail .and. ii .le. maxsi)
228                  call gen_side(itype(i),theta(i+1),alph(i),omeg(i),fail)
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, only:refstr
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
517       real(kind=8) :: rms,frac,frac_nn,co
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 (refstr) then
531          call rms_nac_nnc(rms,frac,frac_nn,co,.false.)
532           write (line1,'(i10,f15.2,3f12.3,f7.2,4f6.3,3f12.3,i5,$)') &
533                 itime,totT,EK,potE,totE,&
534                 rms,frac,frac_nn,co,amax,kinetic_T,t_bath,gyrate(),me
535           format1="a133"
536         else
537           write (line1,'(i10,f15.2,7f12.3,i5,$)') &
538                  itime,totT,EK,potE,totE,&
539                  amax,kinetic_T,t_bath,gyrate(),me
540           format1="a114"
541         endif
542         if(usampl.and.totT.gt.eq_time) then
543            write(line2,'(i5,2f9.4,300f7.4)') iset,uconst,uconst_back,&
544             (qfrag(ii1),ii1=1,nfrag),(qpair(ii2),ii2=1,npair),&
545             (utheta(i),ugamma(i),uscdiff(i),i=1,nfrag_back)
546            write(format2,'(a1,i3.3)') "a",23+7*nfrag+7*npair &
547                    +21*nfrag_back
548         else
549            format2="a001"
550            line2=' '
551         endif
552         if (print_compon) then
553           if(itime.eq.0) then
554            write(format,'(a1,a4,a1,a4,a10)') "(",format1,",",format2,&
555                                                            ",20a12)"
556            write (istat,format) "#","",&
557             (ename(print_order(i)),i=1,nprint_ene)
558           endif
559           write(format,'(a1,a4,a1,a4,a10)') "(",format1,",",format2,&
560                                                            ",20f12.3)"
561           write (istat,format) line1,line2,&
562             (potEcomp(print_order(i)),i=1,nprint_ene)
563         else
564           write(format,'(a1,a4,a1,a4,a1)') "(",format1,",",format2,")"
565           write (istat,format) line1,line2
566         endif
567 #if defined(AIX)
568         call flush(istat)
569 #else
570         close(istat)
571 #endif
572       return
573       end subroutine  statout
574 !-----------------------------------------------------------------------------
575 ! readrtns_CSA.F
576 !-----------------------------------------------------------------------------
577       subroutine readrtns
578
579       use control_data
580       use energy_data
581       use MPI_data
582       use muca_md, only:read_muca
583 !      implicit real*8 (a-h,o-z)
584 !      include 'DIMENSIONS'
585 #ifdef MPI
586       include 'mpif.h'
587 #endif
588 !      include 'COMMON.SETUP'
589 !      include 'COMMON.CONTROL'
590 !      include 'COMMON.SBRIDGE'
591 !      include 'COMMON.IOUNITS'
592       logical :: file_exist
593       integer :: i
594 ! Read force-field parameters except weights
595       call parmread
596 ! Read job setup parameters
597       call read_control
598 ! Read control parameters for energy minimzation if required
599       if (minim) call read_minim
600 ! Read MCM control parameters if required
601       if (modecalc.eq.3 .or. modecalc.eq.6) call mcmread
602 ! Read MD control parameters if reqjuired
603       if (modecalc.eq.12) call read_MDpar
604 ! Read MREMD control parameters if required
605       if (modecalc.eq.14) then 
606          call read_MDpar
607          call read_REMDpar
608       endif
609 ! Read MUCA control parameters if required
610       if (lmuca) call read_muca
611 ! Read CSA control parameters if required (from fort.40 if exists
612 ! otherwise from general input file)
613       if (modecalc.eq.8) then
614        inquire (file="fort.40",exist=file_exist)
615        if (.not.file_exist) call csaread
616       endif 
617 !fmc      if (modecalc.eq.10) call mcmfread
618 ! Read molecule information, molecule geometry, energy-term weights, and
619 ! restraints if requested
620       call molread
621 ! Print restraint information
622 #ifdef MPI
623       if (.not. out1file .or. me.eq.king) then
624 #endif
625       if (nhpb.gt.nss) &
626       write (iout,'(a,i5,a)') "The following",nhpb-nss,&
627        " distance constraints have been imposed"
628       do i=nss+1,nhpb
629         write (iout,'(3i6,f10.5)') i-nss,ihpb(i),jhpb(i),forcon(i)
630       enddo
631 #ifdef MPI
632       endif
633 #endif
634 !      print *,"Processor",myrank," leaves READRTNS"
635 !      write(iout,*) "end readrtns"
636       return
637       end subroutine readrtns
638 !-----------------------------------------------------------------------------
639       subroutine molread
640 !
641 ! Read molecular data.
642 !
643 !      use control, only: ilen
644       use control_data
645       use geometry_data
646       use energy_data
647       use energy
648       use compare_data
649       use MD_data, only: t_bath
650       use MPI_data
651       use compare, only:seq_comp,contact
652       use control
653 !      implicit real*8 (a-h,o-z)
654 !      include 'DIMENSIONS'
655 #ifdef MPI
656       include 'mpif.h'
657       integer :: error_msg,ierror,ierr,ierrcode
658 #endif
659 !      include 'COMMON.IOUNITS'
660 !      include 'COMMON.GEO'
661 !      include 'COMMON.VAR'
662 !      include 'COMMON.INTERACT'
663 !      include 'COMMON.LOCAL'
664 !      include 'COMMON.NAMES'
665 !      include 'COMMON.CHAIN'
666 !      include 'COMMON.FFIELD'
667 !      include 'COMMON.SBRIDGE'
668 !      include 'COMMON.HEADER'
669 !      include 'COMMON.CONTROL'
670 !      include 'COMMON.DBASE'
671 !      include 'COMMON.THREAD'
672 !      include 'COMMON.CONTACTS'
673 !      include 'COMMON.TORCNSTR'
674 !      include 'COMMON.TIME1'
675 !      include 'COMMON.BOUNDS'
676 !      include 'COMMON.MD'
677 !      include 'COMMON.SETUP'
678       character(len=4),dimension(:),allocatable :: sequence     !(maxres)
679 !      integer :: rescode
680 !      double precision x(maxvar)
681       character(len=256) :: pdbfile
682       character(len=320) :: weightcard
683       character(len=80) :: weightcard_t!,ucase
684 !      integer,dimension(:),allocatable :: itype_pdb    !(maxres)
685 !      common /pizda/ itype_pdb
686       logical :: fail   !seq_comp,
687       real(kind=8) :: energia(0:n_ene)
688 !      integer ilen
689 !el      external ilen
690 !el local varables
691       integer :: i,j,l,k,kkk,ii,i1,i2,it1,it2
692
693       real(kind=8),dimension(3,maxres2+2) :: c_alloc
694       real(kind=8),dimension(3,0:maxres2) :: dc_alloc
695       integer,dimension(maxres) :: itype_alloc
696
697       integer :: iti,nsi,maxsi,itrial,itmp
698       real(kind=8) :: wlong,scalscp,co
699       allocate(weights(n_ene))
700 !-----------------------------
701       allocate(c(3,2*maxres+2)) !(3,maxres2+2) maxres2=2*maxres
702       allocate(dc(3,0:2*maxres)) !(3,0:maxres2)
703       allocate(itype(maxres)) !(maxres)
704 !
705 ! Zero out tables.
706 !
707       c(:,:)=0.0D0
708       dc(:,:)=0.0D0
709       itype(:)=0
710 !-----------------------------
711 !
712 ! Body
713 !
714 ! Read weights of the subsequent energy terms.
715       call card_concat(weightcard,.true.)
716       call reada(weightcard,'WLONG',wlong,1.0D0)
717       call reada(weightcard,'WSC',wsc,wlong)
718       call reada(weightcard,'WSCP',wscp,wlong)
719       call reada(weightcard,'WELEC',welec,1.0D0)
720       call reada(weightcard,'WVDWPP',wvdwpp,welec)
721       call reada(weightcard,'WEL_LOC',wel_loc,1.0D0)
722       call reada(weightcard,'WCORR4',wcorr4,0.0D0)
723       call reada(weightcard,'WCORR5',wcorr5,0.0D0)
724       call reada(weightcard,'WCORR6',wcorr6,0.0D0)
725       call reada(weightcard,'WTURN3',wturn3,1.0D0)
726       call reada(weightcard,'WTURN4',wturn4,1.0D0)
727       call reada(weightcard,'WTURN6',wturn6,1.0D0)
728       call reada(weightcard,'WSCCOR',wsccor,1.0D0)
729       call reada(weightcard,'WSTRAIN',wstrain,1.0D0)
730       call reada(weightcard,'WBOND',wbond,1.0D0)
731       call reada(weightcard,'WTOR',wtor,1.0D0)
732       call reada(weightcard,'WTORD',wtor_d,1.0D0)
733       call reada(weightcard,'WSHIELD',wshield,0.05D0)
734       call reada(weightcard,'LIPSCALE',lipscale,1.0D0)
735       call reada(weightcard,'WLT',wliptran,1.0D0)
736       call reada(weightcard,'WANG',wang,1.0D0)
737       call reada(weightcard,'WSCLOC',wscloc,1.0D0)
738       call reada(weightcard,'SCAL14',scal14,0.4D0)
739       call reada(weightcard,'SCALSCP',scalscp,1.0d0)
740       call reada(weightcard,'CUTOFF',cutoff_corr,7.0d0)
741       call reada(weightcard,'DELT_CORR',delt_corr,0.5d0)
742       call reada(weightcard,'TEMP0',temp0,300.0d0)
743       if (index(weightcard,'SOFT').gt.0) ipot=6
744 ! 12/1/95 Added weight for the multi-body term WCORR
745       call reada(weightcard,'WCORRH',wcorr,1.0D0)
746       if (wcorr4.gt.0.0d0) wcorr=wcorr4
747       weights(1)=wsc
748       weights(2)=wscp
749       weights(3)=welec
750       weights(4)=wcorr
751       weights(5)=wcorr5
752       weights(6)=wcorr6
753       weights(7)=wel_loc
754       weights(8)=wturn3
755       weights(9)=wturn4
756       weights(10)=wturn6
757       weights(11)=wang
758       weights(12)=wscloc
759       weights(13)=wtor
760       weights(14)=wtor_d
761       weights(15)=wstrain
762       weights(16)=wvdwpp
763       weights(17)=wbond
764       weights(18)=scal14
765       weights(21)=wsccor
766       if(me.eq.king.or..not.out1file) &
767        write (iout,10) wsc,wscp,welec,wvdwpp,wbond,wang,wscloc,wtor,&
768         wtor_d,wstrain,wel_loc,wcorr,wcorr5,wcorr6,wsccor,wturn3,&
769         wturn4,wturn6
770    10 format (/'Energy-term weights (unscaled):'// &
771        'WSCC=   ',f10.6,' (SC-SC)'/ &
772        'WSCP=   ',f10.6,' (SC-p)'/ &
773        'WELEC=  ',f10.6,' (p-p electr)'/ &
774        'WVDWPP= ',f10.6,' (p-p VDW)'/ &
775        'WBOND=  ',f10.6,' (stretching)'/ &
776        'WANG=   ',f10.6,' (bending)'/ &
777        'WSCLOC= ',f10.6,' (SC local)'/ &
778        'WTOR=   ',f10.6,' (torsional)'/ &
779        'WTORD=  ',f10.6,' (double torsional)'/ &
780        'WSTRAIN=',f10.6,' (SS bridges & dist. cnstr.)'/ &
781        'WEL_LOC=',f10.6,' (multi-body 3-rd order)'/ &
782        'WCORR4= ',f10.6,' (multi-body 4th order)'/ &
783        'WCORR5= ',f10.6,' (multi-body 5th order)'/ &
784        'WCORR6= ',f10.6,' (multi-body 6th order)'/ &
785        'WSCCOR= ',f10.6,' (back-scloc correlation)'/ &
786        'WTURN3= ',f10.6,' (turns, 3rd order)'/ &
787        'WTURN4= ',f10.6,' (turns, 4th order)'/ &
788        'WTURN6= ',f10.6,' (turns, 6th order)')
789       if(me.eq.king.or..not.out1file)then
790        if (wcorr4.gt.0.0d0) then
791         write (iout,'(/2a/)') 'Local-electrostatic type correlation ',&
792          'between contact pairs of peptide groups'
793         write (iout,'(2(a,f5.3/))') &
794         'Cutoff on 4-6th order correlation terms: ',cutoff_corr,&
795         'Range of quenching the correlation terms:',2*delt_corr 
796        else if (wcorr.gt.0.0d0) then
797         write (iout,'(/2a/)') 'Hydrogen-bonding correlation ',&
798          'between contact pairs of peptide groups'
799        endif
800        write (iout,'(a,f8.3)') &
801         'Scaling factor of 1,4 SC-p interactions:',scal14
802        write (iout,'(a,f8.3)') &
803         'General scaling factor of SC-p interactions:',scalscp
804       endif
805       r0_corr=cutoff_corr-delt_corr
806       do i=1,ntyp
807         aad(i,1)=scalscp*aad(i,1)
808         aad(i,2)=scalscp*aad(i,2)
809         bad(i,1)=scalscp*bad(i,1)
810         bad(i,2)=scalscp*bad(i,2)
811       enddo
812       call rescale_weights(t_bath)
813       if(me.eq.king.or..not.out1file) &
814        write (iout,22) wsc,wscp,welec,wvdwpp,wbond,wang,wscloc,wtor,&
815         wtor_d,wstrain,wel_loc,wcorr,wcorr5,wcorr6,wsccor,wturn3,&
816         wturn4,wturn6
817    22 format (/'Energy-term weights (scaled):'// &
818        'WSCC=   ',f10.6,' (SC-SC)'/ &
819        'WSCP=   ',f10.6,' (SC-p)'/ &
820        'WELEC=  ',f10.6,' (p-p electr)'/ &
821        'WVDWPP= ',f10.6,' (p-p VDW)'/ &
822        'WBOND=  ',f10.6,' (stretching)'/ &
823        'WANG=   ',f10.6,' (bending)'/ &
824        'WSCLOC= ',f10.6,' (SC local)'/ &
825        'WTOR=   ',f10.6,' (torsional)'/ &
826        'WTORD=  ',f10.6,' (double torsional)'/ &
827        'WSTRAIN=',f10.6,' (SS bridges & dist. cnstr.)'/ &
828        'WEL_LOC=',f10.6,' (multi-body 3-rd order)'/ &
829        'WCORR4= ',f10.6,' (multi-body 4th order)'/ &
830        'WCORR5= ',f10.6,' (multi-body 5th order)'/ &
831        'WCORR6= ',f10.6,' (multi-body 6th order)'/ &
832        'WSCCOR= ',f10.6,' (back-scloc correlatkion)'/ &
833        'WTURN3= ',f10.6,' (turns, 3rd order)'/ &
834        'WTURN4= ',f10.6,' (turns, 4th order)'/ &
835        'WTURN6= ',f10.6,' (turns, 6th order)')
836       if(me.eq.king.or..not.out1file) &
837        write (iout,*) "Reference temperature for weights calculation:",&
838         temp0
839       call reada(weightcard,"D0CM",d0cm,3.78d0)
840       call reada(weightcard,"AKCM",akcm,15.1d0)
841       call reada(weightcard,"AKTH",akth,11.0d0)
842       call reada(weightcard,"AKCT",akct,12.0d0)
843       call reada(weightcard,"V1SS",v1ss,-1.08d0)
844       call reada(weightcard,"V2SS",v2ss,7.61d0)
845       call reada(weightcard,"V3SS",v3ss,13.7d0)
846       call reada(weightcard,"EBR",ebr,-5.50D0)
847       dyn_ss=(index(weightcard,'DYN_SS').gt.0)
848
849       call reada(weightcard,"HT",Ht,0.0D0)
850       if (dyn_ss) then
851         ss_depth=ebr/wsc-0.25*eps(1,1)
852         Ht=Ht/wsc-0.25*eps(1,1)
853         akcm=akcm*wstrain/wsc
854         akth=akth*wstrain/wsc
855         akct=akct*wstrain/wsc
856         v1ss=v1ss*wstrain/wsc
857         v2ss=v2ss*wstrain/wsc
858         v3ss=v3ss*wstrain/wsc
859       else
860         ss_depth=ebr/wstrain-0.25*eps(1,1)*wsc/wstrain
861       endif
862
863       if(me.eq.king.or..not.out1file) then
864        write (iout,*) "Parameters of the SS-bond potential:"
865        write (iout,*) "D0CM",d0cm," AKCM",akcm," AKTH",akth,&
866        " AKCT",akct
867        write (iout,*) "V1SS",v1ss," V2SS",v2ss," V3SS",v3ss
868        write (iout,*) "EBR",ebr," SS_DEPTH",ss_depth
869        write (iout,*)" HT",Ht
870        print *,'indpdb=',indpdb,' pdbref=',pdbref
871       endif
872       if (indpdb.gt.0 .or. pdbref) then
873         read(inp,'(a)') pdbfile
874         if(me.eq.king.or..not.out1file) &
875          write (iout,'(2a)') 'PDB data will be read from file ',&
876          pdbfile(:ilen(pdbfile))
877         open(ipdbin,file=pdbfile,status='old',err=33)
878         goto 34 
879   33    write (iout,'(a)') 'Error opening PDB file.'
880         stop
881   34    continue
882 !        print *,'Begin reading pdb data'
883         call readpdb
884 !        print *,'Finished reading pdb data'
885         if(me.eq.king.or..not.out1file) &
886          write (iout,'(a,i3,a,i3)')'nsup=',nsup,&
887          ' nstart_sup=',nstart_sup !,"ergwergewrgae"
888 !el        if(.not.allocated(itype_pdb)) 
889         allocate(itype_pdb(nres))
890         do i=1,nres
891           itype_pdb(i)=itype(i)
892         enddo
893         close (ipdbin)
894         nnt=nstart_sup
895         nct=nstart_sup+nsup-1
896 !el        if(.not.allocated(icont_ref))
897         allocate(icont_ref(2,12*nres)) ! maxcont=12*maxres
898         call contact(.false.,ncont_ref,icont_ref,co)
899
900         if (sideadd) then 
901          if(me.eq.king.or..not.out1file) &
902           write(iout,*)'Adding sidechains'
903          maxsi=1000
904          do i=2,nres-1
905           iti=itype(i)
906           if (iti.ne.10 .and. itype(i).ne.ntyp1) then
907             nsi=0
908             fail=.true.
909             do while (fail.and.nsi.le.maxsi)
910               call gen_side(iti,theta(i+1),alph(i),omeg(i),fail)
911               nsi=nsi+1
912             enddo
913             if(fail) write(iout,*)'Adding sidechain failed for res ',&
914                     i,' after ',nsi,' trials'
915           endif
916          enddo
917         endif  
918       endif
919
920       if (indpdb.eq.0) then
921 ! Read sequence if not taken from the pdb file.
922         read (inp,*) nres
923 !        print *,'nres=',nres
924         allocate(sequence(nres))
925         if (iscode.gt.0) then
926           read (inp,'(80a1)') (sequence(i)(1:1),i=1,nres)
927         else
928           read (inp,'(20(1x,a3))') (sequence(i),i=1,nres)
929         endif
930 ! Convert sequence to numeric code
931         do i=1,nres
932           itype(i)=rescode(i,sequence(i),iscode)
933         enddo
934 ! Assign initial virtual bond lengths
935 !elwrite(iout,*) "test_alloc"
936         if(.not.allocated(vbld)) allocate(vbld(2*nres))
937 !elwrite(iout,*) "test_alloc"
938         if(.not.allocated(vbld_inv)) allocate(vbld_inv(2*nres))
939 !elwrite(iout,*) "test_alloc"
940         do i=2,nres
941           vbld(i)=vbl
942           vbld_inv(i)=vblinv
943         enddo
944         do i=2,nres-1
945           vbld(i+nres)=dsc(iabs(itype(i)))
946           vbld_inv(i+nres)=dsc_inv(iabs(itype(i)))
947 !          write (iout,*) "i",i," itype",itype(i),
948 !     &      " dsc",dsc(itype(i))," vbld",vbld(i),vbld(i+nres)
949         enddo
950       endif 
951 !      print *,nres
952 !      print '(20i4)',(itype(i),i=1,nres)
953 !----------------------------
954 !el reallocate tables
955 !      do i=1,maxres2
956 !        do j=1,3
957 !          c_alloc(j,i)=c(j,i)
958 !          dc_alloc(j,i)=dc(j,i)
959 !        enddo
960 !      enddo
961 !      do i=1,maxres
962 !elwrite(iout,*) "itype",i,itype(i)
963 !        itype_alloc(i)=itype(i)
964 !      enddo
965
966 !      deallocate(c)
967 !      deallocate(dc)
968 !      deallocate(itype)
969 !      allocate(c(3,2*nres+4))
970 !      allocate(dc(3,0:2*nres+2))
971 !      allocate(itype(nres+2))
972       allocate(itel(nres+2))
973       itel(:)=0
974
975 !      do i=1,2*nres+2
976 !        do j=1,3
977 !          c(j,i)=c_alloc(j,i)
978 !          dc(j,i)=dc_alloc(j,i)
979 !        enddo
980 !      enddo
981 !      do i=1,nres+2
982 !        itype(i)=itype_alloc(i)
983 !        itel(i)=0
984 !      enddo
985 !--------------------------
986       do i=1,nres
987 #ifdef PROCOR
988         if (itype(i).eq.ntyp1 .or. itype(i+1).eq.ntyp1) then
989 #else
990         if (itype(i).eq.ntyp1) then
991 #endif
992           itel(i)=0
993 #ifdef PROCOR
994         else if (iabs(itype(i+1)).ne.20) then
995 #else
996         else if (iabs(itype(i)).ne.20) then
997 #endif
998           itel(i)=1
999         else
1000           itel(i)=2
1001         endif  
1002       enddo
1003       if(me.eq.king.or..not.out1file)then
1004        write (iout,*) "ITEL"
1005        do i=1,nres-1
1006          write (iout,*) i,itype(i),itel(i)
1007        enddo
1008        print *,'Call Read_Bridge.'
1009       endif
1010       call read_bridge
1011 !--------------------------------
1012 ! znamy nres oraz nss można zaalokowac potrzebne tablice
1013       call alloc_geo_arrays
1014       call alloc_ener_arrays
1015 !--------------------------------
1016 ! 8/13/98 Set limits to generating the dihedral angles
1017       do i=1,nres
1018         phibound(1,i)=-pi
1019         phibound(2,i)=pi
1020       enddo
1021       read (inp,*) ndih_constr
1022       if (ndih_constr.gt.0) then
1023         allocate(idih_constr(ndih_constr),idih_nconstr(ndih_constr)) !(maxdih_constr)
1024         allocate(phi0(ndih_constr),drange(ndih_constr)) !(maxdih_constr)
1025         read (inp,*) ftors
1026         read (inp,*) (idih_constr(i),phi0(i),drange(i),i=1,ndih_constr)
1027         if(me.eq.king.or..not.out1file)then
1028          write (iout,*) &
1029          'There are',ndih_constr,' constraints on phi angles.'
1030          do i=1,ndih_constr
1031           write (iout,'(i5,2f8.3)') idih_constr(i),phi0(i),drange(i)
1032          enddo
1033         endif
1034         do i=1,ndih_constr
1035           phi0(i)=deg2rad*phi0(i)
1036           drange(i)=deg2rad*drange(i)
1037         enddo
1038         if(me.eq.king.or..not.out1file) &
1039          write (iout,*) 'FTORS',ftors
1040         do i=1,ndih_constr
1041           ii = idih_constr(i)
1042           phibound(1,ii) = phi0(i)-drange(i)
1043           phibound(2,ii) = phi0(i)+drange(i)
1044         enddo 
1045       endif
1046       nnt=1
1047 #ifdef MPI
1048       if (me.eq.king) then
1049 #endif
1050        write (iout,'(a)') 'Boundaries in phi angle sampling:'
1051        do i=1,nres
1052          write (iout,'(a3,i5,2f10.1)') &
1053          restyp(itype(i)),i,phibound(1,i)*rad2deg,phibound(2,i)*rad2deg
1054        enddo
1055 #ifdef MP
1056       endif
1057 #endif
1058       nct=nres
1059 !d      print *,'NNT=',NNT,' NCT=',NCT
1060       if (itype(1).eq.ntyp1) nnt=2
1061       if (itype(nres).eq.ntyp1) nct=nct-1
1062       if (pdbref) then
1063         if(me.eq.king.or..not.out1file) &
1064          write (iout,'(a,i3)') 'nsup=',nsup
1065         nstart_seq=nnt
1066         if (nsup.le.(nct-nnt+1)) then
1067           do i=0,nct-nnt+1-nsup
1068             if (seq_comp(itype(nnt+i),itype_pdb(nstart_sup),nsup)) then
1069               nstart_seq=nnt+i
1070               goto 111
1071             endif
1072           enddo
1073           write (iout,'(a)') &
1074                   'Error - sequences to be superposed do not match.'
1075           stop
1076         else
1077           do i=0,nsup-(nct-nnt+1)
1078             if (seq_comp(itype(nnt),itype_pdb(nstart_sup+i),nct-nnt+1)) &
1079             then
1080               nstart_sup=nstart_sup+i
1081               nsup=nct-nnt+1
1082               goto 111
1083             endif
1084           enddo 
1085           write (iout,'(a)') &
1086                   'Error - sequences to be superposed do not match.'
1087         endif
1088   111   continue
1089         if (nsup.eq.0) nsup=nct-nnt
1090         if (nstart_sup.eq.0) nstart_sup=nnt
1091         if (nstart_seq.eq.0) nstart_seq=nnt
1092         if(me.eq.king.or..not.out1file) &
1093          write (iout,*) 'nsup=',nsup,' nstart_sup=',nstart_sup,&
1094                        ' nstart_seq=',nstart_seq !,"242343453254"
1095       endif
1096 !--- Zscore rms -------
1097       if (nz_start.eq.0) nz_start=nnt
1098       if (nz_end.eq.0 .and. nsup.gt.0) then
1099         nz_end=nnt+nsup-1
1100       else if (nz_end.eq.0) then
1101         nz_end=nct
1102       endif
1103       if(me.eq.king.or..not.out1file)then
1104        write (iout,*) 'NZ_START=',nz_start,' NZ_END=',nz_end
1105        write (iout,*) 'IZ_SC=',iz_sc
1106       endif
1107 !----------------------
1108       call init_int_table
1109       if (refstr) then
1110         if (.not.pdbref) then
1111           call read_angles(inp,*38)
1112           goto 39
1113    38     write (iout,'(a)') 'Error reading reference structure.'
1114 #ifdef MPI
1115           call MPI_Finalize(MPI_COMM_WORLD,IERROR)
1116           stop 'Error reading reference structure'
1117 #endif
1118    39     call chainbuild
1119           call setup_var
1120 !zscore          call geom_to_var(nvar,coord_exp_zs(1,1))
1121           nstart_sup=nnt
1122           nstart_seq=nnt
1123           nsup=nct-nnt+1
1124           kkk=1
1125           do i=1,2*nres
1126             do j=1,3
1127               cref(j,i,kkk)=c(j,i)
1128             enddo
1129           enddo
1130           call contact(.true.,ncont_ref,icont_ref,co)
1131         endif
1132 !        write (iout,*) "constr_dist",constr_dist,nstart_sup,nsup
1133         call flush(iout)
1134         if (constr_dist.gt.0) call read_dist_constr
1135         write (iout,*) "After read_dist_constr nhpb",nhpb
1136         call hpb_partition
1137         if(me.eq.king.or..not.out1file) &
1138          write (iout,*) 'Contact order:',co
1139         if (pdbref) then
1140         if(me.eq.king.or..not.out1file) &
1141          write (2,*) 'Shifting contacts:',nstart_seq,nstart_sup
1142         do i=1,ncont_ref
1143           do j=1,2
1144             icont_ref(j,i)=icont_ref(j,i)+nstart_seq-nstart_sup
1145           enddo
1146           if(me.eq.king.or..not.out1file) &
1147            write (2,*) i,' ',restyp(itype(icont_ref(1,i))),' ',&
1148            icont_ref(1,i),' ',&
1149            restyp(itype(icont_ref(2,i))),' ',icont_ref(2,i)
1150         enddo
1151         endif
1152       endif
1153       if (indpdb.eq.0 .and. modecalc.ne.2 .and. modecalc.ne.4 &
1154           .and. modecalc.ne.8 .and. modecalc.ne.9 .and. &
1155           modecalc.ne.10) then
1156 ! If input structure hasn't been supplied from the PDB file read or generate
1157 ! initial geometry.
1158         if (iranconf.eq.0 .and. .not. extconf) then
1159           if(me.eq.king.or..not.out1file .and.fg_rank.eq.0) &
1160            write (iout,'(a)') 'Initial geometry will be read in.'
1161           if (read_cart) then
1162             read(inp,'(8f10.5)',end=36,err=36) &
1163              ((c(l,k),l=1,3),k=1,nres),&
1164              ((c(l,k+nres),l=1,3),k=nnt,nct)
1165             write (iout,*) "Exit READ_CART"
1166             write (iout,'(8f10.5)') &
1167              ((c(l,k),l=1,3),k=1,nres),&
1168              ((c(l,k+nres),l=1,3),k=nnt,nct)
1169             call int_from_cart1(.true.)
1170             write (iout,*) "Finish INT_TO_CART"
1171             do i=1,nres-1
1172               do j=1,3
1173                 dc(j,i)=c(j,i+1)-c(j,i)
1174                 dc_norm(j,i)=dc_norm(j,i)*vbld_inv(i+1)
1175               enddo
1176             enddo
1177             do i=nnt,nct
1178               if (itype(i).ne.10 .and. itype(i).ne.ntyp1) then
1179                 do j=1,3
1180                   dc(j,i+nres)=c(j,i+nres)-c(j,i) 
1181                   dc_norm(j,i+nres)=dc_norm(j,i+nres)*vbld_inv(i+nres)
1182                 enddo
1183               endif
1184             enddo
1185             return
1186           else
1187             call read_angles(inp,*36)
1188           endif
1189           goto 37
1190    36     write (iout,'(a)') 'Error reading angle file.'
1191 #ifdef MPI
1192           call mpi_finalize( MPI_COMM_WORLD,IERR )
1193 #endif
1194           stop 'Error reading angle file.'
1195    37     continue 
1196         else if (extconf) then
1197          if(me.eq.king.or..not.out1file .and. fg_rank.eq.0) &
1198           write (iout,'(a)') 'Extended chain initial geometry.'
1199          do i=3,nres
1200           theta(i)=90d0*deg2rad
1201          enddo
1202          do i=4,nres
1203           phi(i)=180d0*deg2rad
1204          enddo
1205          do i=2,nres-1
1206           alph(i)=110d0*deg2rad
1207          enddo
1208 !elwrite (iout,*)"alph(i)*deg2rad",(alph(i), i=1,nres)
1209          do i=2,nres-1
1210           omeg(i)=-120d0*deg2rad
1211           if (itype(i).le.0) omeg(i)=-omeg(i)
1212          enddo
1213         else
1214           if(me.eq.king.or..not.out1file) &
1215            write (iout,'(a)') 'Random-generated initial geometry.'
1216
1217
1218 #ifdef MPI
1219           if (me.eq.king  .or. fg_rank.eq.0 .and. &
1220                  ( modecalc.eq.12 .or. modecalc.eq.14) ) then  
1221 #endif
1222             do itrial=1,100
1223               itmp=1
1224               call gen_rand_conf(itmp,*30)
1225               goto 40
1226    30         write (iout,*) 'Failed to generate random conformation',&
1227                 ', itrial=',itrial
1228               write (*,*) 'Processor:',me,&
1229                 ' Failed to generate random conformation',&
1230                 ' itrial=',itrial
1231               call intout
1232
1233 #ifdef AIX
1234               call flush_(iout)
1235 #else
1236               call flush(iout)
1237 #endif
1238             enddo
1239             write (iout,'(a,i3,a)') 'Processor:',me,&
1240               ' error in generating random conformation.'
1241             write (*,'(a,i3,a)') 'Processor:',me,&
1242               ' error in generating random conformation.'
1243             call flush(iout)
1244 #ifdef MPI
1245             call MPI_Abort(mpi_comm_world,error_msg,ierrcode)            
1246    40       continue
1247           endif
1248 #else
1249           do itrial=1,100
1250             itmp=1
1251             call gen_rand_conf(itmp,*335)
1252             goto 40
1253   335       write (iout,*) 'Failed to generate random conformation',&
1254               ', itrial=',itrial
1255             write (*,*) 'Failed to generate random conformation',&
1256               ', itrial=',itrial
1257           enddo
1258           write (iout,'(a,i3,a)') 'Processor:',me,&
1259             ' error in generating random conformation.'
1260           write (*,'(a,i3,a)') 'Processor:',me,&
1261             ' error in generating random conformation.'
1262           stop
1263    40     continue
1264 #endif
1265         endif
1266       elseif (modecalc.eq.4) then
1267         read (inp,'(a)') intinname
1268         open (intin,file=intinname,status='old',err=333)
1269         if (me.eq.king .or. .not.out1file.and.fg_rank.eq.0) &
1270         write (iout,'(a)') 'intinname',intinname
1271         write (*,'(a)') 'Processor',myrank,' intinname',intinname
1272         goto 334
1273   333   write (iout,'(2a)') 'Error opening angle file ',intinname
1274 #ifdef MPI 
1275         call MPI_Finalize(MPI_COMM_WORLD,IERR)
1276 #endif   
1277         stop 'Error opening angle file.' 
1278   334   continue
1279
1280       endif 
1281 ! Generate distance constraints, if the PDB structure is to be regularized. 
1282       if (nthread.gt.0) then
1283         call read_threadbase
1284       endif
1285       call setup_var
1286 !elwrite (iout,*)"alph(i)*deg2rad",(alph(i), i=1,nres)
1287       if (me.eq.king .or. .not. out1file) &
1288        call intout
1289 !elwrite (iout,*)"alph(i)*rad2deg",(alph(i)*rad2deg, i=1,nres)
1290       if (ns.gt.0 .and. (me.eq.king .or. .not.out1file) ) then
1291         write (iout,'(/a,i3,a)') &
1292         'The chain contains',ns,' disulfide-bridging cysteines.'
1293         write (iout,'(20i4)') (iss(i),i=1,ns)
1294        if (dyn_ss) then
1295           write(iout,*)"Running with dynamic disulfide-bond formation"
1296        else
1297         write (iout,'(/a/)') 'Pre-formed links are:' 
1298         do i=1,nss
1299           i1=ihpb(i)-nres
1300           i2=jhpb(i)-nres
1301           it1=itype(i1)
1302           it2=itype(i2)
1303           if (me.eq.king.or..not.out1file) &
1304           write (iout,'(2a,i3,3a,i3,a,3f10.3)') &
1305           restyp(it1),'(',i1,') -- ',restyp(it2),'(',i2,')',dhpb(i),&
1306           ebr,forcon(i)
1307         enddo
1308         write (iout,'(a)')
1309        endif
1310       endif
1311       if (ns.gt.0.and.dyn_ss) then
1312           do i=nss+1,nhpb
1313             ihpb(i-nss)=ihpb(i)
1314             jhpb(i-nss)=jhpb(i)
1315             forcon(i-nss)=forcon(i)
1316             dhpb(i-nss)=dhpb(i)
1317           enddo
1318           nhpb=nhpb-nss
1319           nss=0
1320           call hpb_partition
1321           do i=1,ns
1322             dyn_ss_mask(iss(i))=.true.
1323           enddo
1324       endif
1325       if (i2ndstr.gt.0) call secstrp2dihc
1326 !      call geom_to_var(nvar,x)
1327 !      call etotal(energia(0))
1328 !      call enerprint(energia(0))
1329 !      call briefout(0,etot)
1330 !      stop
1331 !d    write (iout,'(2(a,i3))') 'NNT',NNT,' NCT',NCT
1332 !d    write (iout,'(a)') 'Variable list:'
1333 !d    write (iout,'(i4,f10.5)') (i,rad2deg*x(i),i=1,nvar)
1334 #ifdef MPI
1335       if (me.eq.king .or. (fg_rank.eq.0 .and. .not.out1file)) &
1336         write (iout,'(//80(1h*)/20x,a,i4,a/80(1h*)//)') &
1337         'Processor',myrank,': end reading molecular data.'
1338 #endif
1339       return
1340       end subroutine molread
1341 !-----------------------------------------------------------------------------
1342 !-----------------------------------------------------------------------------
1343       end module io