247 TYPE(
nnp_type),
INTENT(INOUT),
POINTER :: nnp_env
248 CHARACTER(LEN=*),
INTENT(IN) :: printtag
250 CHARACTER(len=*),
PARAMETER :: routinen =
'nnp_init_model'
251 INTEGER,
PARAMETER :: def_str_len = 256, &
254 CHARACTER(len=1),
ALLOCATABLE,
DIMENSION(:) :: cactfnct
255 CHARACTER(len=2) :: ele
256 CHARACTER(len=def_str_len) :: dummy, line
257 CHARACTER(len=default_path_length) :: base_name, file_name
258 INTEGER :: handle, i, i_com, io, iweight, j, k, l, &
259 n_weight, nele, nuc_ele, symfnct_type, &
261 LOGICAL :: at_end, atom_e_found, explicit, first, &
263 REAL(kind=
dp) :: energy
264 REAL(kind=
dp),
ALLOCATABLE,
DIMENSION(:) :: weights
265 REAL(kind=
dp),
DIMENSION(7) :: test_array
266 REAL(kind=
dp),
DIMENSION(:),
POINTER :: work
271 CALL timeset(routinen, handle)
277 IF (logger%para_env%is_source())
THEN
279 WRITE (unit_nr, *)
""
280 WRITE (unit_nr, *) trim(printtag)//
"| Neural Network Potential Force Environment"
285 ALLOCATE (nnp_env%atomic_energy(nnp_env%num_atoms, nnp_env%n_committee))
286 ALLOCATE (nnp_env%committee_energy(nnp_env%n_committee))
287 ALLOCATE (nnp_env%myforce(3, nnp_env%num_atoms, nnp_env%n_committee))
288 ALLOCATE (nnp_env%committee_forces(3, nnp_env%num_atoms, nnp_env%n_committee))
289 ALLOCATE (nnp_env%committee_stress(3, 3, nnp_env%n_committee))
292 CALL parser_create(parser, file_name, para_env=logger%para_env)
295 nnp_env%scale_acsf = .false.
296 nnp_env%scale_sigma_acsf = .false.
298 nnp_env%scmin = 0.0_dp
299 nnp_env%scmax = 1.0_dp
300 nnp_env%center_acsf = .false.
301 nnp_env%normnodes = .false.
304 IF (logger%para_env%is_source())
THEN
306 WRITE (unit_nr, *) trim(printtag)//
"| Reading NNP input from file: ", trim(file_name)
310 search_from_begin_of_file=.true.)
312 READ (line, *) dummy, nnp_env%n_ele
314 CALL cp_abort(__location__, trim(printtag)// &
315 "| number of elements missing in NNP_INPUT_FILE")
319 search_from_begin_of_file=.true.)
320 nnp_env%scale_sigma_acsf = found
323 search_from_begin_of_file=.true.)
324 nnp_env%scale_acsf = found
328 IF (found .AND. nnp_env%scale_sigma_acsf)
THEN
329 cpwarn(
'Two scaling keywords in the input, we will ignore sigma scaling in this case')
330 nnp_env%scale_sigma_acsf = .false.
331 ELSE IF (.NOT. found .AND. nnp_env%scale_sigma_acsf)
THEN
332 nnp_env%scale_acsf = .false.
336 search_from_begin_of_file=.true.)
337 IF (found)
READ (line, *) dummy, nnp_env%scmin
340 search_from_begin_of_file=.true.)
341 IF (found)
READ (line, *) dummy, nnp_env%scmax
344 search_from_begin_of_file=.true.)
345 nnp_env%center_acsf = found
347 IF (nnp_env%scale_sigma_acsf .AND. nnp_env%center_acsf)
THEN
348 nnp_env%scale_sigma_acsf = .false.
351 IF (nnp_env%center_acsf .AND. nnp_env%scale_acsf)
THEN
352 IF ((abs(nnp_env%scmin) > epsilon(0.0_dp)*1.0e+4_dp) .OR. (abs(nnp_env%scmax - 1.0_dp) > epsilon(0.0_dp)*1.0e+4_dp))
THEN
353 CALL cp_warn(__location__, &
354 "Centering and scaling of symmetry functions requested while scale_min_short_atomic != 0 and/or "// &
355 "scale_max_short_atomic != 1. Make sure that scaling and centering of symmetry functions in CP2K "// &
356 "is consistent with your training code. "// &
357 "In CP2K: G* = (G - ave(G)) / (max(G) - min(G)) * (Smax - Smin) + Smin")
362 search_from_begin_of_file=.true.)
363 nnp_env%normnodes = found
366 search_from_begin_of_file=.true.)
368 READ (line, *) dummy, nnp_env%cut_type
370 CALL cp_abort(__location__, trim(printtag)// &
371 "| no cutoff type specified in NNP_INPUT_FILE")
375 search_from_begin_of_file=.true.)
377 READ (line, *) dummy, nnp_env%n_hlayer
379 CALL cp_abort(__location__, trim(printtag)// &
380 "| number of hidden layers missing in NNP_INPUT_FILE")
382 nnp_env%n_layer = nnp_env%n_hlayer + 2
385 ALLOCATE (nnp_env%rad(nele))
386 ALLOCATE (nnp_env%ang(nele))
387 ALLOCATE (nnp_env%n_rad(nele))
388 ALLOCATE (nnp_env%n_ang(nele))
389 ALLOCATE (nnp_env%actfnct(nnp_env%n_hlayer + 1))
390 ALLOCATE (cactfnct(nnp_env%n_hlayer + 1))
391 ALLOCATE (nnp_env%ele(nele))
392 ALLOCATE (nnp_env%nuc_ele(nele))
393 ALLOCATE (nnp_env%arc(nele))
395 ALLOCATE (nnp_env%arc(i)%layer(nnp_env%n_layer))
396 ALLOCATE (nnp_env%arc(i)%n_nodes(nnp_env%n_layer))
398 ALLOCATE (nnp_env%n_hnodes(nnp_env%n_hlayer))
399 ALLOCATE (nnp_env%atom_energies(nele))
400 nnp_env%atom_energies = 0.0_dp
408 IF (trim(adjustl(dummy)) ==
"elements")
THEN
409 READ (line, *) dummy, nnp_env%ele(:)
414 CALL cp_abort(__location__, trim(printtag)// &
415 "| elements not specified in NNP_INPUT_FILE")
420 search_from_begin_of_file=.true.)
422 IF (atom_e_found)
THEN
428 READ (line, *) dummy, ele, energy
430 IF (nnp_env%ele(j) == trim(ele))
THEN
432 nnp_env%atom_energies(j) = energy
437 CALL cp_abort(__location__, trim(printtag)// &
438 "| atom energies are not specified")
444 search_from_begin_of_file=.true.)
446 READ (line, *) dummy, nnp_env%n_hnodes(:)
448 CALL cp_abort(__location__, trim(printtag)// &
449 "NNP| global_nodes_short not specified in NNP_INPUT_FILE")
453 search_from_begin_of_file=.true.)
455 READ (line, *) dummy, cactfnct(:)
457 CALL cp_abort(__location__, trim(printtag)// &
458 "| global_activation_short not specified in NNP_INPUT_FILE")
461 DO i = 1, nnp_env%n_hlayer + 1
462 SELECT CASE (cactfnct(i))
482 CALL cp_abort(__location__, trim(printtag)// &
483 "| Activation function unkown")
499 READ (line, *) dummy, ele, symfnct_type
501 IF (trim(ele) .EQ. nnp_env%ele(i))
THEN
502 IF (symfnct_type .EQ. 2)
THEN
503 nnp_env%n_rad(i) = nnp_env%n_rad(i) + 1
504 ELSE IF (symfnct_type .EQ. 3)
THEN
505 nnp_env%n_ang(i) = nnp_env%n_ang(i) + 1
507 CALL cp_abort(__location__, trim(printtag)// &
508 "| Symmetry function type not supported")
514 IF (first)
CALL cp_abort(__location__, trim(printtag)// &
515 "| no symfunction_short specified in NNP_INPUT_FILE")
522 ALLOCATE (nnp_env%rad(i)%y(nnp_env%n_rad(i)))
523 ALLOCATE (nnp_env%rad(i)%funccut(nnp_env%n_rad(i)))
524 ALLOCATE (nnp_env%rad(i)%eta(nnp_env%n_rad(i)))
525 ALLOCATE (nnp_env%rad(i)%rs(nnp_env%n_rad(i)))
526 ALLOCATE (nnp_env%rad(i)%loc_min(nnp_env%n_rad(i)))
527 ALLOCATE (nnp_env%rad(i)%loc_max(nnp_env%n_rad(i)))
528 ALLOCATE (nnp_env%rad(i)%loc_av(nnp_env%n_rad(i)))
529 ALLOCATE (nnp_env%rad(i)%sigma(nnp_env%n_rad(i)))
530 ALLOCATE (nnp_env%rad(i)%ele(nnp_env%n_rad(i)))
531 ALLOCATE (nnp_env%rad(i)%nuc_ele(nnp_env%n_rad(i)))
532 nnp_env%rad(i)%funccut = 0.0_dp
533 nnp_env%rad(i)%eta = 0.0_dp
534 nnp_env%rad(i)%rs = 0.0_dp
535 nnp_env%rad(i)%ele =
'X'
536 nnp_env%rad(i)%nuc_ele = 0
538 ALLOCATE (nnp_env%ang(i)%y(nnp_env%n_ang(i)))
539 ALLOCATE (nnp_env%ang(i)%funccut(nnp_env%n_ang(i)))
540 ALLOCATE (nnp_env%ang(i)%eta(nnp_env%n_ang(i)))
541 ALLOCATE (nnp_env%ang(i)%zeta(nnp_env%n_ang(i)))
542 ALLOCATE (nnp_env%ang(i)%prefzeta(nnp_env%n_ang(i)))
543 ALLOCATE (nnp_env%ang(i)%lam(nnp_env%n_ang(i)))
544 ALLOCATE (nnp_env%ang(i)%loc_min(nnp_env%n_ang(i)))
545 ALLOCATE (nnp_env%ang(i)%loc_max(nnp_env%n_ang(i)))
546 ALLOCATE (nnp_env%ang(i)%loc_av(nnp_env%n_ang(i)))
547 ALLOCATE (nnp_env%ang(i)%sigma(nnp_env%n_ang(i)))
548 ALLOCATE (nnp_env%ang(i)%ele1(nnp_env%n_ang(i)))
549 ALLOCATE (nnp_env%ang(i)%ele2(nnp_env%n_ang(i)))
550 ALLOCATE (nnp_env%ang(i)%nuc_ele1(nnp_env%n_ang(i)))
551 ALLOCATE (nnp_env%ang(i)%nuc_ele2(nnp_env%n_ang(i)))
552 nnp_env%ang(i)%funccut = 0.0_dp
553 nnp_env%ang(i)%eta = 0.0_dp
554 nnp_env%ang(i)%zeta = 0.0_dp
555 nnp_env%ang(i)%prefzeta = 1.0_dp
556 nnp_env%ang(i)%lam = 0.0_dp
557 nnp_env%ang(i)%ele1 =
'X'
558 nnp_env%ang(i)%ele2 =
'X'
559 nnp_env%ang(i)%nuc_ele1 = 0
560 nnp_env%ang(i)%nuc_ele2 = 0
563 nnp_env%arc(i)%n_nodes(1) = nnp_env%n_rad(i) + nnp_env%n_ang(i)
564 nnp_env%arc(i)%n_nodes(2:nnp_env%n_layer - 1) = nnp_env%n_hnodes
565 nnp_env%arc(i)%n_nodes(nnp_env%n_layer) = 1
566 DO j = 1, nnp_env%n_layer
567 ALLOCATE (nnp_env%arc(i)%layer(j)%node(nnp_env%arc(i)%n_nodes(j)))
568 ALLOCATE (nnp_env%arc(i)%layer(j)%node_grad(nnp_env%arc(i)%n_nodes(j)))
569 ALLOCATE (nnp_env%arc(i)%layer(j)%tmp_der(nnp_env%arc(i)%n_nodes(1), nnp_env%arc(i)%n_nodes(j)))
580 nnp_env%max_cut = 0.0_dp
584 READ (line, *) dummy, ele, symfnct_type
586 IF (trim(ele) .EQ. nnp_env%ele(i))
THEN
587 IF (symfnct_type .EQ. 2)
THEN
588 nnp_env%n_rad(i) = nnp_env%n_rad(i) + 1
589 READ (line, *) dummy, ele, symfnct_type, &
590 nnp_env%rad(i)%ele(nnp_env%n_rad(i)), &
591 nnp_env%rad(i)%eta(nnp_env%n_rad(i)), &
592 nnp_env%rad(i)%rs(nnp_env%n_rad(i)), &
593 nnp_env%rad(i)%funccut(nnp_env%n_rad(i))
594 IF (nnp_env%max_cut < nnp_env%rad(i)%funccut(nnp_env%n_rad(i)))
THEN
595 nnp_env%max_cut = nnp_env%rad(i)%funccut(nnp_env%n_rad(i))
597 ELSE IF (symfnct_type .EQ. 3)
THEN
598 nnp_env%n_ang(i) = nnp_env%n_ang(i) + 1
599 READ (line, *) dummy, ele, symfnct_type, &
600 nnp_env%ang(i)%ele1(nnp_env%n_ang(i)), &
601 nnp_env%ang(i)%ele2(nnp_env%n_ang(i)), &
602 nnp_env%ang(i)%eta(nnp_env%n_ang(i)), &
603 nnp_env%ang(i)%lam(nnp_env%n_ang(i)), &
604 nnp_env%ang(i)%zeta(nnp_env%n_ang(i)), &
605 nnp_env%ang(i)%funccut(nnp_env%n_ang(i))
606 nnp_env%ang(i)%prefzeta(nnp_env%n_ang(i)) = &
607 2.0_dp**(1.0_dp - nnp_env%ang(i)%zeta(nnp_env%n_ang(i)))
608 IF (nnp_env%max_cut < nnp_env%ang(i)%funccut(nnp_env%n_ang(i)))
THEN
609 nnp_env%max_cut = nnp_env%ang(i)%funccut(nnp_env%n_ang(i))
612 CALL cp_abort(__location__, trim(printtag)// &
613 "| Symmetry function type not supported")
619 IF (first)
CALL cp_abort(__location__, trim(printtag)// &
620 "| no symfunction_short specified in NNP_INPUT_FILE")
627 DO j = 1, nnp_env%n_rad(i)
628 CALL get_ptable_info(nnp_env%rad(i)%ele(j), number=nnp_env%rad(i)%nuc_ele(j))
630 DO j = 1, nnp_env%n_ang(i)
631 CALL get_ptable_info(nnp_env%ang(i)%ele1(j), number=nnp_env%ang(i)%nuc_ele1(j))
632 CALL get_ptable_info(nnp_env%ang(i)%ele2(j), number=nnp_env%ang(i)%nuc_ele2(j))
634 IF (nnp_env%ang(i)%nuc_ele1(j) .GT. nnp_env%ang(i)%nuc_ele2(j))
THEN
635 ele = nnp_env%ang(i)%ele1(j)
636 nnp_env%ang(i)%ele1(j) = nnp_env%ang(i)%ele2(j)
637 nnp_env%ang(i)%ele2(j) = ele
638 nuc_ele = nnp_env%ang(i)%nuc_ele1(j)
639 nnp_env%ang(i)%nuc_ele1(j) = nnp_env%ang(i)%nuc_ele2(j)
640 nnp_env%ang(i)%nuc_ele2(j) = nuc_ele
653 IF (nnp_env%scale_acsf .OR. nnp_env%center_acsf .OR. nnp_env%scale_sigma_acsf)
THEN
654 IF (logger%para_env%is_source())
THEN
655 WRITE (unit_nr, *) trim(printtag)//
"| Reading scaling information from file: ", trim(file_name)
659 CALL parser_create(parser, file_name, para_env=logger%para_env)
665 READ (parser%input_line, *, iostat=io) test_array(1:k)
671 IF (k == 5 .AND. nnp_env%scale_sigma_acsf)
THEN
672 cpabort(
"Sigma scaling requested, but scaling.data does not contain sigma.")
676 DO i = 1, nnp_env%n_ele
677 DO j = 1, nnp_env%n_rad(i)
679 IF (nnp_env%scale_sigma_acsf)
THEN
680 READ (parser%input_line, *) dummy, dummy, &
681 nnp_env%rad(i)%loc_min(j), &
682 nnp_env%rad(i)%loc_max(j), &
683 nnp_env%rad(i)%loc_av(j), &
684 nnp_env%rad(i)%sigma(j)
686 READ (parser%input_line, *) dummy, dummy, &
687 nnp_env%rad(i)%loc_min(j), &
688 nnp_env%rad(i)%loc_max(j), &
689 nnp_env%rad(i)%loc_av(j)
692 DO j = 1, nnp_env%n_ang(i)
694 IF (nnp_env%scale_sigma_acsf)
THEN
695 READ (parser%input_line, *) dummy, dummy, &
696 nnp_env%ang(i)%loc_min(j), &
697 nnp_env%ang(i)%loc_max(j), &
698 nnp_env%ang(i)%loc_av(j), &
699 nnp_env%ang(i)%sigma(j)
701 READ (parser%input_line, *) dummy, dummy, &
702 nnp_env%ang(i)%loc_min(j), &
703 nnp_env%ang(i)%loc_max(j), &
704 nnp_env%ang(i)%loc_av(j)
714 DO i = 1, nnp_env%n_ele
715 DO j = 2, nnp_env%n_layer
716 ALLOCATE (nnp_env%arc(i)%layer(j)%weights(nnp_env%arc(i)%n_nodes(j - 1), &
717 nnp_env%arc(i)%n_nodes(j), nnp_env%n_committee))
718 ALLOCATE (nnp_env%arc(i)%layer(j)%bweights(nnp_env%arc(i)%n_nodes(j), nnp_env%n_committee))
721 DO i_com = 1, nnp_env%n_committee
723 IF (logger%para_env%is_source())
THEN
724 WRITE (unit_nr, *) trim(printtag)//
"| Initializing weights for model: ", i_com
726 DO i = 1, nnp_env%n_ele
727 WRITE (file_name,
'(A,I0.3,A)') trim(base_name)//
".", nnp_env%nuc_ele(i),
".data"
728 IF (logger%para_env%is_source())
THEN
729 WRITE (unit_nr, *) trim(printtag)//
"| Reading weights from file: ", trim(file_name)
731 CALL parser_create(parser, file_name, para_env=logger%para_env)
736 n_weight = n_weight + 1
739 ALLOCATE (weights(n_weight))
744 READ (parser%input_line, *) weights(j)
750 DO j = 2, nnp_env%n_layer
751 DO k = 1, nnp_env%arc(i)%n_nodes(j - 1)
752 DO l = 1, nnp_env%arc(i)%n_nodes(j)
753 iweight = iweight + 1
754 nnp_env%arc(i)%layer(j)%weights(k, l, i_com) = weights(iweight)
758 DO k = 1, nnp_env%arc(i)%n_nodes(j)
759 iweight = iweight + 1
760 nnp_env%arc(i)%layer(j)%bweights(k, i_com) = weights(iweight)
772 NULLIFY (bias_section)
776 IF (
ASSOCIATED(bias_section))
CALL section_vals_get(bias_section, explicit=explicit)
777 nnp_env%bias = .false.
779 IF (nnp_env%n_committee > 1)
THEN
780 IF (logger%para_env%is_source())
THEN
781 WRITE (unit_nr, *)
"NNP| Biasing of committee disagreement enabled"
783 nnp_env%bias = .true.
784 ALLOCATE (nnp_env%bias_forces(3, nnp_env%num_atoms))
785 ALLOCATE (nnp_env%bias_e_avrg(nnp_env%n_committee))
788 nnp_env%bias_e_avrg(:) = 0.0_dp
790 nnp_env%bias_align = explicit
794 IF (
SIZE(work) .NE. nnp_env%n_committee)
THEN
795 cpabort(
"ALIGN_NNP_ENERGIES size mismatch wrt committee size.")
797 nnp_env%bias_e_avrg(:) = work
798 IF (logger%para_env%is_source())
THEN
799 WRITE (unit_nr, *) trim(printtag)//
"| Biasing is aligned by shifting the energy prediction of the C-NNP members"
803 cpwarn(
"NNP committee size is 1, BIAS section is ignored.")
807 IF (logger%para_env%is_source())
THEN
808 WRITE (unit_nr, *) trim(printtag)//
"| NNP force environment initialized"
811 CALL timestop(handle)