92#include "../base/base_uses.f90" 
   98   CHARACTER(len=*), 
PARAMETER, 
PRIVATE :: moduleN = 
'tmc_worker' 
  103   INTEGER, 
PARAMETER :: DEBUG = 0
 
  118      CHARACTER(LEN=*), 
PARAMETER                        :: routinen = 
'do_tmc_worker' 
  120      CHARACTER(LEN=default_string_length)               :: c_tmp
 
  121      INTEGER                                            :: calc_stat, handle, i1, i2, ierr, itmp, &
 
  123      INTEGER, 
DIMENSION(:), 
POINTER                     :: ana_restart_conf
 
  124      LOGICAL                                            :: flag, master
 
  131      NULLIFY (conf, para_env_m_w, ana_restart_conf)
 
  133      cpassert(
ASSOCIATED(tmc_env))
 
  136      CALL timeset(routinen, handle)
 
  139      IF (tmc_env%tmc_comp_set%group_nr .GT. 0) 
THEN 
  140         cpassert(
ASSOCIATED(tmc_env%tmc_comp_set%para_env_sub_group))
 
  141         IF (tmc_env%w_env%env_id_ener .GT. 0) 
THEN 
  142            itmp = tmc_env%w_env%env_id_ener
 
  144            itmp = tmc_env%w_env%env_id_approx
 
  148                                      atoms=tmc_env%params%atoms, cell=tmc_env%params%cell)
 
  149         para_env_m_w => tmc_env%tmc_comp_set%para_env_m_w
 
  153         cpassert(
ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_ana))
 
  154         para_env_m_w => tmc_env%tmc_comp_set%para_env_m_ana
 
  162         IF (tmc_env%tmc_comp_set%group_nr .GT. 0) 
THEN 
  163            IF (tmc_env%w_env%env_id_ener .GT. 0) 
THEN 
  164               itmp = tmc_env%w_env%env_id_ener
 
  166               itmp = tmc_env%w_env%env_id_approx
 
  170            IF (tmc_env%params%use_scf_energy_info) &
 
  171               CALL set_intermediate_info_comm(env_id=itmp, &
 
  172                                               comm=tmc_env%tmc_comp_set%para_env_m_w)
 
  173            IF (tmc_env%params%SPECULATIVE_CANCELING) &
 
  186                             para_env=para_env_m_w, &
 
  187                             result_count=ana_restart_conf, &
 
  188                             tmc_params=tmc_env%params, elem=conf)
 
  191               WRITE (tmc_env%w_env%io_unit, *) 
"worker: group master of group ", &
 
  192               tmc_env%tmc_comp_set%group_nr, 
"got task ", work_stat
 
  194            SELECT CASE (work_stat)
 
  201                                para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
 
  202                                tmc_params=tmc_env%params)
 
  208                                para_env=para_env_m_w, &
 
  209                                tmc_params=tmc_env%params)
 
  212                  WRITE (tmc_env%w_env%io_unit, *) 
"master worker of group", &
 
  213                  tmc_env%tmc_comp_set%group_nr, 
" exit work time." 
  214               EXIT master_work_time
 
  217               IF (tmc_env%w_env%env_id_ener .GT. 0) 
