40#include "./base/base_uses.f90" 
   46   CHARACTER(len=*), 
PARAMETER, 
PRIVATE :: moduleN = 
'input_cp2k_binary_restarts' 
   69                                      subsys_section, binary_file_read)
 
   75      LOGICAL, 
INTENT(OUT)                               :: binary_file_read
 
   77      CHARACTER(LEN=*), 
PARAMETER :: routinen = 
'read_binary_coordinates' 
   79      CHARACTER(LEN=default_path_length)                 :: binary_restart_file_name
 
   80      CHARACTER(LEN=default_string_length)               :: string
 
   81      INTEGER                                            :: handle, iatom, ikind, input_unit, istat, &
 
   82                                                            iw, natom, natomkind, ncore, &
 
   83                                                            nmolecule, nmoleculekind, nshell
 
   84      INTEGER, 
ALLOCATABLE, 
DIMENSION(:)                 :: ibuf, id_name
 
   88      CALL timeset(routinen, handle)
 
   91      cpassert(
ASSOCIATED(root_section))
 
   92      cpassert(
ASSOCIATED(para_env))
 
   93      cpassert(
ASSOCIATED(subsys_section))
 
   96      binary_file_read = .false.
 
   99                                c_val=binary_restart_file_name)
 
  101      IF (trim(adjustl(binary_restart_file_name)) == 
"") 
THEN 
  102         CALL timestop(handle)
 
  107                                extension=
".subsysLog")
 
  117      IF (para_env%is_source()) 
THEN 
  118         CALL open_file(file_name=binary_restart_file_name, &
 
  120                        file_form=
"UNFORMATTED", &
 
  121                        file_action=
"READWRITE", &
 
  122                        file_position=
"REWIND", &
 
  123                        unit_number=input_unit, &
 
  125         READ (unit=input_unit, iostat=istat) &
 
  126            natomkind, natom, ncore, nshell, nmoleculekind, nmolecule
 
  128            CALL stop_read(
"natomkind,natom,ncore,nshell,nmoleculekind,nmolecule "// &
 
  129                           "(IOSTAT = "//trim(adjustl(
cp_to_string(istat)))//
")", &
 
  133            WRITE (unit=iw, fmt=
"(T2,A,T71,I10)") &
 
  134               "Number of atomic kinds:", natomkind, &
 
  135               "Number of atoms:", natom, &
 
  136               "Number of cores (only core-shell model):", ncore, &
 
  137               "Number of shells (only core-shell model):", nshell, &
 
  138               "Number of molecule kinds:", nmoleculekind, &
 
  139               "Number of molecules", nmolecule
 
  143      CALL para_env%bcast(natomkind)
 
  144      CALL para_env%bcast(natom)
 
  145      CALL para_env%bcast(ncore)
 
  146      CALL para_env%bcast(nshell)
 
  147      CALL para_env%bcast(nmoleculekind)
 
  148      CALL para_env%bcast(nmolecule)
 
  150      ALLOCATE (id_name(natomkind))
 
  152      DO ikind = 1, natomkind
 
  153         IF (para_env%is_source()) 
THEN 
  154            READ (unit=input_unit, iostat=istat) string
 
  155            IF (istat /= 0) 
