5/20/2012 by Adam
[unres.git] / source / cluster / wham / src / 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 #ifdef MPI
40       write (iout,*) me," indstart",indstart(me)," indend",indend(me)
41       call daread_ccoords(indstart(me),indend(me))
42 #endif
43 c      write (iout,*) "ncon",ncon
44       temper=1.0d0/(beta_h(ib)*1.987D-3)
45 c      write (iout,*) "ib",ib," beta_h",beta_h(ib)," temper",temper
46 c      quot=1.0d0/(T0*beta_h(ib)*1.987D-3)
47 c      quotl=1.0d0
48 c      kfacl=1.0d0
49 c      do l=1,5
50 c        quotl1=quotl
51 c        quotl=quotl*quot
52 c        kfacl=kfacl*kfac
53 c        fT(l)=kfacl/(kfacl-1.0d0+quotl)
54 c      enddo
55             if (rescale_mode.eq.1) then
56               quot=1.0d0/(T0*beta_h(ib)*1.987D-3)
57               quotl=1.0d0
58               kfacl=1.0d0
59               do l=1,5
60                 quotl1=quotl
61                 quotl=quotl*quot
62                 kfacl=kfacl*kfac
63                 fT(l)=kfacl/(kfacl-1.0d0+quotl)
64               enddo
65             else if (rescale_mode.eq.2) then
66               quot=1.0d0/(T0*beta_h(ib)*1.987D-3)
67               quotl=1.0d0
68               do l=1,5
69                 quotl=quotl*quot
70                 fT(l)=1.12692801104297249644d0/
71      &             dlog(dexp(quotl)+dexp(-quotl))
72               enddo
73 c              write (iout,*) 1.0d0/(beta_h(ib)*1.987D-3),ft
74               call flush(iout)
75             endif
76
77 #ifdef MPI
78       do i=1,scount(me)
79         ii=i+indstart(me)-1
80 #else
81       do i=1,ncon
82         ii=i
83 #endif
84 c        write (iout,*) "i",i," ii",ii
85         call flush(iout)
86         if (ib.eq.1) then
87           do j=1,nres
88             do k=1,3
89               c(k,j)=allcart(k,j,i)
90               c(k,j+nres)=allcart(k,j+nres,i)
91             enddo
92           enddo
93           do k=1,3
94             c(k,nres+1)=c(k,1)
95             c(k,nres+nres)=c(k,nres)
96           enddo
97           nss=nss_all(i)
98           do j=1,nss
99             ihpb(j)=ihpb_all(j,i)
100             jhpb(j)=jhpb_all(j,i)
101           enddo 
102           call int_from_cart1(.false.)
103           call etotal(energia(0),fT)
104           totfree(i)=energia(0)
105 #ifdef DEBUG
106           write (iout,*) i," energia",(energia(j),j=0,21)
107           call enerprint(energia(0),ft)
108           call flush(iout)
109 #endif
110           do k=1,max_ene
111             enetb(k,i)=energia(k)
112           enddo
113         endif
114         evdw=enetb(1,i)
115 #ifdef SCP14
116         evdw2_14=enetb(17,i)
117         evdw2=enetb(2,i)+evdw2_14
118 #else
119         evdw2=enetb(2,i)
120         evdw2_14=0.0d0
121 #endif
122 #ifdef SPLITELE
123         ees=enetb(3,i)
124         evdw1=enetb(16,i)
125 #else
126         ees=enetb(3,i)
127         evdw1=0.0d0
128 #endif
129         ecorr=enetb(4,i)
130         ecorr5=enetb(5,i)
131         ecorr6=enetb(6,i)
132         eel_loc=enetb(7,i)
133         eello_turn3=enetb(8,i)
134         eello_turn4=enetb(9,i)
135         eturn6=enetb(10,i)
136         ebe=enetb(11,i)
137         escloc=enetb(12,i)
138         etors=enetb(13,i)
139         etors_d=enetb(14,i)
140         ehpb=enetb(15,i)
141         estr=enetb(18,i)
142         esccor=enetb(19,i)
143         edihcnstr=enetb(20,i)
144 #ifdef SPLITELE
145         etot=wsc*evdw+wscp*evdw2+ft(1)*welec*ees+wvdwpp*evdw1
146      &  +wang*ebe+ft(1)*wtor*etors+wscloc*escloc
147      &  +wstrain*ehpb+nss*ebr+ft(3)*wcorr*ecorr+ft(4)*wcorr5*ecorr5
148      &  +ft(5)*wcorr6*ecorr6+ft(3)*wturn4*eello_turn4
149      &  +ft(2)*wturn3*eello_turn3
150      &  +ft(5)*wturn6*eturn6+ft(2)*wel_loc*eel_loc
151      &  +edihcnstr+ft(2)*wtor_d*etors_d+ft(1)*wsccor*esccor
152      &  +wbond*estr
153 #else
154         etot=wsc*evdw+wscp*evdw2+ft(1)*welec*(ees+evdw1)
155      &  +wang*ebe+ft(1)*wtor*etors+wscloc*escloc
156      &  +wstrain*ehpb+nss*ebr+ft(3)*wcorr*ecorr+ft(4)*wcorr5*ecorr5
157      &  +ft(5)*wcorr6*ecorr6+ft(3)*wturn4*eello_turn4
158      &  +ft(2)*wturn3*eello_turn3
159      &  +ft(5)*wturn6*eturn6+ft(2)*wel_loc*eel_loc+edihcnstr
160      &  +ft(2)*wtor_d*etors_d+ft(1)*wsccor*esccor
161      &  +wbond*estr
162 #endif
163         Fdimless(i)=beta_h(ib)*etot+entfac(ii)
164         totfree(i)=etot
165 #ifdef DEBUG
166         write (iout,*) i,ii,ib,
167      &   1.0d0/(1.987d-3*beta_h(ib)),totfree(i),
168      &   entfac(ii),Fdimless(i)
169 #endif
170       enddo   ! i
171 #ifdef MPI
172       call MPI_Gatherv(Fdimless(1),scount(me),
173      & MPI_REAL,Fdimless(1),
174      & scount(0),idispl(0),MPI_REAL,Master,
175      & MPI_COMM_WORLD, IERROR)
176       call MPI_Gatherv(totfree(1),scount(me),
177      & MPI_DOUBLE_PRECISION,totfree(1),
178      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
179      & MPI_COMM_WORLD, IERROR)
180       call MPI_Gatherv(entfac(indstart(me)+1),scount(me),
181      & MPI_DOUBLE_PRECISION,entfac(1),
182      & scount(0),idispl(0),MPI_DOUBLE_PRECISION,Master,
183      & MPI_COMM_WORLD, IERROR)
184       if (me.eq.Master) then
185 #endif
186 #ifdef DEBUG
187         write (iout,*) "The FDIMLESS array before sorting"
188         do i=1,ncon
189           write (iout,*) i,fdimless(i)
190         enddo
191 #endif
192         call mysort1(ncon,Fdimless,list_conf)
193 #ifdef DEBUG
194         write (iout,*) "The FDIMLESS array after sorting"
195         do i=1,ncon
196           write (iout,*) i,list_conf(i),fdimless(i)
197         enddo
198 #endif
199         do i=1,ncon
200           totfree(i)=fdimless(i)
201         enddo
202         qfree=0.0d0
203         do i=1,ncon
204           qfree=qfree+exp(-fdimless(i)+fdimless(1))
205         enddo
206 c        write (iout,*) "qfree",qfree
207         nlist=1
208         sumprob=0.0
209         do i=1,min0(ncon,maxstr_proc)-1 
210           sumprob=sumprob+exp(-fdimless(i)+fdimless(1))/qfree 
211 #ifdef DEBUG
212           write (iout,*) i,ib,beta_h(ib),
213      &     1.0d0/(1.987d-3*beta_h(ib)),list_conf(i),
214      &     totfree(list_conf(i)),
215      &     -entfac(list_conf(i)),fdimless(i),sumprob
216 #endif
217           if (sumprob.gt.prob_limit) goto 122
218 c          if (sumprob.gt.1.00d0) goto 122
219           nlist=nlist+1
220         enddo  
221   122   continue
222 #ifdef MPI
223       endif
224       call MPI_Bcast(nlist, 1, MPI_INTEGER, Master, MPI_COMM_WORLD, 
225      &   IERROR)
226       call MPI_Bcast(list_conf,nlist,MPI_INTEGER,Master,MPI_COMM_WORLD,
227      &   IERROR)
228 c      do iproc=0,nprocs
229 c        write (iout,*) "iproc",iproc," indstart",indstart(iproc),
230 c     &   " indend",indend(iproc) 
231 c      enddo
232       write (iout,*) "nlist",nlist
233 #endif
234       return
235       end
236 !--------------------------------------------------
237       subroutine mysort1(n, x, ipermut)
238       implicit none
239       integer i,j,imax,ipm,n
240       real x(n)
241       integer ipermut(n)
242       real xtemp
243       do i=1,n
244         xtemp=x(i)
245         imax=i
246         do j=i+1,n
247           if (x(j).lt.xtemp) then
248             imax=j
249             xtemp=x(j)
250           endif
251         enddo
252         x(imax)=x(i)
253         x(i)=xtemp
254         ipm=ipermut(imax)
255         ipermut(imax)=ipermut(i)
256         ipermut(i)=ipm
257       enddo
258       return
259       end