MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
memorymanagerextmodule Module Reference

Data Types

interface  mem_set_value
 

Functions/Subroutines

subroutine, public memorylist_remove (component, subcomponent, context)
 
subroutine mem_set_value_logical (p_mem, varname, memory_path, found)
 Set pointer to value of memory list logical variable. More...
 
subroutine mem_set_value_int (p_mem, varname, memory_path, found)
 Set pointer to value of memory list int variable. More...
 
subroutine mem_set_value_int_setval (p_mem, varname, memory_path, setval, found)
 
subroutine mem_set_value_str_mapped_int (p_mem, varname, memory_path, str_list, found)
 
subroutine mem_set_value_int1d (p_mem, varname, memory_path, found)
 Set pointer to value of memory list 1d int array variable. More...
 
subroutine mem_set_value_int1d_mapped (p_mem, varname, memory_path, map, found)
 Set pointer to value of memory list 1d int array variable with mapping. More...
 
subroutine mem_set_value_int2d (p_mem, varname, memory_path, found)
 Set pointer to value of memory list 2d int array variable. More...
 
subroutine mem_set_value_int3d (p_mem, varname, memory_path, found)
 Set pointer to value of memory list 3d int array variable. More...
 
subroutine mem_set_value_dbl (p_mem, varname, memory_path, found)
 Set pointer to value of memory list double variable. More...
 
subroutine mem_set_value_dbl1d (p_mem, varname, memory_path, found)
 Set pointer to value of memory list 1d dbl array variable. More...
 
subroutine mem_set_value_dbl1d_mapped (p_mem, varname, memory_path, map, found)
 Set pointer to value of memory list 1d dbl array variable with mapping. More...
 
subroutine mem_set_value_dbl2d (p_mem, varname, memory_path, found)
 Set pointer to value of memory list 2d dbl array variable. More...
 
subroutine mem_set_value_dbl3d (p_mem, varname, memory_path, found)
 Set pointer to value of memory list 3d dbl array variable. More...
 
subroutine mem_set_value_str (p_mem, varname, memory_path, found)
 
subroutine mem_set_value_charstr1d (p_mem, varname, memory_path, found)
 

Function/Subroutine Documentation

◆ mem_set_value_charstr1d()

subroutine memorymanagerextmodule::mem_set_value_charstr1d ( type(characterstringtype), dimension(:), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to charstr 1d array
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 372 of file MemoryManagerExt.f90.

374  type(CharacterStringType), dimension(:), &
375  pointer, contiguous, intent(inout) :: p_mem !< pointer to charstr 1d array
376  character(len=*), intent(in) :: varname !< variable name
377  character(len=*), intent(in) :: memory_path !< path where variable is stored
378  logical(LGP), intent(inout) :: found
379  type(MemoryType), pointer :: mt
380  logical(LGP) :: checkfail = .false.
381  integer(I4B) :: n
382 
383  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
384  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'STRING') then
385  do n = 1, size(mt%acharstr1d)
386  p_mem(n) = mt%acharstr1d(n)
387  end do
388  end if
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23

◆ mem_set_value_dbl()

subroutine memorymanagerextmodule::mem_set_value_dbl ( real(dp), intent(inout), pointer  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to dbl scalar
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 235 of file MemoryManagerExt.f90.

236  real(DP), pointer, intent(inout) :: p_mem !< pointer to dbl scalar
237  character(len=*), intent(in) :: varname !< variable name
238  character(len=*), intent(in) :: memory_path !< path where variable is stored
239  logical(LGP), intent(inout) :: found
240  type(MemoryType), pointer :: mt
241  logical(LGP) :: checkfail = .false.
242 
243  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
244  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'DOUBLE') then
245  p_mem = mt%dblsclr
246  end if

◆ mem_set_value_dbl1d()