CALL stop_read(
"string (IOSTAT = "// &
 
  159         CALL para_env%bcast(string)
 
  160         id_name(ikind) = 
str2id(string)
 
  165      ALLOCATE (atom_info%id_molname(natom))
 
  166      atom_info%id_molname(:) = 0
 
  167      ALLOCATE (atom_info%id_resname(natom))
 
  168      atom_info%id_resname(:) = 0
 
  169      ALLOCATE (atom_info%resid(natom))
 
  171      ALLOCATE (atom_info%id_atmname(natom))
 
  172      atom_info%id_atmname = 0
 
  173      ALLOCATE (atom_info%r(3, natom))
 
  174      atom_info%r(:, :) = 0.0_dp
 
  175      ALLOCATE (atom_info%atm_mass(natom))
 
  176      atom_info%atm_mass(:) = huge(0.0_dp)
 
  177      ALLOCATE (atom_info%atm_charge(natom))
 
  178      atom_info%atm_charge(:) = -huge(0.0_dp)
 
  179      ALLOCATE (atom_info%occup(natom))
 
  180      atom_info%occup(:) = 0.0_dp
 
  181      ALLOCATE (atom_info%beta(natom))
 
  182      atom_info%beta(:) = 0.0_dp
 
  183      ALLOCATE (atom_info%id_element(natom))
 
  184      atom_info%id_element(:) = 0
 
  185      ALLOCATE (ibuf(natom))
 
  188      IF (para_env%is_source()) 
THEN 
  189         READ (unit=input_unit, iostat=istat) ibuf(1:natom)
 
  190         IF (istat /= 0) 
CALL stop_read(
"ibuf (IOSTAT = "// &
 
  194      CALL para_env%bcast(ibuf)
 
  197         atom_info%id_atmname(iatom) = id_name(ikind)
 
  198         atom_info%id_element(iatom) = id_name(ikind)
 
  203      IF (para_env%is_source()) 
THEN 
  204         READ (unit=input_unit, iostat=istat) atom_info%r(1:3, 1:natom)
 
  205         IF (istat /= 0) 
CALL stop_read(
"atom_info%r(1:3,1:natom) (IOSTAT = "// &
 
  209      CALL para_env%bcast(atom_info%r)
 
  212      IF (nmolecule > 0) 
THEN 
  213         ALLOCATE (id_name(nmoleculekind))
 
  215         DO ikind = 1, nmoleculekind
 
  216            IF (para_env%is_source()) 
THEN 
  217               READ (unit=input_unit, iostat=istat) string
 
  218               IF (istat /= 0) 
CALL stop_read(
"string (IOSTAT = "// &
 
  222            CALL para_env%bcast(string)
 
  223            id_name(ikind) = 
str2id(string)
 
  226         IF (para_env%is_source()) 
THEN 
  227            READ (unit=input_unit, iostat=istat) ibuf(1:natom)
 
  228            IF (istat /= 0) 
CALL stop_read(
"ibuf(1:natom) (IOSTAT = "// &
 
  232         CALL para_env%bcast(ibuf)
 
  235            atom_info%id_molname(iatom) = id_name(ikind)
 
  239         IF (para_env%is_source()) 
THEN 
  240            READ (unit=input_unit, iostat=istat) atom_info%resid(1:natom)
 
  241            IF (istat /= 0) 
CALL stop_read(
"atom_info%resid(1:natom) (IOSTAT = "// &
 
  245         CALL para_env%bcast(atom_info%resid)
 
  254      topology%molname_generated = .false.
 
  258         WRITE (unit=iw, fmt=
"(T2,A)") &
 
  259            "BEGIN of COORD section data [Angstrom] read in binary format from file "// &
 
  260            trim(binary_restart_file_name)
 
  262            WRITE (unit=iw, fmt=
"(T2,A2,3(1X,ES25.16),2(1X,A))") &
 
  263               trim(adjustl(
id2str(atom_info%id_atmname(iatom)))), &
 
  265               trim(adjustl(
id2str(atom_info%id_molname(iatom)))), &
 
  266               trim(adjustl(
id2str(atom_info%id_resname(iatom))))
 
  268         WRITE (unit=iw, fmt=
"(T2,A)") &
 
  269            "END of COORD section data [Angstrom] read from binary restart file "// &
 
  270            trim(binary_restart_file_name)
 
  273      IF (para_env%is_source()) 
CALL close_file(unit_number=input_unit, &
 
  274                                                keep_preconnection=.true.)
 
  276      binary_file_read = .true.
 
  278      CALL timestop(handle)
 
 
  296                                         subsys_section, binary_file_read)
 
  298      CHARACTER(LEN=*), 
INTENT(IN)                       :: prefix
 
  301      LOGICAL, 
INTENT(OUT)                               :: binary_file_read
 
  303      CHARACTER(LEN=*), 
PARAMETER :: routinen = 
'read_binary_cs_coordinates' 
  305      CHARACTER(LEN=default_path_length)                 :: binary_restart_file_name, message
 
  306      CHARACTER(LEN=default_string_length)               :: section_label, section_name
 
  307      INTEGER                                            :: handle, input_unit, iparticle, istat, &
 
  309      INTEGER, 
ALLOCATABLE, 
DIMENSION(:)                 :: ibuf
 
  310      LOGICAL                                            :: exit_routine
 
  311      REAL(kind=
dp), 
ALLOCATABLE, 
DIMENSION(:, :)        :: rbuf
 
  315      CALL timeset(routinen, handle)
 
  318      cpassert(
ASSOCIATED(root_section))
 
  319      cpassert(
ASSOCIATED(subsys_section))
 
  321      para_env => logger%para_env
 
  323      binary_file_read = .false.
 
  325      IF (
ASSOCIATED(particle_set)) 
THEN 
  326         exit_routine = .false.
 
  327         nparticle = 
SIZE(particle_set)
 
  329         exit_routine = .true.
 
  334                                c_val=binary_restart_file_name)
 
  336      IF (trim(adjustl(binary_restart_file_name)) == 
"") 
THEN 
  337         CALL timestop(handle)
 
  342                                extension=
".subsysLog")
 
  344      section_name = prefix//
" COORDINATES" 
  347      IF (para_env%is_source()) 
THEN 
  348         CALL open_file(file_name=trim(binary_restart_file_name), &
 
  350                        file_form=
"UNFORMATTED", &
 
  351                        file_action=
"READWRITE", &
 
  352                        file_position=
"ASIS", &
 
  353                        unit_number=input_unit, &
 
  355         READ (unit=input_unit, iostat=istat) section_label, nbuf
 
  356         IF (istat /= 0) 
CALL stop_read(
"section_label, nbuf -> "//trim(section_label)//
", "// &
 
  358                                        " (IOSTAT = "//trim(adjustl(
cp_to_string(istat)))//
"). "// &
 
  359                                        "Section "//trim(adjustl(section_name))//
" was expected.", &
 
  361         IF (trim(section_label) == trim(section_name)) 
THEN 
  362            IF (nbuf /= nparticle) 
THEN 
  364                  message = 
"INFO: The requested number of "//trim(section_name)//
" ("// &
 
  365                            trim(adjustl(
cp_to_string(nparticle)))//
") does not match the "// &
 
  366                            "number ("//trim(adjustl(
cp_to_string(nbuf)))//
") available from the "// &
 
  367                            "binary restart file <"//trim(binary_restart_file_name)// &
 
  368                            ">. The restart file information is ignored." 
  374                  ALLOCATE (rbuf(3, nbuf))
 
  375                  READ (unit=input_unit, iostat=istat) rbuf(1:3, 1:nbuf)
 
  376                  IF (istat /= 0) 
CALL stop_read(
"rbuf(1:3,1:nbuf) -> "//prefix// &
 
  377                                                 " coordinates (IOSTAT = "// &
 
  381                  ALLOCATE (ibuf(nbuf))
 
  382                  READ (unit=input_unit, iostat=istat) ibuf(1:nbuf)
 
  383                  IF (istat /= 0) 
CALL stop_read(
"ibuf(1:nparticle) -> atomic indices of the "// &
 
  384                                                 trim(section_name)//
" (IOSTAT = "// &
 
  389               exit_routine = .true.
 
  392                  WRITE (unit=iw, fmt=
"(T2,A,T71,I10)") &
 
  393                     "Number of "//prefix//
" particles:", nparticle
 
  395               IF (nparticle == 0) exit_routine = .true.
 
  398            CALL cp_abort(__location__, &
 
  399                          "Section label <"//trim(section_label)//
"> read from the "// &
 
  400                          "binary restart file <"//trim(binary_restart_file_name)// &
 
  401                          "> does not match the requested section name <"// &
 
  402                          trim(section_name)//
">.")
 
  406      CALL para_env%bcast(exit_routine)
 
  407      IF (exit_routine) 
THEN 
  408         IF (para_env%is_source()) 
CALL close_file(unit_number=input_unit, &
 
  409                                                   keep_preconnection=.true.)
 
  410         CALL timestop(handle)
 
  414      cpassert(nparticle > 0)
 
  416      ALLOCATE (rbuf(3, nparticle))
 
  418      IF (para_env%is_source()) 
THEN 
  419         READ (unit=input_unit, iostat=istat) rbuf(1:3, 1:nparticle)
 
  420         IF (istat /= 0) 
CALL stop_read(
"rbuf(1:3,1:nparticle) -> "//prefix// &
 
  421                                        " coordinates (IOSTAT = "// &
 
  425      CALL para_env%bcast(rbuf)
 
  427      DO iparticle = 1, nparticle
 
  428         particle_set(iparticle)%r(1:3) = rbuf(1:3, iparticle)
 
  433      ALLOCATE (ibuf(nparticle))
 
  435      IF (para_env%is_source()) 
THEN 
  436         READ (unit=input_unit, iostat=istat) ibuf(1:nparticle)
 
  437         IF (istat /= 0) 
CALL stop_read(
"ibuf(1:nparticle) -> atomic indices of the "// &
 
  438                                        trim(section_name)//
" (IOSTAT = "// &
 
  443      CALL para_env%bcast(ibuf)
 
  445      DO iparticle = 1, nparticle
 
  446         particle_set(iparticle)%atom_index = ibuf(iparticle)
 
  452         WRITE (unit=iw, fmt=
"(T2,A)") &
 
  453            "BEGIN of "//trim(adjustl(section_name))// &
 
  454            " section data [Angstrom] read in binary format from file "// &
 
  455            trim(binary_restart_file_name)
 
  456         DO iparticle = 1, nparticle
 
  457            WRITE (unit=iw, fmt=
"(T2,A2,3(1X,ES25.16),1X,I0)") &
 
  458               trim(adjustl(particle_set(iparticle)%atomic_kind%name)), &
 
  459               particle_set(iparticle)%r(1:3)*
angstrom, &
 
  460               particle_set(iparticle)%atom_index
 
  462         WRITE (unit=iw, fmt=
"(T2,A)") &
 
  463            "END of "//trim(adjustl(section_name))// &
 
  464            " section data [Angstrom] read from binary restart file "// &
 
  465            trim(binary_restart_file_name)
 
  468      IF (para_env%is_source()) 
CALL close_file(unit_number=input_unit, &
 
  469                                                keep_preconnection=.true.)
 
  471      binary_file_read = .true.
 
  473      CALL timestop(handle)
 
 
  492                                     subsys_section, binary_file_read)
 
  494      CHARACTER(LEN=*), 
INTENT(IN)                       :: prefix
 
  499      LOGICAL, 
INTENT(OUT)                               :: binary_file_read
 
  501      CHARACTER(LEN=*), 
PARAMETER :: routinen = 
'read_binary_velocities' 
  503      CHARACTER(LEN=default_path_length)                 :: binary_restart_file_name, message
 
  504      CHARACTER(LEN=default_string_length)               :: section_label, section_name
 
  505      INTEGER                                            :: handle, i, input_unit, iparticle, istat, &
 
  507      LOGICAL                                            :: have_velocities
 
  508      REAL(kind=
dp), 
ALLOCATABLE, 
DIMENSION(:, :)        :: rbuf
 
  511      CALL timeset(routinen, handle)
 
  514      cpassert(
ASSOCIATED(root_section))
 
  515      cpassert(
ASSOCIATED(para_env))
 
  516      cpassert(
ASSOCIATED(subsys_section))
 
  519      binary_file_read = .false.
 
  522                                c_val=binary_restart_file_name)
 
  524      IF (trim(adjustl(binary_restart_file_name)) == 
"") 
THEN 
  525         CALL timestop(handle)
 
  530                                extension=
".subsysLog")
 
  532      IF (len_trim(prefix) == 0) 
THEN 
  533         section_name = 
"VELOCITIES" 
  535         section_name = prefix//
" VELOCITIES" 
  538      have_velocities = .false.
 
  540      IF (
ASSOCIATED(particle_set)) 
THEN 
  541         nparticle = 
SIZE(particle_set)
 
  548      IF (para_env%is_source()) 
THEN 
  549         CALL open_file(file_name=binary_restart_file_name, &
 
  551                        file_form=
"UNFORMATTED", &
 
  552                        file_action=
"READWRITE", &
 
  553                        file_position=
"ASIS", &
 
  554                        unit_number=input_unit, &
 
  557            READ (unit=input_unit, iostat=istat) section_label, nbuf
 
  558            IF (istat /= 0) 
CALL stop_read(
"section_label, nbuf -> "//trim(section_label)//
", "// &
 
  560                                           " (IOSTAT = "//trim(adjustl(
cp_to_string(istat)))//
"). "// &
 
  561                                           "Section "//trim(adjustl(section_name))//
" was expected.", &
 
  563            IF (index(section_label, 
"THERMOSTAT") > 0) 
THEN 
  566                  ALLOCATE (rbuf(nbuf, 1))
 
  569                     READ (unit=input_unit, iostat=istat) rbuf(1:nbuf, 1)
 
  570                     IF (istat /= 0) 
CALL stop_read(
"rbuf(1:nbuf,1) -> "// &
 
  571                                                    trim(adjustl(section_label))// &
 
  572                                                    " (IOSTAT = "//trim(adjustl(
cp_to_string(istat)))//
")", &
 
  577                     message = 
"INFO: Ignoring section <"//trim(adjustl(section_label))// &
 
  578                               "> from binary restart file <"//trim(binary_restart_file_name)//
">." 
  583            ELSE IF (index(section_label, 
"VELOCIT") == 0) 
THEN 
  584               CALL cp_abort(__location__, &
 
  585                             "Section label <"//trim(section_label)//
"> read from the "// &
 
  586                             "binary restart file <"//trim(binary_restart_file_name)// &
 
  587                             "> does not match the requested section name <"// &
 
  588                             trim(section_name)//
">.")
 
  590               IF (nbuf > 0) have_velocities = .true.
 
  596      CALL para_env%bcast(nbuf)
 
  597      CALL para_env%bcast(have_velocities)
 
  599      IF (have_velocities) 
THEN 
  601         ALLOCATE (rbuf(3, nbuf))
 
  603         IF (para_env%is_source()) 
THEN 
  604            READ (unit=input_unit, iostat=istat) rbuf(1:3, 1:nbuf)
 
  605            IF (istat /= 0) 
CALL stop_read(
"rbuf(1:3,1:nbuf) -> "// &
 
  606                                           trim(adjustl(section_name))// &
 
  607                                           " (IOSTAT = "//trim(adjustl(
cp_to_string(istat)))//
")", &
 
  611         IF (nbuf == nparticle) 
