source: metropolis.f@ 229cc35

Last change on this file since 229cc35 was 229cc35, checked in by baerbaer <baerbaer@…>, 16 years ago

Removed unnecessary call to energy in metropolis.

git-svn-id: svn+ssh://svn.berlios.de/svnroot/repos/smmp/trunk@14 26dc1dd8-5c4e-0410-9ffe-d298b4865968

  • Property mode set to 100644
File size: 6.1 KB
Line 
1! **************************************************************
2!
3! This file contains the subroutines: metropolis
4!
5! Copyright 2003-2005 Frank Eisenmenger, U.H.E. Hansmann,
6! Shura Hayryan, Chin-Ku
7! Copyright 2007 Frank Eisenmenger, U.H.E. Hansmann,
8! Jan H. Meinke, Sandipan Mohanty
9!
10! **************************************************************
11
12
13 subroutine metropolis(eol1,acz,dummy)
14!
15! SUBROUTINE FOR METROPOLIS UPDATE OF CONFIGURATIONS
16!
17! CALLS: energy,addang,grnd,dummy (function provided as argument)
18!
19 include 'INCL.H'
20 include 'INCP.H'
21 include 'incl_lund.h'
22 external dummy
23! common/bet/beta
24 common/updstats/ncalls(5),nacalls(5)
25 integer updtch1, updtch2,bgs
26 double precision vrol(mxvr), gbol
27!f2py intent(in, out) eol
28!f2py intent(in, out) acz
29 eol = energy()
30! external rand
31 do nsw=1,nvr
32! Loop over dihedrals
33!
34 iupstate=0
35 iupt=1
36 if (rndord) then
37 ivar = 1+int(nvr*grnd())
38 else
39 ivar=nsw
40 endif
41 jv = idvr(ivar)
42 if (nmvr(jv)(1:1).eq.'x') then
43 iupt=1
44 else
45 if (upchswitch.eq.0) then
46 iupt=1
47 else if (upchswitch.eq.1) then
48 iupt=updtch1(ivar,beta)
49 else
50 iupt=updtch2(ivar,beta)
51 endif
52 endif
53 if (iupt.eq.2) then
54 iupstate=bgs(eol,dummy)
55 else
56! Simple twist of
57! Get Proposal configuration
58 vrol=vlvr!(jv)
59 dv=axvr(jv)*(grnd()-0.5)
60 vlvr(jv)=addang(vrol(jv),dv)
61!
62! Get dummy of proposal configuration
63!
64 enw = energy()
65!
66 delta = dummy(enw) - dummy(eol)
67! ___________________________ check acceptance criteria
68 if (delta.le.0.0d0) then
69 eol=enw
70 iupstate=1
71 else
72 rd=grnd()
73 delta = min(delta,100.0d0)
74 ex=exp( -delta )
75 if ( ex .ge. rd ) then
76 eol=enw
77 iupstate=1
78 else
79 vlvr=vrol
80 endif
81 endif
82 endif
83 acz=acz+iupstate*1.0
84 call accanalyze(iupt,iupstate)
85 end do
86
87! Updates on relative position of different molecules when there are many
88 if (ntlml.gt.1) then
89 do iml=1, ntlml
90 do i=1,3
91 iupstate=0
92 gbol = gbpr(i, iml)
93 gbpr(i, iml) = gbpr(i, iml) + (grnd()-0.5)
94 if (boxsize.gt.0) then
95 if (gbpr(i, iml).gt.boxsize) then
96 gbpr(i, iml)=boxsize
97 elseif (gbpr(i, iml).lt.-boxsize) then
98 gbpr(i, iml)=-boxsize
99 endif
100 endif
101!
102! Get dummy of proposal configuration
103!
104 enw = energy()
105!
106 delta = dummy(enw) - dummy(eol)
107!
108! ____________________________ check acceptance criteria
109!
110 if (delta.le.0.0d0) then
111 eol=enw
112 iupstate=1
113 else
114 rd=grnd()
115 delta = min(delta,100.0d0)
116 ex=exp( -delta )
117 if ( ex .ge. rd ) then
118 eol=enw
119 iupstate=1
120 else
121 gbpr(i, iml)=gbol
122 endif
123 endif
124 acz=acz+iupstate*1.0
125 call accanalyze(3,iupstate)
126 enddo
127 do i=4,6
128 iupstate=0
129 gbol = gbpr(i, iml)
130 if (i.eq.5) then ! global psi value must be in [-pi/2, pi/2]
131 gbpr(i, iml) = (grnd()-0.5) * pi
132 else
133 gbpr(i, iml) = (grnd()-0.5) * pi2
134 endif
135!
136! Get dummy of proposal configuration
137!
138 enw = energy()
139!
140 delta = dummy(enw) - dummy(eol)
141!
142! ____________________________ check acceptance criteria
143!
144 if (delta.le.0.0d0) then
145 eol=enw
146 iupstate=1
147 else
148 rd=grnd()
149 delta = min(delta,100.0d0)
150 ex=exp( -delta )
151 if ( ex .ge. rd ) then
152 eol=enw
153 iupstate=1
154 else
155 gbpr(i, iml)=gbol
156 endif
157 endif
158 acz=acz+iupstate*1.0
159 call accanalyze(4,iupstate)
160 enddo
161 enddo
162 endif
163!
164! Re-calculate energy
165!
166 enw = energy()
167 if(abs(eol-enw).gt.0.000001) then
168 write(*,*) 'metropolis: eol,enw,difference:', eol, enw, eol-enw
169 if (eol.lt.100000) then
170 stop 'metropolis: eol and enw difference unacceptable'
171 endif
172 endif
173!
174 eol1 = eol
175 return
176!
177 end
178
179 subroutine accanalyze(iuptype,iupdstate)
180 common/updstats/ncalls(5),nacalls(5)
181 ncalls(5)=ncalls(5)+1
182 nacalls(5)=nacalls(5)+iupdstate
183 ncalls(iuptype)=ncalls(iuptype)+1
184 nacalls(iuptype)=nacalls(iuptype)+iupdstate
185 end
186
187
188 integer function updtch1(iiii,bbbb)
189 logical rndord
190 integer upchswitch, iiii
191 double precision bgsprob, grnd, bbbb
192 common /updchois/rndord,upchswitch,bgsprob
193 if (grnd().lt.bgsprob) then
194 updtch1=2
195 else
196 updtch1=1
197 endif
198 return
199 end
200
201 integer function updtch2(iiii,bbbb)
202 integer iiii
203 double precision bbbb,curprob, grnd,up2bmax,up2bmin
204 common/updtparam/up2bmax,up2bmin
205 curprob=(bbbb-up2bmin)/(up2bmax-up2bmin)
206 if (grnd().lt.curprob) then
207 updtch2=2
208 else
209 updtch2=1
210 endif
211 end
212 block data updtchs
213 double precision up2bmax, up2bmin
214 common/updtparam/up2bmax,up2bmin
215 data up2bmax,up2bmin/4.0d0,0.5d0/
216 common/updstats/ncalls(5),nacalls(5)
217 data ncalls/5*0/
218 data nacalls/5*0/
219 end
Note: See TracBrowser for help on using the repository browser.