subroutine memorymanagerextmodule::mem_set_value_dbl1d ( real(dp), dimension(:), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 1d dbl array
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 251 of file MemoryManagerExt.f90.

252  real(DP), dimension(:), pointer, contiguous, intent(inout) :: p_mem !< pointer to 1d dbl array
253  character(len=*), intent(in) :: varname !< variable name
254  character(len=*), intent(in) :: memory_path !< path where variable is stored
255  logical(LGP), intent(inout) :: found
256  type(MemoryType), pointer :: mt
257  logical(LGP) :: checkfail = .false.
258  integer(I4B) :: n
259 
260  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
261  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'DOUBLE') then
262  if (size(mt%adbl1d) /= size(p_mem)) then
263  call store_error('mem_set_value() size mismatch dbl1d, varname='//&
264  &trim(varname), terminate=.true.)
265  end if
266  do n = 1, size(mt%adbl1d)
267  p_mem(n) = mt%adbl1d(n)
268  end do
269  end if

◆ mem_set_value_dbl1d_mapped()

subroutine memorymanagerextmodule::mem_set_value_dbl1d_mapped ( real(dp), dimension(:), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
integer(i4b), dimension(:), intent(in), pointer, contiguous  map,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 1d dbl array
[in]varnamevariable name
[in]memory_pathpath where variable is stored
[in]mappointer to 1d int mapping array

Definition at line 274 of file MemoryManagerExt.f90.

276  real(DP), dimension(:), pointer, contiguous, intent(inout) :: p_mem !< pointer to 1d dbl array
277  character(len=*), intent(in) :: varname !< variable name
278  character(len=*), intent(in) :: memory_path !< path where variable is stored
279  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: map !< pointer to 1d int mapping array
280  logical(LGP), intent(inout) :: found
281  type(MemoryType), pointer :: mt
282  logical(LGP) :: checkfail = .false.
283  integer(I4B) :: n
284 
285  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
286  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'DOUBLE') then
287  if (associated(map)) then
288  do n = 1, size(p_mem)
289  p_mem(n) = mt%adbl1d(map(n))
290  end do
291  else
292  if (size(mt%adbl1d) /= size(p_mem)) then
293  call store_error('mem_set_value() size mismatch dbl1d, varname='//&
294  &trim(varname), terminate=.true.)
295  end if
296  do n = 1, size(mt%adbl1d)
297  p_mem(n) = mt%adbl1d(n)
298  end do
299  end if
300  end if

◆ mem_set_value_dbl2d()

subroutine memorymanagerextmodule::mem_set_value_dbl2d ( real(dp), dimension(:, :), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 2d dbl array
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 305 of file MemoryManagerExt.f90.

306  real(DP), dimension(:, :), pointer, contiguous, intent(inout) :: p_mem !< pointer to 2d dbl array
307  character(len=*), intent(in) :: varname !< variable name
308  character(len=*), intent(in) :: memory_path !< path where variable is stored
309  logical(LGP), intent(inout) :: found
310  type(MemoryType), pointer :: mt
311  logical(LGP) :: checkfail = .false.
312  integer(I4B) :: i, j
313 
314  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
315  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'DOUBLE') then
316  if (size(mt%adbl2d, dim=1) /= size(p_mem, dim=1) .or. &
317  size(mt%adbl2d, dim=2) /= size(p_mem, dim=2)) then
318  call store_error('mem_set_value() size mismatch dbl2d, varname='//&
319  &trim(varname), terminate=.true.)
320  end if
321  do j = 1, size(mt%adbl2d, dim=2)
322  do i = 1, size(mt%adbl2d, dim=1)
323  p_mem(i, j) = mt%adbl2d(i, j)
324  end do
325  end do
326  end if

◆ mem_set_value_dbl3d()