THEN 
  612            CALL para_env%bcast(rbuf)
 
  613            DO iparticle = 1, nparticle
 
  614               particle_set(iparticle)%v(1:3) = rbuf(1:3, iparticle)
 
  618               message = 
"INFO: The requested number of "//trim(adjustl(section_name))// &
 
  619                         " ("//trim(adjustl(
cp_to_string(nparticle)))//
") does not match the "// &
 
  620                         "number ("//trim(adjustl(
cp_to_string(nbuf)))//
") available from the "// &
 
  621                         "binary restart file <"//trim(binary_restart_file_name)// &
 
  622                         ">. The restart file information is ignored." 
  631      IF (nbuf == nparticle) 
THEN 
  633            WRITE (unit=iw, fmt=
"(T2,A)") &
 
  634               "BEGIN of "//trim(adjustl(section_name))// &
 
  635               " section data [a.u.] read in binary format from file "// &
 
  636               trim(binary_restart_file_name)
 
  637            IF (have_velocities) 
THEN 
  638               DO iparticle = 1, nparticle
 
  639                  WRITE (unit=iw, fmt=
"(T2,A2,3(1X,ES25.16))") &
 
  640                     trim(adjustl(particle_set(iparticle)%atomic_kind%name)), &
 
  641                     particle_set(iparticle)%v(1:3)
 
  644               WRITE (unit=iw, fmt=
"(A)") &
 
  645                  "# No "//trim(adjustl(section_name))//
