Changeset 32289cd for init_molecule.f


Ignore:
Timestamp:
11/19/09 11:29:41 (14 years ago)
Author:
baerbaer <baerbaer@…>
Branches:
master
Children:
38d77eb
Parents:
6650a56
Message:

Explicitly declare variables.

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • init_molecule.f

    r6650a56 r32289cd  
    44!
    55! Copyright 2003-2005  Frank Eisenmenger, U.H.E. Hansmann,
    6 !                      Shura Hayryan, Chin-Ku 
     6!                      Shura Hayryan, Chin-Ku
    77! Copyright 2007       Frank Eisenmenger, U.H.E. Hansmann,
    88!                      Jan H. Meinke, Sandipan Mohanty
     
    1616! PURPOSE: construct starting structure of molecule(s)
    1717!
    18 !          iabin = 1  : ab Initio using sequence & 
     18!          iabin = 1  : ab Initio using sequence &
    1919!                       variables given in input files
    2020!          iabin != 1 : sequence, variable information
     
    3232      include 'INCP.H'
    3333
     34      integer iabin, iendst, ntl, i, j, l, it, ier, ir, nursvr, i1, i2
     35      integer its
     36
    3437Cf2py character*80 optional, intent(in) :: seqfile = ' '
    35 Cf2py character*80 optional, intent(in) :: varfile = ' ' 
    36      
     38Cf2py character*80 optional, intent(in) :: varfile = ' '
     39
    3740      character grpn*4,grpc*4
    38       character navr*3, nars*4 
     41      character navr*3, nars*4
    3942      character seqfile*80, varfile*80
    4043      integer ontlml
     
    4447      readFromStdin = .false.
    4548
    46       write (*,*) 'init_molecule: Solvent: ', itysol
    47       if (iabin.eq.1) then 
    48          
     49      write (logString, *) 'init_molecule: Solvent: ', itysol
     50      if (iabin.eq.1) then
     51
    4952!     ----------------------------------------- get sequence for molecule(s)
    5053         lunseq=11
     
    5356         endif
    5457         if (iendst(seqfile).le.1.or.seqfile.eq.' ') then
    55  1          write (*,'(/,a,$)') ' file with SEQUENCE:'
     58 1          write (logString, '(/,a,$)') ' file with SEQUENCE:'
    5659            seqfil=' '
    5760            read (*,'(a)',err=1) seqfil
    5861            readFromStdin = .true.
    59          else 
     62         else
    6063            seqfil = seqfile
    61          endif 
     64         endif
    6265         call redseq
    63          
    64          write (*,*) 'File with sequence is ', seqfil(1:iendst(seqfil))
    65          
     66
     67         write (logString, *) 'File with sequence is ',
     68     &      seqfil(1:iendst(seqfil))
     69
    6670!     --------------------------------- read & assemble data from libraries
    6771!     initial coordinates, interaction lists
    68          
     72
    6973         ntl = ntlml
    7074         do i=ontlml, ntl
    71            
     75
    7276            call getmol(i)      ! assemble data from libraries
    73            
     77
    7478            do j=1,6            ! initialize global parameters
    7579               gbpr(j,i)=0.d0
    7680            enddo
    77            
     81
    7882            call bldmol(i)      ! co-ordinates
    79            
     83
    8084            ntlml = i
    8185            call addend(i,grpn,grpc) ! modify ends
    8286            call setmvs(i) ! determine sets of moving atoms for given variables
    8387            call mklist(i)      ! compile lists of interaction partners
    84            
     88
    8589         enddo
    86          
     90
    8791!     --------------------------- Read the initial conformation if necessary
    88          if(readFromStdin) then 
    89             write (*,'(a,$)') ' file with VARIABLES:'
    90 !     
     92         if(readFromStdin) then
     93            write (logString, '(a,$)') ' file with VARIABLES:'
     94!
    9195            varfil=' '
    9296            read(*,'(a)',end=2,err=2) varfil
     
    96100         l=iendst(varfil)
    97101         if (l.gt.0.and.varfil.ne.' ') then
    98             write (*,'(1x,a,/)') varfil(1:l)
     102            write (logString, '(1x,a,/)') varfil(1:l)
    99103            lunvar=13
    100            
     104
    101105            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
     106
     107         endif
     108
     109 2       write (logString, *) ' '
    140110
    141111!     -------------------- get: nvr,idvr, vlvr, olvlvr
     
    161131         enddo
    162132
     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
    163155!     -------------------------- set var. amplitudes for simulations
    164      
     156
    165157      do i=1,ivrml1(ntlml)+nvrml(ntlml)-1
    166          
     158
    167159         if (ityvr(i).eq.3.and..not.fxvr(i)) then ! torsion
    168            
     160
    169161            navr = nmvr(i)
    170            
     162
    171163            ir = nursvr(i)
    172164            nars = seq(ir)
    173            
     165
    174166            if (                         navr(1:2).eq.'om'
    175            
     167
    176168     &     .or.nars(1:3).eq.'arg'.and.(navr(1:2).eq.'x5'
    177169     &           .or.navr(1:2).eq.'x6')
    178            
     170
    179171     &           .or.(nars(1:3).eq.'asn'.or.nars(1:3).eq.'asp')
    180172     &           .and.navr(1:2).eq.'x3'
    181            
     173
    182174     &           .or.(nars(1:3).eq.'gln'.or.nars(1:3).eq.'glu')
    183175     &           .and.navr(1:2).eq.'x4'
    184            
     176
    185177     &           ) then
    186            
     178
    187179!     axvr(i) = pi/9.d0  ! 20 deg.
    188180            axvr(i) = pi2       ! Trying out 360 deg. for these as well
    189            
     181
    190182         else
    191183            axvr(i) = pi2       ! 360 deg.
    192184         endif
    193          
     185
    194186      else
    195187         axvr(i) = 0.d0
    196188      endif
    197      
     189
    198190      enddo                     ! vars.
    199      
     191
    200192!     --------------------- initialize solvation pars. if necessary
    201193
    202194      if (itysol.ne.0) then
    203          
     195
    204196         i1=iatrs1(irsml1(1))   ! 1st atom of 1st molecule
    205197         i2=iatrs2(irsml2(ntlml)) ! last atom of last molecule
    206          
     198
    207199         its = iabs(itysol)
    208          
     200
    209201         do i=i1,i2             ! all atoms
    210202            it=ityat(i)
    211203            sigma(i)=coef_sl(its,it)
    212204            rvdw(i) =rad_vdw(its,it)
    213            
     205
    214206            if (nmat(i)(1:1).ne.'h') rvdw(i)=rvdw(i)+rwater
    215            
     207
    216208         enddo
    217          
     209
    218210      endif
    219211! Initialize calpha array
    220212      do i=ontlml, ntlml
    221          call c_alfa(i,1)   
     213         call c_alfa(i,1)
    222214      enddo
    223215
    224216!     Initialize arrays used in the BGS update
    225       call init_lund()     
     217      call init_lund()
    226218      return
    227219      end
    228      
    229      
     220
     221
Note: See TracChangeset for help on using the changeset viewer.