(git:ccc2433)
farming_types.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 ! **************************************************************************************************
10 
11  USE kinds, ONLY: default_path_length,&
12  dp
13 #include "./base/base_uses.f90"
14 
15  IMPLICIT NONE
16  PRIVATE
17 
18  PUBLIC :: farming_env_type, deallocate_farming_env, init_farming_env, init_job_type
19 
20  INTEGER, PUBLIC, PARAMETER :: job_pending = 1, job_running = 2, job_finished = 3
21 
22 ! **************************************************************************************************
23  TYPE job_type
24  CHARACTER(LEN=default_path_length) :: cwd ! the directory to go to
25  CHARACTER(LEN=default_path_length) :: input ! the input file to use
26  CHARACTER(LEN=default_path_length) :: output ! the output file to use
27  INTEGER :: id ! the ID of this job
28  INTEGER, POINTER, DIMENSION(:) :: dependencies ! the dependencies of this job
29  INTEGER :: status ! pending,running,finished
30  END TYPE job_type
31 
32 ! **************************************************************************************************
33  TYPE farming_env_type
34  INTEGER :: group_size_wish
35  LOGICAL :: group_size_wish_set
36  INTEGER :: ngroup_wish
37  LOGICAL :: ngroup_wish_set
38  LOGICAL :: restart
39  LOGICAL :: cycle
40  LOGICAL :: captain_minion
41  INTEGER, DIMENSION(:), POINTER :: group_partition ! user preference for partitioning the cpus
42  CHARACTER(LEN=default_path_length) :: restart_file_name ! restart file for farming
43  CHARACTER(LEN=default_path_length) :: cwd ! directory we started from
44  INTEGER :: njobs ! how many jobs to run
45  INTEGER :: restart_n ! where to start
46  INTEGER :: max_steps ! max number of steps,
47  ! results in max_steps*Ngroup jobs being run
48  INTEGER :: stride ! for creating minion groups.
49  TYPE(job_type), DIMENSION(:), POINTER :: job ! a list of jobs
50  REAL(kind=dp) :: wait_time
51  END TYPE farming_env_type
52 
53 CONTAINS
54 
55 ! **************************************************************************************************
56 !> \brief help poor compilers do their job
57 !> i.e. provide a default initialization
58 !> \param farming_env an associated farming env pointer
59 !> \par History
60 !> 03.2004 created [Joost VandeVondele ]
61 ! **************************************************************************************************
62  SUBROUTINE init_farming_env(farming_env)
63  TYPE(farming_env_type), POINTER :: farming_env
64 
65  IF (ASSOCIATED(farming_env)) THEN
66  farming_env%group_size_wish = 0
67  farming_env%group_size_wish_set = .false.
68  farming_env%ngroup_wish = 0
69  farming_env%ngroup_wish_set = .false.
70  farming_env%restart = .false.
71  farming_env%restart_n = 1
72  farming_env%cycle = .false.
73  farming_env%captain_minion = .false.
74  NULLIFY (farming_env%group_partition)
75  farming_env%cwd = "."
76  farming_env%Njobs = 0
77  ! so that maxsteps*ngroup is (likely) not overflowing
78  farming_env%max_steps = 65535
79  NULLIFY (farming_env%Job)
80  END IF
81  END SUBROUTINE
82 
83 ! **************************************************************************************************
84 !> \brief provide a default initialization
85 !> \param job ...
86 !> \par History
87 !> 09.2007 created [Joost VandeVondele ]
88 ! **************************************************************************************************
89  ELEMENTAL SUBROUTINE init_job_type(job)
90  TYPE(job_type), INTENT(OUT) :: job
91 
92  job%cwd = ""
93  job%input = ""
94  job%output = ""
95  job%ID = -1
96  job%status = job_pending
97  NULLIFY (job%dependencies)
98 
99  END SUBROUTINE init_job_type
100 
101 ! **************************************************************************************************
102 !> \brief deallocates all memory associated with this job
103 !> \param job ...
104 !> \par History
105 !> 09.2007 created [Joost VandeVondele ]
106 ! **************************************************************************************************
107  SUBROUTINE deallocate_job_type(job)
108  TYPE(job_type) :: job
109 
110  IF (ASSOCIATED(job%dependencies)) DEALLOCATE (job%dependencies)
111 
112  END SUBROUTINE deallocate_job_type
113 
114 ! **************************************************************************************************
115 !> \brief deallocates all associated fields of the farming_env type
116 !> and the type itself
117 !> \param farming_env ...
118 !> \par History
119 !> 03.2004 created [Joost VandeVondele]
120 ! **************************************************************************************************
121  SUBROUTINE deallocate_farming_env(farming_env)
122  TYPE(farming_env_type), POINTER :: farming_env
123 
124  INTEGER :: i
125 
126  IF (ASSOCIATED(farming_env)) THEN
127  IF (ASSOCIATED(farming_env%job)) THEN
128  DO i = 1, SIZE(farming_env%job, 1)
129  CALL deallocate_job_type(farming_env%job(i))
130  END DO
131  DEALLOCATE (farming_env%job)
132  END IF
133  IF (ASSOCIATED(farming_env%group_partition)) DEALLOCATE (farming_env%group_partition)
134  DEALLOCATE (farming_env) ! and the type itself
135  END IF
136  END SUBROUTINE deallocate_farming_env
137 END MODULE farming_types
elemental subroutine, public init_job_type(job)
provide a default initialization
Definition: farming_types.F:90
subroutine, public deallocate_farming_env(farming_env)
deallocates all associated fields of the farming_env type and the type itself
integer, parameter, public job_finished
Definition: farming_types.F:20
integer, parameter, public job_running
Definition: farming_types.F:20
integer, parameter, public job_pending
Definition: farming_types.F:20
subroutine, public init_farming_env(farming_env)
help poor compilers do their job i.e. provide a default initialization
Definition: farming_types.F:63
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public default_path_length
Definition: kinds.F:58