" available" 
  647            WRITE (unit=iw, fmt=
"(T2,A)") &
 
  648               "END of "//trim(adjustl(section_name))// &
 
  649               " section data [a.u.] read from binary restart file "// &
 
  650               trim(binary_restart_file_name)
 
  652         binary_file_read = .true.
 
  655      IF (para_env%is_source()) 
CALL close_file(unit_number=input_unit, &
 
  656                                                keep_preconnection=.true.)
 
  658      CALL timestop(handle)
 
 
  678      CHARACTER(LEN=*), 
INTENT(IN)                       :: prefix
 
  680      CHARACTER(LEN=*), 
INTENT(IN)                       :: binary_restart_file_name
 
  681      LOGICAL, 
INTENT(OUT)                               :: restart
 
  684      CHARACTER(LEN=*), 
PARAMETER :: routinen = 
'read_binary_thermostats_nose' 
  686      CHARACTER(LEN=default_string_length)               :: section_label, section_name
 
  687      INTEGER                                            :: handle, i, 
idx, input_unit, istat, j, &
 
  688                                                            nhc_size, output_unit
 
  690      REAL(kind=
dp), 
ALLOCATABLE, 
DIMENSION(:)           :: rbuf
 
  693      CALL timeset(routinen, handle)
 
  695      cpassert(
ASSOCIATED(nhc))
 
  696      cpassert(
ASSOCIATED(para_env))
 
  711      section_name = prefix//
