(git:1f285aa)
global_types.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 Define type storing the global information of a run. Keep the amount of stored data small.
10 !> Use it sparingly and try not to send it too deep in your structures.
11 !> \par History
12 !> - print keys, basis_set_file name and potential_file_name added to the
13 !> global type (27.02.2001, MK)
14 !> - added pp_library_path to type (28.11.2001, JGH)
15 !> - Merged with MODULE print_keys (17.01.2002, MK)
16 !> - reference counting, create (08.2004, fawzi)
17 !> - new (parallel) random number generator (11.03.2006, MK)
18 !> - add eps_check_diag, remove id_nr from globenv, and revise initialization (04.05.2021, MK)
19 !> \author JGH, MK, fawzi
20 ! **************************************************************************************************
22 
24  USE kinds, ONLY: default_path_length,&
26  dp
27  USE machine, ONLY: m_walltime
28  USE parallel_rng_types, ONLY: rng_stream_type
29 #include "./base/base_uses.f90"
30 
31  IMPLICIT NONE
32 
33  PRIVATE
34 
35  ! Global parameters
36 
37  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'global_types'
38 
39  INTEGER, PARAMETER :: SILENT = 0, &
40  low = 1, &
41  medium = 2, &
42  high = 3, &
43  debug = 4
44 
45  ! Public data types
46 
47  PUBLIC :: global_environment_type
48 
49  ! Public subroutines
50 
51  PUBLIC :: globenv_create, &
54 
55 ! **************************************************************************************************
56 !> \brief contains the initially parsed file and the initial parallel environment
57 !> \param ref_count reference count (see doc/ReferenceCounting.html)
58 !> \param handle handle with the total time of the computation
59 !>
60 !> Personally I think that all the other attributes should go away
61 !> (and maybe add a logger)[fawzi]
62 !> \note
63 !> This is not but really should be passed as pointer and use reference
64 !> counting. Use it accordingly wherever possible.
65 ! **************************************************************************************************
66  TYPE global_environment_type
67  INTEGER :: ref_count = 0
68  TYPE(rng_stream_type), ALLOCATABLE :: gaussian_rng_stream
69  CHARACTER(LEN=default_string_length) :: diag_library = "ScaLAPACK"
70  CHARACTER(LEN=default_string_length) :: default_fft_library = "FFTSG"
71  CHARACTER(LEN=default_path_length) :: fftw_wisdom_file_name = "/etc/fftw/wisdom"
72  CHARACTER(LEN=default_string_length) :: default_dgemm_library = "BLAS"
73 
74  INTEGER :: fft_pool_scratch_limit = 0 ! limit number of used FFT scratches
75  INTEGER :: fftw_plan_type = 0 ! which kind of planning to use with FFTW
76  INTEGER :: idum = 0 ! random number seed
77  INTEGER :: prog_name_id = 0 ! index to define the type of program
78  INTEGER :: run_type_id = 0 ! index to define the run_tupe
79  INTEGER :: blacs_grid_layout = blacs_grid_square ! will store the user preference for the BLACS grid
80  INTEGER :: k_elpa = 1 ! optimized kernel for the ELPA diagonalization library
81  INTEGER :: elpa_neigvec_min = 0 ! Minimum number of eigenvectors for ELPA usage
82  LOGICAL :: elpa_qr = .false. ! allow ELPA to use QR during diagonalization
83  LOGICAL :: elpa_print = .false. ! if additional information about ELPA diagonalization should be printed
84  LOGICAL :: elpa_qr_unsafe = .false. ! enable potentially unsafe ELPA options
85  INTEGER :: dlaf_neigvec_min = 0 ! Minimum number of eigenvectors for DLAF usage
86  LOGICAL :: blacs_repeatable = .false. ! will store the user preference for the repeatability of BLACS collectives
87  REAL(KIND=dp) :: cp2k_start_time = 0.0_dp
88  REAL(KIND=dp) :: cp2k_target_time = huge(0.0_dp) ! Maximum run time in seconds
89  ! Threshold value for the orthonormality of the eigenvectors after diagonalization
90  ! A negative threshold value disables the check which is the default
91  REAL(KIND=dp) :: eps_check_diag = -1.0_dp
92  INTEGER :: handle = 0
93  END TYPE global_environment_type
94 
95 CONTAINS
96 
97 ! **************************************************************************************************
98 !> \brief Creates the global environment globenv
99 !> \param globenv the globenv to create
100 !> \author fawzi
101 ! **************************************************************************************************
102  SUBROUTINE globenv_create(globenv)
103  TYPE(global_environment_type), POINTER :: globenv
104 
105  cpassert(.NOT. ASSOCIATED(globenv))
106  ALLOCATE (globenv)
107  ALLOCATE (globenv%gaussian_rng_stream)
108  globenv%ref_count = 1
109  globenv%cp2k_start_time = m_walltime()
110 
111  END SUBROUTINE globenv_create
112 
113 ! **************************************************************************************************
114 !> \brief Retains the global environment globenv
115 !> \param globenv the global environment to retain
116 !> \author fawzi
117 ! **************************************************************************************************
118  SUBROUTINE globenv_retain(globenv)
119  TYPE(global_environment_type), POINTER :: globenv
120 
121  cpassert(ASSOCIATED(globenv))
122  cpassert(globenv%ref_count > 0)
123  globenv%ref_count = globenv%ref_count + 1
124 
125  END SUBROUTINE globenv_retain
126 
127 ! **************************************************************************************************
128 !> \brief Releases the global environment globenv
129 !> \param globenv the global environment to release
130 !> \author fawzi
131 ! **************************************************************************************************
132  SUBROUTINE globenv_release(globenv)
133  TYPE(global_environment_type), POINTER :: globenv
134 
135  IF (ASSOCIATED(globenv)) THEN
136  cpassert(globenv%ref_count > 0)
137  globenv%ref_count = globenv%ref_count - 1
138  IF (globenv%ref_count == 0) THEN
139  IF (ALLOCATED(globenv%gaussian_rng_stream)) &
140  DEALLOCATE (globenv%gaussian_rng_stream)
141  DEALLOCATE (globenv)
142  END IF
143  END IF
144 
145  NULLIFY (globenv)
146 
147  END SUBROUTINE globenv_release
148 
149 END MODULE global_types
methods related to the blacs parallel environment
Definition: cp_blacs_env.F:15
integer, parameter, public blacs_grid_square
Definition: cp_blacs_env.F:32
Define type storing the global information of a run. Keep the amount of stored data small....
Definition: global_types.F:21
subroutine, public globenv_retain(globenv)
Retains the global environment globenv.
Definition: global_types.F:119
subroutine, public globenv_create(globenv)
Creates the global environment globenv.
Definition: global_types.F:103
subroutine, public globenv_release(globenv)
Releases the global environment globenv.
Definition: global_types.F:133
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
Machine interface based on Fortran 2003 and POSIX.
Definition: machine.F:17
real(kind=dp) function, public m_walltime()
returns time from a real-time clock, protected against rolling early/easily
Definition: machine.F:123
Parallel (pseudo)random number generator (RNG) for multiple streams and substreams of random numbers.