source: enysol.f@ cb47b9c

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

Explicitly declare variables.

All variables should be declared so that we can remove the implicit statements
from the beginning of the INCL.H file.

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

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