subroutine memorymanagerextmodule::mem_set_value_dbl3d ( real(dp), dimension(:, :, :), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 3d dbl array
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 331 of file MemoryManagerExt.f90.

332  real(DP), dimension(:, :, :), pointer, contiguous, intent(inout) :: p_mem !< pointer to 3d dbl array
333  character(len=*), intent(in) :: varname !< variable name
334  character(len=*), intent(in) :: memory_path !< path where variable is stored
335  logical(LGP), intent(inout) :: found
336  type(MemoryType), pointer :: mt
337  logical(LGP) :: checkfail = .false.
338  integer(I4B) :: i, j, k
339 
340  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
341  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'DOUBLE') then
342  if (size(mt%adbl3d, dim=1) /= size(p_mem, dim=1) .or. &
343  size(mt%adbl3d, dim=2) /= size(p_mem, dim=2) .or. &
344  size(mt%adbl3d, dim=3) /= size(p_mem, dim=3)) then
345  call store_error('mem_set_value() size mismatch dbl3d, varname='//&
346  &trim(varname), terminate=.true.)
347  end if
348  do k = 1, size(mt%adbl3d, dim=3)
349  do j = 1, size(mt%adbl3d, dim=2)
350  do i = 1, size(mt%adbl3d, dim=1)
351  p_mem(i, j, k) = mt%adbl3d(i, j, k)
352  end do
353  end do
354  end do
355  end if

◆ mem_set_value_int()

subroutine memorymanagerextmodule::mem_set_value_int ( integer(i4b), intent(inout), pointer  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to int scalar
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 74 of file MemoryManagerExt.f90.

75  integer(I4B), pointer, intent(inout) :: p_mem !< pointer to int scalar
76  character(len=*), intent(in) :: varname !< variable name
77  character(len=*), intent(in) :: memory_path !< path where variable is stored
78  logical(LGP), intent(inout) :: found
79  type(MemoryType), pointer :: mt
80  logical(LGP) :: checkfail = .false.
81 
82  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
83  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'INTEGER') then
84  p_mem = mt%intsclr
85  end if

◆ mem_set_value_int1d()

subroutine memorymanagerextmodule::mem_set_value_int1d ( integer(i4b), dimension(:), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 1d int array
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 126 of file MemoryManagerExt.f90.

127  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: p_mem !< pointer to 1d int array
128  character(len=*), intent(in) :: varname !< variable name
129  character(len=*), intent(in) :: memory_path !< path where variable is stored
130  logical(LGP), intent(inout) :: found
131  type(MemoryType), pointer :: mt
132  logical(LGP) :: checkfail = .false.
133  integer(I4B) :: n
134 
135  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
136  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'INTEGER') then
137  if (size(mt%aint1d) /= size(p_mem)) then
138  call store_error('mem_set_value() size mismatch int1d, varname='//&
139  &trim(varname), terminate=.true.)
140  end if
141  do n = 1, size(mt%aint1d)
142  p_mem(n) = mt%aint1d(n)
143  end do
144  end if

◆ mem_set_value_int1d_mapped()

subroutine memorymanagerextmodule::mem_set_value_int1d_mapped ( integer(i4b), dimension(:), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
integer(i4b), dimension(:), intent(in), pointer, contiguous  map,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 1d int array
[in]varnamevariable name
[in]memory_pathpath where variable is stored
[in]mappointer to 1d int mapping array

Definition at line 149 of file MemoryManagerExt.f90.

151  integer(I4B), dimension(:), pointer, contiguous, intent(inout) :: p_mem !< pointer to 1d int array
152  character(len=*), intent(in) :: varname !< variable name
153  character(len=*), intent(in) :: memory_path !< path where variable is stored
154  integer(I4B), dimension(:), pointer, contiguous, intent(in) :: map !< pointer to 1d int mapping array
155  logical(LGP), intent(inout) :: found
156  type(MemoryType), pointer :: mt
157  logical(LGP) :: checkfail = .false.
158  integer(I4B) :: n
159 
160  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
161  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'INTEGER') then
162  if (associated(map)) then
163  do n = 1, size(p_mem)
164  p_mem(n) = mt%aint1d(map(n))
165  end do
166  else
167  if (size(mt%aint1d) /= size(p_mem)) then
168  call store_error('mem_set_value() size mismatch int1d, varname='//&
169  &trim(varname), terminate=.true.)
170  end if
171  do n = 1, size(mt%aint1d)
172  p_mem(n) = mt%aint1d(n)
173  end do
174  end if
175  end if

