CAMP 1.0.0
Chemistry Across Multiple Phases
camp_state.F90
Go to the documentation of this file.
1! Copyright (C) 2021 Barcelona Supercomputing Center and University of
2! Illinois at Urbana-Champaign
3! SPDX-License-Identifier: MIT
4
5!> \file
6!> The camp_camp_state module.
7
8!> The camp_state_t structure and associated subroutines.
10
11! Define array size for contain temperature and pressure
12#define CAMP_STATE_NUM_ENV_PARAM 2
13
14#ifdef CAMP_USE_MPI
15 use mpi
16#endif
18 use camp_mpi
19 use camp_util, only : die_msg, string_t
20
21 implicit none
22 private
23
25
26 !> Model state
27 !!
28 !! Temporal state of the model
30 !> Environmental state array. This array will include one entry
31 !! for every environmental variable requried to solve the
32 !! chemical mechanism(s)
33 real(kind=dp), allocatable :: env_var(:)
34 !> State variable array. This array includes one entry for each
35 !! variable whose state will be solved for during the mechanism
36 !! integration.
37 !! units are ppm (gases) or kg m-3 (aerosol species)
38 real(kind=dp), allocatable :: state_var(:)
39 !> Environmental conditions
40 type(env_state_ptr), pointer :: env_states(:)
41 !> Flag indicating whether the env_state object is owned by the
42 !! state object
43 logical, private :: owns_env_states = .false.
44 contains
45 !> Update the environmental state array
46 procedure :: update_env_state
47 !> Finalize the state
48 final :: finalize
49 end type camp_state_t
50
51 ! Constructor for camp_state_t
52 interface camp_state_t
54 end interface camp_state_t
55
56 !> Pointer type for building arrays
58 type(camp_state_t), pointer :: val => null()
59 contains
60 !> Dereference the pointer
61 procedure :: dereference
62 !> Finalize the pointer
63 final :: ptr_finalize
64 end type camp_state_ptr
65
66contains
67
68!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
69
70 !> Constructor for camp_state_t
71 function constructor_one_cell(env_state) result (new_obj)
72
73 !> New model state
74 type(camp_state_t), pointer :: new_obj
75 !> Environmental state
76 type(env_state_t), target, intent(in), optional :: env_state
77
78 ! Allocate space for the new object
79 allocate(new_obj)
80 allocate(new_obj%env_states(1))
81
82 ! Set the environmental state (if present)
83 if (present(env_state)) then
84 new_obj%env_states(1)%val => env_state
85 else
86 allocate(new_obj%env_states(1)%val)
87 new_obj%owns_env_states = .true.
88 end if
89
90 ! Set up the environmental state array
91 allocate(new_obj%env_var(camp_state_num_env_param))
92
93 end function constructor_one_cell
94
95!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
96
97 !> Constructor for camp_state_t
98 function constructor_multi_cell(num_cells, env_states) result (new_obj)
99
100 !> New model state
101 type(camp_state_t), pointer :: new_obj
102 !> Number of grid cells to solve simultaneously
103 integer(kind=i_kind), intent(in) :: num_cells
104 !> Environmental state
105 type(env_state_ptr), target, intent(in), optional :: env_states(:)
106
107 integer(kind=i_kind) :: i_cell
108
109 ! Allocate space for the new object
110 allocate(new_obj)
111
112 ! Set the environmental state (if present)
113 if (present(env_states)) then
114 new_obj%env_states => env_states
115 else
116 allocate(new_obj%env_states(num_cells))
117 do i_cell = 1, num_cells
118 allocate(new_obj%env_states(i_cell)%val)
119 end do
120 new_obj%owns_env_states = .true.
121 end if
122
123 ! Set up the environmental state array
124 allocate(new_obj%env_var(camp_state_num_env_param*num_cells))
125
126 end function constructor_multi_cell
127
128!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
129
130 !> Update the environmental state array
131 subroutine update_env_state(this)
132
133 !> Model state
134 class(camp_state_t), intent(inout) :: this
135
136 integer :: i_cell, grid_offset
137
138 do i_cell = 1, size(this%env_states)
139 grid_offset = (i_cell-1)*camp_state_num_env_param
140 this%env_var(grid_offset+1) = this%env_states(i_cell)%val%temp ! Temperature (K)
141 this%env_var(grid_offset+2) = this%env_states(i_cell)%val%pressure ! Pressure (Pa)
142 end do
143
144 end subroutine update_env_state
145
146!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
147
148 !> Finalize the state
149 elemental subroutine finalize(this)
150
151 !> CAMP model state
152 type(camp_state_t), intent(inout) :: this
153
154 integer(kind=i_kind) :: i_cell
155
156 if (allocated(this%env_var)) deallocate(this%env_var)
157 if (allocated(this%state_var)) deallocate(this%state_var)
158 if (associated(this%env_states) .and. this%owns_env_states) then
159 do i_cell = 1, size(this%env_states)
160 deallocate(this%env_states(i_cell)%val)
161 end do
162 deallocate(this%env_states)
163 end if
164
165 end subroutine finalize
166
167!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
168
169 !> Deference a pointer to a camp state
170 elemental subroutine dereference(this)
171
172 !> Pointer to the camp state
173 class(camp_state_ptr), intent(inout) :: this
174
175 this%val => null()
176
177 end subroutine dereference
178
179!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
180
181 !> Finalize a pointer to a camp state
182 elemental subroutine ptr_finalize(this)
183
184 !> Pointer to the camp state
185 type(camp_state_ptr), intent(inout) :: this
186
187 if (associated(this%val)) deallocate(this%val)
188
189 end subroutine ptr_finalize
190
191!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
192
193end module camp_camp_state
The camp_state_t structure and associated subroutines.
Definition camp_state.F90:9
type(camp_state_t) function, pointer constructor_one_cell(env_state)
Constructor for camp_state_t.
elemental subroutine ptr_finalize(this)
Finalize a pointer to a camp state.
elemental subroutine finalize(this)
Finalize the state.
subroutine update_env_state(this)
Update the environmental state array.
elemental subroutine dereference(this)
Deference a pointer to a camp state.
type(camp_state_t) function, pointer constructor_multi_cell(num_cells, env_states)
Constructor for camp_state_t.
The env_state_t structure and associated subroutines.
Definition env_state.F90:9
Wrapper functions for MPI.
Definition mpi.F90:13
Common utility subroutines.
Definition util.F90:9
subroutine die_msg(code, error_msg)
Error immediately.
Definition util.F90:196
Pointer type for building arrays.
Pointer for env_state_t.
Definition env_state.F90:57
Current environment state.
Definition env_state.F90:24
String type for building arrays of string of various size.
Definition util.F90:38