source: enysol.f

Last change on this file was 38d77eb, checked in by baerbaer <baerbaer@…>, 14 years ago

Redirected standard out to logString.

SMMP produced a lot of log messages. This became an issue when run in massively
parallel environments. I replaced all writes to standard out to a write to logString.
The next step is to pass this string to a function that writes the messages to a log
file according to their importance and the chosen log level.

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

  • Property mode set to 100644
File size: 9.9 KB
Line 
1! **************************************************************
2!
3! This file contains the subroutines: enysol,tessel
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 real*8 function enysol(nmol)
14
15 include 'INCL.H'
16! --------------------------------------------------------------
17!
18! Double Cubic Lattice algorithm for calculating the
19! solvation energy of proteins using
20! solvent accessible area method.
21!
22! if nmol == 0 do solvation energy over all residues.
23! CALLS: nursat
24!
25! -------------------------------------------------------------
26! TODO: Check the solvent energy for multiple molecules
27! arguments
28 integer nmol
29
30! functions
31 integer nursat
32
33
34 integer numbox, inbox, indsort, look, i, ii, ia, ib, ibox, icount
35 integer ilk, il, ik, ix, iy, iz, j, jy, jbox, jbi, jres, jj, jcnt
36 integer jtk, jx, jz, lbn, lst, mhx, mx, nsy, ndy, mz, my, nboxj
37 integer ndx, ncbox, nbt, nez, ndz, nex, ney, nlow, nhx, nnei
38 integer nrshi, nqxy, nrslow, mbt, nsx, nsz, numat, nup
39 double precision xyz, radb, radb2, ymin, diamax, area, akrad
40 double precision avr_x, avr_y, avr_z, dd, dr, dx, dy, dz, sizex
41 double precision rmax, shiftx, shifty, shiftz, sizey, sizez
42 double precision sizes, trad, zmin, xmax, xmin, ymax, zmax
43 double precision sdr, sdd, volume
44
45 dimension numbox(mxat),inbox(mxbox+1),indsort(mxat),look(mxat)
46 dimension xyz(mxinbox,3),radb(mxinbox),radb2(mxinbox)
47 logical surfc(mxpoint)
48
49! common/ressurf/surfres(mxrs)
50
51 eyslh = 0.0
52 eyslp = 0.0
53 if (nmol.eq.0) then
54 nrslow=irsml1(1)
55 nrshi=irsml2(ntlml)
56 else
57 nrslow = irsml1(nmol)
58 nrshi = irsml2(nmol)
59 endif
60 nlow = iatrs1(nrslow)
61 nup = iatrs2(nrshi)
62 do i=nrslow,nrshi
63 surfres(i) = 0.0d0
64 end do
65
66 numat= nup - nlow + 1
67
68 do i=1,mxbox+1
69 inbox(i)=0
70 end do
71
72 asa=0.0d0
73 vdvol=0.0d0
74 eysl=0.0d0
75
76 avr_x=xat(nlow)
77 avr_y=yat(nlow)
78 avr_z=zat(nlow)
79 xmin=xat(nlow)
80 ymin=yat(nlow)
81 zmin=zat(nlow)
82 xmax=xmin
83 ymax=ymin
84 zmax=zmin
85
86 rmax=rvdw(nlow)
87
88 do j=nlow+1,nup
89 if(xat(j).le.xmin) then
90 xmin=xat(j)
91 else if(xat(j).ge.xmax) then
92 xmax=xat(j)
93 end if
94 avr_x=avr_x+xat(j)
95 if(yat(j).le.ymin) then
96 ymin=yat(j)
97 else if(yat(j).ge.ymax) then
98 ymax=yat(j)
99 end if
100 avr_y=avr_y+yat(j)
101 if(zat(j).le.zmin) then
102 zmin=zat(j)
103 else if(zat(j).ge.zmax) then
104 zmax=zat(j)
105 end if
106 avr_z=avr_z+zat(j)
107 if(rvdw(j).ge.rmax) rmax=rvdw(j)
108 end do
109
110 avr_x=avr_x/dble(numat)
111 avr_y=avr_y/dble(numat)
112 avr_z=avr_z/dble(numat)
113 diamax=2.d0*rmax
114
115! The sizes of the big box
116
117 sizex=xmax-xmin
118 sizey=ymax-ymin
119 sizez=zmax-zmin
120
121! How many maximal diameters in each size ?
122
123 ndx=sizex/diamax + 1
124 ndy=sizey/diamax + 1
125 ndz=sizez/diamax + 1
126
127! We may need the number of quadratic boxes in (X,Y) plane
128
129 nqxy=ndx*ndy
130
131! The number of cubic boxes of the size "diamax"
132
133 ncbox=nqxy*ndz
134 if(ncbox.ge.mxbox) then
135 print *,'enysol> bad ncbox',ncbox
136 stop
137 end if
138
139! Let us shift the borders to home all boxes
140
141 shiftx=(dble(ndx)*diamax-sizex)/2.d0
142 shifty=(dble(ndy)*diamax-sizey)/2.d0
143 shiftz=(dble(ndz)*diamax-sizez)/2.d0
144 xmin=xmin-shiftx
145 ymin=ymin-shifty
146 zmin=zmin-shiftz
147 xmax=xmax+shiftx
148 ymax=ymax+shifty
149 zmax=zmax+shiftz
150
151! Finding the box of each atom
152
153 do j=nlow,nup
154 mx=min(int(max((xat(j)-xmin)/diamax,0.0d0)),ndx-1)
155 my=min(int(max((yat(j)-ymin)/diamax,0.0d0)),ndy-1)
156 mz=min(int(max((zat(j)-zmin)/diamax,0.0d0)),ndz-1)
157 nboxj=mx+my*ndx+mz*nqxy+1
158 numbox(j)=nboxj
159 if (nboxj.gt.mxbox) then
160 write (logString, '(a)') 'enysol> bad mxboxe-2'
161 write (logString, *) 'diagnostics ...'
162 write (logString, *) 'atom ',j
163 write (logString, *) 'position ',xat(j),yat(j),zat(j)
164 write (logString, *) 'box indices ',mx,my,mz
165 write (logString, *) 'resulting boxindex and limit ',
166 & nboxj,mxbox
167
168 stop
169 else
170 inbox(nboxj)=inbox(nboxj)+1
171 end if
172 end do
173
174! Summation over the boxes
175
176 do i=1,ncbox
177 inbox(i+1)=inbox(i+1)+inbox(i)
178 end do
179
180
181! Sorting the atoms by the their box numbers
182
183 do i=nlow,nup
184 j=numbox(i)
185 jj=inbox(j)
186 indsort(jj)=i
187 inbox(j)=jj-1
188 end do
189
190! Getting started
191
192 do iz=0,ndz-1 ! Over the boxes along Z-axis
193 do iy=0,ndy-1 !Over the boxes along Y-axis
194 do ix=0,ndx-1 !Over the boxes along X-axis
195
196 ibox=ix+iy*ndx+iz*nqxy + 1
197
198! Does this box contain atoms ?
199
200 lbn=inbox(ibox+1)-inbox(ibox)
201
202 if(lbn.gt.0) then ! There are some atoms
203 nsx=max(ix-1,0)
204 nsy=max(iy-1,0)
205 nsz=max(iz-1,0)
206 nex=min(ix+1,ndx-1)
207 ney=min(iy+1,ndy-1)
208 nez=min(iz+1,ndz-1)
209
210! Atoms in the boxes around
211
212 jcnt=1
213 do jz=nsz,nez
214 do jy=nsy,ney
215 do jx=nsx,nex
216 jbox=jx+jy*ndx+jz*nqxy+1
217 do ii=inbox(jbox)+1,inbox(jbox+1)
218 if(rvdw(indsort(ii)).gt.0.0d0) then
219 look(jcnt)=indsort(ii)
220 jcnt=jcnt+1
221 end if
222 end do
223 end do
224 end do
225 end do
226
227 do ia=inbox(ibox)+1,inbox(ibox+1)
228 jbi=indsort(ia)
229 trad=rvdw(jbi)
230 if(trad.gt.0.0) then
231 nnei=0
232 do ib=1,jcnt-1
233 jtk=look(ib)
234 if(jtk.ne.jbi)then
235 dx=(xat(jbi)-xat(jtk))/trad
236 dy=(yat(jbi)-yat(jtk))/trad
237 dz=(zat(jbi)-zat(jtk))/trad
238 dd=dx*dx+dy*dy+dz*dz
239 akrad=rvdw(jtk)/trad
240 dr=1.0d0+akrad
241 dr=dr*dr
242!c if contact
243 if(dd.le.dr) then
244 nnei=nnei+1
245 xyz(nnei,1)=dx
246 xyz(nnei,2)=dy
247 xyz(nnei,3)=dz
248 radb(nnei)=akrad
249 radb2(nnei)=akrad*akrad
250 end if
251 end if
252 end do
253!c
254 do il=1,npnt
255 surfc(il)=.false.
256 end do
257
258! Check overlap
259
260 lst=1
261 do il=1,npnt
262 sdd = 0.0d0
263 do ilk=1,3
264 sdd = sdd +(xyz(lst,ilk)+spoint(il,ilk))**2
265 end do
266 if(sdd.gt.radb2(lst)) then
267 do ik=1,nnei
268 sdd =0.0d0
269 do ilk=1,3
270 sdd = sdd +(xyz(ik,ilk)+spoint(il,ilk))**2
271 end do
272 if(sdd.le.radb2(ik)) then
273 lst=ik
274 go to 99
275 end if
276 end do
277 99 continue
278
279 if(ik.gt.nnei)then
280 surfc(il)=.true.
281 end if
282 end if
283 end do
284
285 icount=0
286 dx=0.0d0
287 dy=0.0d0
288 dz=0.0d0
289 do il=1,npnt
290 if(surfc(il)) then
291 icount=icount+1
292 dx=dx+spoint(il,1)
293 dy=dy+spoint(il,2)
294 dz=dz+spoint(il,3)
295 end if
296 end do
297 sdr=4.d0*pi*trad*trad/dble(npnt)
298 area = sdr*dble(icount)
299 volume = sdr/3.0d0*(trad*dble(icount)
300 & +(xat(jbi)-avr_x)*dx
301 & +(yat(jbi)-avr_y)*dy
302 & +(zat(jbi)-avr_z)*dz)
303
304 asa=asa+area
305 vdvol=vdvol+volume
306 eysl=eysl+area*sigma(jbi)
307! Separate hydrophilic (h) and hyrdophobic (p) contributions to eysl
308 if (sigma(jbi).lt.0) then
309 eyslp = eyslp + area * sigma(jbi)
310 asap = asap + area
311 endif
312 if (sigma(jbi).gt.0) then
313 eyslh = eyslh + area * sigma(jbi)
314 asah = asah + area
315 endif
316! Measure how much a residue is solvent accessible:
317 jres = nursat(jbi)
318 surfres(jres) = surfres(jres) + area
319 end if
320 end do
321 end if
322 end do
323 end do
324 end do
325
326!
327 if (isolscl) then
328 nhx=0
329 mhx=0
330 nbt=0
331 mbt=0
332 call helix(nhx,mhx,nbt,mbt)
333 eysl=((nhx+nbt)*eysl)/(irsml2(ntlml)-irsml1(1))
334 endif
335
336 enysol = eysl
337
338 return
339 end
340! *********************
341 subroutine tessel
342 include 'INCL.H'
343 character lin*80
344 integer i
345! Skipping comment lines, which begin with '!'
346 read(20,'(a)') lin
347 do while(lin(1:1).eq.'!')
348 read (20,'(a)') lin
349 end do
350
351! The first non-comment line is the number of the surface points
352
353 read(lin(1:5),'(i5)') npnt
354! write (logString, '(a,i5)') 'the number of points---->',npnt
355
356! Read the surface points
357
358 do i=1,npnt
359 read(20,'(3f20.10)') spoint(i,1),spoint(i,2),spoint(i,3)
360! write(31,'(3f20.10)') spoint(i,1),spoint(i,2),spoint(i,3)
361 end do
362
363 return
364
365 end
366
Note: See TracBrowser for help on using the repository browser.