(git:374b731)
Loading...
Searching...
No Matches
atom.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! **************************************************************************************************
9MODULE atom
10 USE atom_basis, ONLY: atom_basis_opt
17 USE header, ONLY: atom_footer,&
27 USE periodic_table, ONLY: nelem,&
28 ptable
29#include "./base/base_uses.f90"
30
31 IMPLICIT NONE
32 PRIVATE
33 PUBLIC :: atom_code
34
35 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'atom'
36
37CONTAINS
38
39! **************************************************************************************************
40!> \brief Driver routine to perform atomic calculations.
41!> \param root_section root input section
42!> \par History
43!> * 08.2008 created [Juerg Hutter]
44! **************************************************************************************************
45 SUBROUTINE atom_code(root_section)
46 TYPE(section_vals_type), POINTER :: root_section
47
48 CHARACTER(len=*), PARAMETER :: routinen = 'atom_code'
49
50 INTEGER :: handle, iw, run_type_id
51 TYPE(cp_logger_type), POINTER :: logger
52 TYPE(section_vals_type), POINTER :: atom_section
53
54 CALL timeset(routinen, handle)
55
56 logger => cp_get_default_logger()
57 NULLIFY (atom_section)
58 atom_section => section_vals_get_subs_vals(root_section, "ATOM")
59
60 iw = cp_print_key_unit_nr(logger, atom_section, "PRINT%PROGRAM_BANNER", extension=".log")
61 CALL atom_header(iw)
62 CALL cp_print_key_finished_output(iw, logger, atom_section, "PRINT%PROGRAM_BANNER")
63
64 CALL atom_test(atom_section)
65
66 CALL section_vals_val_get(atom_section, "RUN_TYPE", i_val=run_type_id)
67 SELECT CASE (run_type_id)
68 CASE (atom_no_run)
69 ! do (almost) nothing
70 CASE (atom_energy_run)
71 CALL atom_energy_opt(atom_section)
72 CASE (atom_basis_run)
73 CALL atom_basis_opt(atom_section)
74 CASE (atom_pseudo_run)
75 CALL atom_pseudo_opt(atom_section)
76 CASE default
77 cpabort("")
78 END SELECT
79
80 iw = cp_print_key_unit_nr(logger, atom_section, "PRINT%PROGRAM_BANNER", extension=".log")
81 CALL atom_footer(iw)
82 CALL cp_print_key_finished_output(iw, logger, atom_section, "PRINT%PROGRAM_BANNER")
83
84 CALL timestop(handle)
85
86 END SUBROUTINE atom_code
87
88! **************************************************************************************************
89!> \brief Check consistency between the element symbol and its atomic number.
90!> \param atom_section ATOM input section
91!> \par History
92!> * 08.2008 created [Juerg Hutter]
93! **************************************************************************************************
94 SUBROUTINE atom_test(atom_section)
95 TYPE(section_vals_type), POINTER :: atom_section
96
97 CHARACTER(len=*), PARAMETER :: routinen = 'atom_test'
98
99 CHARACTER(len=2) :: elem
100 CHARACTER(len=default_string_length) :: z_string
101 INTEGER :: handle, i, z
102 LOGICAL :: explicit_elem, explicit_z
103
104 CALL timeset(routinen, handle)
105
106 CALL section_vals_val_get(atom_section, "ATOMIC_NUMBER", i_val=z, explicit=explicit_z)
107 CALL section_vals_val_get(atom_section, "ELEMENT", c_val=elem, explicit=explicit_elem)
108
109 IF (explicit_z .AND. (z <= 0 .AND. z > nelem)) THEN
110 ! an explicit atomic number is not found in the periodic table
111 WRITE (z_string, '(I0)') z
112 CALL cp_abort(__location__, &
113 "The element with the atomic number "//trim(z_string)//" is not found in the periodic table.")
114 END IF
115
116 IF (explicit_elem) THEN
117 ! check that the element symbol is part of the periodic table
118 DO i = 1, nelem
119 IF (ptable(i)%symbol == elem) EXIT
120 END DO
121
122 IF (i > nelem) THEN
123 CALL cp_abort(__location__, &
124 "The element symbol ("//trim(elem)//") is not found in the periodic table.")
125 END IF
126 END IF
127
128 IF (explicit_z .AND. explicit_elem) THEN
129 ! check that the element symbol read from the input file
130 ! matches for the explicitly given atomic number
131 IF (ptable(z)%symbol /= elem) THEN
132 WRITE (z_string, '(I0)') z
133 CALL cp_abort(__location__, &
134 "The element symbol ("//trim(elem)// &
135 ") contradicts with the explicitly given atomic number ("// &
136 trim(z_string)//").")
137 END IF
138 ELSE IF (.NOT. (explicit_z .OR. explicit_elem)) THEN
139 ! default (implicit) element symbol and atomic number are usually consistent,
140 ! but check them just in case
141 cpassert(ptable(z)%symbol == elem)
142 END IF
143
144 CALL timestop(handle)
145 END SUBROUTINE atom_test
146
147END MODULE atom
subroutine, public atom_basis_opt(atom_section)
Optimize the atomic basis set.
Definition atom_basis.F:53
subroutine, public atom_energy_opt(atom_section)
Compute the atomic energy.
Definition atom_energy.F:81
subroutine, public atom_pseudo_opt(atom_section)
...
Definition atom_pseudo.F:65
Definition atom.F:9
subroutine, public atom_code(root_section)
Driver routine to perform atomic calculations.
Definition atom.F:46
various routines to log and control the output. The idea is that decisions about where to log should ...
type(cp_logger_type) function, pointer, public cp_get_default_logger()
returns the default logger
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer function, public cp_print_key_unit_nr(logger, basis_section, print_key_path, extension, middle_name, local, log_filename, ignore_should_output, file_form, file_position, file_action, file_status, do_backup, on_file, is_new_file, mpi_io, fout)
...
subroutine, public cp_print_key_finished_output(unit_nr, logger, basis_section, print_key_path, local, ignore_should_output, on_file, mpi_io)
should be called after you finish working with a unit obtained with cp_print_key_unit_nr,...
subroutine, public atom_header(iw)
...
Definition header.F:292
subroutine, public atom_footer(iw)
...
Definition header.F:314
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public atom_pseudo_run
integer, parameter, public atom_no_run
integer, parameter, public atom_basis_run
integer, parameter, public atom_energy_run
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public default_string_length
Definition kinds.F:57
Periodic Table related data definitions.
type(atom), dimension(0:nelem), public ptable
integer, parameter, public nelem
type of a logger, at the moment it contains just a print level starting at which level it should be l...