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