53 CHARACTER(LEN=*),
INTENT(IN) :: file_name
58 CHARACTER(len=*),
PARAMETER :: routinen =
'read_topology_gromos'
61 CHARACTER(LEN=default_string_length) :: label, string
62 CHARACTER(LEN=default_string_length), &
63 DIMENSION(21) :: avail_section
64 CHARACTER(LEN=default_string_length),
POINTER :: namearray1(:), namearray2(:)
65 INTEGER :: begin, handle, i, iatom, ibond, icon, ii(50), index_now, iresid, isolvent, itemp, &
66 itype, iw, jatom, natom, natom_prev, nbond, nbond_prev, ncon, nsolute, nsolvent, ntype, &
68 INTEGER,
POINTER :: ba(:), bb(:), na(:)
70 REAL(kind=
dp) :: ftemp
71 REAL(kind=
dp),
POINTER :: ac(:), am(:)
78 NULLIFY (namearray1, namearray2)
81 extension=
".subsysLog")
82 CALL timeset(routinen, handle)
84 avail_section(1) =
"TITLE"
85 avail_section(2) =
"TOPPHYSCON"
86 avail_section(3) =
"TOPVERSION"
87 avail_section(4) =
"ATOMTYPENAME"
88 avail_section(5) =
"RESNAME"
89 avail_section(6) =
"SOLUTEATOM"
90 avail_section(7) =
"BONDTYPE"
91 avail_section(8) =
"BONDH"
92 avail_section(9) =
"BOND"
93 avail_section(10) =
"BONDANGLETYPE"
94 avail_section(11) =
"BONDANGLEH"
95 avail_section(12) =
"BONDANGLE"
96 avail_section(13) =
"IMPDIHEDRALTYPE"
97 avail_section(14) =
"IMPDIHEDRALH"
98 avail_section(15) =
"IMPDIHEDRAL"
99 avail_section(16) =
"DIHEDRALTYPE"
100 avail_section(17) =
"DIHEDRALH"
101 avail_section(18) =
"DIHEDRAL"
102 avail_section(19) =
"LJPARAMETERS"
103 avail_section(20) =
"SOLVENTATOM"
104 avail_section(21) =
"SOLVENTCONSTR"
110 IF (
ASSOCIATED(atom_info%id_molname)) natom_prev =
SIZE(atom_info%id_molname)
112 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the TITLE section'
114 label = trim(avail_section(1))
120 IF (string == trim(
"END"))
EXIT
121 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| ", trim(string)
126 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the TOPPHYSCON section'
128 label = trim(avail_section(2))
134 IF (string == trim(
"END"))
EXIT
135 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| ", trim(string)
140 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the TOPVERSION section'
142 label = trim(avail_section(3))
148 IF (string == trim(
"END"))
EXIT
149 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| ", trim(string)
154 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the ATOMTYPENAME section'
156 label = trim(avail_section(4))
165 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| ", trim(namearray1(itype))
170 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the RESNAME section'
172 label = trim(avail_section(5))
181 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| ", trim(namearray2(itype))
187 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the SOLUTEATOM section'
189 label = trim(avail_section(6))
194 CALL reallocate(atom_info%id_molname, 1, natom_prev + natom)
195 CALL reallocate(atom_info%resid, 1, natom_prev + natom)
196 CALL reallocate(atom_info%id_resname, 1, natom_prev + natom)
197 CALL reallocate(atom_info%id_atmname, 1, natom_prev + natom)
198 CALL reallocate(atom_info%id_element, 1, natom_prev + natom)
199 CALL reallocate(atom_info%atm_charge, 1, natom_prev + natom)
200 CALL reallocate(atom_info%atm_mass, 1, natom_prev + natom)
203 index_now = iatom + natom_prev
206 atom_info%resid(index_now) = itemp
207 atom_info%id_molname(index_now) =
str2id(
s2s(namearray2(itemp)))
208 atom_info%id_resname(index_now) =
str2id(
s2s(namearray2(itemp)))
211 atom_info%id_atmname(index_now) =
str2id(
s2s(namearray1(itemp)))
212 atom_info%id_element(index_now) =
str2id(
s2s(namearray1(itemp)))
216 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT SOLUTEATOM INFO HERE!"
225 IF (begin .EQ. 1)
THEN
226 READ (parser%input_line, iostat=stat, fmt=*) itemp, itemp, ctemp, itemp, ftemp, ftemp, &
227 itemp, itemp, (ii(i), i=begin, ntype)
228 ELSE IF (begin .GT. 1)
THEN
230 READ (parser%input_line, iostat=stat, fmt=*) (ii(i), i=begin, ntype)
233 IF (ii(i) .LT. 0)
THEN
237 IF (stat .EQ. 0)
EXIT
244 itemp = (itemp - 1)/6 + 1
246 IF (
ASSOCIATED(conn_info%onfo_a)) offset =
SIZE(conn_info%onfo_a)
247 CALL reallocate(conn_info%onfo_a, 1, offset + ntype)
248 CALL reallocate(conn_info%onfo_b, 1, offset + ntype)
249 conn_info%onfo_a(offset + 1:offset + ntype) = index_now
257 IF (begin .EQ. 1)
THEN
258 READ (parser%input_line, iostat=stat, fmt=*) itemp, (ii(i), i=begin, ntype)
259 ELSE IF (begin .GT. 1)
THEN
261 READ (parser%input_line, iostat=stat, fmt=*) (ii(i), i=begin, ntype)
264 IF (ii(i) .LT. 0)
THEN
268 IF (stat .EQ. 0)
EXIT
271 conn_info%onfo_b(offset + i) = ii(i)
285 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the BONDH section'
286 label = trim(avail_section(8))
292 IF (
ASSOCIATED(conn_info%bond_a)) offset =
SIZE(conn_info%bond_a)
293 CALL reallocate(conn_info%bond_a, 1, offset + ntype)
294 CALL reallocate(conn_info%bond_b, 1, offset + ntype)
295 CALL reallocate(conn_info%bond_type, 1, offset + ntype)
301 conn_info%bond_type(offset + itype) = itemp
302 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT BONDH INFO HERE!"
304 conn_info%bond_a(offset + 1:offset + ntype) = conn_info%bond_a(offset + 1:offset + ntype) + natom_prev
305 conn_info%bond_b(offset + 1:offset + ntype) = conn_info%bond_b(offset + 1:offset + ntype) + natom_prev
308 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the BOND section'
309 label = trim(avail_section(9))
315 IF (
ASSOCIATED(conn_info%bond_a)) offset =
SIZE(conn_info%bond_a)
316 CALL reallocate(conn_info%bond_a, 1, offset + ntype)
317 CALL reallocate(conn_info%bond_b, 1, offset + ntype)
318 CALL reallocate(conn_info%bond_type, 1, offset + ntype)
324 conn_info%bond_type(offset + itype) = itemp
325 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT BOND INFO HERE!"
327 conn_info%bond_a(offset + 1:offset + ntype) = conn_info%bond_a(offset + 1:offset + ntype) + natom_prev
328 conn_info%bond_b(offset + 1:offset + ntype) = conn_info%bond_b(offset + 1:offset + ntype) + natom_prev
331 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the BONDANGLEH section'
332 label = trim(avail_section(11))
338 IF (
ASSOCIATED(conn_info%theta_a)) offset =
SIZE(conn_info%theta_a)
339 CALL reallocate(conn_info%theta_a, 1, offset + ntype)
340 CALL reallocate(conn_info%theta_b, 1, offset + ntype)
341 CALL reallocate(conn_info%theta_c, 1, offset + ntype)
342 CALL reallocate(conn_info%theta_type, 1, offset + ntype)
349 conn_info%theta_type(offset + itype) = itemp
350 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT BONDANGLEH INFO HERE!"
352 conn_info%theta_a(offset + 1:offset + ntype) = conn_info%theta_a(offset + 1:offset + ntype) + natom_prev
353 conn_info%theta_b(offset + 1:offset + ntype) = conn_info%theta_b(offset + 1:offset + ntype) + natom_prev
354 conn_info%theta_c(offset + 1:offset + ntype) = conn_info%theta_c(offset + 1:offset + ntype) + natom_prev
357 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the BONDANGLE section'
358 label = trim(avail_section(12))
364 IF (
ASSOCIATED(conn_info%theta_a)) offset =
SIZE(conn_info%theta_a)
365 CALL reallocate(conn_info%theta_a, 1, offset + ntype)
366 CALL reallocate(conn_info%theta_b, 1, offset + ntype)
367 CALL reallocate(conn_info%theta_c, 1, offset + ntype)
368 CALL reallocate(conn_info%theta_type, 1, offset + ntype)
375 conn_info%theta_type(offset + itype) = itemp
376 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT BONDANGLE INFO HERE!"
378 conn_info%theta_a(offset + 1:offset + ntype) = conn_info%theta_a(offset + 1:offset + ntype) + natom_prev
379 conn_info%theta_b(offset + 1:offset + ntype) = conn_info%theta_b(offset + 1:offset + ntype) + natom_prev
380 conn_info%theta_c(offset + 1:offset + ntype) = conn_info%theta_c(offset + 1:offset + ntype) + natom_prev
383 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the IMPDIHEDRALH section'
384 label = trim(avail_section(14))
390 IF (
ASSOCIATED(conn_info%impr_a)) offset =
SIZE(conn_info%impr_a)
391 CALL reallocate(conn_info%impr_a, 1, offset + ntype)
392 CALL reallocate(conn_info%impr_b, 1, offset + ntype)
393 CALL reallocate(conn_info%impr_c, 1, offset + ntype)
394 CALL reallocate(conn_info%impr_d, 1, offset + ntype)
395 CALL reallocate(conn_info%impr_type, 1, offset + ntype)
403 conn_info%impr_type(offset + itype) = itemp
404 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT IMPDIHEDRALH INFO HERE!"
406 conn_info%impr_a(offset + 1:offset + ntype) = conn_info%impr_a(offset + 1:offset + ntype) + natom_prev
407 conn_info%impr_b(offset + 1:offset + ntype) = conn_info%impr_b(offset + 1:offset + ntype) + natom_prev
408 conn_info%impr_c(offset + 1:offset + ntype) = conn_info%impr_c(offset + 1:offset + ntype) + natom_prev
409 conn_info%impr_d(offset + 1:offset + ntype) = conn_info%impr_d(offset + 1:offset + ntype) + natom_prev
412 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the IMPDIHEDRAL section'
413 label = trim(avail_section(15))
419 IF (
ASSOCIATED(conn_info%impr_a)) offset =
SIZE(conn_info%impr_a)
420 CALL reallocate(conn_info%impr_a, 1, offset + ntype)
421 CALL reallocate(conn_info%impr_b, 1, offset + ntype)
422 CALL reallocate(conn_info%impr_c, 1, offset + ntype)
423 CALL reallocate(conn_info%impr_d, 1, offset + ntype)
424 CALL reallocate(conn_info%impr_type, 1, offset + ntype)
432 conn_info%impr_type(offset + itype) = itemp
433 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT IMPDIHEDRAL INFO HERE!"
435 conn_info%impr_a(offset + 1:offset + ntype) = conn_info%impr_a(offset + 1:offset + ntype) + natom_prev
436 conn_info%impr_b(offset + 1:offset + ntype) = conn_info%impr_b(offset + 1:offset + ntype) + natom_prev
437 conn_info%impr_c(offset + 1:offset + ntype) = conn_info%impr_c(offset + 1:offset + ntype) + natom_prev
438 conn_info%impr_d(offset + 1:offset + ntype) = conn_info%impr_d(offset + 1:offset + ntype) + natom_prev
441 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the DIHEDRALH section'
442 label = trim(avail_section(17))
448 IF (
ASSOCIATED(conn_info%phi_a)) offset =
SIZE(conn_info%phi_a)
449 CALL reallocate(conn_info%phi_a, 1, offset + ntype)
450 CALL reallocate(conn_info%phi_b, 1, offset + ntype)
451 CALL reallocate(conn_info%phi_c, 1, offset + ntype)
452 CALL reallocate(conn_info%phi_d, 1, offset + ntype)
453 CALL reallocate(conn_info%phi_type, 1, offset + ntype)
461 conn_info%phi_type(offset + itype) = itemp
462 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT DIHEDRALH INFO HERE!"
464 conn_info%phi_a(offset + 1:offset + ntype) = conn_info%phi_a(offset + 1:offset + ntype) + natom_prev
465 conn_info%phi_b(offset + 1:offset + ntype) = conn_info%phi_b(offset + 1:offset + ntype) + natom_prev
466 conn_info%phi_c(offset + 1:offset + ntype) = conn_info%phi_c(offset + 1:offset + ntype) + natom_prev
467 conn_info%phi_d(offset + 1:offset + ntype) = conn_info%phi_d(offset + 1:offset + ntype) + natom_prev
470 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the DIHEDRAL section'
471 label = trim(avail_section(18))
477 IF (
ASSOCIATED(conn_info%phi_a)) offset =
SIZE(conn_info%phi_a)
478 CALL reallocate(conn_info%phi_a, 1, offset + ntype)
479 CALL reallocate(conn_info%phi_b, 1, offset + ntype)
480 CALL reallocate(conn_info%phi_c, 1, offset + ntype)
481 CALL reallocate(conn_info%phi_d, 1, offset + ntype)
482 CALL reallocate(conn_info%phi_type, 1, offset + ntype)
490 conn_info%phi_type(offset + itype) = itemp
491 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT DIHEDRAL INFO HERE!"
493 conn_info%phi_a(offset + 1:offset + ntype) = conn_info%phi_a(offset + 1:offset + ntype) + natom_prev
494 conn_info%phi_b(offset + 1:offset + ntype) = conn_info%phi_b(offset + 1:offset + ntype) + natom_prev
495 conn_info%phi_c(offset + 1:offset + ntype) = conn_info%phi_c(offset + 1:offset + ntype) + natom_prev
496 conn_info%phi_d(offset + 1:offset + ntype) = conn_info%phi_d(offset + 1:offset + ntype) + natom_prev
501 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'GTOP_INFO| Parsing the SOLVENTATOM section'
502 nsolvent = (
SIZE(atom_info%r(1, :)) - nsolute)/3
504 NULLIFY (na, am, ac, ba, bb)
506 label = trim(avail_section(20))
521 IF (iw > 0)
WRITE (iw, *)
"GTOP_INFO| PUT SOLVENTATOM INFO HERE!"
524 label = trim(avail_section(21))
541 IF (
ASSOCIATED(atom_info%id_molname)) offset =
SIZE(atom_info%id_molname)
542 CALL reallocate(atom_info%id_molname, 1, offset + nsolvent*natom)
543 CALL reallocate(atom_info%resid, 1, offset + nsolvent*natom)
544 CALL reallocate(atom_info%id_resname, 1, offset + nsolvent*natom)
545 CALL reallocate(atom_info%id_atmname, 1, offset + nsolvent*natom)
546 CALL reallocate(atom_info%id_element, 1, offset + nsolvent*natom)
547 CALL reallocate(atom_info%atm_charge, 1, offset + nsolvent*natom)
548 CALL reallocate(atom_info%atm_mass, 1, offset + nsolvent*natom)
549 DO isolvent = 1, nsolvent
550 offset = nsolute + natom*isolvent - natom
552 index_now = offset + iatom
553 atom_info%id_atmname(index_now) =
str2id(
s2s(namearray1(na(iatom))))
554 atom_info%id_element(index_now) =
str2id(
s2s(namearray1(na(iatom))))
555 atom_info%id_molname(index_now) =
str2id(
s2s(
"SOL"))
556 atom_info%id_resname(index_now) =
str2id(
s2s(
"SOL"))
557 atom_info%resid(index_now) = isolvent
558 atom_info%atm_mass(index_now) = am(iatom)
559 atom_info%atm_charge(index_now) = ac(iatom)
564 IF (
ASSOCIATED(conn_info%bond_a)) offset =
SIZE(conn_info%bond_a)
565 offset2 = maxval(conn_info%bond_type(:))
566 CALL reallocate(conn_info%bond_a, 1, offset + ncon*nsolvent)
567 CALL reallocate(conn_info%bond_b, 1, offset + ncon*nsolvent)
568 CALL reallocate(conn_info%bond_type, 1, offset + ncon*nsolvent)
569 offset = offset - ncon
570 DO isolvent = 1, nsolvent
571 offset = offset + ncon
573 conn_info%bond_a(offset + icon) = nsolute + isolvent*ncon - ncon + ba(icon)
574 conn_info%bond_b(offset + icon) = nsolute + isolvent*ncon - ncon + bb(icon)
575 conn_info%bond_type(offset + icon) = offset2 + isolvent*ncon - ncon + icon
581 IF (
ASSOCIATED(conn_info%c_bond_a)) i =
SIZE(conn_info%c_bond_a)
582 nbond =
SIZE(conn_info%bond_a)
583 DO ibond = 1 + nbond_prev, nbond + nbond_prev
584 iatom = conn_info%bond_a(ibond)
585 jatom = conn_info%bond_b(ibond)
587 IF ((atom_info%id_molname(iatom) /= atom_info%id_molname(jatom)) .OR. &
588 (atom_info%resid(iatom) /= atom_info%resid(jatom)) .OR. &
589 (atom_info%id_resname(iatom) /= atom_info%id_resname(jatom)))
THEN
590 IF (iw > 0)
WRITE (iw,
'(T2,A,2I3)')
"GTOP_INFO| PARA_RES, bond between molecules atom ", &
596 conn_info%c_bond_a(i) = iatom
597 conn_info%c_bond_b(i) = jatom
598 conn_info%c_bond_type(i) = conn_info%bond_type(ibond)
601 IF (atom_info%id_molname(iatom) /= atom_info%id_molname(jatom))
THEN
607 DEALLOCATE (namearray1)
608 DEALLOCATE (namearray2)
612 IF (
ASSOCIATED(ba)) &
614 IF (
ASSOCIATED(bb)) &
617 CALL timestop(handle)
619 "PRINT%TOPOLOGY_INFO/GTOP_INFO")
634 CHARACTER(len=*),
PARAMETER :: routinen =
'read_coordinate_g96'
635 INTEGER,
PARAMETER :: nblock = 1000
637 CHARACTER(LEN=default_string_length) :: label, string, strtmp, strtmp2
638 CHARACTER(LEN=default_string_length),
DIMENSION(5) :: avail_section
639 INTEGER :: handle, itemp, iw, natom, newsize
641 REAL(kind=
dp) :: pfactor
642 REAL(kind=
dp),
DIMENSION(:, :),
POINTER :: velocity
648 NULLIFY (logger, velocity)
651 extension=
".subsysLog")
652 CALL timeset(routinen, handle)
654 pfactor =
section_get_rval(subsys_section,
"TOPOLOGY%MEMORY_PROGRESSION_FACTOR")
656 IF (iw > 0)
WRITE (iw, *)
" Reading in G96 file ", trim(
topology%coord_file_name)
657 avail_section(1) =
"TITLE"
658 avail_section(2) =
"TIMESTEP"
659 avail_section(3) =
"POSITION"
660 avail_section(4) =
"VELOCITY"
661 avail_section(5) =
"BOX"
666 CALL reallocate(atom_info%id_molname, 1, nblock)
667 CALL reallocate(atom_info%id_resname, 1, nblock)
669 CALL reallocate(atom_info%id_atmname, 1, nblock)
670 CALL reallocate(atom_info%id_element, 1, nblock)
672 CALL reallocate(atom_info%atm_mass, 1, nblock)
673 CALL reallocate(atom_info%atm_charge, 1, nblock)
677 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'G96_INFO| Parsing the TITLE section'
679 label = trim(avail_section(1))
685 IF (string == trim(
"END"))
EXIT
686 IF (iw > 0)
WRITE (iw, *)
"G96_INFO| ", trim(string)
691 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'G96_INFO| Parsing the POSITION section'
693 label = trim(avail_section(3))
700 IF (string == trim(
"END"))
EXIT
702 IF (natom >
SIZE(atom_info%id_molname))
THEN
703 newsize = int(pfactor*natom)
704 CALL reallocate(atom_info%id_molname, 1, newsize)
705 CALL reallocate(atom_info%id_resname, 1, newsize)
707 CALL reallocate(atom_info%id_atmname, 1, newsize)
708 CALL reallocate(atom_info%id_element, 1, newsize)
709 CALL reallocate(atom_info%r, 1, 3, 1, newsize)
710 CALL reallocate(atom_info%atm_mass, 1, newsize)
711 CALL reallocate(atom_info%atm_charge, 1, newsize)
716 atom_info%resid(natom), strtmp, strtmp2, &
717 itemp, atom_info%r(1, natom), atom_info%r(2, natom), atom_info%r(3, natom)
718 atom_info%id_resname(natom) =
str2id(
s2s(strtmp))
719 atom_info%id_atmname(natom) =
str2id(
s2s(strtmp2))
720 atom_info%id_molname(natom) = atom_info%id_resname(natom)
721 atom_info%id_element(natom) = atom_info%id_atmname(natom)
725 IF (iw > 0)
WRITE (iw, *)
"G96_INFO| PUT POSITION INFO HERE!"
734 IF (iw > 0)
WRITE (iw,
'(T2,A)')
'G96_INFO| Parsing the VELOCITY section'
736 label = trim(avail_section(4))
743 IF (string == trim(
"END"))
EXIT
746 atom_info%resid(natom), strtmp, strtmp2, &
747 itemp, velocity(1, natom), velocity(2, natom), velocity(3, natom)
748 atom_info%id_resname(natom) =
str2id(strtmp)
749 atom_info%id_atmname(natom) =
str2id(strtmp2)
750 atom_info%id_molname(natom) = atom_info%id_resname(natom)
751 atom_info%id_element(natom) = atom_info%id_atmname(natom)
755 IF (iw > 0)
WRITE (iw, *)
"G96_INFO| PUT VELOCITY INFO HERE!"
765 DEALLOCATE (velocity)
767 CALL reallocate(atom_info%id_molname, 1, natom)
768 CALL reallocate(atom_info%id_resname, 1, natom)
770 CALL reallocate(atom_info%id_atmname, 1, natom)
771 CALL reallocate(atom_info%id_element, 1, natom)
774 CALL reallocate(atom_info%atm_charge, 1, natom)
778 IF (.NOT.
topology%para_res) atom_info%resid(:) = 1
782 "PRINT%TOPOLOGY_INFO/G96_INFO")
783 CALL timestop(handle)