(git:374b731)
Loading...
Searching...
No Matches
topology_psf.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 Functionality to read in PSF topologies and convert it into local
10!> data structures
11!> \author ikuo
12!> tlaino 10.2006
13! **************************************************************************************************
30 USE input_constants, ONLY: do_conn_psf,&
36 USE kinds, ONLY: default_string_length,&
37 dp
41 USE string_table, ONLY: id2str,&
42 s2s,&
43 str2id
51 USE util, ONLY: sort
52#include "./base/base_uses.f90"
53
54 IMPLICIT NONE
55
56 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'topology_psf'
57
58 PRIVATE
59 PUBLIC :: read_topology_psf, &
63
64CONTAINS
65
66! **************************************************************************************************
67!> \brief Read PSF topology file
68!> Teodoro Laino - Introduced CHARMM31 EXT PSF standard format
69!> \param filename ...
70!> \param topology ...
71!> \param para_env ...
72!> \param subsys_section ...
73!> \param psf_type ...
74!> \par History
75!> 04-2007 Teodoro Laino - Zurich University [tlaino]
76!> This routine should contain only information read from the PSF format
77!> and all post_process should be performef in the psf_post_process
78! **************************************************************************************************
79 SUBROUTINE read_topology_psf(filename, topology, para_env, subsys_section, psf_type)
80 CHARACTER(LEN=*), INTENT(IN) :: filename
81 TYPE(topology_parameters_type), INTENT(INOUT) :: topology
82 TYPE(mp_para_env_type), POINTER :: para_env
83 TYPE(section_vals_type), POINTER :: subsys_section
84 INTEGER, INTENT(IN) :: psf_type
85
86 CHARACTER(len=*), PARAMETER :: routinen = 'read_topology_psf'
87
88 CHARACTER(LEN=2*default_string_length) :: psf_format
89 CHARACTER(LEN=3) :: c_int
90 CHARACTER(LEN=default_string_length) :: dummy_field, field, label, strtmp1, &
91 strtmp2, strtmp3
92 INTEGER :: handle, i, iatom, ibond, idum, index_now, iphi, itheta, iw, natom, natom_prev, &
93 nbond, nbond_prev, nphi, nphi_prev, ntheta, ntheta_prev, output_unit
94 LOGICAL :: found
95 TYPE(atom_info_type), POINTER :: atom_info
96 TYPE(connectivity_info_type), POINTER :: conn_info
97 TYPE(cp_logger_type), POINTER :: logger
98 TYPE(cp_parser_type) :: parser
99
100 NULLIFY (logger)
101 logger => cp_get_default_logger()
102 output_unit = cp_logger_get_default_io_unit(logger)
103 iw = cp_print_key_unit_nr(logger, subsys_section, "PRINT%TOPOLOGY_INFO/PSF_INFO", &
104 extension=".subsysLog")
105 CALL timeset(routinen, handle)
106 CALL parser_create(parser, filename, para_env=para_env)
107
108 atom_info => topology%atom_info
109 conn_info => topology%conn_info
110 natom_prev = 0
111 IF (ASSOCIATED(atom_info%id_molname)) natom_prev = SIZE(atom_info%id_molname)
112 c_int = 'I8'
113 label = 'PSF'
114 CALL parser_search_string(parser, label, .true., found, begin_line=.true.)
115 IF (.NOT. found) THEN
116 IF (output_unit > 0) THEN
117 WRITE (output_unit, '(A)') "ERROR| Missing PSF specification line"
118 END IF
119 cpabort("")
120 END IF
121 DO WHILE (parser_test_next_token(parser) /= "EOL")
122 CALL parser_get_object(parser, field)
123 SELECT CASE (field(1:3))
124 CASE ("PSF")
125 IF (psf_type == do_conn_psf) THEN
126 ! X-PLOR PSF format "similar" to the plain CHARMM PSF format
127 psf_format = '(I8,1X,A4,I5,1X,A4,1X,A4,1X,A4,1X,2G14.6,I8)'
128 END IF
129 CASE ("EXT")
130 IF (psf_type == do_conn_psf) THEN
131 ! EXTEnded CHARMM31 format
132 psf_format = '(I10,T12,A7,T21,I8,T30,A7,T39,A6,T47,A6,T53,F10.6,T69,F8.3,T88,I1)'
133 c_int = 'I10'
134 ELSE
135 cpabort("PSF_INFO| "//field(1:3)//" :: not available for UPSF format!")
136 END IF
137 CASE DEFAULT
138 cpabort("PSF_INFO| "//field(1:3)//" :: Unimplemented keyword in CP2K PSF/UPSF format!")
139 END SELECT
140 END DO
141 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| Parsing the NATOM section'
142 !
143 ! ATOM section
144 !
145 label = '!NATOM'
146 CALL parser_search_string(parser, label, .true., found, begin_line=.true.)
147 IF (.NOT. found) THEN
148 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| No NATOM section '
149 natom = 0
150 ELSE
151 CALL parser_get_object(parser, natom)
152 IF (natom_prev + natom > topology%natoms) &
153 CALL cp_abort(__location__, &
154 "Number of atoms in connectivity control is larger than the "// &
155 "number of atoms in coordinate control. check coordinates and "// &
156 "connectivity. ")
157 IF (iw > 0) WRITE (iw, '(T2,A,'//trim(c_int)//')') 'PSF_INFO| NATOM = ', natom
158 !malloc the memory that we need
159 CALL reallocate(atom_info%id_molname, 1, natom_prev + natom)
160 CALL reallocate(atom_info%resid, 1, natom_prev + natom)
161 CALL reallocate(atom_info%id_resname, 1, natom_prev + natom)
162 CALL reallocate(atom_info%id_atmname, 1, natom_prev + natom)
163 CALL reallocate(atom_info%atm_charge, 1, natom_prev + natom)
164 CALL reallocate(atom_info%atm_mass, 1, natom_prev + natom)
165 !Read in the atom info
166 IF (psf_type == do_conn_psf_u) THEN
167 DO iatom = 1, natom
168 index_now = iatom + natom_prev
169 CALL parser_get_next_line(parser, 1)
170 READ (parser%input_line, fmt=*, err=9) i, &
171 strtmp1, &
172 atom_info%resid(index_now), &
173 strtmp2, &
174 dummy_field, &
175 strtmp3, &
176 atom_info%atm_charge(index_now), &
177 atom_info%atm_mass(index_now)
178 atom_info%id_molname(index_now) = str2id(s2s(strtmp1))
179 atom_info%id_resname(index_now) = str2id(s2s(strtmp2))
180 atom_info%id_atmname(index_now) = str2id(s2s(strtmp3))
181 END DO
182 ELSE
183 DO iatom = 1, natom
184 index_now = iatom + natom_prev
185 CALL parser_get_next_line(parser, 1)
186 READ (parser%input_line, fmt=psf_format) &
187 i, &
188 strtmp1, &
189 atom_info%resid(index_now), &
190 strtmp2, &
191 dummy_field, &
192 strtmp3, &
193 atom_info%atm_charge(index_now), &
194 atom_info%atm_mass(index_now), &
195 idum
196 atom_info%id_molname(index_now) = str2id(s2s(strtmp1))
197 atom_info%id_resname(index_now) = str2id(s2s(strtmp2))
198 atom_info%id_atmname(index_now) = str2id(s2s(adjustl(strtmp3)))
199 END DO
200 END IF
201 END IF
202
203 !
204 ! BOND section
205 !
206 nbond_prev = 0
207 IF (ASSOCIATED(conn_info%bond_a)) nbond_prev = SIZE(conn_info%bond_a)
208
209 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| Parsing the NBOND section'
210 IF (iw > 0) WRITE (iw, '(T2,A,I8)') 'PSF_INFO| Previous number of allocated BOND: ', nbond_prev
211 label = '!NBOND'
212 CALL parser_search_string(parser, label, .true., found, begin_line=.true.)
213 IF (.NOT. found) THEN
214 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| No NBOND section '
215 nbond = 0
216 ELSE
217 CALL parser_get_object(parser, nbond)
218 IF (iw > 0) WRITE (iw, '(T2,A,'//trim(c_int)//')') 'PSF_INFO| NBOND = ', nbond
219 !malloc the memory that we need
220 CALL reallocate(conn_info%bond_a, 1, nbond_prev + nbond)
221 CALL reallocate(conn_info%bond_b, 1, nbond_prev + nbond)
222 !Read in the bond info
223 IF (psf_type == do_conn_psf_u) THEN
224 DO ibond = 1, nbond, 4
225 CALL parser_get_next_line(parser, 1)
226 index_now = nbond_prev + ibond - 1
227 READ (parser%input_line, fmt=*, err=9) (conn_info%bond_a(index_now + i), &
228 conn_info%bond_b(index_now + i), &
229 i=1, min(4, (nbond - ibond + 1)))
230 END DO
231 ELSE
232 DO ibond = 1, nbond, 4
233 CALL parser_get_next_line(parser, 1)
234 index_now = nbond_prev + ibond - 1
235 READ (parser%input_line, fmt='(8'//trim(c_int)//')') &
236 (conn_info%bond_a(index_now + i), &
237 conn_info%bond_b(index_now + i), &
238 i=1, min(4, (nbond - ibond + 1)))
239 END DO
240 END IF
241 IF (any(conn_info%bond_a(nbond_prev + 1:) <= 0) .OR. &
242 any(conn_info%bond_a(nbond_prev + 1:) > natom) .OR. &
243 any(conn_info%bond_b(nbond_prev + 1:) <= 0) .OR. &
244 any(conn_info%bond_b(nbond_prev + 1:) > natom)) THEN
245 cpabort("topology_read, invalid bond")
246 END IF
247 conn_info%bond_a(nbond_prev + 1:) = conn_info%bond_a(nbond_prev + 1:) + natom_prev
248 conn_info%bond_b(nbond_prev + 1:) = conn_info%bond_b(nbond_prev + 1:) + natom_prev
249 END IF
250 !
251 ! THETA section
252 !
253 ntheta_prev = 0
254 IF (ASSOCIATED(conn_info%theta_a)) ntheta_prev = SIZE(conn_info%theta_a)
255
256 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| Parsing the NTHETA section'
257 IF (iw > 0) WRITE (iw, '(T2,A,I8)') 'PSF_INFO| Previous number of allocated THETA: ', ntheta_prev
258 label = '!NTHETA'
259 CALL parser_search_string(parser, label, .true., found, begin_line=.true.)
260 IF (.NOT. found) THEN
261 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| No NTHETA section '
262 ntheta = 0
263 ELSE
264 CALL parser_get_object(parser, ntheta)
265 IF (iw > 0) WRITE (iw, '(T2,A,'//trim(c_int)//')') 'PSF_INFO| NTHETA = ', ntheta
266 !malloc the memory that we need
267 CALL reallocate(conn_info%theta_a, 1, ntheta_prev + ntheta)
268 CALL reallocate(conn_info%theta_b, 1, ntheta_prev + ntheta)
269 CALL reallocate(conn_info%theta_c, 1, ntheta_prev + ntheta)
270 !Read in the bend info
271 IF (psf_type == do_conn_psf_u) THEN
272 DO itheta = 1, ntheta, 3
273 CALL parser_get_next_line(parser, 1)
274 index_now = ntheta_prev + itheta - 1
275 READ (parser%input_line, fmt=*, err=9) (conn_info%theta_a(index_now + i), &
276 conn_info%theta_b(index_now + i), &
277 conn_info%theta_c(index_now + i), &
278 i=1, min(3, (ntheta - itheta + 1)))
279 END DO
280 ELSE
281 DO itheta = 1, ntheta, 3
282 CALL parser_get_next_line(parser, 1)
283 index_now = ntheta_prev + itheta - 1
284 READ (parser%input_line, fmt='(9'//trim(c_int)//')') &
285 (conn_info%theta_a(index_now + i), &
286 conn_info%theta_b(index_now + i), &
287 conn_info%theta_c(index_now + i), &
288 i=1, min(3, (ntheta - itheta + 1)))
289 END DO
290 END IF
291 conn_info%theta_a(ntheta_prev + 1:) = conn_info%theta_a(ntheta_prev + 1:) + natom_prev
292 conn_info%theta_b(ntheta_prev + 1:) = conn_info%theta_b(ntheta_prev + 1:) + natom_prev
293 conn_info%theta_c(ntheta_prev + 1:) = conn_info%theta_c(ntheta_prev + 1:) + natom_prev
294 END IF
295 !
296 ! PHI section
297 !
298 nphi_prev = 0
299 IF (ASSOCIATED(conn_info%phi_a)) nphi_prev = SIZE(conn_info%phi_a)
300
301 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| Parsing the NPHI section'
302 IF (iw > 0) WRITE (iw, '(T2,A,I8)') 'PSF_INFO| Previous number of allocated PHI: ', nphi_prev
303 label = '!NPHI'
304 CALL parser_search_string(parser, label, .true., found, begin_line=.true.)
305 IF (.NOT. found) THEN
306 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| No NPHI section '
307 nphi = 0
308 ELSE
309 CALL parser_get_object(parser, nphi)
310 IF (iw > 0) WRITE (iw, '(T2,A,'//trim(c_int)//')') 'PSF_INFO| NPHI = ', nphi
311 !malloc the memory that we need
312 CALL reallocate(conn_info%phi_a, 1, nphi_prev + nphi)
313 CALL reallocate(conn_info%phi_b, 1, nphi_prev + nphi)
314 CALL reallocate(conn_info%phi_c, 1, nphi_prev + nphi)
315 CALL reallocate(conn_info%phi_d, 1, nphi_prev + nphi)
316 !Read in the torsion info
317 IF (psf_type == do_conn_psf_u) THEN
318 DO iphi = 1, nphi, 2
319 CALL parser_get_next_line(parser, 1)
320 index_now = nphi_prev + iphi - 1
321 READ (parser%input_line, fmt=*, err=9) (conn_info%phi_a(index_now + i), &
322 conn_info%phi_b(index_now + i), &
323 conn_info%phi_c(index_now + i), &
324 conn_info%phi_d(index_now + i), &
325 i=1, min(2, (nphi - iphi + 1)))
326 END DO
327 ELSE
328 DO iphi = 1, nphi, 2
329 CALL parser_get_next_line(parser, 1)
330 index_now = nphi_prev + iphi - 1
331 READ (parser%input_line, fmt='(8'//trim(c_int)//')') &
332 (conn_info%phi_a(index_now + i), &
333 conn_info%phi_b(index_now + i), &
334 conn_info%phi_c(index_now + i), &
335 conn_info%phi_d(index_now + i), &
336 i=1, min(2, (nphi - iphi + 1)))
337 END DO
338 END IF
339 conn_info%phi_a(nphi_prev + 1:) = conn_info%phi_a(nphi_prev + 1:) + natom_prev
340 conn_info%phi_b(nphi_prev + 1:) = conn_info%phi_b(nphi_prev + 1:) + natom_prev
341 conn_info%phi_c(nphi_prev + 1:) = conn_info%phi_c(nphi_prev + 1:) + natom_prev
342 conn_info%phi_d(nphi_prev + 1:) = conn_info%phi_d(nphi_prev + 1:) + natom_prev
343 END IF
344 !
345 ! IMPHI section
346 !
347 nphi_prev = 0
348 IF (ASSOCIATED(conn_info%impr_a)) nphi_prev = SIZE(conn_info%impr_a)
349
350 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| Parsing the NIMPHI section'
351 IF (iw > 0) WRITE (iw, '(T2,A,I8)') 'PSF_INFO| Previous number of allocated IMPHI: ', nphi_prev
352 label = '!NIMPHI'
353 CALL parser_search_string(parser, label, .true., found, begin_line=.true.)
354 IF (.NOT. found) THEN
355 IF (iw > 0) WRITE (iw, '(T2,A)') 'PSF_INFO| No NIMPHI section '
356 nphi = 0
357 ELSE
358 CALL parser_get_object(parser, nphi)
359 IF (iw > 0) WRITE (iw, '(T2,A,'//trim(c_int)//')') 'PSF_INFO| NIMPR = ', nphi
360 !malloc the memory that we need
361 CALL reallocate(conn_info%impr_a, 1, nphi_prev + nphi)
362 CALL reallocate(conn_info%impr_b, 1, nphi_prev + nphi)
363 CALL reallocate(conn_info%impr_c, 1, nphi_prev + nphi)
364 CALL reallocate(conn_info%impr_d, 1, nphi_prev + nphi)
365 !Read in the improper torsion info
366 IF (psf_type == do_conn_psf_u) THEN
367 DO iphi = 1, nphi, 2
368 CALL parser_get_next_line(parser, 1)
369 index_now = nphi_prev + iphi - 1
370 READ (parser%input_line, fmt=*, err=9) (conn_info%impr_a(index_now + i), &
371 conn_info%impr_b(index_now + i), &
372 conn_info%impr_c(index_now + i), &
373 conn_info%impr_d(index_now + i), &
374 i=1, min(2, (nphi - iphi + 1)))
375 END DO
376 ELSE
377 DO iphi = 1, nphi, 2
378 CALL parser_get_next_line(parser, 1)
379 index_now = nphi_prev + iphi - 1
380 READ (parser%input_line, fmt='(8'//trim(c_int)//')') &
381 (conn_info%impr_a(index_now + i), &
382 conn_info%impr_b(index_now + i), &
383 conn_info%impr_c(index_now + i), &
384 conn_info%impr_d(index_now + i), &
385 i=1, min(2, (nphi - iphi + 1)))
386 END DO
387 END IF
388 conn_info%impr_a(nphi_prev + 1:) = conn_info%impr_a(nphi_prev + 1:) + natom_prev
389 conn_info%impr_b(nphi_prev + 1:) = conn_info%impr_b(nphi_prev + 1:) + natom_prev
390 conn_info%impr_c(nphi_prev + 1:) = conn_info%impr_c(nphi_prev + 1:) + natom_prev
391 conn_info%impr_d(nphi_prev + 1:) = conn_info%impr_d(nphi_prev + 1:) + natom_prev
392 END IF
393
394 CALL parser_release(parser)
395 CALL timestop(handle)
396 CALL cp_print_key_finished_output(iw, logger, subsys_section, &
397 "PRINT%TOPOLOGY_INFO/PSF_INFO")
398 RETURN
3999 CONTINUE
400 ! Print error and exit
401 IF (output_unit > 0) THEN
402 WRITE (output_unit, '(T2,A)') &
403 "PSF_INFO| Error while reading PSF using the unformatted PSF reading option!", &
404 "PSF_INFO| Try using PSF instead of UPSF."
405 END IF
406
407 cpabort("Error while reading PSF data!")
408
409 END SUBROUTINE read_topology_psf
410
411! **************************************************************************************************
412!> \brief Post processing of PSF informations
413!> \param topology ...
414!> \param subsys_section ...
415! **************************************************************************************************
416 SUBROUTINE psf_post_process(topology, subsys_section)
417 TYPE(topology_parameters_type), INTENT(INOUT) :: topology
418 TYPE(section_vals_type), POINTER :: subsys_section
419
420 CHARACTER(len=*), PARAMETER :: routinen = 'psf_post_process'
421
422 INTEGER :: handle, i, iatom, ibond, ionfo, iw, &
423 jatom, n, natom, nbond, nonfo, nphi, &
424 ntheta
425 TYPE(array1_list_type), DIMENSION(:), POINTER :: ex_bend_list, ex_bond_list
426 TYPE(atom_info_type), POINTER :: atom_info
427 TYPE(connectivity_info_type), POINTER :: conn_info
428 TYPE(cp_logger_type), POINTER :: logger
429
430 NULLIFY (logger)
431 logger => cp_get_default_logger()
432 iw = cp_print_key_unit_nr(logger, subsys_section, "PRINT%TOPOLOGY_INFO/PSF_INFO", &
433 extension=".subsysLog")
434 CALL timeset(routinen, handle)
435 atom_info => topology%atom_info
436 conn_info => topology%conn_info
437 !
438 ! PARA_RES structure
439 !
440 natom = 0
441 nbond = 0
442 i = 0
443 IF (ASSOCIATED(atom_info%id_molname)) natom = SIZE(atom_info%id_molname)
444 IF (ASSOCIATED(conn_info%bond_a)) nbond = SIZE(conn_info%bond_a)
445 IF (ASSOCIATED(conn_info%c_bond_a)) i = SIZE(conn_info%c_bond_a)
446 DO ibond = 1, nbond
447 iatom = conn_info%bond_a(ibond)
448 jatom = conn_info%bond_b(ibond)
449 IF (topology%para_res) THEN
450 IF ((atom_info%id_molname(iatom) /= atom_info%id_molname(jatom)) .OR. &
451 (atom_info%resid(iatom) /= atom_info%resid(jatom)) .OR. &
452 (atom_info%id_resname(iatom) /= atom_info%id_resname(jatom))) THEN
453 IF (iw > 0) WRITE (iw, '(T2,A,2I6)') "PSF_INFO| PARA_RES, bond between molecules atom ", &
454 iatom, jatom
455 i = i + 1
456 CALL reallocate(conn_info%c_bond_a, 1, i)
457 CALL reallocate(conn_info%c_bond_b, 1, i)
458 conn_info%c_bond_a(i) = iatom
459 conn_info%c_bond_b(i) = jatom
460 END IF
461 ELSE
462 IF (atom_info%id_molname(iatom) /= atom_info%id_molname(jatom)) THEN
463 cpabort("")
464 END IF
465 END IF
466 END DO
467 !
468 ! UB structure
469 !
470 ntheta = 0
471 IF (ASSOCIATED(conn_info%theta_a)) ntheta = SIZE(conn_info%theta_a)
472 CALL reallocate(conn_info%ub_a, 1, ntheta)
473 CALL reallocate(conn_info%ub_b, 1, ntheta)
474 CALL reallocate(conn_info%ub_c, 1, ntheta)
475 conn_info%ub_a(:) = conn_info%theta_a(:)
476 conn_info%ub_b(:) = conn_info%theta_b(:)
477 conn_info%ub_c(:) = conn_info%theta_c(:)
478 !
479 ! ONFO structure
480 !
481 nphi = 0
482 nonfo = 0
483 IF (ASSOCIATED(conn_info%phi_a)) nphi = SIZE(conn_info%phi_a)
484 CALL reallocate(conn_info%onfo_a, 1, nphi)
485 CALL reallocate(conn_info%onfo_b, 1, nphi)
486 conn_info%onfo_a(1:) = conn_info%phi_a(1:)
487 conn_info%onfo_b(1:) = conn_info%phi_d(1:)
488 ! Reorder bonds
489 ALLOCATE (ex_bond_list(natom))
490 DO i = 1, natom
491 ALLOCATE (ex_bond_list(i)%array1(0))
492 END DO
493 n = 0
494 IF (ASSOCIATED(conn_info%bond_a)) n = SIZE(conn_info%bond_a)
495 CALL reorder_structure(ex_bond_list, conn_info%bond_a, conn_info%bond_b, n)
496 ! Reorder bends
497 ALLOCATE (ex_bend_list(natom))
498 DO i = 1, natom
499 ALLOCATE (ex_bend_list(i)%array1(0))
500 END DO
501 n = 0
502 IF (ASSOCIATED(conn_info%theta_a)) n = SIZE(conn_info%theta_a)
503 CALL reorder_structure(ex_bend_list, conn_info%theta_a, conn_info%theta_c, n)
504 DO ionfo = 1, nphi
505 ! Check if the torsion is not shared between angles or bonds
506 IF (any(ex_bond_list(conn_info%onfo_a(ionfo))%array1 == conn_info%onfo_b(ionfo)) .OR. &
507 any(ex_bend_list(conn_info%onfo_a(ionfo))%array1 == conn_info%onfo_b(ionfo))) cycle
508 nonfo = nonfo + 1
509 conn_info%onfo_a(nonfo) = conn_info%onfo_a(ionfo)
510 conn_info%onfo_b(nonfo) = conn_info%onfo_b(ionfo)
511 END DO
512 ! deallocate bends
513 DO i = 1, natom
514 DEALLOCATE (ex_bend_list(i)%array1)
515 END DO
516 DEALLOCATE (ex_bend_list)
517 ! deallocate bonds
518 DO i = 1, natom
519 DEALLOCATE (ex_bond_list(i)%array1)
520 END DO
521 DEALLOCATE (ex_bond_list)
522 ! Get unique onfo
523 ALLOCATE (ex_bond_list(natom))
524 DO i = 1, natom
525 ALLOCATE (ex_bond_list(i)%array1(0))
526 END DO
527 n = 0
528 IF (ASSOCIATED(conn_info%onfo_a)) n = nonfo
529 CALL reorder_structure(ex_bond_list, conn_info%onfo_a, conn_info%onfo_b, n)
530 nonfo = 0
531 DO i = 1, natom
532 DO ionfo = 1, SIZE(ex_bond_list(i)%array1)
533 IF (count(ex_bond_list(i)%array1 == ex_bond_list(i)%array1(ionfo)) /= 1) THEN
534 ex_bond_list(i)%array1(ionfo) = 0
535 ELSE
536 IF (ex_bond_list(i)%array1(ionfo) <= i) cycle
537 nonfo = nonfo + 1
538 conn_info%onfo_a(nonfo) = i
539 conn_info%onfo_b(nonfo) = ex_bond_list(i)%array1(ionfo)
540 END IF
541 END DO
542 END DO
543 DO i = 1, natom
544 DEALLOCATE (ex_bond_list(i)%array1)
545 END DO
546 DEALLOCATE (ex_bond_list)
547 CALL reallocate(conn_info%onfo_a, 1, nonfo)
548 CALL reallocate(conn_info%onfo_b, 1, nonfo)
549
550 CALL timestop(handle)
551 CALL cp_print_key_finished_output(iw, logger, subsys_section, &
552 "PRINT%TOPOLOGY_INFO/PSF_INFO")
553 END SUBROUTINE psf_post_process
554
555! **************************************************************************************************
556!> \brief Input driven modification (IDM) of PSF defined structures
557!> \param topology ...
558!> \param section ...
559!> \param subsys_section ...
560!> \author Teodoro Laino - Zurich University 04.2007
561! **************************************************************************************************
562 SUBROUTINE idm_psf(topology, section, subsys_section)
563 TYPE(topology_parameters_type), INTENT(INOUT) :: topology
564 TYPE(section_vals_type), POINTER :: section, subsys_section
565
566 CHARACTER(len=*), PARAMETER :: routinen = 'idm_psf'
567
568 INTEGER :: handle, i, iend, iend1, istart, istart1, &
569 item, iw, j, mol_id, n_rep, natom, &
570 nbond, nimpr, noe, nphi, ntheta
571 INTEGER, DIMENSION(:), POINTER :: tag_mols, tmp, wrk
572 LOGICAL :: explicit
573 TYPE(array1_list_type), DIMENSION(:), POINTER :: ex_bond_list
574 TYPE(atom_info_type), POINTER :: atom_info
575 TYPE(connectivity_info_type), POINTER :: conn_info
576 TYPE(cp_logger_type), POINTER :: logger
577 TYPE(section_vals_type), POINTER :: subsection
578
579 NULLIFY (logger)
580 logger => cp_get_default_logger()
581 iw = cp_print_key_unit_nr(logger, subsys_section, "PRINT%TOPOLOGY_INFO/PSF_INFO", &
582 extension=".subsysLog")
583 CALL timeset(routinen, handle)
584 CALL section_vals_get(section, explicit=explicit)
585 IF (explicit) THEN
586 atom_info => topology%atom_info
587 conn_info => topology%conn_info
588 natom = 0
589 IF (ASSOCIATED(atom_info%id_molname)) natom = SIZE(atom_info%id_molname)
590 nbond = 0
591 IF (ASSOCIATED(conn_info%bond_a)) nbond = SIZE(conn_info%bond_a)
592 ntheta = 0
593 IF (ASSOCIATED(conn_info%theta_a)) ntheta = SIZE(conn_info%theta_a)
594 nphi = 0
595 IF (ASSOCIATED(conn_info%phi_a)) nphi = SIZE(conn_info%phi_a)
596 nimpr = 0
597 IF (ASSOCIATED(conn_info%impr_a)) nimpr = SIZE(conn_info%impr_a)
598 ! Any new defined bond
599 subsection => section_vals_get_subs_vals(section, "BONDS")
600 CALL section_vals_get(subsection, explicit=explicit)
601 IF (explicit) THEN
602 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", n_rep_val=n_rep)
603 CALL reallocate(conn_info%bond_a, 1, n_rep + nbond)
604 CALL reallocate(conn_info%bond_b, 1, n_rep + nbond)
605 DO i = 1, n_rep
606 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", i_rep_val=i, i_vals=tmp)
607 conn_info%bond_a(nbond + i) = tmp(1)
608 conn_info%bond_b(nbond + i) = tmp(2)
609 END DO
610 ! And now modify the molecule name if two molecules have been bridged
611 ALLOCATE (ex_bond_list(natom))
612 ALLOCATE (tag_mols(natom))
613 ALLOCATE (wrk(natom))
614 DO j = 1, natom
615 ALLOCATE (ex_bond_list(j)%array1(0))
616 END DO
617 CALL reorder_structure(ex_bond_list, conn_info%bond_a, conn_info%bond_b, nbond + n_rep)
618 ! Loop over atoms to possiblyt change molecule name
619 tag_mols = -1
620 mol_id = 1
621 DO i = 1, natom
622 IF (tag_mols(i) /= -1) cycle
623 CALL tag_molecule(tag_mols, ex_bond_list, i, mol_id)
624 mol_id = mol_id + 1
625 END DO
626 mol_id = mol_id - 1
627 IF (iw > 0) WRITE (iw, '(T2,A,I8)') 'PSF_INFO| Number of molecules detected after merging: ', mol_id
628 ! Now simply check about the contiguousness of molecule definition
629 CALL sort(tag_mols, natom, wrk)
630 item = tag_mols(1)
631 istart = 1
632 DO i = 2, natom
633 IF (tag_mols(i) == item) cycle
634 iend = i - 1
635 noe = iend - istart + 1
636 istart1 = minval(wrk(istart:iend))
637 iend1 = maxval(wrk(istart:iend))
638 cpassert(iend1 - istart1 + 1 == noe)
639 atom_info%id_molname(istart1:iend1) = str2id(s2s("MOL"//cp_to_string(item)))
640 item = tag_mols(i)
641 istart = i
642 END DO
643 iend = i - 1
644 noe = iend - istart + 1
645 istart1 = minval(wrk(istart:iend))
646 iend1 = maxval(wrk(istart:iend))
647 cpassert(iend1 - istart1 + 1 == noe)
648 atom_info%id_molname(istart1:iend1) = str2id(s2s("MOL"//cp_to_string(item)))
649 ! Deallocate bonds
650 DO i = 1, natom
651 DEALLOCATE (ex_bond_list(i)%array1)
652 END DO
653 DEALLOCATE (ex_bond_list)
654 DEALLOCATE (tag_mols)
655 DEALLOCATE (wrk)
656 END IF
657 ! Any new defined angle
658 subsection => section_vals_get_subs_vals(section, "ANGLES")
659 CALL section_vals_get(subsection, explicit=explicit)
660 IF (explicit) THEN
661 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", n_rep_val=n_rep)
662 CALL reallocate(conn_info%theta_a, 1, n_rep + ntheta)
663 CALL reallocate(conn_info%theta_b, 1, n_rep + ntheta)
664 CALL reallocate(conn_info%theta_c, 1, n_rep + ntheta)
665 DO i = 1, n_rep
666 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", i_rep_val=i, i_vals=tmp)
667 conn_info%theta_a(ntheta + i) = tmp(1)
668 conn_info%theta_b(ntheta + i) = tmp(2)
669 conn_info%theta_c(ntheta + i) = tmp(3)
670 END DO
671 END IF
672 ! Any new defined torsion
673 subsection => section_vals_get_subs_vals(section, "TORSIONS")
674 CALL section_vals_get(subsection, explicit=explicit)
675 IF (explicit) THEN
676 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", n_rep_val=n_rep)
677 CALL reallocate(conn_info%phi_a, 1, n_rep + nphi)
678 CALL reallocate(conn_info%phi_b, 1, n_rep + nphi)
679 CALL reallocate(conn_info%phi_c, 1, n_rep + nphi)
680 CALL reallocate(conn_info%phi_d, 1, n_rep + nphi)
681 DO i = 1, n_rep
682 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", i_rep_val=i, i_vals=tmp)
683 conn_info%phi_a(nphi + i) = tmp(1)
684 conn_info%phi_b(nphi + i) = tmp(2)
685 conn_info%phi_c(nphi + i) = tmp(3)
686 conn_info%phi_d(nphi + i) = tmp(4)
687 END DO
688 END IF
689 ! Any new defined improper
690 subsection => section_vals_get_subs_vals(section, "IMPROPERS")
691 CALL section_vals_get(subsection, explicit=explicit)
692 IF (explicit) THEN
693 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", n_rep_val=n_rep)
694 CALL reallocate(conn_info%impr_a, 1, n_rep + nimpr)
695 CALL reallocate(conn_info%impr_b, 1, n_rep + nimpr)
696 CALL reallocate(conn_info%impr_c, 1, n_rep + nimpr)
697 CALL reallocate(conn_info%impr_d, 1, n_rep + nimpr)
698 DO i = 1, n_rep
699 CALL section_vals_val_get(subsection, "_DEFAULT_KEYWORD_", i_rep_val=i, i_vals=tmp)
700 conn_info%impr_a(nimpr + i) = tmp(1)
701 conn_info%impr_b(nimpr + i) = tmp(2)
702 conn_info%impr_c(nimpr + i) = tmp(3)
703 conn_info%impr_d(nimpr + i) = tmp(4)
704 END DO
705 END IF
706 END IF
707 CALL timestop(handle)
708 CALL cp_print_key_finished_output(iw, logger, subsys_section, &
709 "PRINT%TOPOLOGY_INFO/PSF_INFO")
710
711 END SUBROUTINE idm_psf
712
713! **************************************************************************************************
714!> \brief Teodoro Laino - 01.2006
715!> Write PSF topology file in the CHARMM31 EXT standard format
716!> \param file_unit ...
717!> \param topology ...
718!> \param subsys_section ...
719!> \param force_env_section ...
720! **************************************************************************************************
721 SUBROUTINE write_topology_psf(file_unit, topology, subsys_section, force_env_section)
722 INTEGER, INTENT(IN) :: file_unit
723 TYPE(topology_parameters_type), INTENT(INOUT) :: topology
724 TYPE(section_vals_type), POINTER :: subsys_section, force_env_section
725
726 CHARACTER(len=*), PARAMETER :: routinen = 'write_topology_psf'
727
728 CHARACTER(LEN=2*default_string_length) :: psf_format
729 CHARACTER(LEN=default_string_length) :: c_int, my_tag1, my_tag2, my_tag3, record
730 CHARACTER(LEN=default_string_length), &
731 DIMENSION(:), POINTER :: charge_atm
732 INTEGER :: handle, i, iw, j, my_index, nchg
733 LOGICAL :: explicit, ldum
734 REAL(kind=dp), DIMENSION(:), POINTER :: charge_inp, charges
735 TYPE(atom_info_type), POINTER :: atom_info
736 TYPE(connectivity_info_type), POINTER :: conn_info
737 TYPE(cp_logger_type), POINTER :: logger
738 TYPE(section_vals_type), POINTER :: print_key, tmp_section
739
740 NULLIFY (logger)
741 logger => cp_get_default_logger()
742 print_key => section_vals_get_subs_vals(subsys_section, "TOPOLOGY%DUMP_PSF")
743 iw = cp_print_key_unit_nr(logger, subsys_section, "PRINT%TOPOLOGY_INFO/PSF_INFO", &
744 extension=".subsysLog")
745 CALL timeset(routinen, handle)
746
747 atom_info => topology%atom_info
748 conn_info => topology%conn_info
749
750 ! Check for charges.. (need to dump them in the PSF..)
751 ALLOCATE (charges(topology%natoms))
752 charges = atom_info%atm_charge
753 ! Collect charges from Input file..
754 NULLIFY (tmp_section)
755 tmp_section => section_vals_get_subs_vals(force_env_section, "MM%FORCEFIELD%CHARGE")
756 CALL section_vals_get(tmp_section, explicit=explicit, n_repetition=nchg)
757 IF (explicit) THEN
758 ALLOCATE (charge_atm(nchg))
759 ALLOCATE (charge_inp(nchg))
760 CALL read_chrg_section(charge_atm, charge_inp, section=tmp_section, start=0)
761 DO j = 1, topology%natoms
762 record = id2str(atom_info%id_atmname(j))
763 ldum = qmmm_ff_precond_only_qm(record)
764 CALL uppercase(record)
765 DO i = 1, nchg
766 IF (record == charge_atm(i)) THEN
767 charges(j) = charge_inp(i)
768 EXIT
769 END IF
770 END DO
771 END DO
772 DEALLOCATE (charge_atm)
773 DEALLOCATE (charge_inp)
774 END IF
775 ! fixup for topology output
776 DO j = 1, topology%natoms
777 IF (charges(j) .EQ. -huge(0.0_dp)) charges(j) = -99.0_dp
778 END DO
779 record = cp_print_key_generate_filename(logger, print_key, &
780 extension=".psf", my_local=.false.)
781 ! build the EXT format
782 c_int = "I10"
783 psf_format = '(I10,T12,A,T21,I0,T30,A,T39,A,T47,A,T53,F10.6,T69,F8.3,T88,I1)'
784 IF (iw > 0) WRITE (iw, '(T2,A)') &
785 "PSF_WRITE| Writing out PSF file with CHARMM31 EXTErnal format: ", trim(record)
786
787 WRITE (file_unit, fmt='(A)') "PSF EXT"
788 WRITE (file_unit, fmt='(A)') ""
789 WRITE (file_unit, fmt='('//trim(c_int)//',A)') 1, " !NTITLE"
790 WRITE (file_unit, fmt='(A)') " CP2K generated DUMP of connectivity"
791 WRITE (file_unit, fmt='(A)') ""
792
793 WRITE (file_unit, fmt='('//trim(c_int)//',A)') topology%natoms, " !NATOM"
794 my_index = 1
795 i = 1
796 my_tag1 = id2str(atom_info%id_molname(i))
797 my_tag2 = id2str(atom_info%id_resname(i))
798 my_tag3 = id2str(atom_info%id_atmname(i))
799 ldum = qmmm_ff_precond_only_qm(my_tag1)
800 ldum = qmmm_ff_precond_only_qm(my_tag2)
801 ldum = qmmm_ff_precond_only_qm(my_tag3)
802 WRITE (file_unit, fmt=psf_format) &
803 i, &
804 trim(my_tag1), &
805 my_index, &
806 trim(my_tag2), &
807 trim(my_tag3), &
808 trim(my_tag3), &
809 charges(i), &
810 atom_info%atm_mass(i), &
811 0
812 DO i = 2, topology%natoms
813 IF ((atom_info%map_mol_num(i) /= atom_info%map_mol_num(i - 1)) .OR. &
814 (atom_info%map_mol_res(i) /= atom_info%map_mol_res(i - 1))) my_index = my_index + 1
815 my_tag1 = id2str(atom_info%id_molname(i))
816 my_tag2 = id2str(atom_info%id_resname(i))
817 my_tag3 = id2str(atom_info%id_atmname(i))
818 ldum = qmmm_ff_precond_only_qm(my_tag1)
819 ldum = qmmm_ff_precond_only_qm(my_tag2)
820 ldum = qmmm_ff_precond_only_qm(my_tag3)
821 WRITE (file_unit, fmt=psf_format) &
822 i, &
823 trim(my_tag1), &
824 my_index, &
825 trim(my_tag2), &
826 trim(my_tag3), &
827 trim(my_tag3), &
828 charges(i), &
829 atom_info%atm_mass(i), &
830 0
831 END DO
832 WRITE (file_unit, fmt='(/)')
833 DEALLOCATE (charges)
834
835 WRITE (file_unit, fmt='('//trim(c_int)//',A)') SIZE(conn_info%bond_a), " !NBOND"
836 DO i = 1, SIZE(conn_info%bond_a), 4
837 j = 0
838 DO WHILE ((j < 4) .AND. ((i + j) <= SIZE(conn_info%bond_a)))
839 WRITE (file_unit, fmt='(2('//trim(c_int)//'))', advance="NO") &
840 conn_info%bond_a(i + j), conn_info%bond_b(i + j)
841 j = j + 1
842 END DO
843 WRITE (file_unit, fmt='(/)', advance="NO")
844 END DO
845 WRITE (file_unit, fmt='(/)')
846
847 WRITE (file_unit, fmt='('//trim(c_int)//',A)') SIZE(conn_info%theta_a), " !NTHETA"
848 DO i = 1, SIZE(conn_info%theta_a), 3
849 j = 0
850 DO WHILE ((j < 3) .AND. ((i + j) <= SIZE(conn_info%theta_a)))
851 WRITE (file_unit, fmt='(3('//trim(c_int)//'))', advance="NO") &
852 conn_info%theta_a(i + j), conn_info%theta_b(i + j), &
853 conn_info%theta_c(i + j)
854 j = j + 1
855 END DO
856 WRITE (file_unit, fmt='(/)', advance="NO")
857 END DO
858 WRITE (file_unit, fmt='(/)')
859
860 WRITE (file_unit, fmt='('//trim(c_int)//',A)') SIZE(conn_info%phi_a), " !NPHI"
861 DO i = 1, SIZE(conn_info%phi_a), 2
862 j = 0
863 DO WHILE ((j < 2) .AND. ((i + j) <= SIZE(conn_info%phi_a)))
864 WRITE (file_unit, fmt='(4('//trim(c_int)//'))', advance="NO") &
865 conn_info%phi_a(i + j), conn_info%phi_b(i + j), &
866 conn_info%phi_c(i + j), conn_info%phi_d(i + j)
867 j = j + 1
868 END DO
869 WRITE (file_unit, fmt='(/)', advance="NO")
870 END DO
871 WRITE (file_unit, fmt='(/)')
872
873 WRITE (file_unit, fmt='('//trim(c_int)//',A)') SIZE(conn_info%impr_a), " !NIMPHI"
874 DO i = 1, SIZE(conn_info%impr_a), 2
875 j = 0
876 DO WHILE ((j < 2) .AND. ((i + j) <= SIZE(conn_info%impr_a)))
877 WRITE (file_unit, fmt='(4('//trim(c_int)//'))', advance="NO") &
878 conn_info%impr_a(i + j), conn_info%impr_b(i + j), &
879 conn_info%impr_c(i + j), conn_info%impr_d(i + j)
880 j = j + 1
881 END DO
882 WRITE (file_unit, fmt='(/)', advance="NO")
883 END DO
884 WRITE (file_unit, fmt='(/)')
885
886 WRITE (file_unit, fmt='('//trim(c_int)//',A)') 0, " !NDON"
887 WRITE (file_unit, fmt='(/)')
888 WRITE (file_unit, fmt='('//trim(c_int)//',A)') 0, " !NACC"
889 WRITE (file_unit, fmt='(/)')
890 WRITE (file_unit, fmt='('//trim(c_int)//',A)') 0, " !NNB"
891 WRITE (file_unit, fmt='(/)')
892
893 CALL cp_print_key_finished_output(iw, logger, subsys_section, &
894 "PRINT%TOPOLOGY_INFO/PSF_INFO")
895 CALL timestop(handle)
896
897 END SUBROUTINE write_topology_psf
898
899END MODULE topology_psf
900
various routines to log and control the output. The idea is that decisions about where to log should ...
integer function, public cp_logger_get_default_io_unit(logger)
returns the unit nr for the ionode (-1 on all other processors) skips as well checks if the procs cal...
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)
...
character(len=default_path_length) function, public cp_print_key_generate_filename(logger, print_key, middle_name, extension, my_local)
Utility function that returns a unit number to write the print key. Might open a file with a unique f...
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,...
Utility routines to read data from files. Kept as close as possible to the old parser because.
subroutine, public parser_get_next_line(parser, nline, at_end)
Read the next input line and broadcast the input information. Skip (nline-1) lines and skip also all ...
character(len=3) function, public parser_test_next_token(parser, string_length)
Test next input object.
subroutine, public parser_search_string(parser, string, ignore_case, found, line, begin_line, search_from_begin_of_file)
Search a string pattern in a file defined by its logical unit number "unit". A case sensitive search ...
Utility routines to read data from files. Kept as close as possible to the old parser because.
subroutine, public parser_release(parser)
releases the parser
subroutine, public parser_create(parser, file_name, unit_nr, para_env, end_section_label, separator_chars, comment_char, continuation_char, quote_char, section_char, parse_white_lines, initial_variables, apply_preprocessing)
Start a parser run. Initial variables allow to @SET stuff before opening the file.
subroutine, public read_chrg_section(charge_atm, charge, section, start)
Reads the CHARGE section.
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_conn_psf_u
integer, parameter, public do_conn_psf
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
integer, parameter, public default_string_length
Definition kinds.F:57
Utility routines for the memory handling.
Interface to the message passing library MPI.
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 ...
generates a unique id number for a string (str2id) that can be used two compare two strings....
character(len=default_string_length) function, public s2s(str)
converts a string in a string of default_string_length
integer function, public str2id(str)
returns a unique id for a given string, and stores the string for later retrieval using the id.
character(len=default_string_length) function, public id2str(id)
returns the string associated with a given id
Utilities for string manipulations.
elemental subroutine, public uppercase(string)
Convert all lower case characters in a string to upper case.
Functionality to read in PSF topologies and convert it into local data structures.
subroutine, public read_topology_psf(filename, topology, para_env, subsys_section, psf_type)
Read PSF topology file Teodoro Laino - Introduced CHARMM31 EXT PSF standard format.
subroutine, public idm_psf(topology, section, subsys_section)
Input driven modification (IDM) of PSF defined structures.
subroutine, public write_topology_psf(file_unit, topology, subsys_section, force_env_section)
Teodoro Laino - 01.2006 Write PSF topology file in the CHARMM31 EXT standard format.
subroutine, public psf_post_process(topology, subsys_section)
Post processing of PSF informations.
Collection of subroutine needed for topology related things.
recursive subroutine, public tag_molecule(icheck, bond_list, i, my_mol)
gives back a mapping of molecules.. icheck needs to be initialized with -1
Control for reading in different topologies and coordinates.
Definition topology.F:13
All kind of helpful little routines.
Definition util.F:14
type of a logger, at the moment it contains just a print level starting at which level it should be l...
stores all the informations relevant to an mpi environment