Skip to content

Commit

Permalink
Fixes for NVHPC
Browse files Browse the repository at this point in the history
  • Loading branch information
mathomp4 committed Oct 3, 2023
1 parent d218108 commit c36ff9f
Show file tree
Hide file tree
Showing 8 changed files with 27 additions and 21 deletions.
2 changes: 1 addition & 1 deletion Apps/Regrid_Util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -338,7 +338,7 @@ Program Regrid_Util

subroutine main()

type(regrid_support) :: support
type(regrid_support), target :: support

type(ESMF_VM) :: vm ! ESMF Virtual Machine

Expand Down
2 changes: 2 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,8 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0

### Fixed

- Various fixes for NVHPCP work

### Removed

### Deprecated
Expand Down
1 change: 1 addition & 0 deletions docs/tutorial/driver_app/Example_Driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
program Example_Driver
use MPI
use MAPL
use mapl_CapOptionsMod, only: MAPL_CapOptions
implicit none

type (MAPL_Cap) :: cap
Expand Down
5 changes: 4 additions & 1 deletion generic/OpenMP_Support.F90
Original file line number Diff line number Diff line change
Expand Up @@ -595,6 +595,7 @@ subroutine copy_callbacks(state, multi_states, rc)
type(CallbackMethodWrapper), pointer :: wrapper
type(CallbackMap), pointer :: callbacks
type(CallbackMapIterator) :: iter
procedure(), pointer :: userRoutine

n_multi = size(multi_states)
call get_callbacks(state, callbacks, _RC)
Expand All @@ -604,7 +605,9 @@ subroutine copy_callbacks(state, multi_states, rc)
do while (iter /= e)
wrapper => iter%second()
do i = 1, n_multi
call ESMF_MethodAdd(multi_states(i), label=iter%first(), userRoutine=wrapper%userRoutine, _RC)
!call ESMF_MethodAdd(multi_states(i), label=iter%first(), userRoutine=wrapper%userRoutine, _RC)
userRoutine => wrapper%userRoutine
call ESMF_MethodAdd(multi_states(i), label=iter%first(), userRoutine=userRoutine, _RC)
end do
call iter%next()
end do
Expand Down
8 changes: 4 additions & 4 deletions gridcomps/Cap/FargparseCLI.F90
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module MAPL_FargparseCLIMod
use gFTL2_IntegerVector
use mapl_KeywordEnforcerMod
use mapl_ExceptionHandling
use mapl_CapOptionsMod, only: MAPL_CapOptions !Rename is for backward compatibility. Remove renaming for 3.0
use mapl_CapOptionsMod, only: MAPL_CapOptions_ => MAPL_CapOptions !Rename is for backward compatibility. Remove renaming for 3.0
implicit none
private

Expand Down Expand Up @@ -45,7 +45,7 @@ subroutine I_extraoptions(parser, rc)

function new_CapOptions_from_fargparse(unusable, dummy, extra, rc) result (cap_options)
class(KeywordEnforcer), optional, intent(in) :: unusable
type (MAPL_CapOptions) :: cap_options
type (MAPL_CapOptions_) :: cap_options
character(*), intent(in) :: dummy !Needed for backward compatibility. Remove after 3.0
procedure(I_extraoptions), optional :: extra
integer, optional, intent(out) :: rc
Expand Down Expand Up @@ -230,7 +230,7 @@ end subroutine add_command_line_options

subroutine fill_cap_options(fargparseCLI, cap_options, unusable, rc)
class(MAPL_FargparseCLI), intent(inout) :: fargparseCLI
type(MAPL_CapOptions), intent(out) :: cap_options
type(MAPL_CapOptions_), intent(out) :: cap_options
class(KeywordEnforcer), optional, intent(in) :: unusable
integer, optional, intent(out) :: rc
integer :: status
Expand Down Expand Up @@ -416,7 +416,7 @@ end subroutine fill_cap_options