THEN 
  218                  itmp = tmc_env%w_env%env_id_ener
 
  220                  itmp = tmc_env%w_env%env_id_approx
 
  229                                para_env=para_env_m_w, &
 
  230                                tmc_params=tmc_env%params, elem=conf, &
 
  231                                wait_for_message=.true.)
 
  233               IF (
ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_first_w)) &
 
  236                                              para_env=tmc_env%tmc_comp_set%para_env_m_first_w)
 
  239               cpassert(tmc_env%w_env%env_id_approx .GT. 0)
 
  244                                para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
 
  245                                tmc_params=tmc_env%params, elem=conf)
 
  247                                          env_id=tmc_env%w_env%env_id_approx, &
 
  248                                          exact_approx_pot=.false., &
 
  254                                para_env=para_env_m_w, &
 
  255                                tmc_params=tmc_env%params, elem=conf)
 
  262                                para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
 
  263                                tmc_params=tmc_env%params, elem=conf)
 
  267                  CALL nested_markov_chain_mc(conf=conf, &
 
  268                                              env_id=tmc_env%w_env%env_id_approx, &
 
  269                                              tmc_env=tmc_env, calc_status=calc_stat)
 
  272                  cpabort(
"there is no Hybrid MC implemented yet.")
 
  275                  cpabort(
"unknown task type for workers.")
 
  281                                para_env=para_env_m_w, &
 
  282                                tmc_params=tmc_env%params, &
 
  284               SELECT CASE (calc_stat)
 
  286                  SELECT CASE (work_stat)
 
  292                     CALL cp_abort(__location__, &
 
  293                                   "unknown work status after possible NMC subgroup "// &
 
  299                  CALL cp_abort(__location__, &
 
  300                                "unknown calc status before sending NMC result "// &
 
  307                                para_env=para_env_m_w, &
 
  308                                tmc_params=tmc_env%params, elem=conf)
 
  310               cpassert(tmc_env%w_env%env_id_ener .GT. 0)
 
  315                                para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
 
  316                                tmc_params=tmc_env%params, elem=conf)
 
  319                                          env_id=tmc_env%w_env%env_id_ener, &
 
  320                                          exact_approx_pot=.true., &
 
  327                                para_env=para_env_m_w, &
 
  328                                tmc_params=tmc_env%params, success=flag)
 
  329               SELECT CASE (calc_stat)
 
  331                  SELECT CASE (work_stat)
 
  335                     IF (tmc_env%params%print_dipole) 
THEN 
  337                        CALL get_result_r1(env_id=tmc_env%w_env%env_id_ener, &
 
  338                                           description=c_tmp, n=3, result=conf%dipole, &
 
  339                                           res_exist=flag, ierr=ierr)
 
  340                        IF (.NOT. flag) tmc_env%params%print_dipole = .false.
 
  343                           CALL cp_abort(__location__, &
 
  344                                         "TMC: The requested dipoles are not porvided by the "// &
 
  345                                         "force environment.")
 
  348                     CALL cp_abort(__location__, &
 
  349                                   "energy worker should handle unknown stat "// &
 
  355                  CALL cp_abort(__location__, &
 
  356                                "worker while energy calc is in unknown state "// &
 
  362                  WRITE (tmc_env%w_env%io_unit, *) 
"worker group ", &
 
  363                  tmc_env%tmc_comp_set%group_nr, &
 
  364                  "calculations done, send result energy", conf%potential
 
  368                                para_env=para_env_m_w, &
 
  369                                tmc_params=tmc_env%params, elem=conf)
 
  371               cpassert(
ASSOCIATED(ana_restart_conf))
 
  372               cpassert(
SIZE(ana_restart_conf) .EQ. tmc_env%params%nr_temp)
 
  373               cpassert(
PRESENT(ana_list))
 
  374               cpassert(
ASSOCIATED(ana_list))
 
  377                                           source=itmp, para_env=tmc_env%tmc_comp_set%para_env_m_ana)
 
  379               num_dim = 
SIZE(conf%pos)
 
  380               DO itmp = 1, tmc_env%params%nr_temp
 
  382                  ana_list(itmp)%temp%temperature = tmc_env%params%Temp(itmp)
 
  383                  ana_list(itmp)%temp%atoms => tmc_env%params%atoms
 
  384                  ana_list(itmp)%temp%cell => tmc_env%params%cell
 
  387                  CALL analysis_init(ana_env=ana_list(itmp)%temp, nr_dim=num_dim)
 
  388                  ana_list(itmp)%temp%print_test_output = tmc_env%params%print_test_output
 
  389                  IF (.NOT. 
ASSOCIATED(conf)) &
 
  391                                                     next_el=conf, nr_dim=num_dim)
 
  396                  IF ((.NOT. 
ASSOCIATED(ana_list(itmp)%temp%last_elem)) .AND. &
 
  397                      ana_restart_conf(itmp) .GT. 0) 
