Changeset bd2278d for mulcan_sim.f


Ignore:
Timestamp:
09/05/08 11:49:42 (16 years ago)
Author:
baerbaer <baerbaer@…>
Branches:
master
Children:
fafe4d6
Parents:
2ebb8b6
Message:

Reformatting comments and continuation marks.

Fortran 90 and higher use ! to mark comments no matter where they are in the
code. The only valid continuation marker is &.
I also added the SMMP.kdevelop.filelist to the repository to make it easier
to use kdevelop.

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • mulcan_sim.f

    r2ebb8b6 rbd2278d  
    1 c **************************************************************
    2 c
    3 c This file contains the subroutines: mulcan_sim,muca_weight2
    4 c
    5 c Copyright 2003-2005  Frank Eisenmenger, U.H.E. Hansmann,
    6 c                      Shura Hayryan, Chin-Ku
    7 c Copyright 2007       Frank Eisenmenger, U.H.E. Hansmann,
    8 c                      Jan H. Meinke, Sandipan Mohanty
    9 c
    10 c **************************************************************
     1! **************************************************************
     2!
     3! This file contains the subroutines: mulcan_sim,muca_weight2
     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! **************************************************************
    1111
    1212      subroutine  mulcan_sim
    13 C
    14 C PURPOSE: PERFORM A MULTICANONICAL SIMULATION
    15 C REQUIRES AS INPUT THE MULTICANONICAL PARAMETER AS CALCULATED
    16 C BY THE SUBROUTINE mulcan_par
    17 C
    18 c CALLS: addang, contacts,energy,metropolis
    19 c
     13!
     14! PURPOSE: PERFORM A MULTICANONICAL SIMULATION
     15! REQUIRES AS INPUT THE MULTICANONICAL PARAMETER AS CALCULATED
     16! BY THE SUBROUTINE mulcan_par
     17!
     18! CALLS: addang, contacts,energy,metropolis
     19!
    2020      include 'INCL.H'
    2121
    22 c     external rand
     22!     external rand
    2323      external muca_weight2
    2424
     
    2929      parameter(nsweep=100000,nequi=100)
    3030      Parameter(nsave=1000,nmes=10)
    31 C
    32 C     restart: .true. =  restart of simulation
    33 C              .false. = start of simulation with random configuration
    34 C     kmin,kmax: Range of multicanonical parameter
    35 C     ebin:      bin size for multicanonical parameter
    36 C     nequi: Number of sweeps for equilibrisation
    37 C     nsweep:  Number of sweeps for simulation run
    38 C     nsave:  Number of sweeps after which actual configuration is saved
    39 C             for re-starts
    40 C     nmes: Number of sweeps between measurments
    41 C
     31!
     32!     restart: .true. =  restart of simulation
     33!              .false. = start of simulation with random configuration
     34!     kmin,kmax: Range of multicanonical parameter
     35!     ebin:      bin size for multicanonical parameter
     36!     nequi: Number of sweeps for equilibrisation
     37!     nsweep:  Number of sweeps for simulation run
     38!     nsave:  Number of sweeps after which actual configuration is saved
     39!             for re-starts
     40!     nmes: Number of sweeps between measurments
     41!
    4242
    4343      dimension xhist(kmin:kmax),ihist(kmin:kmax)
     
    4545
    4646 
    47 C FILE with last conformation (for re-starts)
     47! FILE with last conformation (for re-starts)
    4848      open(8,file='EXAMPLES/start.d')
    49 C File with contact map of reference configuration
     49! File with contact map of reference configuration
    5050      open(9,file='EXAMPLES/enkefa.ref')
    51 C File with multicanonical parameter
     51! File with multicanonical parameter
    5252      open(10,file='EXAMPLES/muca.d')
    53 C Result file: Time series of certain quantities
     53! Result file: Time series of certain quantities
    5454      open(11, file='EXAMPLES/time.d')
    5555
     
    6060
    6161      nresi=irsml2(1)-irsml1(1) + 1
    62 c     nresi:  Number of residues
    63 
    64 C READ  REFERENCE CONTACT MAP
     62!     nresi:  Number of residues
     63
     64! READ  REFERENCE CONTACT MAP
    6565      nci = 0
    6666      do i=1,nresi
     
    7474      write(*,*) 'Number of contacts in reference conformation:',nci
    7575
    76 C READ IN FIELDS WITH MULTICANONICAL PARAMETER
     76! READ IN FIELDS WITH MULTICANONICAL PARAMETER
    7777      Do j=kmin,kmax
    7878       read(10,*) i,b(i),alpha(i)
    7979      end do
    80 C
     80!
    8181
    8282      if(restart) then
     
    9090       write(*,*) 'Last iteration, energy:',nswm,eol_old
    9191      else
    92 c _________________________________ random start
     92! _________________________________ random start
    9393       do i=1,nvr
    9494        iv=idvr(i)  ! provides index of non-fixed variable
     
    9898       enddo
    9999      end if
    100 c
     100!
    101101      eol = energy()
    102102      write (*,'(e12.5,/)')  eol
     
    109109      end do
    110110      write(*,*)
    111 C
     111!
    112112
    113113     
    114114      if(.not.restart) then
    115 c =====================Equilibrization by  Metropolis
     115! =====================Equilibrization by  Metropolis
    116116       do nsw=1,nequi
    117117        call metropolis(eol,acz,muca_weight2)
     
    123123      end if
    124124
    125 C======================Simulation
     125!======================Simulation
    126126      acz = 0.0d0
    127 C LOOP OVER SWEEPS
     127! LOOP OVER SWEEPS
    128128      do nsw=nswm,nsweep
    129 C
    130 C METROPOLIS UPDATE
     129!
     130! METROPOLIS UPDATE
    131131       call metropolis(eol,acz,muca_weight2)
    132132       muold = min(kmax,max(kmin,int(eol/ebin+sign(0.5d0,eol))))
    133133       ihist(muold) = ihist(muold) + 1
    134 C
    135 C  SAVE ACTUAL CONFORMATIONS FOR RE-STARTS:
     134!
     135!  SAVE ACTUAL CONFORMATIONS FOR RE-STARTS:
    136136       if(mod(nsw,nsave).eq.0) then
    137137        rewind 8
     
    143143        end do
    144144       end if
    145 C Measurements after NMES sweeps
     145! Measurements after NMES sweeps
    146146       if(mod(nsw,nmes).eq.0) then
    147 C Take a histogram of energy
     147! Take a histogram of energy
    148148        do i=kmin,kmax
    149149         xhist(i) = xhist(i) + ihist(i)
    150150         ihist(i) = 0
    151151        end do
    152 c Calculate contacts in actual configuartion and compare with reference
    153 C configuration
    154 c       call contacts(nhx,nhy,dham)
    155 C nhx : Number of contcats in actual conformation
    156 C nhy : Number of contacts which are identical in actual and reference
    157 C       configuration
    158 C dham:  Hamming distance between actual and reference configuration     
    159 C
     152! Calculate contacts in actual configuartion and compare with reference
     153! configuration
     154!       call contacts(nhx,nhy,dham)
     155! nhx : Number of contcats in actual conformation
     156! nhy : Number of contacts which are identical in actual and reference
     157!       configuration
     158! dham:  Hamming distance between actual and reference configuration     
     159!
    160160        write(11,'(i7,f12.2,2i8,f12.4)')  nsw,eol,nhx,nhy,dham
    161161       end if
    162162      end do
    163 C END OF SIMULATION
    164 
    165 C FINAL OUTPUT:
     163! END OF SIMULATION
     164
     165! FINAL OUTPUT:
    166166      acz = acz/dble(nsw*nvr)
    167167      write(*,*) 'last energy',eol
    168168      write(*,*) 'aczeptance rate:',acz
    169169
    170 C WRITE DOWN (UN-REWEIGHTED) HISTOGRAM OF MULTICANONICAL SIMULATION
     170! WRITE DOWN (UN-REWEIGHTED) HISTOGRAM OF MULTICANONICAL SIMULATION
    171171      do i=kmin,kmax
    172172       if(xhist(i).gt.0.0d0) then
     
    174174       end if
    175175      end do
    176 c =====================
     176! =====================
    177177      close(8)
    178178      close(9)
     
    183183      end
    184184
    185 c ************************************************************
     185! ************************************************************
    186186      real*8 function muca_weight2(x)
    187187
Note: See TracChangeset for help on using the changeset viewer.