74 CHARACTER(len=*),
PARAMETER :: routinen =
'read_force_field_gromos'
75 REAL(kind=
dp),
PARAMETER :: ekt = 2.5_dp
77 CHARACTER(LEN=default_string_length) :: label
78 CHARACTER(LEN=default_string_length), &
79 DIMENSION(21) :: avail_section
80 CHARACTER(LEN=default_string_length),
POINTER :: namearray(:)
81 INTEGER :: handle, iatom, icon, itemp, itype, iw, &
82 jatom, ncon, ntype, offset
84 REAL(kind=
dp) :: cosphi0, cost2, csq, sdet
89 CALL timeset(routinen, handle)
95 avail_section(1) =
"TITLE"
96 avail_section(2) =
"TOPPHYSCON"
97 avail_section(3) =
"TOPVERSION"
98 avail_section(4) =
"ATOMTYPENAME"
99 avail_section(5) =
"RESNAME"
100 avail_section(6) =
"SOLUTEATOM"
101 avail_section(7) =
"BONDTYPE"
102 avail_section(8) =
"BONDH"
103 avail_section(9) =
"BOND"
104 avail_section(10) =
"BONDANGLETYPE"
105 avail_section(11) =
"BONDANGLEH"
106 avail_section(12) =
"BONDANGLE"
107 avail_section(13) =
"IMPDIHEDRALTYPE"
108 avail_section(14) =
"IMPDIHEDRALH"
109 avail_section(15) =
"IMPDIHEDRAL"
110 avail_section(16) =
"DIHEDRALTYPE"
111 avail_section(17) =
"DIHEDRALH"
112 avail_section(18) =
"DIHEDRAL"
113 avail_section(19) =
"LJPARAMETERS"
114 avail_section(20) =
"SOLVENTATOM"
115 avail_section(21) =
"SOLVENTCONSTR"
117 gro_info => ff_type%gro_info
118 gro_info%ff_gromos_type = ff_type%ff_type
121 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the ATOMTYPENAME section'
122 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
123 label = trim(avail_section(4))
132 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| ", trim(namearray(itype))
138 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GROMOS_FF| Parsing the SOLVENTATOM section'
139 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
141 label = trim(avail_section(21))
153 gro_info%solvent_k(icon) = 0.0_dp
158 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
160 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GROMOS_FF| Parsing the BONDTYPE section'
161 label = trim(avail_section(7))
173 gro_info%bond_k(itype) =
cp_unit_to_cp2k(gro_info%bond_k(itype),
"kjmol*nm^-4")
175 gro_info%bond_k(itype) = (2.0_dp)*gro_info%bond_k(itype)*gro_info%bond_r0(itype)**2
176 gro_info%bond_k(itype) =
cp_unit_to_cp2k(gro_info%bond_k(itype),
"kjmol*nm^-2")
178 gro_info%bond_r0(itype) =
cp_unit_to_cp2k(gro_info%bond_r0(itype),
"nm")
179 IF (iw > 0)
WRITE (iw, *)
"GROMOS_FF| PUT BONDTYPE INFO HERE!"
184 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GROMOS_FF| Parsing the BONDANGLETYPE section'
185 label = trim(avail_section(10))
191 CALL reallocate(gro_info%bend_theta0, 1, ntype)
196 gro_info%bend_theta0(itype) =
cp_unit_to_cp2k(gro_info%bend_theta0(itype),
"deg")
198 gro_info%bend_theta0(itype) = cos(gro_info%bend_theta0(itype))
200 cost2 = cos(gro_info%bend_theta0(itype))*cos(gro_info%bend_theta0(itype))
201 sdet = cost2*cost2 - (2.0_dp*cost2 - 1.0_dp)*(1.0_dp - ekt/gro_info%bend_k(itype))
202 csq = (cost2 - sqrt(sdet))/(2.0_dp*cost2 - 1.0_dp)
203 gro_info%bend_k(itype) = ekt/acos(csq)**2
205 gro_info%bend_k(itype) =
cp_unit_to_cp2k(gro_info%bend_k(itype),
"kjmol")
206 IF (iw > 0)
WRITE (iw, *)
"GROMOS_FF| PUT BONDANGLETYPE INFO HERE!"
211 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GROMOS_FF| Parsing the IMPDIHEDRALTYPE section'
212 label = trim(avail_section(13))
223 gro_info%impr_phi0(itype) =
cp_unit_to_cp2k(gro_info%impr_phi0(itype),
"deg")
224 gro_info%impr_k(itype) =
cp_unit_to_cp2k(gro_info%impr_k(itype),
"kjmol*deg^-2")
225 IF (iw > 0)
WRITE (iw, *)
"GROMOS_FF| PUT IMPDIHEDRALTYPE INFO HERE!"
230 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GROMOS_FF| Parsing the DIHEDRALTYPE section'
231 label = trim(avail_section(16))
238 CALL reallocate(gro_info%torsion_phi0, 1, ntype)
244 gro_info%torsion_phi0(itype) = acos(cosphi0)
245 gro_info%torsion_k(itype) =
cp_unit_to_cp2k(gro_info%torsion_k(itype),
"kjmol")
246 IF (iw > 0)
WRITE (iw, *)
"GROMOS_FF| PUT DIHEDRALTYPE INFO HERE!"
253 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GROMOS_FF| Parsing the LJPARAMETERS section'
254 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
255 label = trim(avail_section(19))
261 IF (
ASSOCIATED(gro_info%nonbond_a)) offset =
SIZE(gro_info%nonbond_a)
262 ntype =
SIZE(namearray)
264 CALL reallocate(gro_info%nonbond_a_14, 1, ntype)
265 CALL reallocate(gro_info%nonbond_c6, 1, ntype, 1, ntype)
266 CALL reallocate(gro_info%nonbond_c12, 1, ntype, 1, ntype)
267 CALL reallocate(gro_info%nonbond_c6_14, 1, ntype, 1, ntype)
268 CALL reallocate(gro_info%nonbond_c12_14, 1, ntype, 1, ntype)
270 gro_info%nonbond_c12 = 0._dp
271 gro_info%nonbond_c6 = 0._dp
272 gro_info%nonbond_c12_14 = 0._dp
273 gro_info%nonbond_c6_14 = 0._dp
275 DO itype = 1, ntype*(ntype + 1)/2
279 IF (iatom == jatom)
THEN
280 gro_info%nonbond_a(iatom) = namearray(iatom)
281 gro_info%nonbond_a_14(iatom) = namearray(iatom)
287 gro_info%nonbond_c6(iatom, jatom) =
cp_unit_to_cp2k(gro_info%nonbond_c6(iatom, jatom),
"kjmol*nm^6")
288 gro_info%nonbond_c12(iatom, jatom) =
cp_unit_to_cp2k(gro_info%nonbond_c12(iatom, jatom),
"kjmol*nm^12")
289 gro_info%nonbond_c6_14(iatom, jatom) =
cp_unit_to_cp2k(gro_info%nonbond_c6_14(iatom, jatom),
"kjmol*nm^6")
290 gro_info%nonbond_c12_14(iatom, jatom) =
cp_unit_to_cp2k(gro_info%nonbond_c12_14(iatom, jatom),
"kjmol*nm^12")
292 gro_info%nonbond_c6_14(jatom, iatom) = gro_info%nonbond_c6_14(iatom, jatom)
293 gro_info%nonbond_c12_14(jatom, iatom) = gro_info%nonbond_c12_14(iatom, jatom)
294 gro_info%nonbond_c6(jatom, iatom) = gro_info%nonbond_c6(iatom, jatom)
295 gro_info%nonbond_c12(jatom, iatom) = gro_info%nonbond_c12(iatom, jatom)
296 IF (iw > 0)
WRITE (iw, *)
"GROMOS_FF| PUT LJPARAMETERS INFO HERE!"
303 CALL timestop(handle)
305 DEALLOCATE (namearray)
321 CHARACTER(len=*),
PARAMETER :: routinen =
'read_force_field_charmm'
323 CHARACTER(LEN=default_string_length) :: label, string, string2, string3, string4
324 CHARACTER(LEN=default_string_length),
DIMENSION(1) :: bond_section
325 CHARACTER(LEN=default_string_length),
DIMENSION(2) :: angl_section, impr_section, &
326 nbon_section, thet_section
327 CHARACTER(LEN=default_string_length), &
328 DIMENSION(20) :: avail_section
329 INTEGER :: dummy, handle, ilab, iw, nbend, nbond, &
330 nimpr, nnonbond, nonfo, ntorsion, nub
336 CALL timeset(routinen, handle)
342 avail_section(1) =
"BOND"; bond_section(1) = avail_section(1)
343 avail_section(11) =
"BONDS"
344 avail_section(2) =
"ANGL"; angl_section(1) = avail_section(2)
345 avail_section(3) =
"THETA"; angl_section(2) = avail_section(3)
346 avail_section(12) =
"THETAS"
347 avail_section(13) =
"ANGLE"
348 avail_section(14) =
"ANGLES"
349 avail_section(4) =
"DIHEDRAL"; thet_section(1) = avail_section(4)
350 avail_section(15) =
"DIHEDRALS"
351 avail_section(5) =
"PHI"; thet_section(2) = avail_section(5)
352 avail_section(6) =
"IMPROPER"; impr_section(1) = avail_section(6)
353 avail_section(20) =
"IMPROPERS"
354 avail_section(7) =
"IMPH"; impr_section(2) = avail_section(7)
355 avail_section(16) =
"IMPHI"
356 avail_section(8) =
"NONBONDED"; nbon_section(1) = avail_section(8)
357 avail_section(9) =
"NBOND"; nbon_section(2) = avail_section(9)
358 avail_section(10) =
"HBOND"
359 avail_section(17) =
"NBFIX"
360 avail_section(18) =
"CMAP"
361 avail_section(19) =
"END"
363 chm_info => ff_type%chm_info
371 DO ilab = 1,
SIZE(bond_section)
372 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
373 label = trim(bond_section(ilab))
378 IF (index(string, trim(label)) /= 1) cycle
379 CALL charmm_get_next_line(parser, 1)
383 IF (any(string == avail_section))
EXIT
391 chm_info%bond_a(nbond) = string
392 chm_info%bond_b(nbond) = string2
395 IF (iw > 0)
WRITE (iw, *)
" CHM BOND ", nbond, &
396 trim(chm_info%bond_a(nbond)),
" ", &
397 trim(chm_info%bond_b(nbond)),
" ", &
398 chm_info%bond_k(nbond), &
399 chm_info%bond_r0(nbond)
401 chm_info%bond_r0(nbond) =
cp_unit_to_cp2k(chm_info%bond_r0(nbond),
"angstrom")
402 chm_info%bond_k(nbond) =
cp_unit_to_cp2k(chm_info%bond_k(nbond),
"kcalmol*angstrom^-2")
403 CALL charmm_get_next_line(parser, 1)
422 DO ilab = 1,
SIZE(angl_section)
423 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
424 label = trim(angl_section(ilab))
429 IF (index(string, trim(label)) /= 1) cycle
430 CALL charmm_get_next_line(parser, 1)
434 IF (any(string == avail_section))
EXIT
444 CALL reallocate(chm_info%bend_theta0, 1, nbend)
445 chm_info%bend_a(nbend) = string
446 chm_info%bend_b(nbend) = string2
447 chm_info%bend_c(nbend) = string3
450 IF (iw > 0)
WRITE (iw, *)
" CHM BEND ", nbend, &
451 trim(chm_info%bend_a(nbend)),
" ", &
452 trim(chm_info%bend_b(nbend)),
" ", &
453 trim(chm_info%bend_c(nbend)),
" ", &
454 chm_info%bend_k(nbend), &
455 chm_info%bend_theta0(nbend)
457 chm_info%bend_theta0(nbend) =
cp_unit_to_cp2k(chm_info%bend_theta0(nbend),
"deg")
458 chm_info%bend_k(nbend) =
cp_unit_to_cp2k(chm_info%bend_k(nbend),
"kcalmol*rad^-2")
466 chm_info%ub_a(nub) = string
467 chm_info%ub_b(nub) = string2
468 chm_info%ub_c(nub) = string3
471 IF (iw > 0)
WRITE (iw, *)
" CHM UB ", nub, &
472 trim(chm_info%ub_a(nub)),
" ", &
473 trim(chm_info%ub_b(nub)),
" ", &
474 trim(chm_info%ub_c(nub)),
" ", &
475 chm_info%ub_k(nub), &
479 chm_info%ub_k(nub) =
cp_unit_to_cp2k(chm_info%ub_k(nub),
"kcalmol*angstrom^-2")
481 CALL charmm_get_next_line(parser, 1)
496 DO ilab = 1,
SIZE(thet_section)
497 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
498 label = trim(thet_section(ilab))
503 IF (index(string, trim(label)) /= 1) cycle
504 CALL charmm_get_next_line(parser, 1)
508 IF (any(string == avail_section))
EXIT
515 ntorsion = ntorsion + 1
516 CALL reallocate(chm_info%torsion_a, 1, ntorsion)
517 CALL reallocate(chm_info%torsion_b, 1, ntorsion)
518 CALL reallocate(chm_info%torsion_c, 1, ntorsion)
519 CALL reallocate(chm_info%torsion_d, 1, ntorsion)
520 CALL reallocate(chm_info%torsion_k, 1, ntorsion)
521 CALL reallocate(chm_info%torsion_m, 1, ntorsion)
522 CALL reallocate(chm_info%torsion_phi0, 1, ntorsion)
523 chm_info%torsion_a(ntorsion) = string
524 chm_info%torsion_b(ntorsion) = string2
525 chm_info%torsion_c(ntorsion) = string3
526 chm_info%torsion_d(ntorsion) = string4
530 IF (iw > 0)
WRITE (iw, *)
" CHM TORSION ", ntorsion, &
531 trim(chm_info%torsion_a(ntorsion)),
" ", &
532 trim(chm_info%torsion_b(ntorsion)),
" ", &
533 trim(chm_info%torsion_c(ntorsion)),
" ", &
534 trim(chm_info%torsion_d(ntorsion)),
" ", &
535 chm_info%torsion_k(ntorsion), &
536 chm_info%torsion_m(ntorsion), &
537 chm_info%torsion_phi0(ntorsion)
539 chm_info%torsion_phi0(ntorsion) =
cp_unit_to_cp2k(chm_info%torsion_phi0(ntorsion), &
541 chm_info%torsion_k(ntorsion) =
cp_unit_to_cp2k(chm_info%torsion_k(ntorsion),
"kcalmol")
542 CALL charmm_get_next_line(parser, 1)
557 DO ilab = 1,
SIZE(impr_section)
558 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
559 label = trim(impr_section(ilab))
564 IF (index(string, trim(label)) /= 1) cycle
565 CALL charmm_get_next_line(parser, 1)
569 IF (any(string == avail_section))
EXIT
583 chm_info%impr_a(nimpr) = string
584 chm_info%impr_b(nimpr) = string2
585 chm_info%impr_c(nimpr) = string3
586 chm_info%impr_d(nimpr) = string4
590 IF (iw > 0)
WRITE (iw, *)
" CHM IMPROPERS ", nimpr, &
591 trim(chm_info%impr_a(nimpr)),
" ", &
592 trim(chm_info%impr_b(nimpr)),
" ", &
593 trim(chm_info%impr_c(nimpr)),
" ", &
594 trim(chm_info%impr_d(nimpr)),
" ", &
595 chm_info%impr_k(nimpr), &
596 chm_info%impr_phi0(nimpr)
598 chm_info%impr_phi0(nimpr) =
cp_unit_to_cp2k(chm_info%impr_phi0(nimpr),
"deg")
599 chm_info%impr_k(nimpr) =
cp_unit_to_cp2k(chm_info%impr_k(nimpr),
"kcalmol")
600 CALL charmm_get_next_line(parser, 1)
614 DO ilab = 1,
SIZE(nbon_section)
615 CALL parser_create(parser, ff_type%ff_file_name, para_env=para_env)
616 label = trim(nbon_section(ilab))
621 IF (index(string, trim(label)) /= 1) cycle
622 CALL charmm_get_next_line(parser, 1)
626 IF (any(string == avail_section))
EXIT
627 nnonbond = nnonbond + 1
628 CALL reallocate(chm_info%nonbond_a, 1, nnonbond)
629 CALL reallocate(chm_info%nonbond_eps, 1, nnonbond)
630 CALL reallocate(chm_info%nonbond_rmin2, 1, nnonbond)
631 chm_info%nonbond_a(nnonbond) = string
635 IF (iw > 0)
WRITE (iw, *)
" CHM NONBOND ", nnonbond, &
636 trim(chm_info%nonbond_a(nnonbond)),
" ", &
637 chm_info%nonbond_eps(nnonbond), &
638 chm_info%nonbond_rmin2(nnonbond)
639 chm_info%nonbond_rmin2(nnonbond) =
cp_unit_to_cp2k(chm_info%nonbond_rmin2(nnonbond), &
641 chm_info%nonbond_eps(nnonbond) =
cp_unit_to_cp2k(chm_info%nonbond_eps(nnonbond), &
645 CALL reallocate(chm_info%nonbond_a_14, 1, nonfo)
646 CALL reallocate(chm_info%nonbond_eps_14, 1, nonfo)
647 CALL reallocate(chm_info%nonbond_rmin2_14, 1, nonfo)
648 chm_info%nonbond_a_14(nonfo) = chm_info%nonbond_a(nnonbond)
652 IF (iw > 0)
WRITE (iw, *)
" CHM ONFO ", nonfo, &
653 trim(chm_info%nonbond_a_14(nonfo)),
" ", &
654 chm_info%nonbond_eps_14(nonfo), &
655 chm_info%nonbond_rmin2_14(nonfo)
656 chm_info%nonbond_rmin2_14(nonfo) =
cp_unit_to_cp2k(chm_info%nonbond_rmin2_14(nonfo), &
658 chm_info%nonbond_eps_14(nonfo) =
cp_unit_to_cp2k(chm_info%nonbond_eps_14(nonfo), &
661 CALL charmm_get_next_line(parser, 1)
671 CALL timestop(handle)