(git:374b731)
Loading...
Searching...
No Matches
tmc_file_io.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief - writing and printing the files, trajectory (pos, cell, dipoles) as
10!> well as restart files
11!> - usually just the Markov Chain elements are regarded, the elements
12!> beside this trajectory are neglected
13!> - futrthermore (by option) just the accepted configurations
14!> are print out to reduce the file sizes
15!> \par History
16!> 12.2012 created [Mandes Schoenherr]
17!> \author Mandes
18! **************************************************************************************************
19
21 USE cp_files, ONLY: close_file,&
24 USE kinds, ONLY: default_path_length,&
26 dp
27 USE physcon, ONLY: au2a => angstrom
32 USE tmc_stati, ONLY: tmc_status_failed,&
40 USE tmc_types, ONLY: tmc_env_type,&
42#include "../base/base_uses.f90"
43
44 IMPLICIT NONE
45
46 PRIVATE
47
48 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'tmc_file_io'
49
50 ! filename manipulation
52 ! read/write restart file
54 ! write the configuration
56 PUBLIC :: write_element_in_file
57 PUBLIC :: write_dipoles_in_file
58 ! analysis read
60
61CONTAINS
62
63!------------------------------------------------------------------------------
64! routines for manipulating the file name
65!------------------------------------------------------------------------------
66! **************************************************************************************************
67!> \brief placing a character string at the end of a file name
68!> (instead of the ending)
69!> \param file_name original file name
70!> \param extra string to be added before the file extension
71!> \return the new filename
72!> \author Mandes 11.2012
73! **************************************************************************************************
74 FUNCTION expand_file_name_ending(file_name, extra) RESULT(result_file_name)
75 CHARACTER(LEN=*) :: file_name, extra
76 CHARACTER(LEN=default_path_length) :: result_file_name
77
78 INTEGER :: ind
79
80 cpassert(file_name .NE. "")
81
82 ind = index(file_name, ".", back=.true.)
83 IF (.NOT. ind .EQ. 0) THEN
84 WRITE (result_file_name, *) file_name(1:ind - 1), ".", &
85 trim(adjustl(extra))
86 ELSE
87 WRITE (result_file_name, *) trim(file_name), ".", extra
88 END IF
89 result_file_name = trim(adjustl(result_file_name))
90 cpassert(result_file_name .NE. "")
91 END FUNCTION expand_file_name_ending
92
93! **************************************************************************************************
94!> \brief placing a character string at the end of a file name
95!> (before the file extension)
96!> \param file_name original file name
97!> \param extra string to be added before the file extension
98!> \return the new filename
99!> \author Mandes 11.2012
100! **************************************************************************************************
101 FUNCTION expand_file_name_char(file_name, extra) RESULT(result_file_name)
102 CHARACTER(LEN=*) :: file_name, extra
103 CHARACTER(LEN=default_path_length) :: result_file_name
104
105 INTEGER :: ind
106
107 cpassert(file_name .NE. "")
108
109 ind = index(file_name, ".", back=.true.)
110 IF (.NOT. ind .EQ. 0) THEN
111 WRITE (result_file_name, *) file_name(1:ind - 1), "_", &
112 trim(adjustl(extra)), file_name(ind:len_trim(file_name))
113 ELSE
114 WRITE (result_file_name, *) trim(file_name), "_", extra
115 END IF
116 result_file_name = trim(adjustl(result_file_name))
117 cpassert(result_file_name .NE. "")
118 END FUNCTION expand_file_name_char
119
120! **************************************************************************************************
121!> \brief placing the temperature at the end of a file name
122!> (before the file extension)
123!> \param file_name original file name
124!> \param rvalue temperature to be added
125!> \return the new filename
126!> \author Mandes 11.2012
127! **************************************************************************************************
128 FUNCTION expand_file_name_temp(file_name, rvalue) RESULT(result_file_name)
129 CHARACTER(LEN=*) :: file_name
130 REAL(kind=dp) :: rvalue
131 CHARACTER(LEN=default_path_length) :: result_file_name
132
133 CHARACTER(LEN=18) :: rval_to_string
134 INTEGER :: ind
135
136 cpassert(file_name .NE. "")
137
138 rval_to_string = ""
139
140 WRITE (rval_to_string, "(F16.2)") rvalue
141 ind = index(file_name, ".", back=.true.)
142 IF (.NOT. ind .EQ. 0) THEN
143 WRITE (result_file_name, *) file_name(1:ind - 1), "_T", &
144 trim(adjustl(rval_to_string)), file_name(ind:len_trim(file_name))
145 ELSE
146 IF (len(file_name) .EQ. 0) THEN
147 WRITE (result_file_name, *) trim(file_name), "T", trim(adjustl(rval_to_string)), &
148 file_name(ind:len_trim(file_name))
149 ELSE
150 WRITE (result_file_name, *) trim(file_name), "_T", trim(adjustl(rval_to_string))
151 END IF
152 END IF
153 result_file_name = trim(adjustl(result_file_name))
154 cpassert(result_file_name .NE. "")
155 END FUNCTION expand_file_name_temp
156
157! **************************************************************************************************
158!> \brief placing an integer at the end of a file name
159!> (before the file extension)
160!> \param file_name original file name
161!> \param ivalue number to be added
162!> \return the new filename
163!> \author Mandes 11.2012
164! **************************************************************************************************
165 FUNCTION expand_file_name_int(file_name, ivalue) RESULT(result_file_name)
166 CHARACTER(LEN=*) :: file_name
167 INTEGER :: ivalue
168 CHARACTER(LEN=default_path_length) :: result_file_name
169
170 CHARACTER(LEN=18) :: rval_to_string
171 INTEGER :: ind
172
173 cpassert(file_name .NE. "")
174
175 rval_to_string = ""
176
177 WRITE (rval_to_string, *) ivalue
178 ind = index(file_name, ".", back=.true.)
179 IF (.NOT. ind .EQ. 0) THEN
180 WRITE (result_file_name, *) file_name(1:ind - 1), "_", &
181 trim(adjustl(rval_to_string)), file_name(ind:len_trim(file_name))
182 ELSE
183 IF (len(file_name) .EQ. 0) THEN
184 WRITE (result_file_name, *) trim(file_name), "", trim(adjustl(rval_to_string)), &
185 file_name(ind:len_trim(file_name))
186 ELSE
187 WRITE (result_file_name, *) trim(file_name), "_", trim(adjustl(rval_to_string)), &
188 file_name(ind:len_trim(file_name))
189 END IF
190 END IF
191 result_file_name = trim(adjustl(result_file_name))
192 cpassert(result_file_name .NE. "")
193 END FUNCTION expand_file_name_int
194
195!------------------------------------------------------------------------------
196! routines for reading and writing RESTART file
197!------------------------------------------------------------------------------
198! **************************************************************************************************
199!> \brief prints out the TMC restart files with all last configurations and
200!> counters etc.
201!> \param tmc_env the tmc environment, storing result lists and counters an in
202!> temperatures
203!> \param job_counts the counters for counting the submitted different job types
204!> \param timings ...
205!> \author Mandes 11.2012
206! **************************************************************************************************
207 SUBROUTINE print_restart_file(tmc_env, job_counts, timings)
208 TYPE(tmc_env_type), POINTER :: tmc_env
209 INTEGER, DIMENSION(:) :: job_counts
210 REAL(kind=dp), DIMENSION(4) :: timings
211
212 CHARACTER(LEN=default_path_length) :: c_tmp, file_name
213 INTEGER :: f_unit, i
214
215 c_tmp = ""
216 cpassert(ASSOCIATED(tmc_env))
217 cpassert(ASSOCIATED(tmc_env%m_env))
218 cpassert(ASSOCIATED(tmc_env%params))
219 cpassert(ASSOCIATED(tmc_env%m_env%gt_act))
220
221 WRITE (c_tmp, fmt='(I9.9)') tmc_env%m_env%result_count(0)
222 file_name = trim(expand_file_name_char( &
224 extra=c_tmp))
225 CALL open_file(file_name=file_name, file_status="REPLACE", &
226 file_action="WRITE", file_form="UNFORMATTED", &
227 unit_number=f_unit)
228 WRITE (f_unit) SIZE(tmc_env%params%Temp)
229 WRITE (f_unit) tmc_env%params%Temp(:), &
230 tmc_env%m_env%gt_act%nr, &
231 tmc_env%m_env%gt_act%rng_seed, &
232 tmc_env%m_env%gt_act%rnd_nr, &
233 tmc_env%m_env%gt_act%prob_acc, &
234 tmc_env%m_env%gt_act%mv_conf, &
235 tmc_env%m_env%gt_act%mv_next_conf, &
236 tmc_env%m_env%result_count(0:), &
237 tmc_env%params%move_types%mv_weight, &
238 tmc_env%params%move_types%acc_count, &
239 tmc_env%params%move_types%mv_count, &
240 tmc_env%params%move_types%subbox_acc_count, &
241 tmc_env%params%move_types%subbox_count, &
242 tmc_env%params%cell%hmat, &
243 job_counts, &
244 timings
245 DO i = 1, SIZE(tmc_env%params%Temp)
246 WRITE (f_unit) tmc_env%m_env%result_list(i)%elem%nr, &
247 tmc_env%m_env%result_list(i)%elem%rng_seed, &
248 tmc_env%m_env%result_list(i)%elem%pos, &
249 tmc_env%m_env%result_list(i)%elem%vel, &
250 tmc_env%m_env%result_list(i)%elem%box_scale, &
251 tmc_env%m_env%result_list(i)%elem%potential, &
252 tmc_env%m_env%result_list(i)%elem%e_pot_approx, &
253 tmc_env%m_env%result_list(i)%elem%ekin, &
254 tmc_env%m_env%result_list(i)%elem%ekin_before_md, &
255 tmc_env%m_env%result_list(i)%elem%temp_created
256 END DO
257 CALL close_file(unit_number=f_unit)
258 ! write the file, where the restart file name is written in
260 file_action="WRITE", file_status="REPLACE", &
261 unit_number=f_unit)
262 WRITE (f_unit, *) trim(file_name)
263 CALL close_file(unit_number=f_unit)
264 END SUBROUTINE print_restart_file
265
266! **************************************************************************************************
267!> \brief reads the TMC restart file with all last configurations and
268!> counters etc.
269!> \param tmc_env the tmc environment, storing result lists and counters an in
270!> temperatures
271!> \param job_counts the counters for counting the submitted different job types
272!> \param timings ...
273!> \param file_name the restart file name
274!> \author Mandes 11.2012
275! **************************************************************************************************
276 SUBROUTINE read_restart_file(tmc_env, job_counts, timings, file_name)
277 TYPE(tmc_env_type), POINTER :: tmc_env
278 INTEGER, DIMENSION(:) :: job_counts
279 REAL(kind=dp), DIMENSION(4) :: timings
280 CHARACTER(LEN=*) :: file_name
281
282 INTEGER :: file_ptr, i, temp_size
283 LOGICAL :: flag
284 REAL(kind=dp), ALLOCATABLE, DIMENSION(:) :: tmp_temp
285 REAL(kind=dp), DIMENSION(nr_mv_types) :: mv_weight_tmp
286
287 cpassert(ASSOCIATED(tmc_env))
288 cpassert(ASSOCIATED(tmc_env%m_env))
289 cpassert(ASSOCIATED(tmc_env%params))
290 cpassert(ASSOCIATED(tmc_env%m_env%gt_act))
291
292 IF (file_name .EQ. tmc_default_restart_in_file_name) THEN
293 INQUIRE (file=tmc_default_restart_in_file_name, exist=flag)
294 cpassert(flag)
295 CALL open_file(file_name=tmc_default_restart_in_file_name, file_status="OLD", &
296 file_action="READ", unit_number=file_ptr)
297 READ (file_ptr, *) file_name
298 CALL close_file(unit_number=file_ptr)
299 END IF
300
301 CALL open_file(file_name=file_name, file_status="OLD", file_form="UNFORMATTED", &
302 file_action="READ", unit_number=file_ptr)
303 READ (file_ptr) temp_size
304 IF (temp_size .NE. SIZE(tmc_env%params%Temp)) &
305 CALL cp_abort(__location__, &
306 "the actual specified temperatures does not "// &
307 "fit in amount with the one from restart file ")
308 ALLOCATE (tmp_temp(temp_size))
309 READ (file_ptr) tmp_temp(:), &
310 tmc_env%m_env%gt_act%nr, &
311 tmc_env%m_env%gt_act%rng_seed, &
312 tmc_env%m_env%gt_act%rnd_nr, &
313 tmc_env%m_env%gt_act%prob_acc, &
314 tmc_env%m_env%gt_act%mv_conf, & !
315 tmc_env%m_env%gt_act%mv_next_conf, & !
316 tmc_env%m_env%result_count(0:), &
317 mv_weight_tmp, & !
318 tmc_env%params%move_types%acc_count, &
319 tmc_env%params%move_types%mv_count, &
320 tmc_env%params%move_types%subbox_acc_count, &
321 tmc_env%params%move_types%subbox_count, & !
322 tmc_env%params%cell%hmat, &
323 job_counts, &
324 timings
325
326 IF (any(abs(tmc_env%params%Temp(:) - tmp_temp(:)) .GE. 0.005)) &
327 CALL cp_abort(__location__, "the temperatures differ from the previous calculation. "// &
328 "There were the following temperatures used:")
329 IF (any(mv_weight_tmp(:) .NE. tmc_env%params%move_types%mv_weight(:))) &
330 cpwarn("The amount of mv types differs between the original and the restart run.")
331
332 DO i = 1, SIZE(tmc_env%params%Temp)
333 tmc_env%m_env%gt_act%conf(i)%elem => tmc_env%m_env%result_list(i)%elem
334 READ (file_ptr) tmc_env%m_env%result_list(i)%elem%nr, &
335 tmc_env%m_env%result_list(i)%elem%rng_seed, &
336 tmc_env%m_env%result_list(i)%elem%pos, &
337 tmc_env%m_env%result_list(i)%elem%vel, &
338 tmc_env%m_env%result_list(i)%elem%box_scale, &
339 tmc_env%m_env%result_list(i)%elem%potential, &
340 tmc_env%m_env%result_list(i)%elem%e_pot_approx, &
341 tmc_env%m_env%result_list(i)%elem%ekin, &
342 tmc_env%m_env%result_list(i)%elem%ekin_before_md, &
343 tmc_env%m_env%result_list(i)%elem%temp_created
344 END DO
345 CALL close_file(unit_number=file_ptr)
346 END SUBROUTINE read_restart_file
347
348 !----------------------------------------------------------------------------
349 ! printing configuration in file
350 !----------------------------------------------------------------------------
351
352! **************************************************************************************************
353!> \brief select the correct configuration to print out the
354!> (coordinates, forces, cell ...)
355!> \param result_list list of configurations for each temperature
356!> \param result_count list with number of Markov Chain number
357!> for each teperature (index 0 for global tree)
358!> \param conf_updated index of the updated (modified element)
359!> \param accepted acceptance flag
360!> \param tmc_params TMC environment parameters
361!> \author Mandes 02.2013
362! **************************************************************************************************
363 SUBROUTINE write_result_list_element(result_list, result_count, conf_updated, &
364 accepted, tmc_params)
365 TYPE(elem_array_type), DIMENSION(:), POINTER :: result_list
366 INTEGER, DIMENSION(:), POINTER :: result_count
367 INTEGER :: conf_updated
368 LOGICAL, INTENT(IN) :: accepted
369 TYPE(tmc_param_type), POINTER :: tmc_params
370
371 CHARACTER(LEN=*), PARAMETER :: routinen = 'write_result_list_element'
372
373 CHARACTER(LEN=default_path_length) :: file_name
374 INTEGER :: handle, i
375
376 file_name = ""
377
378 cpassert(ASSOCIATED(result_list))
379 cpassert(ASSOCIATED(result_count))
380 cpassert(ASSOCIATED(tmc_params))
381 cpassert(ASSOCIATED(tmc_params%Temp))
382 cpassert(conf_updated .GE. 0)
383 cpassert(conf_updated .LE. SIZE(tmc_params%Temp))
384
385 ! start the timing
386 CALL timeset(routinen, handle)
387
388 IF (conf_updated .EQ. 0) THEN
389 ! for debugging print every configuration of every temperature
390 DO i = 1, SIZE(tmc_params%Temp)
391 WRITE (file_name, *) "every_step_", trim(tmc_default_trajectory_file_name)
392 CALL write_element_in_file(elem=result_list(i)%elem, &
393 tmc_params=tmc_params, conf_nr=result_count(0), &
394 file_name=expand_file_name_temp(file_name=file_name, rvalue=tmc_params%Temp(i)))
395 END DO
396 ELSE
397 IF ((.NOT. tmc_params%print_only_diff_conf) .OR. &
398 (tmc_params%print_only_diff_conf .AND. accepted)) THEN
399 CALL write_element_in_file(elem=result_list(conf_updated)%elem, &
400 tmc_params=tmc_params, conf_nr=result_count(conf_updated), &
402 rvalue=tmc_params%Temp(conf_updated)))
403 END IF
404 END IF
405 ! end the timing
406 CALL timestop(handle)
407 END SUBROUTINE write_result_list_element
408
409! **************************************************************************************************
410!> \brief writes the trajectory element in a file from sub tree element
411!> \param elem actual tree element to be printed out
412!> \param tmc_params TMC environment parameters
413!> \param temp_index ...
414!> \param file_name file name will be extended by type of file (pos, cell,...)
415!> \param conf_nr Markov chain element number
416!> \param conf_info whole header line
417!> \author Mandes 11.2012
418! **************************************************************************************************
419 SUBROUTINE write_element_in_file(elem, tmc_params, temp_index, file_name, conf_nr, &
420 conf_info)
421 TYPE(tree_type), POINTER :: elem
422 TYPE(tmc_param_type), POINTER :: tmc_params
423 INTEGER, OPTIONAL :: temp_index
424 CHARACTER(LEN=*), OPTIONAL :: file_name
425 INTEGER, OPTIONAL :: conf_nr
426 CHARACTER(LEN=*), OPTIONAL :: conf_info
427
428 CHARACTER(LEN=*), PARAMETER :: routinen = 'write_element_in_file'
429
430 CHARACTER(LEN=default_path_length) :: file_name_act, tmp_name
431 CHARACTER(LEN=default_string_length) :: header
432 INTEGER :: file_ptr, handle, i, nr_atoms
433 LOGICAL :: file_exists, print_it
434 REAL(kind=dp) :: vol
435 REAL(kind=dp), DIMENSION(3, 3) :: hmat_scaled
436
437 file_name_act = ""
438 tmp_name = ""
439 header = ""
440 print_it = .true.
441
442 cpassert(ASSOCIATED(elem))
443 cpassert(ASSOCIATED(tmc_params))
444 cpassert(ASSOCIATED(tmc_params%atoms))
445 cpassert(PRESENT(conf_nr) .OR. PRESENT(conf_info))
446
447 IF (print_it) THEN
448 ! start the timing
449 CALL timeset(routinen, handle)
450
451 ! set default file name
452 IF (PRESENT(file_name)) THEN
453 cpassert(file_name .NE. "")
454 file_name_act = file_name
455 ELSE
456 cpassert(ASSOCIATED(tmc_params%Temp))
457 cpassert(PRESENT(temp_index))
459 rvalue=tmc_params%Temp(temp_index))
460 END IF
461
462 nr_atoms = SIZE(elem%pos)/tmc_params%dim_per_elem
463
464 ! set header (for coordinate or force file)
465 IF (tmc_params%print_trajectory .OR. tmc_params%print_forces) THEN
466 IF (PRESENT(conf_info)) THEN
467 WRITE (header, *) trim(adjustl(conf_info))
468 ELSE
469 !WRITE(header,FMT="(A,I8,A,F20.10)") " i = ", conf_nr,", E = ", elem%potential
470 WRITE (header, fmt="(A,I8,A,F20.10,F20.10,A,I8,I8)") "i =", conf_nr, " ,E =", &
471 elem%potential, elem%ekin, " st elem", elem%sub_tree_nr, elem%nr
472 END IF
473 END IF
474
475 ! write the coordinates
476 IF (tmc_params%print_trajectory) THEN
477 tmp_name = expand_file_name_ending(file_name_act, "xyz")
478 CALL open_file(file_name=tmp_name, file_status="UNKNOWN", &
479 file_action="WRITE", file_position="APPEND", &
480 unit_number=file_ptr)
481 WRITE (file_ptr, fmt="(I8)") nr_atoms
482 WRITE (file_ptr, *) trim(header)
483 DO i = 1, SIZE(elem%pos), tmc_params%dim_per_elem
484 WRITE (file_ptr, fmt="(A4,1X,1000F20.10)") &
485 trim(tmc_params%atoms((i - 1)/tmc_params%dim_per_elem + 1)%name), &
486 elem%pos(i:i + tmc_params%dim_per_elem - 1)*au2a
487 END DO
488 CALL close_file(unit_number=file_ptr)
489 END IF
490
491 ! write the forces
492 IF (tmc_params%print_forces) THEN
493 tmp_name = expand_file_name_ending(file_name_act, "frc")
494 CALL open_file(file_name=tmp_name, file_status="UNKNOWN", &
495 file_action="WRITE", file_position="APPEND", &
496 unit_number=file_ptr)
497 WRITE (file_ptr, fmt="(I8)") nr_atoms
498 WRITE (file_ptr, *) trim(header)
499 DO i = 1, SIZE(elem%pos), tmc_params%dim_per_elem
500 WRITE (file_ptr, fmt="(A4,1X,1000F20.10)") &
501 trim(tmc_params%atoms((i - 1)/tmc_params%dim_per_elem + 1)%name), &
502 elem%frc(i:i + tmc_params%dim_per_elem - 1)
503 END DO
504 CALL close_file(unit_number=file_ptr)
505 END IF
506
507 ! write the cell dipoles
508 IF (tmc_params%print_dipole) THEN
509 CALL write_dipoles_in_file(file_name=file_name_act, &
510 conf_nr=conf_nr, dip=elem%dipole)
511 END IF
512
513 ! write the cell file
514 IF (tmc_params%print_cell) THEN
515 tmp_name = expand_file_name_ending(file_name_act, "cell")
516 ! header
517 INQUIRE (file=tmp_name, exist=file_exists) ! file_exists will be TRUE if the file exist
518 IF (.NOT. file_exists) THEN
519 CALL open_file(file_name=tmp_name, file_status="NEW", &
520 file_action="WRITE", unit_number=file_ptr)
521 WRITE (file_ptr, fmt='(A,9(7X,A2," [Angstrom]"),6X,A)') &
522 "# MC step ", "Ax", "Ay", "Az", "Bx", "By", "Bz", "Cx", "Cy", "Cz", &
523 "Volume [Angstrom^3]"
524 ELSE
525 CALL open_file(file_name=tmp_name, file_status="OLD", &
526 file_action="WRITE", file_position="APPEND", &
527 unit_number=file_ptr)
528 END IF
529 CALL get_scaled_cell(cell=tmc_params%cell, &
530 box_scale=elem%box_scale, scaled_hmat=hmat_scaled, &
531 vol=vol)
532 WRITE (file_ptr, fmt="(I8,9(1X,F19.10),1X,F24.10)") conf_nr, &
533 hmat_scaled(:, :)*au2a, vol*au2a**3
534 !TODO better cell output e.g. using cell_types routine
535 CALL close_file(unit_number=file_ptr)
536 END IF
537
538 ! write the different energies
539 IF (tmc_params%print_energies) THEN
540 tmp_name = expand_file_name_ending(file_name_act, "ener")
541 ! header
542 INQUIRE (file=tmp_name, exist=file_exists) ! file_exists will be TRUE if the file exist
543 IF (.NOT. file_exists) THEN
544 CALL open_file(file_name=tmp_name, file_status="NEW", &
545 file_action="WRITE", unit_number=file_ptr)
546 WRITE (file_ptr, fmt='(A,4A20)') &
547 "# MC step ", " exact ", " approx ", " last SCF ", " kinetic "
548 ELSE
549 CALL open_file(file_name=tmp_name, file_status="OLD", &
550 file_action="WRITE", file_position="APPEND", &
551 unit_number=file_ptr)
552 END IF
553 WRITE (file_ptr, fmt="(I8,14F20.10)") conf_nr, elem%potential, elem%e_pot_approx, &
554 elem%scf_energies(mod(elem%scf_energies_count, 4) + 1), elem%ekin
555 CALL close_file(unit_number=file_ptr)
556 END IF
557
558 ! end the timing
559 CALL timestop(handle)
560 END IF
561 END SUBROUTINE write_element_in_file
562
563! **************************************************************************************************
564!> \brief writes the cell dipoles in dipole trajectory file
565!> \param file_name ...
566!> \param conf_nr ...
567!> \param dip ...
568!> \param file_ext ...
569!> \param
570!> \author Mandes 11.2012
571! **************************************************************************************************
572 SUBROUTINE write_dipoles_in_file(file_name, conf_nr, dip, file_ext)
573 CHARACTER(LEN=default_path_length) :: file_name
574 INTEGER :: conf_nr
575 REAL(kind=dp), DIMENSION(:), POINTER :: dip
576 CHARACTER(LEN=*), INTENT(in), OPTIONAL :: file_ext
577
578 CHARACTER(LEN=default_path_length) :: file_name_tmp
579 INTEGER :: file_ptr
580 LOGICAL :: file_exists
581
582 cpassert(ASSOCIATED(dip))
583
584 IF (PRESENT(file_ext)) THEN
585 cpassert(file_ext .NE. "")
586 file_name_tmp = expand_file_name_ending(file_name, trim(file_ext))
587 ELSE
588 file_name_tmp = expand_file_name_ending(file_name, "dip")
589 END IF
590 INQUIRE (file=file_name_tmp, exist=file_exists)
591 IF (.NOT. file_exists) THEN
592 CALL open_file(file_name=file_name_tmp, file_status="NEW", &
593 file_action="WRITE", unit_number=file_ptr)
594 WRITE (file_ptr, fmt='(A8,10A20)') "# conf_nr", "dip_x [C Angstrom]", &
595 "dip_y [C Angstrom]", "dip_z [C Angstrom]"
596 ELSE
597 CALL open_file(file_name=file_name_tmp, file_status="OLD", &
598 file_action="WRITE", file_position="APPEND", &
599 unit_number=file_ptr)
600 END IF
601 WRITE (file_ptr, fmt="(I8,10F20.10)") conf_nr, dip(:)
602 CALL close_file(unit_number=file_ptr)
603 END SUBROUTINE write_dipoles_in_file
604
605 !----------------------------------------------------------------------------
606 ! read configuration from file
607 !----------------------------------------------------------------------------
608
609! **************************************************************************************************
610!> \brief read the trajectory element from a file from sub tree element
611!> \param elem actual tree element to be printed out
612!> \param tmc_ana TMC analysis environment parameters
613!> \param conf_nr Markov chain element number
614!> (input the old number and read only if conf nr from file is greater
615!> \param stat ...
616!> \author Mandes 03.2013
617! **************************************************************************************************
618 SUBROUTINE read_element_from_file(elem, tmc_ana, conf_nr, stat)
619 TYPE(tree_type), POINTER :: elem
620 TYPE(tmc_analysis_env), POINTER :: tmc_ana
621 INTEGER :: conf_nr, stat
622
623 CHARACTER(LEN=*), PARAMETER :: routinen = 'read_element_from_file'
624
625 INTEGER :: conf_nr_old, handle, i_tmp
626 LOGICAL :: files_conf_missmatch
627
628 stat = tmc_status_ok
629 conf_nr_old = conf_nr
630 files_conf_missmatch = .false.
631
632 cpassert(ASSOCIATED(elem))
633 cpassert(ASSOCIATED(tmc_ana))
634 cpassert(ASSOCIATED(tmc_ana%atoms))
635
636 ! start the timing
637 CALL timeset(routinen, handle)
638
639 ! read the coordinates
640 IF (tmc_ana%id_traj .GT. 0) THEN
641 i_tmp = conf_nr_old
642 CALL read_pos_from_file(elem=elem, tmc_ana=tmc_ana, stat=stat, &
643 conf_nr=i_tmp)
644 IF (stat .EQ. tmc_status_wait_for_new_task) THEN
645 CALL cp_warn(__location__, &
646 'end of position file reached at line '// &
647 cp_to_string(real(tmc_ana%lc_traj, kind=dp))//", last element "// &
648 cp_to_string(tmc_ana%last_elem%nr))
649 ELSE
650 cpassert(i_tmp .GT. conf_nr_old)
651 conf_nr = i_tmp
652 elem%nr = i_tmp
653 END IF
654 END IF
655
656 ! read the forces
657 ! TODO if necessary
658
659 ! read the dipoles file
660 IF (tmc_ana%id_dip .GT. 0 .AND. stat .EQ. tmc_status_ok) THEN
661 i_tmp = conf_nr_old
662 search_conf_dip: DO
663 CALL read_dipole_from_file(elem=elem, tmc_ana=tmc_ana, stat=stat, &
664 conf_nr=i_tmp)
665 IF (stat .EQ. tmc_status_wait_for_new_task) THEN
666 CALL cp_warn(__location__, &
667 'end of dipole file reached at line'// &
668 cp_to_string(real(tmc_ana%lc_dip, kind=dp)))
669 EXIT search_conf_dip
670 END IF
671 ! check consitence with pos file
672 IF (tmc_ana%id_traj .GT. 0) THEN
673 IF (i_tmp .EQ. conf_nr) THEN
674 files_conf_missmatch = .false.
675 EXIT search_conf_dip
676 ELSE
677 ! the configuration numbering differ from the position file,
678 ! but we keep on searching for the correct configuration
679 files_conf_missmatch = .true.
680 END IF
681 ! if no pos file, just take the next conf
682 ELSE IF (i_tmp .GT. conf_nr_old) THEN
683 conf_nr = i_tmp
684 elem%nr = i_tmp
685 EXIT search_conf_dip
686 END IF
687 END DO search_conf_dip
688 END IF
689
690 ! read the cell file
691 IF (tmc_ana%id_cell .GT. 0 .AND. stat .EQ. tmc_status_ok) THEN
692 search_conf_cell: DO
693 CALL read_cell_from_file(elem=elem, tmc_ana=tmc_ana, stat=stat, &
694 conf_nr=i_tmp)
695 IF (stat .EQ. tmc_status_wait_for_new_task) THEN
696 CALL cp_warn(__location__, &
697 'end of cell file reached at line at line'// &
698 cp_to_string(real(tmc_ana%lc_cell, kind=dp)))
699 EXIT search_conf_cell
700 END IF
701 ! check consitence with pos file
702 IF (tmc_ana%id_traj .GT. 0) THEN
703 IF (i_tmp .EQ. conf_nr) THEN
704 files_conf_missmatch = .false.
705 EXIT search_conf_cell
706 ELSE
707 ! the configuration numbering differ from the position file,
708 ! but we keep on searching for the correct configuration
709 files_conf_missmatch = .true.
710 END IF
711 ! if no pos file, just take the next conf
712 ELSE IF (i_tmp .GT. conf_nr_old) THEN
713 conf_nr = i_tmp
714 elem%nr = i_tmp
715 EXIT search_conf_cell
716 END IF
717 END DO search_conf_cell
718
719 END IF
720
721 ! write the different energies
722 ! TODO if necessary
723
724 IF (files_conf_missmatch) &
725 CALL cp_warn(__location__, &
726 'there is a missmatch in the configuration numbering. '// &
727 "Read number of lines (pos|cell|dip)"// &
728 cp_to_string(tmc_ana%lc_traj)//"|"// &
729 cp_to_string(tmc_ana%lc_cell)//"|"// &
730 cp_to_string(tmc_ana%lc_dip))
731
732 ! end the timing
733 CALL timestop(handle)
734 END SUBROUTINE read_element_from_file
735
736! **************************************************************************************************
737!> \brief search for the next configurational position in file
738!> \param elem actual tree element to be read
739!> \param tmc_ana ...
740!> \param stat ...
741!> \param conf_nr Markov chain element number
742!> (input the old number and read only if conf nr from file is greater
743!> \param header_info ...
744!> \author Mandes 03.2013
745! **************************************************************************************************
746 SUBROUTINE read_pos_from_file(elem, tmc_ana, stat, conf_nr, header_info)
747 TYPE(tree_type), POINTER :: elem
748 TYPE(tmc_analysis_env), POINTER :: tmc_ana
749 INTEGER :: stat, conf_nr
750 CHARACTER(LEN=*), OPTIONAL :: header_info
751
752 CHARACTER(LEN=*), PARAMETER :: routinen = 'read_pos_from_file'
753
754 CHARACTER(LEN=default_string_length) :: c_tmp
755 INTEGER :: handle, i, i_tmp, status
756
757 stat = tmc_status_failed
758
759 cpassert(ASSOCIATED(elem))
760 cpassert(ASSOCIATED(elem%pos))
761 cpassert(ASSOCIATED(tmc_ana))
762 cpassert(tmc_ana%id_traj .GT. 0)
763
764 ! start the timing
765 CALL timeset(routinen, handle)
766
767 search_next_conf: DO
768 c_tmp(:) = " "
769 tmc_ana%lc_traj = tmc_ana%lc_traj + 1
770 READ (tmc_ana%id_traj, '(A)', iostat=status) c_tmp(:)
771 IF (status .GT. 0) &
772 CALL cp_abort(__location__, &
773 "configuration header read error at line: "// &
774 cp_to_string(tmc_ana%lc_traj)//": "//c_tmp)
775 IF (status .LT. 0) THEN ! end of file reached
777 EXIT search_next_conf
778 END IF
779 IF (index(c_tmp, "=") .GT. 0) THEN
780 READ (c_tmp(index(c_tmp, "=") + 1:), *, iostat=status) i_tmp ! read the configuration number
781 IF (status .NE. 0) &
782 CALL cp_abort(__location__, &
783 "configuration header read error (for conf nr) at line: "// &
784 cp_to_string(tmc_ana%lc_traj))
785 IF (i_tmp .GT. conf_nr) THEN
786 ! TODO we could also read the energy ...
787 conf_nr = i_tmp
788 IF (PRESENT(header_info)) header_info = c_tmp
789 stat = tmc_status_ok
790 EXIT search_next_conf
791 END IF
792 END IF
793 END DO search_next_conf
794
795 IF (stat .EQ. tmc_status_ok) THEN
796 pos_loop: DO i = 1, SIZE(elem%pos), tmc_ana%dim_per_elem
797 tmc_ana%lc_traj = tmc_ana%lc_traj + 1
798 READ (tmc_ana%id_traj, fmt="(A4,1X,1000F20.10)", iostat=status) &
799 c_tmp, elem%pos(i:i + tmc_ana%dim_per_elem - 1)
800 IF (status .NE. 0) THEN
801 CALL cp_abort(__location__, &
802 "configuration pos read error at line: "// &
803 cp_to_string(tmc_ana%lc_traj))
804 END IF
805 END DO pos_loop
806 elem%pos(:) = elem%pos(:)/au2a
807 END IF
808
809 ! end the timing
810 CALL timestop(handle)
811 END SUBROUTINE read_pos_from_file
812
813! **************************************************************************************************
814!> \brief search for the dipole entry
815!> \param elem actual tree element to be read
816!> \param tmc_ana ...
817!> \param stat ...
818!> \param conf_nr Markov chain element number
819!> (input the old number and read only if conf nr from file is greater
820!> \author Mandes 03.2013
821! **************************************************************************************************
822 SUBROUTINE read_dipole_from_file(elem, tmc_ana, stat, conf_nr)
823 TYPE(tree_type), POINTER :: elem
824 TYPE(tmc_analysis_env), POINTER :: tmc_ana
825 INTEGER :: stat, conf_nr
826
827 CHARACTER(LEN=*), PARAMETER :: routinen = 'read_dipole_from_file'
828
829 CHARACTER(LEN=250) :: c_tmp
830 INTEGER :: handle, status
831
832 stat = tmc_status_failed
833
834 cpassert(ASSOCIATED(elem))
835 cpassert(ASSOCIATED(elem%dipole))
836 cpassert(ASSOCIATED(tmc_ana))
837 cpassert(tmc_ana%id_dip .GT. 0)
838
839 ! start the timing
840 CALL timeset(routinen, handle)
841 tmc_ana%lc_dip = tmc_ana%lc_dip + 1
842 READ (tmc_ana%id_dip, fmt="(A)", iostat=status) c_tmp
843 IF (status .EQ. 0) THEN
844 ! skip the initial line (header)
845 IF (index(c_tmp, "#") .GT. 0) THEN
846 tmc_ana%lc_dip = tmc_ana%lc_dip + 1
847 READ (tmc_ana%id_dip, fmt="(A)", iostat=status) c_tmp
848 END IF
849 END IF
850 IF (status .EQ. 0) THEN
851 READ (c_tmp, fmt="(I8,10F20.10)", iostat=status) &
852 conf_nr, elem%dipole(:)
853 END IF
854 IF (status .EQ. 0) THEN ! success
855 stat = tmc_status_ok
856 ELSE IF (status .LT. 0) THEN ! end of file reached
858 ELSE
859 IF (status .NE. 0) &
860 cpwarn("configuration dipole read error at line: "//cp_to_string(tmc_ana%lc_dip))
861 stat = tmc_status_failed
862 END IF
863
864 ! end the timing
865 CALL timestop(handle)
866 END SUBROUTINE read_dipole_from_file
867
868! **************************************************************************************************
869!> \brief search for the cell entry
870!> \param elem actual tree element to be read
871!> \param tmc_ana ...
872!> \param stat ...
873!> \param conf_nr Markov chain element number
874!> (input the old number and read only if conf nr from file is greater
875!> \author Mandes 03.2013
876! **************************************************************************************************
877 SUBROUTINE read_cell_from_file(elem, tmc_ana, stat, conf_nr)
878 TYPE(tree_type), POINTER :: elem
879 TYPE(tmc_analysis_env), POINTER :: tmc_ana
880 INTEGER :: stat, conf_nr
881
882 CHARACTER(LEN=*), PARAMETER :: routinen = 'read_cell_from_file'
883
884 CHARACTER(LEN=250) :: c_tmp
885 INTEGER :: handle, status
886 REAL(kind=dp) :: r_tmp
887 REAL(kind=dp), DIMENSION(3, 3) :: hmat
888
889 stat = tmc_status_failed
890
891 cpassert(ASSOCIATED(elem))
892 cpassert(ASSOCIATED(tmc_ana))
893 cpassert(ASSOCIATED(tmc_ana%cell))
894 cpassert(tmc_ana%id_cell .GT. 0)
895
896 ! start the timing
897 CALL timeset(routinen, handle)
898
899 tmc_ana%lc_cell = tmc_ana%lc_cell + 1
900 READ (tmc_ana%id_cell, fmt="(A)", iostat=status) c_tmp
901 IF (status .EQ. 0) THEN
902 ! skip the initial line (header)
903 IF (index(c_tmp, "#") .GT. 0) THEN
904 tmc_ana%lc_cell = tmc_ana%lc_cell + 1
905 READ (tmc_ana%id_cell, fmt="(A)", iostat=status) c_tmp
906 END IF
907 END IF
908 IF (status .EQ. 0) THEN
909 READ (c_tmp, fmt="(I8,9(1X,F19.10),1X,F24.10)", iostat=status) conf_nr, &
910 hmat(:, :), r_tmp
911 END IF
912 IF (status .LT. 0) THEN ! end of file reached
914 ELSE IF (status .GT. 0) THEN
915 IF (status .NE. 0) &
916 cpabort("configuration cell read error at line: "//cp_to_string(tmc_ana%lc_cell))
917 stat = tmc_status_failed
918 ELSE
919 IF (elem%nr .LT. 0) elem%nr = conf_nr
920 hmat(:, :) = hmat(:, :)/au2a
921 ! get the box scaling
922 CALL get_cell_scaling(cell=tmc_ana%cell, scaled_hmat=hmat, &
923 box_scale=elem%box_scale)
924 stat = tmc_status_ok
925 END IF
926 ! end the timing
927 CALL timestop(handle)
928 END SUBROUTINE read_cell_from_file
929
930 !----------------------------------------------------------------------------
931 ! get the configurations from file and calc
932 !----------------------------------------------------------------------------
933
934! **************************************************************************************************
935!> \brief opens the files for reading configurations data to analyze
936!> \param tmc_ana ...
937!> \param stat ...
938!> \param dir_ind ...
939!> \param
940!> \author Mandes 02.2013
941! **************************************************************************************************
942 SUBROUTINE analyse_files_open(tmc_ana, stat, dir_ind)
943 TYPE(tmc_analysis_env), POINTER :: tmc_ana
944 INTEGER :: stat
945 INTEGER, OPTIONAL :: dir_ind
946
947 CHARACTER(LEN=*), PARAMETER :: routinen = 'analyse_files_open'
948
949 CHARACTER(LEN=default_path_length) :: dir_name, file_name_act, file_name_temp
950 INTEGER :: handle
951 LOGICAL :: file_exists
952
953 cpassert(ASSOCIATED(tmc_ana))
954
956
957 ! start the timing
958 CALL timeset(routinen, handle)
959
960 IF (PRESENT(dir_ind)) THEN
961 cpassert(ASSOCIATED(tmc_ana%dirs))
962 cpassert(dir_ind .GT. 0)
963 cpassert(dir_ind .LE. SIZE(tmc_ana%dirs))
964
965 IF (index(tmc_ana%dirs(dir_ind), "/", back=.true.) .EQ. &
966 len_trim(tmc_ana%dirs(dir_ind))) THEN
967 dir_name = trim(tmc_ana%dirs(dir_ind))
968 ELSE
969 dir_name = trim(tmc_ana%dirs(dir_ind))//"/"
970 END IF
971 ELSE
972 dir_name = "./"
973 END IF
974
975 ! open the files
976 file_name_temp = expand_file_name_temp( &
978 rvalue=tmc_ana%temperature)
979 ! position file
980 IF (tmc_ana%costum_pos_file_name .NE. "") THEN
981 file_name_act = trim(dir_name)//tmc_ana%costum_pos_file_name
982 ELSE
983 file_name_act = trim(dir_name)// &
984 expand_file_name_ending(file_name_temp, "xyz")
985 END IF
986 INQUIRE (file=file_name_act, exist=file_exists)
987 IF (file_exists) THEN
988 CALL open_file(file_name=file_name_act, file_status="OLD", &
989 file_action="READ", unit_number=tmc_ana%id_traj)
990 WRITE (tmc_ana%io_unit, fmt='(T2,A,"| ",A,T41,A40)') "TMC_ANA", &
991 "read xyz file", trim(file_name_act)
992 END IF
993
994 ! cell file
995 IF (tmc_ana%costum_cell_file_name .NE. "") THEN
996 file_name_act = trim(dir_name)//tmc_ana%costum_cell_file_name
997 ELSE
998 file_name_act = trim(dir_name)// &
999 expand_file_name_ending(file_name_temp, "cell")
1000 END IF
1001 INQUIRE (file=file_name_act, exist=file_exists)
1002 IF (file_exists) THEN
1003 CALL open_file(file_name=file_name_act, file_status="OLD", &
1004 file_action="READ", unit_number=tmc_ana%id_cell)
1005 WRITE (tmc_ana%io_unit, fmt='(T2,A,"| ",A,T41,A40)') "TMC_ANA", &
1006 "read cell file", trim(file_name_act)
1007 END IF
1008
1009 ! dipole file
1010 IF (tmc_ana%costum_dip_file_name .NE. "") THEN
1011 file_name_act = trim(dir_name)//tmc_ana%costum_dip_file_name
1012 ELSE
1013 file_name_act = trim(dir_name)// &
1014 expand_file_name_ending(file_name_temp, "dip")
1015 END IF
1016 INQUIRE (file=file_name_act, exist=file_exists)
1017 IF (file_exists) THEN
1018 CALL open_file(file_name=file_name_act, file_status="OLD", &
1019 file_action="READ", unit_number=tmc_ana%id_dip)
1020 WRITE (tmc_ana%io_unit, fmt='(T2,A,"| ",A,T41,A40)') "TMC_ANA", &
1021 "read dip file", trim(file_name_act)
1022 END IF
1023
1024 IF (tmc_ana%id_traj .GT. 0 .OR. tmc_ana%id_cell .GT. 0 .OR. &
1025 tmc_ana%id_dip .GT. 0) THEN
1026 stat = tmc_status_ok
1027 ELSE
1028 CALL cp_warn(__location__, &
1029 "There is no file to open for temperature "//cp_to_string(tmc_ana%temperature)// &
1030 "K in directory "//trim(dir_name))
1031 END IF
1032 ! end the timing
1033 CALL timestop(handle)
1034 END SUBROUTINE analyse_files_open
1035
1036! **************************************************************************************************
1037!> \brief close the files for reading configurations data to analyze
1038!> \param tmc_ana ...
1039!> \param
1040!> \author Mandes 02.2013
1041! **************************************************************************************************
1042 SUBROUTINE analyse_files_close(tmc_ana)
1043 TYPE(tmc_analysis_env), POINTER :: tmc_ana
1044
1045 CHARACTER(LEN=*), PARAMETER :: routinen = 'analyse_files_close'
1046
1047 INTEGER :: handle
1048
1049 cpassert(ASSOCIATED(tmc_ana))
1050
1051 ! start the timing
1052 CALL timeset(routinen, handle)
1053
1054 ! position file
1055 IF (tmc_ana%id_traj .GT. 0) CALL close_file(unit_number=tmc_ana%id_traj)
1056
1057 ! cell file
1058 IF (tmc_ana%id_cell .GT. 0) CALL close_file(unit_number=tmc_ana%id_cell)
1059
1060 ! dipole file
1061 IF (tmc_ana%id_dip .GT. 0) CALL close_file(unit_number=tmc_ana%id_dip)
1062
1063 ! end the timing
1064 CALL timestop(handle)
1065 END SUBROUTINE analyse_files_close
1066
1067END MODULE tmc_file_io
Utility routines to open and close files. Tracking of preconnections.
Definition cp_files.F:16
subroutine, public open_file(file_name, file_status, file_form, file_action, file_position, file_pad, unit_number, debug, skip_get_unit_number, file_access)
Opens the requested file using a free unit number.
Definition cp_files.F:308
subroutine, public close_file(unit_number, file_status, keep_preconnection)
Close an open file given by its logical unit number. Optionally, keep the file and unit preconnected.
Definition cp_files.F:119
logical function, public file_exists(file_name)
Checks if file exists, considering also the file discovery mechanism.
Definition cp_files.F:494
various routines to log and control the output. The idea is that decisions about where to log should ...
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_string_length
Definition kinds.F:57
integer, parameter, public default_path_length
Definition kinds.F:58
Definition of physical constants:
Definition physcon.F:68
real(kind=dp), parameter, public angstrom
Definition physcon.F:144
Timing routines for accounting.
Definition timings.F:17
module provides variables for the TMC analysis tool
calculation section for TreeMonteCarlo
subroutine, public get_scaled_cell(cell, box_scale, scaled_hmat, scaled_cell, vol, abc, vec)
handles properties and calculations of a scaled cell
subroutine, public get_cell_scaling(cell, scaled_hmat, box_scale)
handles properties and calculations of a scaled cell
writing and printing the files, trajectory (pos, cell, dipoles) as well as restart files
Definition tmc_file_io.F:20
subroutine, public analyse_files_close(tmc_ana)
close the files for reading configurations data to analyze
subroutine, public write_result_list_element(result_list, result_count, conf_updated, accepted, tmc_params)
select the correct configuration to print out the (coordinates, forces, cell ...)
subroutine, public print_restart_file(tmc_env, job_counts, timings)
prints out the TMC restart files with all last configurations and counters etc.
subroutine, public write_dipoles_in_file(file_name, conf_nr, dip, file_ext)
writes the cell dipoles in dipole trajectory file
subroutine, public read_element_from_file(elem, tmc_ana, conf_nr, stat)
read the trajectory element from a file from sub tree element
subroutine, public write_element_in_file(elem, tmc_params, temp_index, file_name, conf_nr, conf_info)
writes the trajectory element in a file from sub tree element
subroutine, public analyse_files_open(tmc_ana, stat, dir_ind)
opens the files for reading configurations data to analyze
character(len=default_path_length) function, public expand_file_name_char(file_name, extra)
placing a character string at the end of a file name (before the file extension)
character(len=default_path_length) function, public expand_file_name_temp(file_name, rvalue)
placing the temperature at the end of a file name (before the file extension)
character(len=default_path_length) function, public expand_file_name_int(file_name, ivalue)
placing an integer at the end of a file name (before the file extension)
subroutine, public read_restart_file(tmc_env, job_counts, timings, file_name)
reads the TMC restart file with all last configurations and counters etc.
tree nodes creation, searching, deallocation, references etc.
integer, parameter, public nr_mv_types
tree nodes creation, searching, deallocation, references etc.
Definition tmc_stati.F:15
integer, parameter, public tmc_status_failed
Definition tmc_stati.F:57
character(len= *), parameter, public tmc_default_trajectory_file_name
Definition tmc_stati.F:24
integer, parameter, public tmc_status_wait_for_new_task
Definition tmc_stati.F:52
character(len= *), parameter, public tmc_default_restart_in_file_name
Definition tmc_stati.F:28
character(len= *), parameter, public tmc_default_restart_out_file_name
Definition tmc_stati.F:26
integer, parameter, public tmc_status_ok
Definition tmc_stati.F:51
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
Definition tmc_types.F:32