diff --git a/CHANGELOG.md b/CHANGELOG.md index fac9d6bc40d9..93486da0fa7b 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -6,6 +6,7 @@ The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/), and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html). ## [v3.0.0 - Development] +- Added benchmark to test creation of ESMF_GridComp objects ### Removed @@ -36,6 +37,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0 - Added capability for HistoryCollectionGridComp to extract field names from expressions - Added ability for HistoryCollectionGridComp to extract multiple field names from expressions - Added vertical and ungridded dimensions to output for History3G +- Added benchmark to test the performance of gridcomp creation ### Changed diff --git a/benchmarks/esmf/CMakeLists.txt b/benchmarks/esmf/CMakeLists.txt index c5e85be0dbc6..bb430cfc61c3 100644 --- a/benchmarks/esmf/CMakeLists.txt +++ b/benchmarks/esmf/CMakeLists.txt @@ -1,5 +1,6 @@ set(exe gc_run.x) +add_subdirectory(gridcomp_creation) ecbuild_add_executable ( TARGET ${exe} SOURCES gc_run.F90) diff --git a/benchmarks/esmf/gridcomp_creation/CMakeLists.txt b/benchmarks/esmf/gridcomp_creation/CMakeLists.txt new file mode 100644 index 000000000000..0896267ac32e --- /dev/null +++ b/benchmarks/esmf/gridcomp_creation/CMakeLists.txt @@ -0,0 +1,16 @@ +set(exe gridcomp_create.x) +set(MODULE_DIRECTORY ${esma_include}/benchmarks/esmf/gridcomp_creation) + +ecbuild_add_executable ( + TARGET ${exe} + SOURCES GridCompCreationTester.F90 GridCompCreator.F90 GridCompCreationShared.F90 GridCompCreatorMemoryProfile.F90 +) + +target_link_libraries (${exe} PRIVATE MAPL.shared MAPL.base ESMF::ESMF ) +target_include_directories (${exe} PUBLIC $) +set_target_properties (${exe} PROPERTIES Fortran_MODULE_DIRECTORY ${MODULE_DIRECTORY}) + +# CMake has an OpenMP issue with NAG Fortran: https://gitlab.kitware.com/cmake/cmake/-/issues/21280 +if (NOT CMAKE_Fortran_COMPILER_ID MATCHES "NAG") + target_link_libraries(${exe} PRIVATE OpenMP::OpenMP_Fortran) +endif () diff --git a/benchmarks/esmf/gridcomp_creation/GridCompCreationShared.F90 b/benchmarks/esmf/gridcomp_creation/GridCompCreationShared.F90 new file mode 100644 index 000000000000..5791f50a4484 --- /dev/null +++ b/benchmarks/esmf/gridcomp_creation/GridCompCreationShared.F90 @@ -0,0 +1,56 @@ +module grid_comp_creation_shared + + use, intrinsic :: iso_fortran_env, only: R64 => real64 + + implicit none + private + public :: to_characters + public :: MAXSTR + public :: JOIN + + integer, parameter :: MAXSTR = 256 + character(len=*), parameter :: JOIN = ', ' + + interface to_characters + module procedure :: real_to_characters + module procedure :: integer_to_characters + end interface to_characters + +contains + + function real_to_characters(t, fixed, rc) result(chars) + character(len=:), allocatable :: chars + real(R64), intent(in) :: t + logical, optional, intent(in) :: fixed + integer, optional, intent(out) :: rc + integer :: status + integer, parameter :: TW = 12 + character(len=TW), parameter :: SF = '( ES24.16 )' + character(len=TW), parameter :: FD = '( F8.4 )' + character(len=TW) :: FMT_ + character(len=MAXSTR) :: raw + + FMT_ = SF + if(present(fixed)) then + if(fixed) FMT_ = FD + end if + write(raw, fmt=FMT_, iostat=status) t + if(present(rc)) rc = status + chars = trim(adjustl(raw)) + + end function real_to_characters + + function integer_to_characters(n, rc) result(chars) + character(len=:), allocatable :: chars + integer, intent(in) :: n + integer, optional, intent(out) :: rc + integer :: status + character(len=MAXSTR) :: raw + + write(raw, fmt='(I0)', iostat=status) n + if(present(rc)) rc = status + chars = trim(adjustl(raw)) + + end function integer_to_characters + +end module grid_comp_creation_shared diff --git a/benchmarks/esmf/gridcomp_creation/GridCompCreationTester.F90 b/benchmarks/esmf/gridcomp_creation/GridCompCreationTester.F90 new file mode 100644 index 000000000000..d4d3f8eaff9e --- /dev/null +++ b/benchmarks/esmf/gridcomp_creation/GridCompCreationTester.F90 @@ -0,0 +1,49 @@ +program grid_comp_creation_tester + + use grid_comp_creation_shared + use grid_comp_creator + use grid_comp_creator_memory_profiler + + implicit none + + integer, parameter :: SUCCESS = 0 + integer, parameter :: GENERAL_ERROR = 1 + integer, parameter :: NGC_NOT_SET = 2*GENERAL_ERROR + integer, parameter :: RUN_FAILED = 2*NGC_NOT_SET + + character(len=*), parameter :: OPTION_USE_OWN_VM = '--use-own-vm' + + integer :: rc, status + integer :: ngc + character(len=MAXSTR) :: raw + integer :: i, n + logical :: is_silent = .TRUE. + logical :: use_own_vm = .FALSE. + + rc = SUCCESS + ngc = -1 + do i = 1, command_argument_count() + call get_command_argument(i, value=raw, status=status) + if(status /= SUCCESS) cycle + raw = adjustl(raw) + if(raw == OPTION_USE_OWN_VM) then + use_own_vm = .TRUE. + cycle + end if + read(raw, fmt='(I32)', iostat=status) n + if(status == SUCCESS) ngc = n + end do + + if(ngc < 0) then + rc = rc + NGC_NOT_SET + error stop rc, QUIET=is_silent + end if + + call run(ngc, use_own_vm, status) + + if(status /= SUCCESS) rc = rc + RUN_FAILED + rc = finalize() + if(rc == SUCCESS) stop rc, QUIET=is_silent + error stop rc, QUIET=is_silent + +end program grid_comp_creation_tester diff --git a/benchmarks/esmf/gridcomp_creation/GridCompCreator.F90 b/benchmarks/esmf/gridcomp_creation/GridCompCreator.F90 new file mode 100644 index 000000000000..2cb504b3a746 --- /dev/null +++ b/benchmarks/esmf/gridcomp_creation/GridCompCreator.F90 @@ -0,0 +1,300 @@ +#include "MAPL_Generic.h" +module grid_comp_creator + + use grid_comp_creation_shared + use grid_comp_creator_memory_profiler + use mapl_ErrorHandlingMod + use esmf + use mpi + use, intrinsic :: iso_fortran_env, only: R64 => real64, I64 => int64 + + implicit none + private + + public :: run + public :: finalize + + type :: CreatorData + ! parameters + integer :: ngc = -1 + logical :: use_own_vm = .FALSE. + ! result data + integer(kind=I64) :: start_time = -1_I64 + integer(kind=I64) :: end_time = -1_I64 + integer(kind=I64) :: count_rate = -1_I64 + type(MemoryProfile) :: prior + type(MemoryProfile) :: post + logical :: valid = .FALSE. + contains + procedure :: write_results => write_creator_results + procedure :: run_options => write_run_options + end type CreatorData + + type :: Wrapper + type(CreatorData), pointer :: ptr => null() + end type Wrapper + + interface CreatorData + module procedure :: construct_creator_data + end interface CreatorData + + interface run + module procedure :: creation_driver + end interface run + +contains + + function construct_creator_data(num_gc, use_own_vm) result(r) + type(CreatorData) :: r + integer, intent(in) :: num_gc + logical, intent(in) :: use_own_vm + + r%valid = num_gc >= 0 + if(.not. r%valid) return + r%ngc = num_gc + r%use_own_vm = use_own_vm + + end function construct_creator_data + + subroutine creation_driver(num_gc, use_own_vm, rc) + integer, intent(in) :: num_gc + logical, intent(in) :: use_own_vm + integer, optional, intent(out) :: rc + integer :: status + type(CreatorData) :: cdata + type(ESMF_GridComp) :: gc + + cdata = CreatorData(num_gc, use_own_vm) + _ASSERT(cdata%valid, 'Number of gridcomponents is negative.') + call ESMF_Initialize(logKindFlag=ESMF_LOGKIND_NONE, _RC) + gc = ESMF_GridCompCreate(name='GC_', contextFlag=ESMF_CONTEXT_OWN_VM, _RC) + call ESMF_GridCompSetServices(gc, userRoutine=GC_SetServices, _RC) + call GC_SetInternal(gc, cdata, _RC) + call ESMF_GridCompRun(gc, _RC) + call ESMF_GridCompFinalize(gc, _RC) + _RETURN(_SUCCESS) + + end subroutine creation_driver + + subroutine GC_SetServices(gc, rc) + type(ESMF_GridComp) :: gc + integer, intent(out) :: rc + integer :: status + type(CreatorData), pointer :: cdata + type(Wrapper) :: wrap + + allocate(cdata, stat=status) + _VERIFY(status) + wrap%ptr => cdata + call ESMF_GridCompSetInternalState(gc, wrap, _RC) + call ESMF_GridCompSetEntryPoint(gc, ESMF_METHOD_RUN, GC_Run, _RC) + call ESMF_GridCompSetEntryPoint(gc, ESMF_METHOD_FINALIZE, GC_Final, _RC) + _RETURN(_SUCCESS) + + end subroutine GC_SetServices + + subroutine GC_SetInternal(gc, cdata, rc) + type(ESMF_GridComp) :: gc + class(CreatorData), target, intent(in) :: cdata + integer, optional, intent(out) :: rc + integer :: status + type(Wrapper) :: wrap + + call ESMF_GridCompGetInternalState(gc, wrap, _RC) + wrap%ptr => cdata + call ESMF_GridCompSetInternalState(gc, wrap, _RC) + _RETURN(_SUCCESS) + + end subroutine GC_SetInternal + + subroutine GC_GetInternal(gc, cdata, rc) + type(ESMF_GridComp) :: gc + type(CreatorData), pointer, intent(out) :: cdata + integer, optional, intent(out) :: rc + type(Wrapper) :: wrap + integer :: status + + call ESMF_GridCompGetInternalState(gc, wrap, _RC) + cdata => wrap%ptr + _RETURN(_SUCCESS) + + end subroutine GC_GetInternal + + subroutine GC_Run(gc, importState, exportState, clock, rc) + type(ESMF_GridComp) :: gc + type(ESMF_State) :: importState + type(ESMF_State) :: exportState + type(ESMF_Clock) :: clock + integer, intent(out) :: rc + integer :: status + type(CreatorData), pointer :: cdata + integer(I64) :: start_time, end_time, count_rate + type(MemoryProfile) :: prior, post + integer :: rank + type(ESMF_GridComp), allocatable :: gcc(:) + integer :: i + + _UNUSED_DUMMY(importState) + _UNUSED_DUMMY(exportState) + _UNUSED_DUMMY(clock) + call GC_GetInternal(gc, cdata, _RC) + + call profile_memory(prior, _RC) + call system_clock(count = start_time, count_rate=count_rate) + + allocate(gcc(cdata%ngc)) + do i = 1, size(gcc) + gcc(i) = make_gridcomp(i, cdata%use_own_vm, _RC) + end do + call system_clock(count = end_time, count_rate=count_rate) + call profile_memory(post, _RC) + call destroy_gridcomps(gcc, _RC) + if(allocated(gcc)) deallocate(gcc) + + call get_rank(gc, rank, _RC) + if(rank == 0) then + cdata%start_time = start_time + cdata%end_time = end_time + cdata%count_rate = count_rate + cdata%prior = prior + cdata%post = post + end if + + _RETURN(_SUCCESS) + + end subroutine GC_Run + + subroutine GC_Final(gc, importState, exportState, clock, rc) + type(ESMF_GridComp) :: gc + type(ESMF_State) :: importState + type(ESMF_State) :: exportState + type(ESMF_Clock) :: clock + integer, intent(out) :: rc + integer :: status + type(CreatorData), pointer :: cdata + integer :: rank + + _UNUSED_DUMMY(importState) + _UNUSED_DUMMY(exportState) + _UNUSED_DUMMY(clock) + call get_rank(gc, rank, _RC) + if(rank == 0) then + call GC_GetInternal(gc, cdata, _RC) + call cdata%write_results() + end if + + _RETURN(_SUCCESS) + + end subroutine GC_Final + + subroutine get_rank(gc, rank, rc) + type(ESMF_GridComp) :: gc + integer, intent(out) :: rank + integer, optional, intent(out) :: rc + integer :: status + type(ESMF_VM) :: vm + integer :: comm + + call ESMF_GridCompGet(gc, vm=vm, _RC) + call ESMF_VMGet(vm, mpiCommunicator=comm, _RC) + call MPI_Comm_rank(comm, rank, _IERROR) + _RETURN(_SUCCESS) + + end subroutine get_rank + + subroutine initialize(rc) + integer, optional, intent(out) :: rc + integer :: status + + call ESMF_Initialize(logKindFlag=ESMF_LOGKIND_NONE, _RC) + _RETURN(_SUCCESS) + + end subroutine initialize + + integer function finalize() result(rc) + call ESMF_Finalize(rc=rc) + end function finalize + + function make_gc_name(n, rc) result(gc_name) + character(len=:), allocatable :: gc_name + integer, intent(in) :: n + integer, optional, intent(out) :: rc + integer :: status + character(len=MAXSTR) :: raw + + write(raw, fmt='(I0)', iostat=status) n + _ASSERT(status == _SUCCESS, 'Unable to make gridcomp name') + gc_name = "GC" // raw + _RETURN(_SUCCESS) + + end function make_gc_name + + function make_gridcomp(n, use_own_vm, rc) result(gc) + type(ESMF_GridComp) :: gc + integer, intent(in) :: n + logical, intent(in) :: use_own_vm + integer, optional, intent(out) :: rc + integer :: status + character(len=:), allocatable :: name + type(ESMF_Context_Flag) :: contextflag = ESMF_CONTEXT_PARENT_VM + + if(use_own_vm) contextflag = ESMF_CONTEXT_OWN_VM + name = make_gc_name(n, _RC) + gc = ESMF_GridCompCreate(name=name, contextFlag=contextflag, _RC) + + _RETURN(_SUCCESS) + + end function make_gridcomp + + subroutine destroy_gridcomps(gc, rc) + type(ESMF_GridComp), intent(inout) :: gc(:) + integer, optional, intent(out) :: rc + integer :: status + integer :: i + + do i=1, size(gc) + call ESMF_GridCompDestroy(gc(i), _RC) + end do + _RETURN(_SUCCESS) + + end subroutine destroy_gridcomps + + subroutine write_creator_results(this) + class(CreatorData), intent(in) :: this + character(len=*), parameter :: NGC_TIME_HEADER = 'num_components, time(s)' + character(len=:), allocatable :: line + integer, parameter :: INDENT_SIZE = 4 + character(len=*), parameter :: indent = repeat(' ', INDENT_SIZE) + character(len=2), parameter :: COMMENT = '# ' + character(len=*), parameter :: FMT = '(A)' + real(R64) :: time + character(len=MAXSTR) :: diffline + + associate(ngc=>this%ngc, pr=>this%prior, pst=>this%post,& + & st=>this%start_time, et=>this%end_time, rate=>this%count_rate) + time = real(et - st, R64)/rate + line = to_characters(ngc) // JOIN // to_characters(time) // JOIN + write(*, FMT) COMMENT // NGC_TIME_HEADER // JOIN // MEMORY_PROFILE_HEADER + write(*, FMT) line // print_memory_profile(pr) // ' ' // COMMENT // 'BEFORE' + write(*, FMT) line // print_memory_profile(pst) // ' ' // COMMENT // 'AFTER' + + diffline = COMMENT // 'Memory profile did not change.' + if(.not. (pst == pr)) diffline = line // print_memory_profile(pst-pr) // ' ' // COMMENT // 'CHANGE' + write(*, FMT) trim(diffline) + + write(*, FMT) COMMENT // trim(this%run_options()) + + end associate + + end subroutine write_creator_results + + function write_run_options(this) result(message) + character(len=MAXSTR) :: message + class(CreatorData), intent(in) :: this + + message = 'use parent VM' + if(this%use_own_vm) message = 'use own VM' + + end function write_run_options + +end module grid_comp_creator diff --git a/benchmarks/esmf/gridcomp_creation/GridCompCreatorMemoryProfile.F90 b/benchmarks/esmf/gridcomp_creation/GridCompCreatorMemoryProfile.F90 new file mode 100644 index 000000000000..a656ada1f963 --- /dev/null +++ b/benchmarks/esmf/gridcomp_creation/GridCompCreatorMemoryProfile.F90 @@ -0,0 +1,123 @@ +#include "MAPL_Generic.h" +module grid_comp_creator_memory_profiler + + use grid_comp_creation_shared + use mapl_ErrorHandlingMod + use MAPL_MemUtilsMod + use, intrinsic :: iso_fortran_env, only: R64 => real64 + implicit none + private + + public :: MemoryProfile + public :: profile_memory + public :: print_memory_profile + public :: MEMORY_PROFILE_HEADER + public :: operator(-) + public :: operator(==) + + type :: MemoryProfile + real(R64) :: total = -1.0 + real(R64) :: used = -1.0 + real(R64) :: committed = -1.0 + real(R64) :: percent_used = -1.0 + real(R64) :: percent_committed = -1.0 + end type MemoryProfile + + interface operator(-) + module procedure :: subtract_memory_profile + end interface operator(-) + + interface operator(==) + module procedure :: equals_memory_profile + end interface operator(==) + + enum, bind(c) + enumerator :: INDEX_ = 0 + enumerator :: INDEX_TOTAL + enumerator :: INDEX_USED + enumerator :: INDEX_COMMITTED + enumerator :: INDEX_PERCENT_USED + enumerator :: INDEX_PERCENT_COMMITTED + end enum + + integer(kind=kind(INDEX_)), parameter :: INDEX_SIZE = INDEX_PERCENT_COMMITTED + character(len=*), parameter :: MEMORY_PROFILE_HEADER = "total (MB), used (MB), committed (MB), percent_used, percent_committed" + +contains + + function as_array(mem) result(arr) + real(R64) :: arr(INDEX_SIZE) + class(MemoryProfile), intent(in) :: mem + + arr(INDEX_TOTAL) = mem%total + arr(INDEX_USED) = mem%used + arr(INDEX_COMMITTED) = mem%committed + arr(INDEX_PERCENT_USED) = mem%percent_used + arr(INDEX_PERCENT_COMMITTED) = mem%percent_committed + + end function as_array + + function from_array(arr) result(mem) + type(MemoryProfile) :: mem + real(R64), intent(in) :: arr(INDEX_SIZE) + + mem%total = arr(INDEX_TOTAL) + mem%used = arr(INDEX_USED) + mem%committed = arr(INDEX_COMMITTED) + mem%percent_used = arr(INDEX_PERCENT_USED) + mem%percent_committed = arr(INDEX_PERCENT_COMMITTED) + + end function from_array + + function subtract_memory_profile(p1, p2) result(diff) + type(MemoryProfile) :: diff + class(MemoryProfile), intent(in) :: p1, p2 + real(R64) :: total = -1.0 + + if(p2%total == p1%total) total = p2%total + diff = from_array(as_array(p1) - as_array(p2)) + diff%total = total + + end function subtract_memory_profile + + logical function equals_memory_profile(p1, p2) result(eq) + class(MemoryProfile), intent(in) :: p1, p2 + + eq = all(as_array(p1)==as_array(p2)) + + end function equals_memory_profile + + subroutine profile_memory(mem, rc) + type(MemoryProfile), intent(out) :: mem + integer, optional, intent(out) :: rc + integer :: status + real :: total, used, committed, percent_used, percent_committed + + ! Get used memory + call MAPL_MemUsed(memtotal=total, used=used, percent_used=percent_used, _RC) + ! Get committed memory + call MAPL_MemCommited(memtotal=total, committed_as=committed, percent_committed=percent_committed, _RC) + mem%total = total + mem%used = used + mem%committed = committed + mem%percent_used = percent_used + mem%percent_committed = percent_committed + + _RETURN(_SUCCESS) + + end subroutine profile_memory + + function print_memory_profile(mem) result(values) + character(len=:), allocatable :: values + class(MemoryProfile), intent(in) :: mem + integer :: status + + values = to_characters(mem%total, rc=status) + values = values // JOIN // to_characters(mem%used, rc=status) + values = values // JOIN // to_characters(mem%committed, rc=status) + values = values // JOIN // to_characters(mem%percent_used, fixed=.TRUE., rc=status) + values = values // JOIN // to_characters(mem%percent_committed, fixed=.TRUE., rc=status) + + end function print_memory_profile + +end module grid_comp_creator_memory_profiler diff --git a/benchmarks/esmf/gridcomp_creation/README.md b/benchmarks/esmf/gridcomp_creation/README.md new file mode 100644 index 000000000000..de02ffa518e9 --- /dev/null +++ b/benchmarks/esmf/gridcomp_creation/README.md @@ -0,0 +1,2 @@ +This benchmark is measuring the performance of grid component creation +measured in time and memory.