Added homology restraints modified from Pawel and Magda's code
[unres.git] / source / cluster / wham / src-restraint-MP / probabl.F
1       subroutine probabl(ib,nlist,ncon,*)
2 ! construct the conformational ensembles at REMD temperatures
3       implicit none
4       include "DIMENSIONS"
5       include "sizesclu.dat"
6 #ifdef MPI
7       include "mpif.h"
8       include "COMMON.MPI"
9       integer ierror,errcode,status(MPI_STATUS_SIZE) 
10 #endif
11       include "COMMON.IOUNITS"
12       include "COMMON.FREE"
13       include "COMMON.FFIELD"
14       include "COMMON.INTERACT"
15       include "COMMON.SBRIDGE"
16       include "COMMON.CHAIN"
17       include "COMMON.CLUSTER"
18       real*4 csingle(3,maxres2)
19       double precision fT(5),fTprim(5),fTbis(5),quot,quotl1,quotl,kfacl,
20      &  eprim,ebis,temper,kfac/2.4d0/,T0/300.0d0/
21       double precision etot,evdw,evdw2,ees,evdw1,ebe,etors,escloc,
22      &      ehpb,ecorr,ecorr5,ecorr6,eello_turn4,eello_turn3,
23      &      eturn6,eel_loc,edihcnstr,etors_d,estr,evdw2_14,esccor
24       integer i,ii,ik,iproc,iscor,j,k,l,ib,nlist,ncon
25       double precision qfree,sumprob,eini,efree,rmsdev
26       character*80 bxname
27       character*2 licz1
28       character*5 ctemper
29       integer ilen
30       external ilen
31       real*4 Fdimless(maxconf)
32       double precision energia(0:max_ene)
33       do i=1,ncon
34         list_conf(i)=i
35       enddo
36 c      do i=1,ncon
37 c        write (iout,*) i,list_conf(i)
38 c      enddo
39 c      do i=1,ncon
40 c        write(iout,*) "entrop before", entfac(i),i
41 c      enddo
42
43 #ifdef MPI
44       write (iout,*) me," indstart",indstart(me)," indend",indend(me)
45       call daread_ccoords(indstart(me),indend(me))
46 #endif
47 c      do i=1,ncon
48 c        write(iout,*) "entrop after", entfac(i),i
49 c      enddo
50
51 c      write (iout,*) "ncon",ncon
52
53       temper=1.0d0/(beta_h(ib)*1.987D-3)
54 c      write (iout,*) "ib",ib," beta_h",beta_h(ib)," temper",temper
55 c      quot=1.0d0/(T0*beta_h(ib)*1.987D-3)
56 c      quotl=1.0d0
57 c      kfacl=1.0d0
58 c      do l=1,5
59 c        quotl1=quotl
60 c        quotl=quotl*quot
61 c        kfacl=kfacl*kfac
62 c        fT(l)=kfacl/(kfacl-1.0d0+quotl)
63 c      enddo
64             if (rescale_mode.eq.1) then
65               quot=1.0d0/(T0*beta_h(ib)*1.987D-3)
66               quotl=1.0d0
67               kfacl=1.0d0
68               do l=1,5
69                 quotl1=quotl
70                 quotl=quotl*quot
71                 kfacl=kfacl*kfac
72                 fT(l)=kfacl/(kfacl-1.0d0+quotl)
73               enddo
74             else if (rescale_mode.eq.2) then
75               quot=1.0d0/(T0*beta_h(ib)*1.987D-3)
76               quotl=1.0d0
77               do l=1,5
78                 quotl=quotl*quot
79                 fT(l)=1.12692801104297249644d0/
80      &             dlog(dexp(quotl)+dexp(-quotl))
81               enddo
82 c              write (iout,*) 1.0d0/(beta_h(ib)*1.987D-3),ft
83               call flush(iout)
84             endif
85
86 #ifdef MPI
87       do i=1,scount(me)
88         ii=i+indstart(me)-1
89 #else
90       do i=1,ncon
91         ii=i
92 #endif
93 c        write (iout,*) "i",i," ii",ii
94         call flush(iout)
95         if (ib.eq.1) then
96           do j=1,nres
97             do k=1,3
98               c(k,j)=allcart(k,j,i)
99               c(k,j+nres)=allcart(k,j+nres,i)
100             enddo
101           enddo
102           do k=1,3
103             c(k,nres+1)=c(k,1)
104             c(k,nres+nres)=c(k,nres)
105           enddo
106           nss=nss_all(i)
107           do j=1,nss
108             ihpb(j)=ihpb_all(j,i)
109             jhpb(j)=jhpb_all(j,i)
110           enddo 
111           call int_from_cart1(.false.)
112           call etotal(energia(0),fT)
113           totfree(i)=energia(0)
114 #ifdef DEBUG
115           write (iout,*) i," energia",(energia(j),j=0,20)
116           call enerprint(energia(0),ft)
117           call flush(iout)
118 #endif
119           do k=1,max_ene
120             enetb(k,i)=energia(k)
121           enddo
122         endif
123         evdw=enetb(1,i)
124 #ifdef SCP14
125         evdw2_14=enetb(17,i)
126         evdw2=enetb(2,i)+evdw2_14
127 #else
128         evdw2=enetb(2,i)
129         evdw2_14=0.0d0
130 #endif
131 #ifdef SPLITELE
132         ees=enetb(3,i)
133         evdw1=enetb(16,i)
134 #else
135         ees=enetb(3,i)
136         evdw1=0.0d0
137 #endif
138         ecorr=enetb(4,i)
139         ecorr5=enetb(5,i)
140         ecorr6=enetb(6,i)
141 cc        if (wcorr6.eq.0) ecorr6=0.0d0
142         eel_loc=enetb(7,i)
143         eello_turn3=enetb(8,i)
144         eello_turn4=enetb(9,i)
145         eturn6=enetb(10,i)
146         ebe=enetb(11,i)
147         escloc=enetb(12,i)
148         etors=enetb(13,i)
149         etors_d=enetb(14,i)
150         ehpb=enetb(15,i)
151         estr=enetb(18,i)
152         esccor=enetb(19,i)
153         edihcnstr=enetb(20,i)
154         ehomology_constr=enetb(21,i)
155 #ifdef SPLITELE
156         etot=wsc*evdw+wscp*evdw2+ft(1)*welec*ees+wvdwpp*evdw1
157      &  +wang*ebe+ft(1)*wtor*etors+wscloc*escloc
158      &  +wstrain*ehpb+ft(3)*wcorr*ecorr+ft(4)*wcorr5*ecorr5
159      &  +ft(5)*wcorr6*ecorr6+ft(3)*wturn4*eello_turn4
160      &  +ft(2)*wturn3*eello_turn3
161      &  +ft(5)*wturn6*eturn6+ft(2)*wel_loc*eel_loc
162      &  +edihcnstr+ft(2)*wtor_d*etors_d+ft(1)*wsccor*esccor
163      &  +wbond*estr+ehomology_constr
164 #else
165         etot=wsc*evdw+wscp*evdw2+ft(1)*welec*(ees+evdw1)
166      &  +wang*ebe+ft(1)*wtor*etors+wscloc*escloc
167      &  +wstrain*ehpb+ft(3)*wcorr*ecorr+ft(4)*wcorr5*ecorr5
168      &  +ft(5)*wcorr6*ecorr6+ft(3)*wturn4*eello_turn4
169      &  +ft(2)*wturn3*eello_turn3
170      &  +ft(5)*wturn6*eturn6+ft(2)*wel_loc*eel_loc+edihcnstr
171      &  +ft(2)*wtor_d*etors_d+ft(1)*wsccor*esccor
172      &  +wbond*estr+ehomology_constr
173 #endif
174         Fdimless(i)=beta_h(ib)*etot+entfac(ii)
175         totfree(i)=etot
176 #ifdef DEBUG
177         
178         write (iout,*) "etrop", i,ii,ib,
179      &   1.0d0/(1.987d-3*beta_h(ib)),totfree(i),
180      &   entfac(ii),Fdimless(i)
181 #endif
182       enddo   ! i
183 #ifdef MPI
184       call MPI_Gatherv(Fdimless(1),scount(me),
185      & MPI_REAL,Fdimless(1),
186      & scount(0),idispl(0),MPI_REAL,Master,
187      & MPI_COMM_WORLD, IERROR)
188       call MPI_Gatherv(totfree(1),scount(me),
189      & MPI_DOUBLE_PRECISION,totfree(1),
190      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
191      & MPI_COMM_WORLD, IERROR)
192       call MPI_Gatherv(entfac(indstart(me)+1),scount(me),
193      & MPI_DOUBLE_PRECISION,entfac(1),
194      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
195      & MPI_COMM_WORLD, IERROR)
196       if (me.eq.Master) then
197 #endif
198 c#define DEBUG
199 #ifdef DEBUG
200         write (iout,*) "The FDIMLESS array before sorting"
201         do i=1,ncon
202           write (iout,*) i,fdimless(i)
203         enddo
204 #endif
205         call mysort1(ncon,Fdimless,list_conf)
206 #ifdef DEBUG
207         write (iout,*) "The FDIMLESS array after sorting"
208         do i=1,ncon
209           write (iout,*) i,list_conf(i),fdimless(i)
210         enddo
211 #endif
212 c#undef DEBUG
213         do i=1,ncon
214           totfree(i)=fdimless(i)
215         enddo
216         qfree=0.0d0
217         do i=1,ncon
218           qfree=qfree+dexp(dble(-fdimless(i)+fdimless(1)))
219         enddo
220 c        write (iout,*) "qfree",qfree
221         nlist=1
222         sumprob=0.0
223         do i=1,min0(ncon,maxstr_proc)-1 
224           sumprob=sumprob+dexp(dble(-fdimless(i)+fdimless(1)))/qfree 
225 c#define DEBUG
226 #ifdef DEBUG
227           write (iout,*) 'i=',i,ib,beta_h(ib),
228      &     1.0d0/(1.987d-3*beta_h(ib)),list_conf(i),
229      &     totfree(list_conf(i)),
230      &     -entfac(list_conf(i)),fdimless(i),sumprob
231 #endif
232 c#undef DEBUG
233           if (sumprob.gt.prob_limit) goto 122
234 c          if (sumprob.gt.1.00d0) goto 122
235           nlist=nlist+1
236         enddo  
237   122   continue
238 #ifdef MPI
239       endif
240       call MPI_Bcast(nlist, 1, MPI_INTEGER, Master, MPI_COMM_WORLD, 
241      &   IERROR)
242       call MPI_Bcast(list_conf,nlist,MPI_INTEGER,Master,MPI_COMM_WORLD,
243      &   IERROR)
244 c      do iproc=0,nprocs
245 c        write (iout,*) "iproc",iproc," indstart",indstart(iproc),
246 c     &   " indend",indend(iproc) 
247 c      enddo
248       write (iout,*) "nlist",nlist
249 #endif
250       return
251       end
252 !--------------------------------------------------
253       subroutine mysort1(n, x, ipermut)
254       implicit none
255       integer i,j,imax,ipm,n
256       real x(n)
257       integer ipermut(n)
258       real xtemp
259       do i=1,n
260         xtemp=x(i)
261         imax=i
262         do j=i+1,n
263           if (x(j).lt.xtemp) then
264             imax=j
265             xtemp=x(j)
266           endif
267         enddo
268         x(imax)=x(i)
269         x(i)=xtemp
270         ipm=ipermut(imax)
271         ipermut(imax)=ipermut(i)
272         ipermut(i)=ipm
273       enddo
274       return
275       end