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

File Contents

# User Rev Content
1 chuckv 4 !=======================================================================
2     ! Parameter module
3     !=======================================================================
4     ! Handles reading and distribution of parameters read from param file
5     ! . Contains:
6     !
7     ! . Subroutines:
8     ! . handle_args Interpets command line arguments
9     ! . read_params reads in parameter file
10     ! . mpi_dist_params distrubutes parameters to all nodes
11    
12     module parameter
13     use definitions, ONLY: DP
14     use io_units, ONLY : output_unit,error_unit
15     implicit none
16    
17     public :: handle_args
18     public :: read_params
19    
20     character(len=80),public :: paramfile
21     character(len=80),public :: file_prefix
22     character(len=80),public :: command
23     character(len=80),public :: sim_type
24     character(len=80),public :: ensemble
25     character(len=80),public :: force_field
26     character(len=80),public :: eam_pot_dir
27     real( kind = DP ),public :: dt
28     real( kind = DP ),public :: rcut
29     real( kind = DP ),public :: skin_thickness
30     real( kind = DP ),public :: therm_variance
31     real( kind = DP ),public :: run_time
32     real( kind = DP ),public :: target_temp
33     integer,public :: iseed
34     integer,public :: check_temp_steps
35     integer,public :: write_config_steps
36     logical,public :: checktemp
37    
38     ! used only in cluster sims:
39     character(len=10),public :: core_model
40     character(len=10),public :: shell_model
41     real( kind = DP ),public :: r_core
42     real( kind = DP ),public :: r_shell
43     real( kind = DP ),public :: cell
44     real( kind = DP ),public :: vacancy_radius
45     real( kind = DP ),public :: vacancy_fraction
46    
47     ! used only in liquid sims:
48     character(len=10),public :: solute_model
49     character(len=10),public :: solvent_model
50     real( kind = DP ),public :: solute_x
51     real( kind = DP ),public :: density
52     integer,public :: ncells
53    
54     ! for MPI
55    
56     logical, public :: newtons_thrd
57    
58     ! langevin variables
59     real ( kind = DP ) :: eta !. viscosity in poise
60     real ( kind = DP ) :: bath_temp
61     real ( kind = DP ) :: langevin_skin_delta
62     logical :: use_langevin_skin
63     logical :: use_target_temp
64    
65     ! vacancy parameter
66     logical,public :: print_vac
67    
68     contains
69    
70    
71     subroutine handle_args(this_error)
72    
73     integer, intent(out) :: this_error
74    
75     this_error = 0
76    
77     select case (command)
78     case ('input')
79     checktemp = .false.
80     case ('resample')
81     if ((ensemble.eq.'NVT') .or. &
82     (ensemble.eq.'langevin')) &
83     then
84     checktemp = .false.
85     else
86     checktemp = .true.
87     endif
88     case ('setup')
89     if ((ensemble.eq.'NVT') .or. &
90     (ensemble.eq.'langevin')) &
91     then
92     checktemp = .false.
93     else
94     checktemp = .true.
95     endif
96     case default
97     this_error = -1
98     end select
99    
100     return
101     end subroutine handle_args
102    
103     subroutine read_params(this_error)
104     use file_units, ONLY : next_unit
105     integer, optional :: this_error
106     integer :: read_error
107     character(len=120) :: msg
108     real( kind = DP ) :: time_between_configs, checktemptime
109     integer :: param_unit
110     integer :: file_open_error
111    
112     ! . Get next available stream unit
113     param_unit = next_unit()
114     ! . Init file subroutine error reporting
115     if (present(this_error)) this_error = 0
116    
117     open(unit=param_unit, file=paramfile, status='old', iostat=file_open_error, &
118     action='read')
119     if (file_open_error /= 0) then
120     write(msg,*) 'Error in opening paramfile ', paramfile
121     if (present(this_error)) this_error = -1
122     return
123     end if
124    
125     !! Read each of the parameters in and check for correctness
126     read(unit=param_unit,fmt=*,iostat=read_error) sim_type !Simulation type
127     if (read_error == 0) then
128     select case (sim_type)
129     case ('liquid')
130     case ('cluster')
131     case default
132     write(error_unit,*) "Error in paramfile line 1: "
133     write(error_unit,*) "Simulation must be liquid or cluster"
134     if (present(this_error)) this_error = -1
135     return
136     end select
137     else
138     write(error_unit,*) "Error reading paramfile sim_type line 1: "
139    
140     if (present(this_error)) this_error = -1
141     return
142     end if
143    
144    
145     read(unit=param_unit,fmt=*,iostat=read_error) ensemble ! ensemble for simulation
146     if (read_error == 0) then
147     select case (ensemble)
148     case ('NVE')
149     case ('NVT')
150     case ('langevin')
151     case default
152     write(error_unit,*) "Error in paramfile line 2: "
153     write(error_unit,*) "Ensemble must be NVE or NVT or langevin"
154    
155     if (present(this_error)) this_error = -1
156     return
157     end select
158     else
159     write(error_unit,*) "Error reading paramfile ensemble line 2: "
160     if (present(this_error)) this_error = -1
161     return
162     end if
163    
164    
165     read(unit=param_unit,fmt=*,iostat=read_error) force_field !Force field model used in simulation
166     if (read_error == 0) then
167     select case (force_field)
168     case ('lj')
169     case ('eam')
170     case ('glue')
171     case ('goddard')
172     case default
173     write(error_unit,*) "Error in paramfile line 3: "
174     write(error_unit,*) "Valid forcefieds are: "
175     write(error_unit,*) "lj"
176     write(error_unit,*) "eam"
177     write(error_unit,*) "goddard"
178     write(error_unit,*) "glue"
179     if (present(this_error)) this_error = -1
180     return
181     end select
182     else
183     write(error_unit,*) "Error reading paramfile force_field line 3: "
184     if (present(this_error)) this_error = -1
185     return
186     end if
187    
188    
189     read(unit=param_unit,fmt=*,iostat=read_error) eam_pot_dir
190     if (read_error /= 0) then
191     write(error_unit,*) "Error reading paramfile eam pot dir line 4: "
192     if (present(this_error)) this_error = -1
193     return
194     end if
195    
196    
197     read(unit=param_unit,fmt=*,iostat=read_error) dt
198     if (read_error /= 0) then
199     write(error_unit,*) "Error reading paramfile time step line 5: "
200     if (present(this_error)) this_error = -1
201     return
202     end if
203    
204     read(unit=param_unit,fmt=*,iostat=read_error) rcut ! OK if zero, will be set by forcefield if possible
205     if (read_error /= 0) then
206     write(error_unit,*) "Error reading paramfile rcut line 6: "
207     if (present(this_error)) this_error = -1
208     return
209     end if
210    
211     read(unit=param_unit,fmt=*,iostat=read_error) skin_thickness
212     if (read_error /= 0) then
213     write(error_unit,*) "Error reading paramfile skin_thinkness line 7: "
214     if (present(this_error)) this_error = -1
215     return
216     end if
217    
218     read(unit=param_unit,fmt=*,iostat=read_error) checktemptime
219     if (read_error /= 0) then
220     write(error_unit,*) "Error reading paramfile checktemptime line 8: "
221     if (present(this_error)) this_error = -1
222     return
223     end if
224    
225     check_temp_steps = &
226     idint(checktemptime/dt)
227    
228     read(unit=param_unit,fmt=*,iostat=read_error) therm_variance
229     if (read_error /= 0) then
230     write(error_unit,*) "Error reading paramfile therm_variance line 9: "
231     if (present(this_error)) this_error = -1
232     return
233     end if
234    
235     read(unit=param_unit,fmt=*,iostat=read_error) time_between_configs
236     if (read_error /= 0) then
237     write(error_unit,*) "Error reading paramfile dump config time line 10: "
238     if (present(this_error)) this_error = -1
239     return
240     end if
241    
242     write_config_steps = &
243     idint(time_between_configs/dt)
244    
245     read(unit=param_unit,fmt=*,iostat=read_error) iseed
246     if (read_error /= 0) then
247     write(error_unit,*) "Error reading paramfile iseed line 11: "
248     if (present(this_error)) this_error = -1
249     return
250     end if
251    
252     ! read cluster params
253     read(unit=param_unit,fmt=*,iostat=read_error) core_model
254     if (read_error /= 0) then
255     write(error_unit,*) "Error reading paramfile core model line 12: "
256     if (present(this_error)) this_error = -1
257     return
258     end if
259    
260     read(unit=param_unit,fmt=*,iostat=read_error) shell_model
261     if (read_error /= 0) then
262     write(error_unit,*) "Error reading paramfile shell model line 13: "
263     if (present(this_error)) this_error = -1
264     return
265     end if
266    
267     read(unit=param_unit,fmt=*,iostat=read_error) r_core
268     if (read_error /= 0) then
269     write(error_unit,*) "Error reading paramfile core radius line 14: "
270     if (present(this_error)) this_error = -1
271     return
272     end if
273    
274     read(unit=param_unit,fmt=*,iostat=read_error) r_shell
275     if (read_error /= 0) then
276     write(error_unit,*) "Error reading paramfile shell radius line 15: "
277     if (present(this_error)) this_error = -1
278     return
279     end if
280    
281     read(unit=param_unit,fmt=*,iostat=read_error) cell
282     if (read_error /= 0) then
283     write(error_unit,*) "Error reading paramfile cell length line 16: "
284     if (present(this_error)) this_error = -1
285     return
286     end if
287    
288     read(unit=param_unit,fmt=*,iostat=read_error) vacancy_radius
289     if (read_error /= 0) then
290     write(error_unit,*) "Error reading paramfile vacancy radius line 17: "
291     if (present(this_error)) this_error = -1
292     return
293     end if
294    
295     read(unit=param_unit,fmt=*,iostat=read_error) vacancy_fraction
296     if (read_error /= 0) then
297     write(error_unit,*) "Error reading paramfile vacancy fraction line 18: "
298     if (present(this_error)) this_error = -1
299     return
300     end if
301    
302     ! read liquid params
303     read(unit=param_unit,fmt=*,iostat=read_error) solute_model
304     if (read_error /= 0) then
305     write(error_unit,*) "Error reading paramfile solute Model line 19: "
306     if (present(this_error)) this_error = -1
307     return
308     end if
309    
310     read(unit=param_unit,fmt=*,iostat=read_error) solvent_model
311     if (read_error /= 0) then
312     write(error_unit,*) "Error reading paramfile solvent model line 20: "
313     if (present(this_error)) this_error = -1
314     return
315     end if
316    
317     read(unit=param_unit,fmt=*,iostat=read_error) solute_x
318     if (read_error /= 0) then
319     write(error_unit,*) "Error reading mol fraction line 21: "
320     if (present(this_error)) this_error = -1
321     return
322     end if
323    
324     read(unit=param_unit,fmt=*,iostat=read_error) density
325     if (read_error /= 0) then
326     write(error_unit,*) "Error reading paramfile density line 22: "
327     if (present(this_error)) this_error = -1
328     return
329     end if
330    
331     read(unit=param_unit,fmt=*,iostat=read_error) ncells
332     if (read_error /= 0) then
333     write(error_unit,*) "Error reading paramfile Number of cells line 23: "
334     if (present(this_error)) this_error = -1
335     return
336     end if
337    
338     ! read MPI
339    
340     read(unit=param_unit,fmt=*,iostat=read_error) newtons_thrd
341     if (read_error /= 0) then
342     write(error_unit,*) "Error reading paramfile Newtons third law line 24: "
343     if (present(this_error)) this_error = -1
344     return
345     end if
346    
347     ! . gamma for langevin dynamics
348     read(unit=param_unit,fmt=*,iostat=read_error) eta
349     if (read_error /= 0) then
350     write(error_unit,*) "Error reading paramfile eta line 25: "
351     if (present(this_error)) this_error = -1
352     return
353     end if
354    
355     ! . bath temperature for langevin dynamics
356     read(unit=param_unit,fmt=*,iostat=read_error) bath_temp
357     if (read_error /= 0) then
358     write(error_unit,*) "Error reading paramfile bath_temp line 26: "
359     if (present(this_error)) this_error = -1
360     return
361     end if
362     read(unit=param_unit,fmt=*,iostat=read_error) use_target_temp
363     if (read_error /= 0) then
364     write(error_unit,*) "Error reading paramfile use_target_temp line 27: "
365     if (present(this_error)) this_error = -1
366     return
367     end if
368    
369     ! . skin radius for langevin dynamics
370     read(unit=param_unit,fmt=*,iostat=read_error) langevin_skin_delta
371     if (read_error /= 0) then
372     write(error_unit,*) "Error reading paramfile langevin skin delta line 27: "
373     if (present(this_error)) this_error = -1
374     return
375     end if
376    
377     ! . logical to use skin radius
378     read(unit=param_unit,fmt=*,iostat=read_error) use_langevin_skin
379     if (read_error /= 0) then
380     write(error_unit,*) "Error reading paramfile langevin skin delta line 27: "
381     if (present(this_error)) this_error = -1
382     return
383     end if
384    
385     ! . vacancy param
386     read(unit=param_unit,fmt=*,iostat=read_error) print_vac
387     if (read_error /= 0) then
388     write(error_unit,*) "Error reading paramfile print_vac line 29: "
389     if (present(this_error)) this_error = -1
390     return
391     end if
392    
393     close(param_unit)
394    
395     if (use_target_temp) then
396     bath_temp = target_temp
397     end if
398    
399    
400    
401     end subroutine read_params
402    
403    
404    
405     end module parameter