(git:ccc2433)
qmmm_ff_fist.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 !> \author teo
10 ! **************************************************************************************************
12 
13  USE kinds, ONLY: default_string_length
14 #include "./base/base_uses.f90"
15 
16  IMPLICIT NONE
17  PRIVATE
18  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qmmm_ff_fist'
19 
20  PUBLIC :: qmmm_ff_precond_only_qm
21 
22 CONTAINS
23 
24 ! **************************************************************************************************
25 !> \brief This function handles the atom names and modifies
26 !> the "_QM_" prefix, in order to find the parameters
27 !> and return .TRUE. if all input labels belong to QM atoms
28 !> \param id1 ...
29 !> \param id2 ...
30 !> \param id3 ...
31 !> \param id4 ...
32 !> \param is_link ...
33 !> \return ...
34 !> \par History
35 !> 11.2004 created [tlaino]
36 !> \author Teodoro Laino
37 ! **************************************************************************************************
38  FUNCTION qmmm_ff_precond_only_qm(id1, id2, id3, id4, is_link) RESULT(only_qm)
39  CHARACTER(LEN=default_string_length), &
40  INTENT(INOUT) :: id1
41  CHARACTER(LEN=default_string_length), &
42  INTENT(INOUT), OPTIONAL :: id2, id3, id4
43  LOGICAL, INTENT(OUT), OPTIONAL :: is_link
44  LOGICAL :: only_qm
45 
46  CHARACTER(LEN=default_string_length) :: tmp
47  INTEGER :: j, my_index
48  LOGICAL :: my_link
49 
50  only_qm = .false.
51  my_link = .false.
52  DO WHILE (index(id1, "_QM_") /= 0)
53  my_link = qmmm_ff_precond_only_link(id1) .OR. my_link
54  my_index = index(id1, "_QM_") + len_trim("_QM_")
55  only_qm = .true.
56  tmp = trim(id1(my_index:))
57  clean_string_1: DO j = 1, default_string_length
58  id1(j:j) = " "
59  END DO clean_string_1
60  id1 = trim(tmp)
61  END DO
62 
63  IF (PRESENT(id2)) THEN
64  IF (index(id2, "_QM_") == 0) only_qm = .false.
65  DO WHILE (index(id2, "_QM_") /= 0)
66  my_link = qmmm_ff_precond_only_link(id2) .OR. my_link
67  my_index = index(id2, "_QM_") + len_trim("_QM_")
68  tmp = trim(id2(my_index:))
69  clean_string_2: DO j = 1, default_string_length
70  id2(j:j) = " "
71  END DO clean_string_2
72  id2 = trim(tmp)
73  END DO
74  END IF
75 
76  IF (PRESENT(id3)) THEN
77  IF (index(id3, "_QM_") == 0) only_qm = .false.
78  DO WHILE (index(id3, "_QM_") /= 0)
79  my_link = qmmm_ff_precond_only_link(id3) .OR. my_link
80  my_index = index(id3, "_QM_") + len_trim("_QM_")
81  tmp = trim(id3(my_index:))
82  clean_string_3: DO j = 1, default_string_length
83  id3(j:j) = " "
84  END DO clean_string_3
85  id3 = trim(tmp)
86  END DO
87  END IF
88 
89  IF (PRESENT(id4)) THEN
90  IF (index(id4, "_QM_") == 0) only_qm = .false.
91  DO WHILE (index(id4, "_QM_") /= 0)
92  my_link = qmmm_ff_precond_only_link(id4) .OR. my_link
93  my_index = index(id4, "_QM_") + len_trim("_QM_")
94  tmp = trim(id4(my_index:))
95  clean_string_4: DO j = 1, default_string_length
96  id4(j:j) = " "
97  END DO clean_string_4
98  id4 = trim(tmp)
99  END DO
100  END IF
101 
102  IF (PRESENT(is_link)) is_link = my_link
103 
104  END FUNCTION qmmm_ff_precond_only_qm
105 
106 ! **************************************************************************************************
107 !> \brief ...
108 !> \param id1 ...
109 !> \return ...
110 ! **************************************************************************************************
111  FUNCTION qmmm_ff_precond_only_link(id1) RESULT(is_link)
112  CHARACTER(LEN=default_string_length), &
113  INTENT(INOUT) :: id1
114  LOGICAL :: is_link
115 
116  CHARACTER(LEN=default_string_length) :: tmp
117  INTEGER :: j, my_index
118 
119  is_link = .false.
120  DO WHILE (index(id1, "_LNK") /= 0)
121  my_index = index(id1, "_LNK") + 1
122  my_index = index(id1(my_index:), "_QM_") + my_index - 1
123  is_link = .true.
124  tmp = trim(id1(my_index:))
125  clean_string_1: DO j = 1, default_string_length
126  id1(j:j) = " "
127  END DO clean_string_1
128  id1 = trim(tmp)
129  END DO
130 
131  END FUNCTION qmmm_ff_precond_only_link
132 
133 END MODULE qmmm_ff_fist
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public default_string_length
Definition: kinds.F:57
logical function, public qmmm_ff_precond_only_qm(id1, id2, id3, id4, is_link)
This function handles the atom names and modifies the "_QM_" prefix, in order to find the parameters ...
Definition: qmmm_ff_fist.F:39