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