◆ mem_set_value_int2d()

subroutine memorymanagerextmodule::mem_set_value_int2d ( integer(i4b), dimension(:, :), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 2d int array
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 180 of file MemoryManagerExt.f90.

181  integer(I4B), dimension(:, :), pointer, contiguous, intent(inout) :: p_mem !< pointer to 2d int array
182  character(len=*), intent(in) :: varname !< variable name
183  character(len=*), intent(in) :: memory_path !< path where variable is stored
184  logical(LGP), intent(inout) :: found
185  type(MemoryType), pointer :: mt
186  logical(LGP) :: checkfail = .false.
187  integer(I4B) :: i, j
188 
189  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
190  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'INTEGER') then
191  if (size(mt%aint2d, dim=1) /= size(p_mem, dim=1) .or. &
192  size(mt%aint2d, dim=2) /= size(p_mem, dim=2)) then
193  call store_error('mem_set_value() size mismatch int2d, varname='//&
194  &trim(varname), terminate=.true.)
195  end if
196  do j = 1, size(mt%aint2d, dim=2)
197  do i = 1, size(mt%aint2d, dim=1)
198  p_mem(i, j) = mt%aint2d(i, j)
199  end do
200  end do
201  end if

◆ mem_set_value_int3d()

subroutine memorymanagerextmodule::mem_set_value_int3d ( integer(i4b), dimension(:, :, :), intent(inout), pointer, contiguous  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to 3d int array
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 206 of file MemoryManagerExt.f90.

207  integer(I4B), dimension(:, :, :), pointer, contiguous, intent(inout) :: p_mem !< pointer to 3d int array
208  character(len=*), intent(in) :: varname !< variable name
209  character(len=*), intent(in) :: memory_path !< path where variable is stored
210  logical(LGP), intent(inout) :: found
211  type(MemoryType), pointer :: mt
212  logical(LGP) :: checkfail = .false.
213  integer(I4B) :: i, j, k
214 
215  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
216  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'INTEGER') then
217  if (size(mt%aint3d, dim=1) /= size(p_mem, dim=1) .or. &
218  size(mt%aint3d, dim=2) /= size(p_mem, dim=2) .or. &
219  size(mt%aint3d, dim=3) /= size(p_mem, dim=3)) then
220  call store_error('mem_set_value() size mismatch int3d, varname='//&
221  &trim(varname), terminate=.true.)
222  end if
223  do k = 1, size(mt%aint3d, dim=3)
224  do j = 1, size(mt%aint3d, dim=2)
225  do i = 1, size(mt%aint3d, dim=1)
226  p_mem(i, j, k) = mt%aint3d(i, j, k)
227  end do
228  end do
229  end do
230  end if

◆ mem_set_value_int_setval()