THEN 
  400                     i2 = ana_restart_conf(itmp)
 
  401                     CALL cp_warn(__location__, &
 
  402                                  "analysis old trajectory up to "// &
 
  404                                  ". Read trajectory file.")
 
  405                  ELSE IF (
ASSOCIATED(ana_list(itmp)%temp%last_elem)) 
THEN 
  406                     IF (.NOT. (ana_list(itmp)%temp%last_elem%nr .EQ. ana_restart_conf(itmp))) 
THEN 
  408                        i1 = ana_list(itmp)%temp%last_elem%nr
 
  409                        i2 = ana_restart_conf(itmp)
 
  410                        CALL cp_warn(__location__, &
 
  411                                     "analysis restart with the incorrect configuration "// &
 
  413                                     " ana "//
cp_to_string(ana_list(itmp)%temp%last_elem%nr)// &
 
  414                                     ". REread trajectory file.")
 
  420                                                      ana_env=ana_list(itmp)%temp, &
 
  421                                                      tmc_params=tmc_env%params)
 
  425               cpassert(
PRESENT(ana_list))
 
  426               cpassert(
ASSOCIATED(ana_list(conf%sub_tree_nr)%temp))
 
  428                                    ana_env=ana_list(conf%sub_tree_nr)%temp)
 
  433                                para_env=para_env_m_w, &
 
  434                                tmc_params=tmc_env%params, elem=conf)
 
  436               CALL cp_abort(__location__, &
 
  437                             "worker received unknown message task type "// &
 
  442               WRITE (tmc_env%w_env%io_unit, *) 
"worker: group ", &
 
  443               tmc_env%tmc_comp_set%group_nr, &
 
  444               "send back status:", work_stat
 
  445            IF (
ASSOCIATED(conf)) &
 
  447         END DO master_work_time
 
  456                             para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
 
  457                             tmc_params=tmc_env%params, elem=conf)
 
  459            SELECT CASE (work_stat)
 
  465               EXIT worker_work_time
 
  468               cpassert(tmc_env%w_env%env_id_approx .GT. 0)
 
  470               SELECT CASE (tmc_env%params%task_type)
 
  472                  IF (tmc_env%params%NMC_inp_file .NE. 
"") 
THEN 
  473                     conf%box_scale(:) = 1.0_dp
 
  475                                                env_id=tmc_env%w_env%env_id_approx, &
 
  476                                                exact_approx_pot=.false., &
 
  480                  CALL cp_abort(__location__, &
 
  481                                "unknown task_type for participants in "// &
 
  482                                "START_CONF_RESULT request ")
 
  489                  CALL nested_markov_chain_mc(conf=conf, &
 
  490                                              env_id=tmc_env%w_env%env_id_approx, &
 
  491                                              tmc_env=tmc_env, calc_status=calc_stat)
 
  494                  cpabort(
"there is no Hybrid MC implemented yet.")
 
  497                  cpabort(
"unknown task type for workers.")
 
  502               cpassert(tmc_env%w_env%env_id_approx .GT. 0)
 
  504                                          env_id=tmc_env%w_env%env_id_approx, &
 
  505                                          exact_approx_pot=.false., &
 
  509               cpassert(tmc_env%w_env%env_id_ener .GT. 0)
 
  511                                          env_id=tmc_env%w_env%env_id_ener, &
 
  512                                          exact_approx_pot=.true., &
 
  515               CALL cp_abort(__location__, &
 
  516                             "group participant got unknown working type "// &
 
  519            IF (
ASSOCIATED(conf)) &
 
  521         END DO worker_work_time
 
  525      IF (
ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_ana)) 
THEN 
  526         DO itmp = 1, tmc_env%params%nr_temp
 
  528            IF (
ASSOCIATED(conf)) &
 
  537         IF (tmc_env%tmc_comp_set%group_nr .GT. 0) 
