(git:ccc2433)
fist_main.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
9 !> \brief perform classical molecular dynamics and path integral simulations
10 !> \par History
11 !> gt SEPT-23-2002: part is allocated/deallocated/initialized in
12 !> read_coord_vel
13 !> CJM rewrite
14 !> \author CJM-Sept-01-02
15 ! **************************************************************************************************
16 MODULE fist_main
17  USE cp_subsys_types, ONLY: cp_subsys_type
18  USE fist_environment, ONLY: fist_init
20  fist_env_set,&
21  fist_environment_type
23  USE force_env_types, ONLY: force_env_type
24  USE global_types, ONLY: global_environment_type
25  USE input_section_types, ONLY: section_vals_type
26  USE message_passing, ONLY: mp_para_env_type
27  USE qmmm_types_low, ONLY: qmmm_env_mm_type
28 #include "./base/base_uses.f90"
29 
30  IMPLICIT NONE
31 
32  PRIVATE
33 
34 ! *** Global parameters ***
35  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'fist_main'
36 
37 ! *** Global variables ***
38  PUBLIC :: fist_create_force_env
39 
40 !!-----------------------------------------------------------------------------!
41 
42 CONTAINS
43 
44 !-----------------------------------------------------------------------------!
45 ! FIST FIST FIST FIST FIST FIST FIST FIST FIST FIST FIST FIST FIST FIST FIST !
46 !-----------------------------------------------------------------------------!
47 
48 ! **************************************************************************************************
49 !> \brief Controls program flow for classical MD and path-integrals
50 !> \param force_env ...
51 !> \param root_section ...
52 !> \param para_env ...
53 !> \param globenv ...
54 !> \param qmmm ...
55 !> \param qmmm_env ...
56 !> \param force_env_section ...
57 !> \param subsys_section ...
58 !> \param use_motion_section ...
59 !> \param prev_subsys ...
60 !> \par Used By
61 !> cp2k
62 !> \author CJM
63 ! **************************************************************************************************
64  SUBROUTINE fist_create_force_env(force_env, root_section, para_env, globenv, &
65  qmmm, qmmm_env, force_env_section, subsys_section, use_motion_section, prev_subsys)
66  TYPE(force_env_type), POINTER :: force_env
67  TYPE(section_vals_type), POINTER :: root_section
68  TYPE(mp_para_env_type), POINTER :: para_env
69  TYPE(global_environment_type), POINTER :: globenv
70  LOGICAL, OPTIONAL :: qmmm
71  TYPE(qmmm_env_mm_type), OPTIONAL, POINTER :: qmmm_env
72  TYPE(section_vals_type), POINTER :: force_env_section, subsys_section
73  LOGICAL, INTENT(IN) :: use_motion_section
74  TYPE(cp_subsys_type), OPTIONAL, POINTER :: prev_subsys
75 
76  CHARACTER(LEN=*), PARAMETER :: routinen = 'fist_create_force_env'
77 
78  INTEGER :: handle
79  LOGICAL :: myqmmm
80  TYPE(fist_environment_type), POINTER :: fist_env
81 
82  CALL timeset(routinen, handle)
83  myqmmm = .false.
84  IF (PRESENT(qmmm)) THEN
85  myqmmm = qmmm
86  END IF
87 
88  ALLOCATE (fist_env)
89  CALL fist_env_create(fist_env, para_env=para_env)
90  IF (PRESENT(qmmm_env)) THEN
91  CALL fist_env_set(fist_env, qmmm=myqmmm, qmmm_env=qmmm_env)
92  ELSE
93  CALL fist_env_set(fist_env, qmmm=myqmmm)
94  END IF
95  ! *** Read the input and the database files and perform further ***
96  ! *** initializations for the setup of the FIST environment ***
97  CALL fist_init(fist_env, root_section, para_env, force_env_section, &
98  subsys_section, use_motion_section, prev_subsys=prev_subsys)
99 
100  CALL force_env_create(force_env, root_section, fist_env=fist_env, &
101  para_env=para_env, globenv=globenv, &
102  force_env_section=force_env_section)
103 
104  CALL timestop(handle)
105  END SUBROUTINE fist_create_force_env
106 
107 END MODULE fist_main
types that represent a subsys, i.e. a part of the system
subroutine, public fist_env_create(fist_env, para_env)
allocates and intitializes a fist_env
subroutine, public fist_env_set(fist_env, atomic_kind_set, particle_set, ewald_pw, local_particles, local_molecules, molecule_kind_set, molecule_set, cell_ref, ewald_env, fist_nonbond_env, thermo, subsys, qmmm, qmmm_env, input, shell_model, shell_model_ad, exclusions, efield)
Set the FIST environment.
initialize fist environment
subroutine, public fist_init(fist_env, root_section, para_env, force_env_section, subsys_section, use_motion_section, prev_subsys)
reads the input and database file for fist
perform classical molecular dynamics and path integral simulations
Definition: fist_main.F:16
subroutine, public fist_create_force_env(force_env, root_section, para_env, globenv, qmmm, qmmm_env, force_env_section, subsys_section, use_motion_section, prev_subsys)
Controls program flow for classical MD and path-integrals.
Definition: fist_main.F:66
Interface for the force calculations.
subroutine, public force_env_create(force_env, root_section, para_env, globenv, fist_env, qs_env, meta_env, sub_force_env, qmmm_env, qmmmx_env, eip_env, pwdft_env, force_env_section, mixed_env, embed_env, nnp_env)
creates and initializes a force environment
Interface for the force calculations.
Define type storing the global information of a run. Keep the amount of stored data small....
Definition: global_types.F:21
objects that represent the structure of input sections and the data contained in an input section
Interface to the message passing library MPI.