Skip to content

Commit

Permalink
memory manager updates including checkin int2d and mem_set_value char…
Browse files Browse the repository at this point in the history
…str1d
  • Loading branch information
mjreno authored and mjreno committed Aug 29, 2023
1 parent 42a8455 commit b4ded84
Show file tree
Hide file tree
Showing 2 changed files with 71 additions and 5 deletions.
44 changes: 44 additions & 0 deletions src/Utilities/Memory/MemoryManager.f90
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,7 @@ module MemoryManagerModule
interface mem_checkin
module procedure &
checkin_int1d, &
checkin_int2d, &
checkin_dbl1d, &
checkin_dbl2d
end interface mem_checkin
Expand Down Expand Up @@ -997,6 +998,49 @@ subroutine checkin_int1d(aint, name, mem_path, name2, mem_path2)
return
end subroutine checkin_int1d

!> @brief Check in an existing 2d integer array with a new address (name + path)
!<
subroutine checkin_int2d(aint2d, name, mem_path, name2, mem_path2)
integer(I4B), dimension(:, :), pointer, contiguous, intent(inout) :: aint2d !< the existing 2d array
character(len=*), intent(in) :: name !< new variable name
character(len=*), intent(in) :: mem_path !< new path where variable is stored
character(len=*), intent(in) :: name2 !< existing variable name
character(len=*), intent(in) :: mem_path2 !< existing path where variable is stored
! -- local
type(MemoryType), pointer :: mt
integer(I4B) :: ncol, nrow, isize
! -- code
!
! -- check the variable name length
call mem_check_length(name, LENVARNAME, "variable")
!
! -- set isize
ncol = size(aint2d, dim=1)
nrow = size(aint2d, dim=2)
isize = ncol * nrow
!
! -- allocate memory type
allocate (mt)
!
! -- set memory type
mt%aint2d => aint2d
mt%isize = isize
mt%name = name
mt%path = mem_path
write (mt%memtype, "(a,' (',i0,',',i0,')')") 'INTEGER', ncol, nrow
!
! -- set master information
mt%master = .false.
mt%mastername = name2
mt%masterPath = mem_path2
!
! -- add memory type to the memory list
call memorylist%add(mt)
!
! -- return
return
end subroutine checkin_int2d

!> @brief Check in an existing 1d double precision array with a new address (name + path)
!<
subroutine checkin_dbl1d(adbl, name, mem_path, name2, mem_path2)
Expand Down
32 changes: 27 additions & 5 deletions src/Utilities/Memory/MemoryManagerExt.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,8 @@ module MemoryManagerExtModule
mem_set_value_int1d, mem_set_value_int1d_mapped, &
mem_set_value_int2d, mem_set_value_int3d, mem_set_value_dbl, &
mem_set_value_dbl1d, mem_set_value_dbl1d_mapped, &
mem_set_value_dbl2d, mem_set_value_dbl3d, mem_set_value_str
mem_set_value_dbl2d, mem_set_value_dbl3d, mem_set_value_str, &
mem_set_value_charstr1d
end interface mem_set_value

contains
Expand All @@ -41,8 +42,6 @@ subroutine memorylist_remove(component, subcomponent, context)
mt => memorylist%Get(ipos)
if (mt%path == memory_path .and. mt%mt_associated()) then
call mt%mt_deallocate()
deallocate (mt)
call memorylist%remove(ipos, .false.)
removed = .true.
exit
end if
Expand All @@ -61,8 +60,12 @@ subroutine mem_set_value_logical(p_mem, varname, memory_path, found)
logical(LGP) :: checkfail = .false.

call get_from_memorylist(varname, memory_path, mt, found, checkfail)
if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'LOGICAL') then
p_mem = mt%logicalsclr
if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'INTEGER') then
if (mt%intsclr == 0) then
p_mem = .false.
else
p_mem = .true.
end if
end if
end subroutine mem_set_value_logical

Expand Down Expand Up @@ -366,4 +369,23 @@ subroutine mem_set_value_str(p_mem, varname, memory_path, found)
end if
end subroutine mem_set_value_str

subroutine mem_set_value_charstr1d(p_mem, varname, memory_path, found)
use CharacterStringModule, only: CharacterStringType
type(CharacterStringType), dimension(:), &
pointer, contiguous, intent(inout) :: p_mem !< pointer to charstr 1d array
character(len=*), intent(in) :: varname !< variable name
character(len=*), intent(in) :: memory_path !< path where variable is stored
logical(LGP), intent(inout) :: found
type(MemoryType), pointer :: mt
logical(LGP) :: checkfail = .false.
integer(I4B) :: n

call get_from_memorylist(varname, memory_path, mt, found, checkfail)
if (found .and. mt%memtype(1:index(mt%memtype, ' ')) == 'STRING') then
do n = 1, size(mt%acharstr1d)
p_mem(n) = mt%acharstr1d(n)
end do
end if
end subroutine mem_set_value_charstr1d

end module MemoryManagerExtModule

0 comments on commit b4ded84

Please sign in to comment.