THEN 
  540            IF (tmc_env%params%use_scf_energy_info) 
THEN 
  541               IF (tmc_env%w_env%env_id_ener .GT. 0) 
THEN 
  542                  itmp = tmc_env%w_env%env_id_ener
 
  544                  itmp = tmc_env%w_env%env_id_approx
 
  546               CALL remove_intermediate_info_comm(env_id=itmp)
 
  549         IF (
ASSOCIATED(tmc_env%tmc_comp_set%para_env_sub_group)) &
 
  551                                  tmc_params=tmc_env%params)
 
  556                          para_env=para_env_m_w, &
 
  557                          tmc_params=tmc_env%params)
 
  558      ELSE IF (
ASSOCIATED(tmc_env%tmc_comp_set%para_env_sub_group)) 
THEN 
  562                          para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
 
  563                          tmc_params=tmc_env%params)
 
  567         WRITE (tmc_env%w_env%io_unit, *) 
"worker ", &
 
  568         tmc_env%tmc_comp_set%para_env_sub_group%mepos, 
"of group ", &
 
  569         tmc_env%tmc_comp_set%group_nr, 
"stops working!" 
  571      IF (
PRESENT(ana_list)) 
THEN 
  572         DO itmp = 1, tmc_env%params%nr_temp
 
  573            ana_list(itmp)%temp%atoms => null()
 
  574            ana_list(itmp)%temp%cell => null()
 
  577      IF (
ASSOCIATED(conf)) &
 
  579      IF (
ASSOCIATED(ana_restart_conf)) 
DEALLOCATE (ana_restart_conf)
 
  582      CALL timestop(handle)
 
 
  597   SUBROUTINE nested_markov_chain_mc(conf, env_id, tmc_env, calc_status)
 
  599      INTEGER, 
INTENT(IN)                                :: env_id
 
  601      INTEGER, 
INTENT(OUT)                               :: calc_status
 
  603      CHARACTER(LEN=*), 
PARAMETER :: routinen = 
'nested_markov_chain_MC' 
  605      INTEGER                                            :: comm_dest, handle, substeps
 
  606      LOGICAL                                            :: accept, change_rejected, flag
 
  607      REAL(kind=
dp)                                      :: rnd_nr
 
  608      TYPE(
tree_type), 
POINTER                           :: last_acc_conf
 
  610      NULLIFY (last_acc_conf)
 
  612      cpassert(
ASSOCIATED(tmc_env))
 
  613      cpassert(
ASSOCIATED(tmc_env%params))
 
  614      cpassert(
ASSOCIATED(tmc_env%tmc_comp_set))
 
  615      cpassert(
ALLOCATED(tmc_env%rng_stream))
 
  616      cpassert(
ASSOCIATED(conf))
 
  617      cpassert(conf%temp_created .GT. 0)
 
  618      cpassert(conf%temp_created .LE. tmc_env%params%nr_temp)
 
  619      cpassert(env_id .GT. 0)
 
  623      CALL timeset(routinen, handle)
 
  626                                      next_el=last_acc_conf, nr_dim=
SIZE(conf%pos))
 
  628      last_acc_conf%pos = conf%pos
 
  629      last_acc_conf%box_scale = conf%box_scale
 
  633                                 env_id=tmc_env%w_env%env_id_approx, exact_approx_pot=.false., &
 
  636      nmc_steps: 
