source: init_molecule.f@ 4fd4338

Last change on this file since 4fd4338 was 4fd4338, checked in by sandipan <sandipan@…>, 16 years ago

Array index overrun in if statements with "and" and "or" operators fixed

Also, when Lund force field is used, omega angles are declared as
fixed variables in init_molecule.

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

  • Property mode set to 100644
File size: 6.6 KB
Line 
1! **************************************************************
2!
3! This file contains the subroutines: init_molecule
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! FIXME: Data in varfile determines which molecule is changed.
12
13 subroutine init_molecule(iabin,grpn,grpc,seqfile,varfile)
14
15! ----------------------------------------------------------
16! PURPOSE: construct starting structure of molecule(s)
17!
18! iabin = 1 : ab Initio using sequence &
19! variables given in input files
20! iabin != 1 : sequence, variable information
21! from PDB-file
22!
23! grpn: N-terminal group
24! grpc: C-terminal group
25!
26! CALLS: addend,bldmol,c_alfa,getmol,iendst, mklist, nursvr,
27! pdbread,pdbvars,redseq,redvar,setmvs
28!
29! ----------------------------------------------------------
30
31 include 'INCL.H'
32 include 'INCP.H'
33
34!f2py character*80 optional, intent(in) :: seqfile = ' '
35!f2py character*80 optional, intent(in) :: varfile = ' '
36
37 character grpn*4,grpc*4
38 character navr*3, nars*4
39 character seqfile*80, varfile*80
40 integer ontlml
41 logical readFromStdin
42
43 ontlml = 1
44 readFromStdin = .false.
45
46 write (*,*) 'init_molecule: Solvent: ', itysol
47 if (iabin.eq.1) then
48
49! ----------------------------------------- get sequence for molecule(s)
50 lunseq=11
51 if (ntlml.gt.0) then
52 ontlml = ntlml + 1
53 endif
54 if (iendst(seqfile).le.1.or.seqfile.eq.' ') then
55 1 write (*,'(/,a,$)') ' file with SEQUENCE:'
56 seqfil=' '
57 read (*,'(a)',err=1) seqfil
58 readFromStdin = .true.
59 else
60 seqfil = seqfile
61 endif
62 call redseq
63
64 write (*,*) 'File with sequence is ', seqfil(1:iendst(seqfil))
65
66! --------------------------------- read & assemble data from libraries
67! initial coordinates, interaction lists
68
69 ntl = ntlml
70 do i=ontlml, ntl
71
72 call getmol(i) ! assemble data from libraries
73
74 do j=1,6 ! initialize global parameters
75 gbpr(j,i)=0.d0
76 enddo
77
78 call bldmol(i) ! co-ordinates
79
80 ntlml = i
81 call addend(i,grpn,grpc) ! modify ends
82 call setmvs(i) ! determine sets of moving atoms for given variables
83 call mklist(i) ! compile lists of interaction partners
84
85 enddo
86
87! --------------------------- Read the initial conformation if necessary
88 if(readFromStdin) then
89 write (*,'(a,$)') ' file with VARIABLES:'
90!
91 varfil=' '
92 read(*,'(a)',end=2,err=2) varfil
93 else
94 varfil = varfile
95 endif
96 l=iendst(varfil)
97 if (l.gt.0.and.varfil.ne.' ') then
98 write (*,'(1x,a,/)') varfil(1:l)
99 lunvar=13
100
101 call redvar ! get vars. and rebuild
102
103 endif
104
105 2 write(*,*) ' '
106
107! If Lund force field is in use, keep omega angles fixed
108 if (ientyp.eq.2) then
109 do iv=1,nvrml(ntlml)
110 if (nmvr(iv).eq.'omg') then
111 print *, 'Fixed variable ',iv,nmvr(iv),vlvr(iv)
112 fxvr(iv)=.true.
113 endif
114 enddo
115 endif
116
117! -------------------- get: nvr,idvr, vlvr, olvlvr
118 nvr = 0
119 do i=1,ivrml1(ntlml)+nvrml(ntlml)-1
120
121 if (.not.fxvr(i)) then
122 nvr=nvr+1
123 idvr(nvr)=i ! index of not fixed var.
124 endif
125
126 it=ityvr(i)
127
128 if (it.eq.3) then ! torsion
129 vlvr(i)=toat(iatvr(i))
130 elseif (it.eq.2) then ! b.angle
131 vlvr(i)=baat(iatvr(i))
132 elseif (it.eq.1) then ! b.length
133 vlvr(i)=blat(iatvr(i))
134 endif
135
136 olvlvr(i) = vlvr(i)
137 enddo
138
139 ireg = 0
140
141 else ! =========================== from PDB
142 if (iendst(seqfile).le.1) then
143 3 write (*,'(/,a,$)') ' PDB-file:'
144 seqfil=' '
145 read (*,'(a)',err=3) seqfil
146 else
147 seqfil = seqfile
148 endif
149 write (*,*) 'PDB structure ',seqfil(1:iendst(seqfil))
150 print *, 'calling readpdb with ',seqfile
151 call pdbread(seqfil,ier)
152
153 if (ier.ne.0) stop
154
155 call pdbvars()
156
157 ireg = 1
158
159 endif
160
161! -------------------------- set var. amplitudes for simulations
162
163 do i=1,ivrml1(ntlml)+nvrml(ntlml)-1
164
165 if (ityvr(i).eq.3.and..not.fxvr(i)) then ! torsion
166
167 navr = nmvr(i)
168
169 ir = nursvr(i)
170 nars = seq(ir)
171
172 if ( navr(1:2).eq.'om'
173
174 & .or.nars(1:3).eq.'arg'.and.(navr(1:2).eq.'x5'
175 & .or.navr(1:2).eq.'x6')
176
177 & .or.(nars(1:3).eq.'asn'.or.nars(1:3).eq.'asp')
178 & .and.navr(1:2).eq.'x3'
179
180 & .or.(nars(1:3).eq.'gln'.or.nars(1:3).eq.'glu')
181 & .and.navr(1:2).eq.'x4'
182
183 & ) then
184
185! axvr(i) = pi/9.d0 ! 20 deg.
186 axvr(i) = pi2 ! Trying out 360 deg. for these as well
187
188 else
189 axvr(i) = pi2 ! 360 deg.
190 endif
191
192 else
193 axvr(i) = 0.d0
194 endif
195
196 enddo ! vars.
197
198! --------------------- initialize solvation pars. if necessary
199
200 if (itysol.ne.0) then
201
202 i1=iatrs1(irsml1(1)) ! 1st atom of 1st molecule
203 i2=iatrs2(irsml2(ntlml)) ! last atom of last molecule
204
205 its = iabs(itysol)
206
207 do i=i1,i2 ! all atoms
208 it=ityat(i)
209 sigma(i)=coef_sl(its,it)
210 rvdw(i) =rad_vdw(its,it)
211
212 if (nmat(i)(1:1).ne.'h') rvdw(i)=rvdw(i)+rwater
213
214 enddo
215
216 endif
217! Initialize calpha array
218 do i=ontlml, ntlml
219 call c_alfa(i,1)
220 enddo
221
222! Initialize arrays used in the BGS update
223 call init_lund()
224 return
225 end
226
227
Note: See TracBrowser for help on using the repository browser.