Line data Source code
1 : !--------------------------------------------------------------------------------------------------!
2 : ! CP2K: A general program to perform molecular dynamics simulations !
3 : ! Copyright 2000-2025 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 : ! **************************************************************************************************
21 : MODULE global_types
22 :
23 : USE cp_blacs_env, ONLY: BLACS_GRID_SQUARE
24 : USE kinds, ONLY: default_path_length,&
25 : default_string_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, &
52 : globenv_retain, &
53 : globenv_release
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) :: cholesky_library = "ScaLAPACK"
71 : CHARACTER(LEN=default_string_length) :: default_fft_library = "FFTSG"
72 : CHARACTER(LEN=default_path_length) :: fftw_wisdom_file_name = "/etc/fftw/wisdom"
73 : CHARACTER(LEN=default_string_length) :: default_dgemm_library = "BLAS"
74 :
75 : INTEGER :: fft_pool_scratch_limit = 0 ! limit number of used FFT scratches
76 : INTEGER :: fftw_plan_type = 0 ! which kind of planning to use with FFTW
77 : INTEGER :: idum = 0 ! random number seed
78 : INTEGER :: prog_name_id = 0 ! index to define the type of program
79 : INTEGER :: run_type_id = 0 ! index to define the run_tupe
80 : INTEGER :: blacs_grid_layout = BLACS_GRID_SQUARE ! will store the user preference for the BLACS grid
81 : INTEGER :: k_elpa = 1 ! optimized kernel for the ELPA diagonalization library
82 : INTEGER :: elpa_neigvec_min = 0 ! Minimum number of eigenvectors for ELPA usage
83 : LOGICAL :: elpa_qr = .FALSE. ! allow ELPA to use QR during diagonalization
84 : LOGICAL :: elpa_print = .FALSE. ! if additional information about ELPA diagonalization should be printed
85 : LOGICAL :: elpa_qr_unsafe = .FALSE. ! enable potentially unsafe ELPA options
86 : INTEGER :: dlaf_neigvec_min = 0 ! Minimum number of eigenvectors for DLAF eigensolver usage
87 : INTEGER :: dlaf_cholesky_n_min = 0 ! Minimum matrix size for DLAF Cholesky decomposition usage
88 : LOGICAL :: blacs_repeatable = .FALSE. ! will store the user preference for the repeatability of BLACS collectives
89 : REAL(KIND=dp) :: cp2k_start_time = 0.0_dp
90 : REAL(KIND=dp) :: cp2k_target_time = HUGE(0.0_dp) ! Maximum run time in seconds
91 : ! Threshold value for the orthonormality of the eigenvectors after diagonalization
92 : ! A negative threshold value disables the check which is the default
93 : REAL(KIND=dp) :: eps_check_diag = -1.0_dp
94 : INTEGER :: handle = 0
95 : END TYPE global_environment_type
96 :
97 : CONTAINS
98 :
99 : ! **************************************************************************************************
100 : !> \brief Creates the global environment globenv
101 : !> \param globenv the globenv to create
102 : !> \author fawzi
103 : ! **************************************************************************************************
104 9881 : SUBROUTINE globenv_create(globenv)
105 : TYPE(global_environment_type), POINTER :: globenv
106 :
107 9881 : CPASSERT(.NOT. ASSOCIATED(globenv))
108 9881 : ALLOCATE (globenv)
109 266787 : ALLOCATE (globenv%gaussian_rng_stream)
110 9881 : globenv%ref_count = 1
111 9881 : globenv%cp2k_start_time = m_walltime()
112 :
113 9881 : END SUBROUTINE globenv_create
114 :
115 : ! **************************************************************************************************
116 : !> \brief Retains the global environment globenv
117 : !> \param globenv the global environment to retain
118 : !> \author fawzi
119 : ! **************************************************************************************************
120 9673 : SUBROUTINE globenv_retain(globenv)
121 : TYPE(global_environment_type), POINTER :: globenv
122 :
123 9673 : CPASSERT(ASSOCIATED(globenv))
124 9673 : CPASSERT(globenv%ref_count > 0)
125 9673 : globenv%ref_count = globenv%ref_count + 1
126 :
127 9673 : END SUBROUTINE globenv_retain
128 :
129 : ! **************************************************************************************************
130 : !> \brief Releases the global environment globenv
131 : !> \param globenv the global environment to release
132 : !> \author fawzi
133 : ! **************************************************************************************************
134 28913 : SUBROUTINE globenv_release(globenv)
135 : TYPE(global_environment_type), POINTER :: globenv
136 :
137 28913 : IF (ASSOCIATED(globenv)) THEN
138 19554 : CPASSERT(globenv%ref_count > 0)
139 19554 : globenv%ref_count = globenv%ref_count - 1
140 19554 : IF (globenv%ref_count == 0) THEN
141 9881 : IF (ALLOCATED(globenv%gaussian_rng_stream)) &
142 9881 : DEALLOCATE (globenv%gaussian_rng_stream)
143 9881 : DEALLOCATE (globenv)
144 : END IF
145 : END IF
146 :
147 28913 : NULLIFY (globenv)
148 :
149 28913 : END SUBROUTINE globenv_release
150 :
151 0 : END MODULE global_types
|