DO substeps = 1, int(tmc_env%params%move_types%mv_size(
mv_type_nmc_moves, 1))
 
  638         IF (
ASSOCIATED(tmc_env%tmc_comp_set%para_env_m_w)) 
THEN 
  644                             para_env=tmc_env%tmc_comp_set%para_env_m_w, &
 
  645                             tmc_params=tmc_env%params, success=flag)
 
  650                          para_env=tmc_env%tmc_comp_set%para_env_sub_group, &
 
  651                          tmc_params=tmc_env%params)
 
  652         SELECT CASE (calc_status)
 
  659            CALL cp_abort(__location__, &
 
  661                          "in the NMC routine, expect only caneling status. ")
 
  665         CALL tmc_env%rng_stream%set( &
 
  666            bg=conf%rng_seed(:, :, 1), cg=conf%rng_seed(:, :, 2), &
 
  667            ig=conf%rng_seed(:, :, 3))
 
  669                          move_types=tmc_env%params%nmc_move_types, &
 
  670                          rnd=tmc_env%rng_stream%next())
 
  671         CALL tmc_env%rng_stream%get( &
 
  672            bg=conf%rng_seed(:, :, 1), cg=conf%rng_seed(:, :, 2), &
 
  673            ig=conf%rng_seed(:, :, 3))
 
  677                         move_types=tmc_env%params%nmc_move_types, &
 
  678                         rng_stream=tmc_env%rng_stream, &
 
  679                         elem=conf, mv_conf=1, new_subbox=.false., &
 
  680                         move_rejected=change_rejected)
 
  687            CALL cp_abort(__location__, &
 
  688                          "Hybrid MC is not implemented yet, "// &
 
  689                          "(no MD section in TMC yet). ")
 
  693         CALL prob_update(move_types=tmc_env%params%nmc_move_types, elem=conf, &
 
  694                          acc=.NOT. change_rejected, subbox=.true., &
 
  695                          prob_opt=tmc_env%params%esimate_acc_prob)
 
  698         IF (.NOT. change_rejected) 
THEN 
  700                                       env_id=tmc_env%w_env%env_id_approx, exact_approx_pot=.false., &
 
  703            conf%e_pot_approx = huge(conf%e_pot_approx)
 
  707         CALL tmc_env%rng_stream%set( &
 
  708            bg=conf%rng_seed(:, :, 1), cg=conf%rng_seed(:, :, 2), &
 
  709            ig=conf%rng_seed(:, :, 3))
 
  710         rnd_nr = tmc_env%rng_stream%next()
 
  711         CALL tmc_env%rng_stream%get( &
 
  712            bg=conf%rng_seed(:, :, 1), cg=conf%rng_seed(:, :, 2), &
 
  713            ig=conf%rng_seed(:, :, 3))
 
  715         IF (.NOT. change_rejected) 
THEN 
  717                                  tmc_params=tmc_env%params, &
 
  718                                  temperature=tmc_env%params%Temp(conf%temp_created), &
 
  719                                  diff_pot_check=.false., &
 
  720                                  accept=accept, approx_ener=.true., rnd_nr=rnd_nr)
 
  725         CALL prob_update(move_types=tmc_env%params%nmc_move_types, elem=conf, &
 
  726                          acc=accept, prob_opt=tmc_env%params%esimate_acc_prob)
 
  729         IF (accept .AND. (.NOT. change_rejected)) 
THEN 
  730            last_acc_conf%pos = conf%pos
 
  731            last_acc_conf%vel = conf%vel
 
  732            last_acc_conf%e_pot_approx = conf%e_pot_approx
 
  733            last_acc_conf%ekin = conf%ekin
 
  734            last_acc_conf%ekin_before_md = conf%ekin_before_md
 
  735            last_acc_conf%box_scale = conf%box_scale
 
  737            conf%pos = last_acc_conf%pos
 
  738            conf%vel = last_acc_conf%vel
 
  739            conf%box_scale = last_acc_conf%box_scale
 
  745      conf%pos = last_acc_conf%pos
 
  746      conf%vel = last_acc_conf%vel
 
  747      conf%e_pot_approx = last_acc_conf%e_pot_approx
 
  748      conf%potential = 0.0_dp
 
  749      conf%ekin = last_acc_conf%ekin
 
  750      conf%ekin_before_md = last_acc_conf%ekin_before_md
 
  755      CALL timestop(handle)
 
  756   END SUBROUTINE nested_markov_chain_mc
 
  771      CHARACTER(LEN=*), 