" THERMOSTATS" 
  714      IF (para_env%is_source()) 
THEN 
  715         CALL open_file(file_name=binary_restart_file_name, &
 
  717                        file_form=
"UNFORMATTED", &
 
  718                        file_action=
"READWRITE", &
 
  719                        file_position=
"ASIS", &
 
  720                        unit_number=input_unit)
 
  721         READ (unit=input_unit, iostat=istat) section_label, nhc_size
 
  722         IF (istat /= 0) 
CALL stop_read(
"nhc_size (IOSTAT = "// &
 
  725         IF (index(section_label, 
"THERMOSTAT") == 0) 
THEN 
  726            CALL cp_abort(__location__, &
 
  727                          "Section label <"//trim(section_label)//
"> read from the "// &
 
  728                          "binary restart file <"//trim(binary_restart_file_name)// &
 
  729                          "> does not match the requested section name <"// &
 
  730                          trim(section_name)//
">.")
 
  732         IF (debug .AND. output_unit > 0) 
THEN 
  733            WRITE (unit=output_unit, fmt=
"(T2,A,/,T2,A,I0)") &
 
  734               "BEGIN of "//trim(adjustl(section_label))// &
 
  735               " section data read in binary format from file "// &
 
  736               trim(binary_restart_file_name), &
 
  737               "# nhc_size = ", nhc_size
 
  741      CALL para_env%bcast(nhc_size)
 
  743      IF (nhc_size > 0) 
THEN 
  745         ALLOCATE (rbuf(nhc_size))
 
  749         IF (para_env%is_source()) 
THEN 
  750            READ (unit=input_unit, iostat=istat) rbuf(1:nhc_size)
 
  751            IF (istat /= 0) 
CALL stop_read(
"eta -> rbuf (IOSTAT = "// &
 
  754            IF (debug .AND. output_unit > 0) 
THEN 
  755               WRITE (unit=output_unit, fmt=
"(T2,A,/,(4(1X,ES25.16)))") &
 
  756                  "&COORD", rbuf(1:nhc_size)
 
  759         CALL para_env%bcast(rbuf)
 
  760         DO i = 1, 
SIZE(nhc%nvt, 2)
 
  761            idx = (nhc%map_info%index(i) - 1)*nhc%nhc_len
 
  762            DO j = 1, 
SIZE(nhc%nvt, 1)
 
  764               nhc%nvt(j, i)%eta = rbuf(
idx)
 
  769         IF (para_env%is_source()) 
THEN 
  770            READ (unit=input_unit, iostat=istat) rbuf(1:nhc_size)
 
  771            IF (istat /= 0) 
CALL stop_read(
"veta -> rbuf (IOSTAT = "// &
 
  774            IF (debug .AND. output_unit > 0) 
THEN 
  775               WRITE (unit=output_unit, fmt=
"(T2,A,/,(4(1X,ES25.16)))") &
 
  776                  "&VELOCITY", rbuf(1:nhc_size)
 
  779         CALL para_env%bcast(rbuf)
 
  780         DO i = 1, 
SIZE(nhc%nvt, 2)
 
  781            idx = (nhc%map_info%index(i) - 1)*nhc%nhc_len
 
  782            DO j = 1, 
SIZE(nhc%nvt, 1)
 
  784               nhc%nvt(j, i)%v = rbuf(
idx)
 
  789         IF (para_env%is_source()) 
THEN 
  790            READ (unit=input_unit, iostat=istat) rbuf(1:nhc_size)
 
  791            IF (istat /= 0) 
CALL stop_read(
"mnhc -> rbuf (IOSTAT = "// &
 
  794            IF (debug .AND. output_unit > 0) 
THEN 
  795               WRITE (unit=output_unit, fmt=
"(T2,A,/,(4(1X,ES25.16)))") &
 
  796                  "&MASS:", rbuf(1:nhc_size)
 
  799         CALL para_env%bcast(rbuf)
 
  800         DO i = 1, 
SIZE(nhc%nvt, 2)
 
  801            idx = (nhc%map_info%index(i) - 1)*nhc%nhc_len
 
  802            DO j = 1, 
SIZE(nhc%nvt, 1)
 
  804               nhc%nvt(j, i)%mass = rbuf(
idx)
 
  809         IF (para_env%is_source()) 
THEN 
  810            READ (unit=input_unit, iostat=istat) rbuf(1:nhc_size)
 
  811            IF (istat /= 0) 
CALL stop_read(
"fnhc -> rbuf (IOSTAT = "// &
 
  814            IF (debug .AND. output_unit > 0) 
THEN 
  815               WRITE (unit=output_unit, fmt=
"(T2,A,/,(4(1X,ES25.16)))") &
 
  816                  "&FORCE", rbuf(1:nhc_size)
 
  819         CALL para_env%bcast(rbuf)
 
  820         DO i = 1, 
SIZE(nhc%nvt, 2)
 
  821            idx = (nhc%map_info%index(i) - 1)*nhc%nhc_len
 
  822            DO j = 1, 
SIZE(nhc%nvt, 1)
 
  824               nhc%nvt(j, i)%f = rbuf(
idx)
 
  834      IF (para_env%is_source()) 
THEN 
  835         IF (debug .AND. output_unit > 0) 
THEN 
  836            WRITE (unit=output_unit, fmt=
"(T2,A)") &
 
  837               "END of"//trim(adjustl(section_label))// &
 
  838               " section data read in binary format from file "// &
 
  839               trim(binary_restart_file_name)
 
  842                         keep_preconnection=.true.)
 
  845      CALL timestop(handle)
 
 
  861   SUBROUTINE stop_read(object, unit_number)
 
  862      CHARACTER(LEN=*), 
INTENT(IN)                       :: object
 
  863      INTEGER, 
INTENT(IN)                                :: unit_number
 
  865      CHARACTER(LEN=2*default_path_length)               :: message
 
  866      CHARACTER(LEN=default_path_length)                 :: file_name
 
  869      IF (unit_number >= 0) 
THEN 
  875         INQUIRE (unit=unit_number, name=file_name)
 
  876         WRITE (unit=message, fmt=
"(A)") &
 
  877            "An error occurred reading data object <"//trim(adjustl(object))// &
 
  878            "> from file <"//trim(adjustl(file_name))//
">" 
  880         WRITE (unit=message, fmt=
"(A,I0,A)") &
 
  881            "Could not read data object <"//trim(adjustl(object))// &
 
  882            "> from logical unit ", unit_number, 
". The I/O unit does not exist." 
  887   END SUBROUTINE stop_read
 
static GRID_HOST_DEVICE int idx(const orbital a)
Return coset index of given orbital angular momentum.
 
Utility routines to open and close files. Tracking of preconnections.
 
subroutine, public open_file(file_name, file_status, file_form, file_action, file_position, file_pad, unit_number, debug, skip_get_unit_number, file_access)
Opens the requested file using a free unit number.
 
subroutine, public close_file(unit_number, file_status, keep_preconnection)
Close an open file given by its logical unit number. Optionally, keep the file and unit preconnected.
 
logical function, public file_exists(file_name)
Checks if file exists, considering also the file discovery mechanism.
 
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, parameter, public debug_print_level
 
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)
...
 
Lumps all possible extended system variables into one type for easy access and passing.
 
Defines the basic variable types.
 
integer, parameter, public dp
 
integer, parameter, public default_string_length
 
integer, parameter, public default_path_length
 
Interface to the message passing library MPI.
 
Define the data structure for the particle information.
 
Definition of physical constants:
 
real(kind=dp), parameter, public angstrom
 
Perform an abnormal program termination.
 
subroutine, public print_message(message, output_unit, declev, before, after)
Perform a basic blocking of the text in message and print it optionally decorated with a frame of sta...
 
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
 
Control for reading in different topologies and coordinates.
 
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