!Function for backward compatibility. Remove for 3.0
function old_CapOptions_from_Fargparse( fargparseCLI, unusable, rc) result (cap_options)
type (MAPL_CapOptions) :: cap_options
type (MAPL_CapOptions_) :: cap_options
type (MAPL_FargparseCLI), intent(inout) :: fargparseCLI
class (KeywordEnforcer), optional, intent(in) :: unusable
integer, optional, intent(out) :: rc
Expand Down
6 changes: 3 additions & 3 deletions gridcomps/History/MAPL_HistoryTrajectoryMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ module HistoryTrajectoryMod
integer :: obsfile_Te_index
logical :: is_valid
contains
procedure :: initialize
procedure :: initialize => initialize_
procedure :: reinitialize
procedure :: create_variable => create_metadata_variable
procedure :: create_file_handle
Expand Down Expand Up @@ -113,15 +113,15 @@ module function HistoryTrajectory_from_config(config,string,clock,rc) result(tra
integer, optional, intent(out) :: rc
end function HistoryTrajectory_from_config

module subroutine initialize(this,items,bundle,timeInfo,vdata,recycle_track,rc)
module subroutine initialize_(this,items,bundle,timeInfo,vdata,recycle_track,rc)
class(HistoryTrajectory), intent(inout) :: this
type(GriddedIOitemVector), target, intent(inout) :: items
type(ESMF_FieldBundle), intent(inout) :: bundle
type(TimeData), intent(inout) :: timeInfo
type(VerticalData), optional, intent(inout) :: vdata
logical, optional, intent(inout) :: recycle_track
integer, optional, intent(out) :: rc
end subroutine initialize
end subroutine initialize_

module subroutine reinitialize(this,rc)
class(HistoryTrajectory), intent(inout) :: this
Expand Down
4 changes: 2 additions & 2 deletions gridcomps/History/MAPL_HistoryTrajectoryMod_smod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@
end procedure


module procedure initialize
module procedure initialize_
integer :: status
type(ESMF_Grid) :: grid
type(variable) :: v
Expand Down Expand Up @@ -223,7 +223,7 @@

_RETURN(_SUCCESS)

end procedure initialize
end procedure initialize_


module procedure reinitialize
Expand Down
20 changes: 10 additions & 10 deletions griddedio/TileIO.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,10 @@ module MAPL_TileIOMod

private

type tile_buffer
real, allocatable :: ptr(:)
end type

type, public :: MAPL_TileIO
private
type(ESMF_FieldBundle) :: bundle
Expand All @@ -22,10 +26,6 @@ module MAPL_TileIOMod
procedure :: process_data_from_file
end type MAPL_TileIO

type tile_buffer
real, allocatable :: ptr(:)
end type

interface MAPL_TileIO
module procedure new_MAPL_TileIO
end interface MAPL_TileIO
Expand All @@ -40,13 +40,13 @@ function new_MAPL_TileIO(bundle,read_collection_id) result(TileIO)
TileIO%bundle = bundle
TileIO%read_collection_id = read_collection_id
end function

subroutine request_data_from_file(this,filename,timeindex,rc)
class(MAPL_TileIO), intent(inout) :: this
character(len=*), intent(in) :: filename
integer, intent(in) :: timeindex
integer, intent(out), optional :: rc

integer :: status
integer :: num_vars,i,rank
type(ArrayReference) :: ref
Expand Down Expand Up @@ -76,10 +76,10 @@ subroutine request_data_from_file(this,filename,timeindex,rc)
allocate(this%tile_buffer(i)%ptr((0)),_STAT)
end if
ref = ArrayReference(this%tile_buffer(i)%ptr)
call i_clients%collective_prefetch_data(this%read_collection_id, filename, trim(names(i)), ref, &
call i_clients%collective_prefetch_data(this%read_collection_id, filename, trim(names(i)), ref, &
start=local_start, global_start=global_start, global_count = global_count)
deallocate(local_start,global_start,global_count)
else
deallocate(local_start,global_start,global_count)
else
_FAIL("rank >1 tile fields not supported")
end if
end do
Expand Down Expand Up @@ -117,5 +117,5 @@ subroutine process_data_from_file(this,rc)
deallocate(this%tile_buffer)
_RETURN(_SUCCESS)
end subroutine

end module

0 comments on commit c36ff9f

Please sign in to comment.