PARAMETER                        :: routinen = 
'get_initial_conf' 
  773      INTEGER                                            :: handle, ierr, mol, ndim, nr_atoms
 
  778      cpassert(.NOT. 
ASSOCIATED(init_conf))
 
  781      CALL timeset(routinen, handle)
 
  784      CALL get_natom(env_id=env_id, n_atom=nr_atoms, ierr=ierr)
 
  785      cpassert(ierr .EQ. 0)
 
  788                                      next_el=init_conf, nr_dim=ndim)
 
  789      CALL get_pos(env_id=env_id, pos=init_conf%pos, n_el=
SIZE(init_conf%pos), &
 
  797      loop_mol: 
DO mol = 1, 
SIZE(molecule_new%els(:))
 
  798         init_conf%mol(molecule_new%els(mol)%first_atom: &
 
  799                       molecule_new%els(mol)%last_atom) = mol
 
  803      CALL timestop(handle)
 
 
  819      INTEGER                                            :: iparticle, nr_atoms, nunits_tot
 
  825      NULLIFY (f_env, subsys, particles)
 
  828      cpassert(env_id .GT. 0)
 
  829      cpassert(.NOT. 
ASSOCIATED(atoms))
 
  830      cpassert(.NOT. 
ASSOCIATED(cell))
 
  834      CALL force_env_get(f_env%force_env, subsys=subsys, cell=cell_tmp)
 
  836      CALL cell_copy(cell_in=cell_tmp, cell_out=cell)
 
  841      nunits_tot = 
SIZE(particles%els(:))
 
  842      IF (nunits_tot .GT. 0) 
THEN 
  843         DO iparticle = 1, nunits_tot
 
  844            atoms(iparticle)%name = particles%els(iparticle)%atomic_kind%name
 
  845            atoms(iparticle)%mass = particles%els(iparticle)%atomic_kind%mass
 
  847         cpassert(iparticle - 1 .EQ. nr_atoms)
 
 
  858   SUBROUTINE set_intermediate_info_comm(comm, env_id)
 
  862      CHARACTER(LEN=default_string_length)               :: description
 
  863      REAL(kind=
dp), 
DIMENSION(3)                        :: values
 
  868      NULLIFY (results, subsys)
 
  869      cpassert(env_id .GT. 0)
 
  873      cpassert(
ASSOCIATED(f_env))
 
  874      cpassert(
ASSOCIATED(f_env%force_env))
 
  875      IF (.NOT. 
ASSOCIATED(f_env%force_env%qs_env)) &
 
  876         CALL cp_abort(__location__, &
 
  877                       "the intermediate SCF energy request can not be set "// &
 
  878                       "employing this force environment! ")
 
  881      values(1) = real(comm%get_handle(), kind=
dp)
 
  884      description = 
"[EXT_SCF_ENER_COMM]" 
  889      CALL put_results(results, description=description, values=values)
 
  890   END SUBROUTINE set_intermediate_info_comm
 
  898   SUBROUTINE remove_intermediate_info_comm(env_id)
 
  901      CHARACTER(LEN=default_string_length)               :: description
 
  906      NULLIFY (subsys, results)
 
  907      cpassert(env_id .GT. 0)
 
  911      cpassert(
ASSOCIATED(f_env))
 
  912      cpassert(
ASSOCIATED(f_env%force_env))
 
  913      IF (.NOT. 
ASSOCIATED(f_env%force_env%qs_env)) &
 
  914         CALL cp_abort(__location__, &
 
  915                       "the SCF intermediate energy communicator can not be "// &
 
  918      description = 
"[EXT_SCF_ENER_COMM]" 
  924   END SUBROUTINE remove_intermediate_info_comm
 
Handles all functions related to the CELL.
 
subroutine, public init_cell(cell, hmat, periodic)
Initialise/readjust a simulation cell after hmat has been changed.
 
Handles all functions related to the CELL.
 
subroutine, public cell_copy(cell_in, cell_out, tag)
Copy cell variable.
 
Routines to handle the external control of CP2K.
 
subroutine, public set_external_comm(comm, in_external_master_id, in_scf_energy_message_tag, in_exit_tag)
set the communicator to an external source or destination, to send messages (e.g. intermediate energi...
 
various routines to log and control the output. The idea is that decisions about where to log should ...
 
set of type/routines to handle the storage of results in force_envs
 
subroutine, public cp_results_erase(results, description, nval)
erase a part of result_list
 
set of type/routines to handle the storage of results in force_envs
 
types that represent a subsys, i.e. a part of the system
 
subroutine, public cp_subsys_get(subsys, ref_count, atomic_kinds, atomic_kind_set, particles, particle_set, local_particles, molecules, molecule_set, molecule_kinds, molecule_kind_set, local_molecules, para_env, colvar_p, shell_particles, core_particles, gci, multipoles, natom, nparticle, ncore, nshell, nkind, atprop, virial, results, cell)
returns information about various attributes of the given subsys
 
interface to use cp2k as library
 
subroutine, public f_env_get_from_id(f_env_id, f_env)
...
 
subroutine, public get_natom(env_id, n_atom, ierr)
returns the number of atoms in the given force env
 
subroutine, public get_pos(env_id, pos, n_el, ierr)
gets the positions of the particles
 
Interface for the force calculations.
 
integer function, public force_env_get_natom(force_env)
returns the number of atoms
 
recursive subroutine, public force_env_get(force_env, in_use, fist_env, qs_env, meta_env, fp_env, subsys, para_env, potential_energy, additional_potential, kinetic_energy, harmonic_shell, kinetic_shell, cell, sub_force_env, qmmm_env, qmmmx_env, eip_env, pwdft_env, globenv, input, force_env_section, method_name_id, root_section, mixed_env, nnp_env, embed_env, ipi_env)
returns various attributes about the force environment
 
Defines the basic variable types.
 
integer, parameter, public dp
 
integer, parameter, public default_string_length
 
Interface to the message passing library MPI.
 
represent a simple array based list of the given type
 
represent a simple array based list of the given type
 
module provides variables for the TMC analysis tool
 
module analyses element of the TMC tree element structure e.g. density, radial distribution function,...
 
subroutine, public analysis_restart_read(ana_env, elem)
read analysis restart file
 
subroutine, public finalize_tmc_analysis(ana_env)
call all the necessarry analysis printing routines
 
subroutine, public analyze_file_configurations(start_id, end_id, dir_ind, ana_env, tmc_params)
read the files and analyze the configurations
 
subroutine, public analysis_init(ana_env, nr_dim)
initialize all the necessarry analysis structures
 
subroutine, public do_tmc_analysis(elem, ana_env)
call all the necessarry analysis routines analysis the previous element with the weight of the differ...
 
subroutine, public analysis_restart_print(ana_env)
print analysis restart file
 
calculation section for TreeMonteCarlo
 
subroutine, public calc_potential_energy(conf, env_id, exact_approx_pot, tmc_env)
start the calculation of the energy (distinguish between exact and approximate)
 
set up the different message for different tasks A TMC message consists of 3 parts (messages) 1: firs...
 
subroutine, public tmc_message(msg_type, send_recv, dest, para_env, tmc_params, elem, elem_array, list_elem, result_count, wait_for_message, success)
tmc message handling, packing messages with integer and real data type. Send first info message with ...
 
subroutine, public communicate_atom_types(atoms, source, para_env)
routines send atom names to the global master (using broadcast in a specialized group consisting of t...
 
integer, parameter, public bcast_group
 
logical function, public check_if_group_master(para_env)
checks if the core is the group master
 
integer, parameter, public master_comm_id
 
subroutine, public stop_whole_group(para_env, worker_info, tmc_params)
send stop command to all group participants
 
logical, parameter, public send_msg
 
logical, parameter, public recv_msg
 
acceptance ratio handling of the different Monte Carlo Moves types For each move type and each temper...
 
subroutine, public clear_move_probs(move_types)
clear the statistics of accepting/rejection moves because worker statistics will be add separately on...
 
integer function, public select_random_move_type(move_types, rnd)
selects a move type related to the weighings and the entered rnd nr
 
subroutine, public prob_update(move_types, pt_el, elem, acc, subbox, prob_opt)
adaptation of acceptance probability of every kind of change/move and the overall acc prob,...
 
tree nodes creation, searching, deallocation, references etc.
 
integer, parameter, public mv_type_md
 
integer, parameter, public mv_type_nmc_moves
 
different move types are applied
 
subroutine, public change_pos(tmc_params, move_types, rng_stream, elem, mv_conf, new_subbox, move_rejected)
applying the preselected move type
 
tree nodes creation, searching, deallocation, references etc.
 
integer, parameter, public tmc_status_calculating
 
integer, parameter, public tmc_status_failed
 
integer, parameter, public tmc_stat_analysis_request
 
integer, parameter, public tmc_status_worker_init
 
integer, parameter, public tmc_stat_md_result
 
integer, parameter, public tmc_stat_md_request
 
integer, parameter, public tmc_stat_approx_energy_result
 
integer, parameter, public tmc_stat_start_conf_result
 
integer, parameter, public tmc_status_wait_for_new_task
 
integer, parameter, public tmc_stat_nmc_result
 
integer, parameter, public tmc_stat_analysis_result
 
integer, parameter, public task_type_mc
 
integer, parameter, public tmc_stat_init_analysis
 
integer, parameter, public tmc_stat_energy_result
 
integer, parameter, public tmc_stat_scf_step_ener_receive
 
integer, parameter, public tmc_stat_approx_energy_request
 
integer, parameter, public tmc_stat_start_conf_request
 
integer, parameter, public tmc_canceling_receipt
 
integer, parameter, public tmc_stat_energy_request
 
integer, parameter, public tmc_stat_nmc_request
 
integer, parameter, public tmc_status_stop_receipt
 
integer, parameter, public tmc_canceling_message
 
integer, parameter, public task_type_ideal_gas
 
tree nodes acceptance code is separated in 3 parts, first the acceptance criteria,...
 
subroutine, public acceptance_check(tree_element, parent_element, tmc_params, temperature, diff_pot_check, accept, rnd_nr, approx_ener)
standard Monte Carlo and 2 potential acceptance check acceptance check of move from old(last accepted...
 
tree nodes creation, deallocation, references etc.
 
subroutine, public deallocate_sub_tree_node(tree_elem)
deallocates an elements of the subtree element structure
 
subroutine, public allocate_new_sub_tree_node(tmc_params, next_el, nr_dim)
allocates an elements of the subtree element structure
 
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
 
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
 
subroutine, public allocate_tmc_atom_type(atoms, nr_atoms)
creates a structure for storing the atom informations
 
module contains the worker routine handling the communication and the calculation / creation of the c...
 
subroutine, public do_tmc_worker(tmc_env, ana_list)
worker get tasks form master and fulfill them
 
subroutine, public get_initial_conf(tmc_params, init_conf, env_id)
get the initial confuguration (pos,...)
 
subroutine, public get_atom_kinds_and_cell(env_id, atoms, cell)
get the pointer to the atoms, for easy handling
 
Type defining parameters related to the simulation cell.
 
contains arbitrary information which need to be stored
 
represents a system: atoms, molecules, their pos,vel,...
 
stores all the informations relevant to an mpi environment
 
represent a list of objects
 
represent a list of objects