Changeset 3fbbfbb


Ignore:
Timestamp:
06/16/10 08:25:47 (14 years ago)
Author:
Jan Meinke <j.meinke@…>
Branches:
master
Children:
5fef0d7
Parents:
9f146fa
Message:

Move to doxygen comments and smmp_p.

Doxygen comments in Fortran are !> ... !! ... !<. I'm planning move the API documentation from the
lyx file into the code. This should make it easier to get documentation for all the common block
variables as well.

Use import smmp_p to indicate the parallel version of the Python bindings.

Files:
12 edited

Legend:

Unmodified
Added
Removed
  • EXAMPLES/1bdd.seq

    r9f146fa r3fbbfbb  
    55  SER GLN SER ALA ASN LEU LEU ALA GLU ALA
    66  LYS LYS LEU ASN ASP ALA
     7
  • INCL.H

    r9f146fa r3fbbfbb  
    88      integer mxhbac, mxtybl, mxtyba, mxtyto, mxrt, mxvrrt, mxrtsu
    99      integer nrsty
    10 !      integer MAXLOGLEVEL, LOGFILEUNIT
     10      integer MAXLOGLEVEL, LOGFILEUNIT
    1111      double precision pi, pi2, pi4, crd, cdr, zero, one
    1212      integer izero, ione
     
    5252      integer enysolct
    5353      double precision boxsize
     54      common /log/MAXLOGLEVEL,LOGFILEUNIT
    5455      common /counter/enysolct
    5556      common /commonrandom/ seed
  • algorithms.py

    r9f146fa r3fbbfbb  
    1111from protein import *
    1212
    13 class CanonicalMonteCarlo:
     13class CanonicalMonteCarlo(object):
    1414    """An implementation of a canonical Monte Carlo run using Metropolis weights.
    1515    After a Monte-Carlo sweep over all internal variables, this implementation
  • enyshe.f

    r9f146fa r3fbbfbb  
    1010! **************************************************************
    1111
     12!> PURPOSE: Calculate internal energy of molecule 'nml' with ECEPP parameters
     13!!
     14!! CALLS: none
     15!!
     16!! The function loops over all moving sets within the molecule. Within
     17!! this loop it loops over the van-der-Waals domains of each atom in the
     18!! moving set and finally over the atoms that belong to the 1-4 interaction
     19!! set.
     20!< ............................................................................
    1221
    1322      real*8 function enyshe(nml)
    1423
    15 ! ............................................................................
    16 !
    17 ! PURPOSE: Calculate internal energy of molecule 'nml' with ECEPP parameters
    18 !
    19 ! CALLS: none
    20 !
    21 ! The function loops over all moving sets within the molecule. Within
    22 ! this loop it loops over the van-der-Waals domains of each atom in the
    23 ! moving set and finally over the atoms that belong to the 1-4 interaction
    24 ! set.
    25 ! ............................................................................
    2624
    2725      include 'INCL.H'
  • enyshe_p.f

    r9f146fa r3fbbfbb  
    1313      real*8 function enyshe(nml)
    1414
    15 !     ............................................................................
    16 !
    17 !     PURPOSE: Calculate internal energy of molecule 'nml' with ECEPP parameters
    18 !
    19 !     CALLS: none
    20 !
    21 !     The function loops over all moving sets within the molecule. Within
    22 !     this loop it loops over the van-der-Waals domains of each atom in the
    23 !     moving set and finally over the atoms that belong to the 1-4 interaction
    24 !     set.
    25 !     ............................................................................
     15!>     PURPOSE: Calculate internal energy of molecule 'nml' with ECEPP parameters
     16!!
     17!!     CALLS: none
     18!!
     19!!     The function loops over all moving sets within the molecule. Within
     20!!     this loop it loops over the van-der-Waals domains of each atom in the
     21!!     moving set and finally over the atoms that belong to the 1-4 interaction
     22!!     set.
     23!<     ............................................................................
    2624
    2725      include 'INCL.H'
  • main.f

    r9f146fa r3fbbfbb  
    1919      program main
    2020
     21      use timer
    2122      include 'INCL.H'
    2223      include 'INCP.H'
    23       double precision eps, temp, e, energy
     24      double precision eps, temp, e, energy, enyshe_simple
    2425
    25       integer maxloglevel, logfileunit, iabin, imin, maxit, nequi
    26       integer nsweep, nmes, ncalls, nacalls
     26      integer iabin, imin, maxit, nequi
     27      integer nsweep, nmes, ncalls, nacalls, i
    2728
    2829      common/updstats/ncalls(5),nacalls(5)
     
    4243!     Set the maximum log level. The larger the number the more detailed
    4344!     the log.
    44       MAXLOGLEVEL = 1
     45      MAXLOGLEVEL = 100
    4546!     File unit to use for the log file.
    4647      LOGFILEUNIT = 27
     
    112113!      call outvar(0, ' ')
    113114!     To do a canonical Monte Carlo simulation uncomment the lines below
    114        nequi = 100
    115        nsweep = 50000
    116        nmes = 10
    117        temp = 300.0
    118        lrand = .true.
    119        E = energy()
    120        write (logString, *) E, eyel,eyvw,eyhb,eyvr
    121        call outpdb(1, "polyA.pdb")
     115      nequi = 100
     116      nsweep = 500
     117      nmes = 10
     118      temp = 300.0
     119      lrand = .true.
     120      E = energy()
     121      write (logString, *) E, eyel,eyvw,eyhb,eyvr
     122      call outpdb(1, "polyrQ.pdb")
    122123!      Canonical Monte Carlo
    123        call canon(nequi, nsweep, nmes, temp, lrand)
     124      call init_timer()
     125      call start_timer(1)
     126      call canon(nequi, nsweep, nmes, temp, lrand)
     127      call stop_timer(1)
    124128
     129      E = 0
     130!      call start_timer(1)
     131!      do i =1, nsweep
     132!         E = E + enyshe_simple()
     133!      end do
     134!      call stop_timer(1)
     135      call evaluate(1)
     136      print *,timingData(1)%average, "s.", E
    125137!      For simulated annealing uncomment the lines below
    126138!      tmin = 200.0
  • partem_p.f

    r9f146fa r3fbbfbb  
    1111!     **************************************************************
    1212
     13!>
     14!!     PURPOSE: SIMULATION OF PROTEINS BY PARALLEL TEMPERING ALGORITHM
     15!!     ON PARALLEL COMPUTERS USING MPI
     16!!
     17!!     switch: Choses the starting configuration:
     18!!     -1 - stretched configuration
     19!!     0 - don't change anything
     20!!     1 - random start configuration
     21!!
     22!!     CALLS:  addang,contacts,energy,hbond,helix,iendst,metropolis,
     23!!     outvar,(rand),rgyr
     24!<
    1325      subroutine  partem_p(num_rep, nequi, nswp, nmes, nsave, newsta,
    1426     &                     switch, rep_id, partem_comm)
    15 !     
    16 !     PURPOSE: SIMULATION OF PROTEINS BY PARALLEL TEMPERING ALGORITHM
    17 !     ON PARALLEL COMPUTERS USING MPI
    18 !     
    19 !     switch: Choses the starting configuration:
    20 !     -1 - stretched configuration
    21 !     0 - don't change anything
    22 !     1 - random start configuration
    23 !     
    24 !     CALLS:  addang,contacts,energy,hbond,helix,iendst,metropolis,
    25 !     outvar,(rand),rgyr
    26 !     
    2727      include 'INCL.H'
    2828      include 'INCP.H'
  • protein.py

    r9f146fa r3fbbfbb  
    66#
    77import sys
    8 import smmp
     8import smmp_p as smmp
    99from math import *
    1010
  • rgyr.f

    r9f146fa r3fbbfbb  
    1111
    1212
    13       subroutine rgyr(nml, rgy, ee)
     13!> CALCULATES THE RADIUS-OF-GYRATION AND THE END-TO-END DISTANCE
     14!! FOR A GIVEN PROTEIN CONFORMATION
     15!! If nml == 0, calculate the radius of gyration for all molecules
     16!!
     17!!     rgy  = radius-of-gyration
     18!!     ee   = end-to-end distance
     19!!
     20!! REQUIREMENTS: c_alfa has to be called BEFORE call of this subroutine
     21!!
     22!! CALLS: NONE
     23!<
     24          subroutine rgyr(nml, rgy, ee)
    1425
    15 ! CALCULATES THE RADIUS-OF-GYRATION AND THE END-TO-END DISTANCE
    16 ! FOR A GIVEN PROTEIN CONFORMATION
    17 ! If nml == 0, calculate the radius of gyration for all molecules
    18 !
    19 !     rgy  = radius-of-gyration
    20 !     ee   = end-to-end distance
    21 !
    22 ! REQUIREMENTS: c_alfa has to be called BEFORE call of this subroutine
    23 !
    24 ! CALLS: NONE
    25 !
    2626      include 'INCL.H'
    2727     
  • timer.F90

    r9f146fa r3fbbfbb  
    5959            ! Initialize timers
    6060            allocate (timingData(initialTimerCount))
    61             forall(i = 1:initialTimerCount)
     61!            forall(i = 1:initialTimerCount)
     62            do i = 1, initialTimerCount
    6263                timingData(i) = TimingStructure(0, -1.0, -1.0, -1.0, -1.0, 0.0, &
    6364                        0.0, -1.0, -1.0)
    64             end forall
     65!            end forall
     66            end do
    6567        end subroutine init_timer
    6668   
  • universe.py

    r9f146fa r3fbbfbb  
    44#                      Jan H. Meinke, Sandipan Mohanty
    55#
    6 import smmp
     6import smmp_p as smmp
    77from math import *
    88
  • utilities.f

    r9f146fa r3fbbfbb  
    77! *********************************************************************
    88
    9 !! Calculate the best way to distribute the work load across processors.
    10 !  It calculates the average number of interactions and then tries to
    11 !  assign a number of interactions to each processor that is as close
    12 !  as possible to the average. The routine should be called once for
    13 !  every molecule in the system.
    14 !
    15 !  @param num_ppr Number of processors per replica
    16 !  @param nml index of molecule or zero.
    17 !
    18 !  @author Jan H. Meinke
     9!> Calculate the best way to distribute the work load across processors.
     10!!  It calculates the average number of interactions and then tries to
     11!!  assign a number of interactions to each processor that is as close
     12!!  as possible to the average. The routine should be called once for
     13!!  every molecule in the system.
     14!!
     15!!  @param num_ppr Number of processors per replica
     16!!  @param nml index of molecule or zero.
     17!!
     18!!  @author Jan H. Meinke
     19!<
    1920      subroutine distributeWorkLoad(num_ppr,nml)
    2021
     
    117118      end subroutine distributeWorkLoad
    118119
    119 !-----------------------------------------------------------------------
    120 !     The function fileNameMP takes a template of a file name in the
    121 !     variable base. The position of the first and last character that
    122 !     may be replaced by rank in the string are given in i1 (first) and
    123 !     i2 (last).
    124 !     The function returns an empty string if the rank would need more
    125 !     characters than is allowed by the template.
    126 !     For example,
    127 !     \code
    128 !     rank = 11
    129 !     fileName = fileNameMP('base_0000.dat', 6, 9, rank)
    130 !     write (logString, *), fileName
    131 !     \endcode
    132 !     will output base_0011.dat.
    133 !
    134 !     @param base the base file name, e.g., base_0000.dat.
    135 !     @param i1 index of the first character that may be replaced
    136 !     @param i2 index of the last character that may be replaced
    137 !     @param rank the number that should be inserted into the file name.
    138 !
    139 !     @return file name for rank
    140 !-----------------------------------------------------------------------
     120!>
     121!!     The function fileNameMP takes a template of a file name in the
     122!!     variable base. The position of the first and last character that
     123!!     may be replaced by rank in the string are given in i1 (first) and
     124!!     i2 (last).
     125!!     The function returns an empty string if the rank would need more
     126!!     characters than is allowed by the template.
     127!!     For example,
     128!!     \code
     129!!     rank = 11
     130!!     fileName = fileNameMP('base_0000.dat', 6, 9, rank)
     131!!     write (logString, *), fileName
     132!!     \endcode
     133!!     will output base_0011.dat.
     134!!
     135!!     @param base the base file name, e.g., base_0000.dat.
     136!!     @param i1 index of the first character that may be replaced
     137!!     @param i2 index of the last character that may be replaced
     138!!     @param rank the number that should be inserted into the file name.
     139!!
     140!!     @return file name for rank
     141!<
    141142      character*80 function fileNameMP(base, i1, i2, rank)
    142143
     
    172173
    173174
    174 !----------------------------------------------------------------------
    175 !     Add messages to log. This routine takes the log (debugging) mes-
    176 !     sages and writes them to the log file if the log level is less or
    177 !     equal to the maximum log level given by the global variable
    178 !     MAXLOGLEVEL.
    179 !
    180 !     @author Jan H. Meinke
    181 !
    182 !     @param loglevel level at which this message should be added to
    183 !            the log.
    184 !     @param message message to be written to the log.
    185 !     @param rank global rank of this node if running an MPI job zero
    186 !            otherwise.
    187 !----------------------------------------------------------------------
     175!>
     176!!     Add messages to log. This routine takes the log (debugging) mes-
     177!!     sages and writes them to the log file if the log level is less or
     178!!     equal to the maximum log level given by the global variable
     179!!     MAXLOGLEVEL.
     180!!
     181!!     @author Jan H. Meinke
     182!!
     183!!     @param loglevel level at which this message should be added to
     184!!            the log.
     185!!     @param message message to be written to the log.
     186!!     @param rank global rank of this node if running an MPI job zero
     187!!            otherwise.
     188!<
    188189      subroutine addLogMessage(loglevel, message, rank)
    189190
    190       integer maxloglevel, logfileunit
     191         integer MAXLOGLEVEL, LOGFILEUNIT
     192         common /log/MAXLOGLEVEL, LOGFILEUNIT
    191193
    192194         integer :: loglevel, rank
Note: See TracChangeset for help on using the changeset viewer.