Skip to content

Commit

Permalink
destroy growing allocation
Browse files Browse the repository at this point in the history
  • Loading branch information
lukasm91 committed Sep 17, 2024
1 parent dd539b0 commit a290f7c
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 9 deletions.
28 changes: 19 additions & 9 deletions src/trans/gpu/algor/growing_allocator_mod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ MODULE GROWING_ALLOCATOR_MOD
PRIVATE
PUBLIC :: GROWING_ALLOCATION_TYPE
PUBLIC :: REALLOCATE_GROWING_ALLOCATION, REGISTER_FREE_FUNCTION
PUBLIC :: DESTROY_GROWING_ALLOCATOR

ABSTRACT INTERFACE
SUBROUTINE FREE_FUNC_PROC(PTR, SZ) BIND(C)
Expand Down Expand Up @@ -32,19 +33,12 @@ SUBROUTINE REALLOCATE_GROWING_ALLOCATION(ALLOC, SZ)
USE TPM_GEN, ONLY: NOUT
IMPLICIT NONE
TYPE(GROWING_ALLOCATION_TYPE), INTENT(INOUT) :: ALLOC
INTEGER(C_SIZE_T) :: SZ
INTEGER :: I
INTEGER(C_SIZE_T), INTENT(IN) :: SZ

! Deallocate existing pointer
IF (ASSOCIATED(ALLOC%PTR) .AND. SZ > SIZE(ALLOC%PTR, 1, C_SIZE_T)) THEN
WRITE(NOUT,*) "WARNING: REALLOCATING GROWING POINTER CAUSING GRAPH REINSTANTIATION"
DO I = 1, ALLOC%FREE_FUNCS_SZ
CALL ALLOC%FREE_FUNCS(I)%FUNC(ALLOC%PTR, &
SIZE(ALLOC%PTR, 1, C_SIZE_T))
ENDDO
!$ACC EXIT DATA DELETE(ALLOC%PTR)
DEALLOCATE(ALLOC%PTR)
NULLIFY(ALLOC%PTR)
CALL DESTROY_GROWING_ALLOCATOR(ALLOC)
ENDIF

IF (.NOT. ASSOCIATED(ALLOC%PTR)) THEN
Expand Down Expand Up @@ -89,4 +83,20 @@ SUBROUTINE REGISTER_FREE_C(ALLOC_C, FREE_FUNC_C) BIND(C, NAME="growing_allocator

END SUBROUTINE

SUBROUTINE DESTROY_GROWING_ALLOCATOR(ALLOC)
USE ISO_C_BINDING, ONLY: C_SIZE_T
IMPLICIT NONE
TYPE(GROWING_ALLOCATION_TYPE) :: ALLOC
INTEGER :: I
IF (ALLOCATED(ALLOC%PTR)) THEN
DO I = 1, ALLOC%FREE_FUNCS_SZ
CALL ALLOC%FREE_FUNCS(I)%FUNC(ALLOC%PTR, &
SIZE(ALLOC%PTR, 1, C_SIZE_T))
ENDDO
!$ACC EXIT DATA DELETE(ALLOC%PTR)
DEALLOCATE(ALLOC%PTR)
NULLIFY(ALLOC%PTR)
ENDIF
END SUBROUTINE

END MODULE
4 changes: 4 additions & 0 deletions src/trans/gpu/external/trans_end.F90
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,8 @@ SUBROUTINE TRANS_END(CDMODE)
USE TPM_FFT, ONLY: T, FFT_RESOL
USE TPM_CTL, ONLY: C, CTL_RESOL
USE TPM_FLT, ONLY: S, FLT_RESOL
USE TPM_TRANS, ONLY: GROWING_ALLOCATION
USE GROWING_ALLOCATOR_MOD,ONLY: DESTROY_GROWING_ALLOCATOR
USE EQ_REGIONS_MOD, ONLY: N_REGIONS
USE SET_RESOL_MOD, ONLY: SET_RESOL
USE DEALLOC_RESOL_MOD, ONLY: DEALLOC_RESOL
Expand Down Expand Up @@ -81,6 +83,8 @@ SUBROUTINE TRANS_END(CDMODE)
DEALLOCATE(LENABLED)
ENDIF

CALL DESTROY_GROWING_ALLOCATOR(GROWING_ALLOCATION)

NULLIFY(R)
IF( ALLOCATED(DIM_RESOL) ) DEALLOCATE(DIM_RESOL)

Expand Down

0 comments on commit a290f7c

Please sign in to comment.