source: init_molecule.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: 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
34Cf2py character*80 optional, intent(in) :: seqfile = ' '
35Cf2py 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 ireg = 0
108
109 else ! =========================== from PDB
110 if (iendst(seqfile).le.1) then
111 3 write (*,'(/,a,$)') ' PDB-file:'
112 seqfil=' '
113 read (*,'(a)',err=3) seqfil
114 else
115 seqfil = seqfile
116 endif
117 write (*,*) 'PDB structure ',seqfil(1:iendst(seqfil))
118 print *, 'calling readpdb with ',seqfile
119 call pdbread(seqfil,ier)
120
121 if (ier.ne.0) stop
122
123 call pdbvars()
124
125 ireg = 1
126
127 endif
128
129! If Lund force field is in use, keep omega angles fixed
130 if (ientyp.eq.2) then
131 do iv=1,nvrml(ntlml)
132 if ((nmvr(iv)(1:2).eq.'om')) then
133 vlvr(iv)=pi
134 toat(iatvr(iv))=pi
135 fxvr(iv)=.true.
136 print *, 'Fixed variable ',iv,nmvr(iv),vlvr(iv)
137 endif
138 enddo
139 endif
140
141! -------------------- get: nvr,idvr, vlvr, olvlvr
142 nvr = 0
143 do i=1,ivrml1(ntlml)+nvrml(ntlml)-1
144
145 if (.not.fxvr(i)) then
146 nvr=nvr+1
147 idvr(nvr)=i ! index of not fixed var.
148 endif
149
150 it=ityvr(i)
151
152 if (it.eq.3) then ! torsion
153 vlvr(i)=toat(iatvr(i))
154 elseif (it.eq.2) then ! b.angle
155 vlvr(i)=baat(iatvr(i))
156 elseif (it.eq.1) then ! b.length
157 vlvr(i)=blat(iatvr(i))
158 endif
159
160 olvlvr(i) = vlvr(i)
161 enddo
162
163! -------------------------- set var. amplitudes for simulations
164
165 do i=1,ivrml1(ntlml)+nvrml(ntlml)-1
166
167 if (ityvr(i).eq.3.and..not.fxvr(i)) then ! torsion
168
169 navr = nmvr(i)
170
171 ir = nursvr(i)
172 nars = seq(ir)
173
174 if ( navr(1:2).eq.'om'
175
176 & .or.nars(1:3).eq.'arg'.and.(navr(1:2).eq.'x5'
177 & .or.navr(1:2).eq.'x6')
178
179 & .or.(nars(1:3).eq.'asn'.or.nars(1:3).eq.'asp')
180 & .and.navr(1:2).eq.'x3'
181
182 & .or.(nars(1:3).eq.'gln'.or.nars(1:3).eq.'glu')
183 & .and.navr(1:2).eq.'x4'
184
185 & ) then
186
187! axvr(i) = pi/9.d0 ! 20 deg.
188 axvr(i) = pi2 ! Trying out 360 deg. for these as well
189
190 else
191 axvr(i) = pi2 ! 360 deg.
192 endif
193
194 else
195 axvr(i) = 0.d0
196 endif
197
198 enddo ! vars.
199
200! --------------------- initialize solvation pars. if necessary
201
202 if (itysol.ne.0) then
203
204 i1=iatrs1(irsml1(1)) ! 1st atom of 1st molecule
205 i2=iatrs2(irsml2(ntlml)) ! last atom of last molecule
206
207 its = iabs(itysol)
208
209 do i=i1,i2 ! all atoms
210 it=ityat(i)
211 sigma(i)=coef_sl(its,it)
212 rvdw(i) =rad_vdw(its,it)
213
214 if (nmat(i)(1:1).ne.'h') rvdw(i)=rvdw(i)+rwater
215
216 enddo
217
218 endif
219! Initialize calpha array
220 do i=ontlml, ntlml
221 call c_alfa(i,1)
222 enddo
223
224! Initialize arrays used in the BGS update
225 call init_lund()
226 return
227 end
228
229
Note: See TracBrowser for help on using the repository browser.