source: init_molecule.f

Last change on this file was 5272e0d, checked in by Jan Meinke <j.meinke@…>, 14 years ago

Added ppybind target to Makefile

Added a new target for creating Python bindings that take advantage so enyshe_p
to the Makefile.
Commented out one call to the log file that broke the compile.

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