subroutine memorymanagerextmodule::mem_set_value_int_setval ( integer(i4b), intent(inout), pointer  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
integer(i4b), intent(in)  setval,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to int scalar
[in]varnamevariable name
[in]memory_pathpath where variable is stored
[in]setvalset p_mem to setval if varname found

Definition at line 88 of file MemoryManagerExt.f90.

89  integer(I4B), pointer, intent(inout) :: p_mem !< pointer to int scalar
90  character(len=*), intent(in) :: varname !< variable name
91  character(len=*), intent(in) :: memory_path !< path where variable is stored
92  integer(I4B), intent(in) :: setval !< set p_mem to setval if varname found
93  logical(LGP), intent(inout) :: found
94  type(MemoryType), pointer :: mt
95  logical(LGP) :: checkfail = .false.
96 
97  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
98  if (found) then
99  p_mem = setval
100  end if

◆ mem_set_value_logical()

subroutine memorymanagerextmodule::mem_set_value_logical ( logical(lgp), intent(inout), pointer  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
Parameters
[in,out]p_mempointer to logical scalar
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 54 of file MemoryManagerExt.f90.

55  logical(LGP), pointer, intent(inout) :: p_mem !< pointer to logical scalar
56  character(len=*), intent(in) :: varname !< variable name
57  character(len=*), intent(in) :: memory_path !< path where variable is stored
58  logical(LGP), intent(inout) :: found
59  type(MemoryType), pointer :: mt
60  logical(LGP) :: checkfail = .false.
61 
62  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
63  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'INTEGER') then
64  if (mt%intsclr == 0) then
65  p_mem = .false.
66  else
67  p_mem = .true.
68  end if
69  end if

◆ mem_set_value_str()

subroutine memorymanagerextmodule::mem_set_value_str ( character(len=*), intent(inout)  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to str scalar
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 358 of file MemoryManagerExt.f90.

359  character(len=*), intent(inout) :: p_mem !< pointer to str scalar
360  character(len=*), intent(in) :: varname !< variable name
361  character(len=*), intent(in) :: memory_path !< path where variable is stored
362  logical(LGP), intent(inout) :: found
363  type(MemoryType), pointer :: mt
364  logical(LGP) :: checkfail = .false.
365 
366  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
367  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'STRING') then
368  p_mem = mt%strsclr
369  end if

◆ mem_set_value_str_mapped_int()

subroutine memorymanagerextmodule::mem_set_value_str_mapped_int ( integer(i4b), intent(inout), pointer  p_mem,
character(len=*), intent(in)  varname,
character(len=*), intent(in)  memory_path,
character(len=*), dimension(:), intent(in)  str_list,
logical(lgp), intent(inout)  found 
)
private
Parameters
[in,out]p_mempointer to int scalar
[in]varnamevariable name
[in]memory_pathpath where variable is stored

Definition at line 103 of file MemoryManagerExt.f90.

105  integer(I4B), pointer, intent(inout) :: p_mem !< pointer to int scalar
106  character(len=*), intent(in) :: varname !< variable name
107  character(len=*), intent(in) :: memory_path !< path where variable is stored
108  character(len=*), dimension(:), intent(in) :: str_list
109  logical(LGP), intent(inout) :: found
110  type(MemoryType), pointer :: mt
111  logical(LGP) :: checkfail = .false.
112  integer(I4B) :: i
113 
114  call get_from_memorylist(varname, memory_path, mt, found, checkfail)
115  if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'STRING') then
116  do i = 1, size(str_list)
117  if (mt%strsclr == str_list(i)) then
118  p_mem = i
119  end if
120  end do
121  end if

◆ memorylist_remove()

subroutine, public memorymanagerextmodule::memorylist_remove ( character(len=*), intent(in)  component,
character(len=*), intent(in), optional  subcomponent,
character(len=*), intent(in), optional  context 
)
Parameters
[in]componentname of the solution, model, or exchange
[in]subcomponentname of the package (optional)
[in]contextname of the context (optional)

Definition at line 25 of file MemoryManagerExt.f90.

27  use constantsmodule, only: lenmempath
28  character(len=*), intent(in) :: component !< name of the solution, model, or exchange
29  character(len=*), intent(in), optional :: subcomponent !< name of the package (optional)
30  character(len=*), intent(in), optional :: context !< name of the context (optional)
31  character(len=LENMEMPATH) :: memory_path !< the memory path
32  type(MemoryType), pointer :: mt
33  integer(I4B) :: ipos
34  logical(LGP) :: removed
35 
36  memory_path = create_mem_path(component, subcomponent, context)
37  removed = .true. !< initialize the loop
38 
39  do while (removed)
40  removed = .false.
41  do ipos = 1, memorylist%count()
42  mt => memorylist%Get(ipos)
43  if (mt%path == memory_path .and. mt%mt_associated()) then
44  call mt%mt_deallocate()
45  removed = .true.
46  exit
47  end if
48  end do
49  end do
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:26
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
Here is the call graph for this function:
Here is the caller graph for this function: