(git:e7e05ae)
fist_efield_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 !> \par History
10 !> \author JGH
11 ! **************************************************************************************************
15  section_vals_type,&
17  USE kinds, ONLY: dp
18 #include "./base/base_uses.f90"
19 
20  IMPLICIT NONE
21 
22  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'fist_efield_types'
23 
24 ! **************************************************************************************************
26  LOGICAL :: apply_field = .false.
27  LOGICAL :: displacement = .false.
28  REAL(kind=dp) :: strength
29  REAL(kind=dp), DIMENSION(3) :: polarisation
30  REAL(kind=dp), DIMENSION(3) :: dfilter
31  END TYPE fist_efield_type
32 ! **************************************************************************************************
33 
34  PRIVATE
35 
36  PUBLIC :: fist_efield_type
37  PUBLIC :: read_efield_section
38 
39 ! **************************************************************************************************
40 
41 CONTAINS
42 
43 ! **************************************************************************************************
44 !> \brief Read input section PERIODIC_EFIELD
45 !> \param input_section ...
46 !> \param efield ...
47 !> \par History
48 !> \author JGH
49 ! **************************************************************************************************
50  SUBROUTINE read_efield_section(input_section, efield)
51  TYPE(section_vals_type), POINTER :: input_section
52  TYPE(fist_efield_type), POINTER :: efield
53 
54  REAL(kind=dp), DIMENSION(:), POINTER :: pp
55  TYPE(section_vals_type), POINTER :: tmp_section
56 
57  IF (.NOT. ASSOCIATED(efield)) ALLOCATE (efield)
58 
59  ! Read the finite field input section for periodic fields
60  tmp_section => section_vals_get_subs_vals(input_section, "PERIODIC_EFIELD")
61  CALL section_vals_get(tmp_section, explicit=efield%apply_field)
62  IF (efield%apply_field) THEN
63  CALL section_vals_val_get(tmp_section, "POLARISATION", r_vals=pp)
64  efield%polarisation(1:3) = pp(1:3)
65  CALL section_vals_val_get(tmp_section, "D_FILTER", r_vals=pp)
66  efield%dfilter(1:3) = pp(1:3)
67  CALL section_vals_val_get(tmp_section, "INTENSITY", r_val=efield%strength)
68  CALL section_vals_val_get(tmp_section, "DISPLACEMENT_FIELD", l_val=efield%displacement)
69  END IF
70 
71  END SUBROUTINE read_efield_section
72 
73 ! **************************************************************************************************
74 
75 END MODULE fist_efield_types
subroutine, public read_efield_section(input_section, efield)
Read input section PERIODIC_EFIELD.
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_get(section_vals, ref_count, n_repetition, n_subs_vals_rep, section, explicit)
returns various attributes about the section_vals
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 dp
Definition: kinds.F:34