ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/nano_mpi/src/dynamics_utilities.F90
Revision: 4
Committed: Mon Jun 10 17:18:36 2002 UTC (22 years, 1 month ago) by chuckv
File size: 5235 byte(s)
Log Message:
Import Root

File Contents

# User Rev Content
1 chuckv 4 module dynamics_utilities
2     use definitions, ONLY : ndim, DP
3     use second_deriv, ONLY : alloc_sec_deriv
4     use parameter, ONLY : DT, file_prefix, write_config_steps,run_time
5     use xyz_io, ONLY: dump_config
6     #ifdef MPI
7     use mpi_module, ONLY : node
8     #endif
9     IMPLICIT NONE
10     PRIVATE
11    
12     public :: init_status
13     public :: init_dynamics_loop
14     public :: evolve_time
15    
16     type, public :: sim_status
17     real( kind = DP ) :: pot_e
18     real( kind = DP ) :: kin_e
19     real( kind = DP ) :: tot_e
20     real( kind = DP ) :: time
21     real( kind = DP ) :: temp
22     end type sim_status
23    
24     ! . dump status variables
25     integer :: status_unit = -1
26     character(len=80) :: status_file
27     character(len=*), parameter :: status_fmt ='(4es15.6)'
28     !. Time constant variables
29     real( kind = DP), public :: DT2
30     real( kind = DP), public :: DTSQRT
31     real( kind = DP), public :: DTSQ2
32     public :: dump_status
33    
34     contains
35    
36    
37     subroutine init_status(this_status)
38     type (sim_status) :: this_status
39     end subroutine init_status
40    
41    
42     subroutine init_dynamics_loop(this_status)
43     use force_module, ONLY: calc_forces
44     use velocity, ONLY: calc_temp
45     use definitions, ONLY : machdep_lnblnk, machdep_flush
46     use status, ONLY : info
47     type (sim_status) :: this_status
48     logical :: nmflag
49     logical :: update_nlist
50     character(len=120) :: msg
51    
52     !. define status dump file name
53     status_file = file_prefix(1:machdep_lnblnk(file_prefix)) // '.status'
54     write(msg,*) 'Temperatures and energies will be in: ' // trim(status_file)
55     call info("Init dynamics", msg)
56    
57     DT2 = DT/2.0E0_DP
58     DTSQRT = sqrt(dt2)
59     DTSQ2 = DT * DT2
60    
61     ! . initialize status variables
62     this_status%pot_e = 0.0E0_DP
63     this_status%kin_e = 0.0E0_DP
64     this_status%tot_e = 0.0E0_DP
65     this_status%time = 0.0E0_DP
66     this_status%temp = 0.0E0_DP
67    
68    
69    
70     ! allocate second derivative matrix
71    
72     call alloc_sec_deriv(1,1)
73    
74     ! set up the initial forces and temperatures.
75    
76    
77     update_nlist = .true.
78     nmflag = .false.
79    
80     call calc_temp(this_status%temp,this_status%kin_e)
81    
82     write(msg,*) "before run, T=", this_status%temp
83     call info("init_dyna_loop", msg)
84    
85    
86     call calc_forces(update_nlist,nmflag,&
87     pe=this_status%pot_e)
88    
89    
90    
91    
92    
93     this_status%tot_e = this_status%pot_e + this_status%kin_e
94    
95    
96    
97     call dump_status(this_status)
98    
99     call dump_config(this_status%time)
100    
101    
102    
103    
104     end subroutine init_dynamics_loop
105    
106    
107    
108    
109    
110     subroutine evolve_time(step,this_status,calc_pe,not_done)
111     use velocity, ONLY : calc_temp
112     integer, intent(in) :: step
113     type (sim_status), intent(inout) :: this_status
114    
115     logical, intent(out) :: calc_pe, not_done
116    
117     calc_pe = .false.
118     not_done = .true.
119     this_status%time = dt * dble(step)
120    
121     ! if true, next step we are going to write status
122     if (mod(step + 1,write_config_steps).eq.0) then
123     calc_pe = .true.
124     endif
125    
126     if (mod(step,write_config_steps).eq.0) then
127     call calc_temp(this_status%temp,this_status%kin_e)
128     this_status%tot_e = this_status%pot_e + this_status%kin_e
129    
130     call dump_config( this_status%time )
131     call dump_status( this_status )
132     end if
133    
134     if (this_status%time.ge.run_time) then
135     not_done = .false.
136     end if
137    
138     end subroutine evolve_time
139    
140    
141    
142     subroutine dump_status(this_status,this_error)
143     use file_units, ONLY : next_unit
144     use definitions, ONLY : machdep_flush
145     use status, ONLY : info
146    
147     type (sim_status) :: this_status
148     integer, optional, intent(out) :: this_error
149     logical :: is_opened
150     integer :: err
151     character(len=40) :: msg
152    
153     #ifndef MPI
154     integer,parameter :: node = 0
155     #endif
156    
157     if ( node /= 0 ) then
158     return
159     endif
160    
161     if (present(this_error)) this_error = 0
162    
163     ! . Check to see if status unit has been opened
164     ! . if not then go ahead and open it.
165     inquire(file = status_file, opened = is_opened)
166     if ( .not. is_opened ) then
167     status_unit = next_unit()
168     open(file=status_file, unit=status_unit, status='replace', iostat=err, &
169     action='write')
170    
171     if (err /=0 ) then
172     write(msg,*) "Error opening status file " // status_file
173     call info("DUMP STATUS", msg)
174     if (present(this_error)) this_error = -1
175     end if
176     write(unit=status_unit,fmt="(a55)") "# Time Temperature Potential Energy Total Energy "
177     endif
178     write(unit=status_unit,fmt=status_fmt, iostat = err) this_status%time, &
179     this_status%temp, &
180     this_status%pot_e, &
181     this_status%tot_e
182     if (err /= 0) then
183     write(msg,*) "Error writing status file " // status_file
184     call info("DUMP STATUS", msg)
185     if (present(this_error)) this_error = -1
186     end if
187    
188    
189    
190     ! . flush status unit
191     call machdep_flush(status_unit)
192    
193    
194    
195    
196    
197     end subroutine dump_status
198    
199    
200    
201    
202     end module dynamics_utilities