Skip to content

Commit

Permalink
Fix problems detected by CI
Browse files Browse the repository at this point in the history
Should fix the following tests:
  - Failure to compile NUOPC cap. Suggested change requires
    consultation with NCAR to understand how to inherit a common
    object from a module
  - Style violations: Ensures that all undocumented procedures and
    excess line lengths in client.F90 are resolved
  - Accidental change of timestep interval when call step_forward_MEKE
  • Loading branch information
ashao committed Jul 8, 2022
1 parent ad92bf0 commit 4960fff
Show file tree
Hide file tree
Showing 5 changed files with 110 additions and 93 deletions.
7 changes: 5 additions & 2 deletions config_src/drivers/nuopc_cap/mom_ocean_model_nuopc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,8 @@ module MOM_ocean_model_nuopc
use MOM_surface_forcing_nuopc, only : convert_IOB_to_forces, ice_ocn_bnd_type_chksum
use MOM_surface_forcing_nuopc, only : ice_ocean_boundary_type, surface_forcing_CS
use MOM_surface_forcing_nuopc, only : forcing_save_restart
use nuopc_shr_methods, only : sr_client
! AES: Following line is commented out for now until after discussion with NCAR
! use nuopc_shr_methods, only : sr_client
use get_stochy_pattern_mod, only : write_stoch_restart_ocn
use iso_fortran_env, only : int64

Expand Down Expand Up @@ -285,7 +286,9 @@ subroutine ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, i
call initialize_MOM(OS%Time, Time_init, param_file, OS%dirs, OS%MOM_CSp, &
OS%restart_CSp, Time_in, offline_tracer_mode=OS%offline_tracer_mode, &
input_restart_file=input_restart_file, &
diag_ptr=OS%diag, count_calls=.true., client_in=sr_client, waves_CSp=OS%Waves)
diag_ptr=OS%diag, count_calls=.true., waves_CSp=OS%Waves)
! AES Following line commented out pending discussions with NCAR
! diag_ptr=OS%diag, count_calls=.true., client_in=sr_client, waves_CSp=OS%Waves)
call get_MOM_state_elements(OS%MOM_CSp, G=OS%grid, GV=OS%GV, US=OS%US, C_p=OS%C_p, &
C_p_scaled=OS%fluxes%C_p, use_temp=use_temperature)

Expand Down
7 changes: 4 additions & 3 deletions config_src/external/smartredis/MOM_MEKE_smartredis.F90
Original file line number Diff line number Diff line change
Expand Up @@ -40,12 +40,13 @@ subroutine infer_meke(G, GV, MEKE, u, v, tv, h, dt, CS)
type(ocean_grid_type), intent(inout) :: G !< Ocean grid
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure
real, dimension(SZI_(G),SZJ_(G)), intent( out) :: MEKE !< Vertically averaged eddy kinetic energy [L2 T-2 ~> m2 s-2]
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(inout) :: u !< Zonal velocity [L T-1 ~> m s-1]
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(inout) :: v !< Meridional velocity [L T-1 ~> m s-1]
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(in) :: u !< Zonal velocity [L T-1 ~> m s-1]
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in) :: v !< Meridional velocity [L T-1 ~> m s-1]
type(thermo_var_ptrs), intent(in) :: tv !< Type containing thermodynamic variables
real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thickness [H ~> m or kg m-2].
real, intent(in) :: dt !< Model(baroclinic) time-step [T ~> s].
type(meke_smartredis_CS_type), intent(in) :: CS !< Control structure for inferring MEKE using SmartRedis
type(meke_smartredis_CS_type), intent(in) :: CS !< Control structure for inferring MEKE
!! using SmartRedis

call MOM_error(FATAL,"infer_meke was compiled using the dummy module. Recompile"//&
"with source code from https://github.com/CrayLabs/MOM6-smartredis")
Expand Down
82 changes: 49 additions & 33 deletions config_src/external/smartredis/client.F90
Original file line number Diff line number Diff line change
Expand Up @@ -138,18 +138,18 @@ module smartredis_client
procedure :: get_datasets_from_list

! Private procedures
procedure, private :: put_tensor_i8
procedure, private :: put_tensor_i16
procedure, private :: put_tensor_i32
procedure, private :: put_tensor_i64
procedure, private :: put_tensor_float
procedure, private :: put_tensor_double
procedure, private :: unpack_tensor_i8
procedure, private :: unpack_tensor_i16
procedure, private :: unpack_tensor_i32
procedure, private :: unpack_tensor_i64
procedure, private :: unpack_tensor_float
procedure, private :: unpack_tensor_double
procedure, private :: put_tensor_i8 !< Put 8-bit integer tensor into database
procedure, private :: put_tensor_i16 !< Put 16-bit integer tensor into database
procedure, private :: put_tensor_i32 !< Put 32-bit integer tensor into database
procedure, private :: put_tensor_i64 !< Put 64-bit tensor into database
procedure, private :: put_tensor_float !< Put 32-bit real tensor into database
procedure, private :: put_tensor_double !< Put 64-bit real tensor into database
procedure, private :: unpack_tensor_i8 !< Unpack a 8-bit integer tensor into memory
procedure, private :: unpack_tensor_i16 !< Unpack a 16-bit integer tensor into memory
procedure, private :: unpack_tensor_i32 !< Unpack a 32-bit integer tensor into memory
procedure, private :: unpack_tensor_i64 !< Unpack a 64-bit integer tensor into memory
procedure, private :: unpack_tensor_float !< Unpack a 32-bit real tensor into memory
procedure, private :: unpack_tensor_double !< Unpack a 64-bit real tensor into memory

end type client_type

Expand Down Expand Up @@ -454,36 +454,42 @@ function set_model_from_file(self, name, model_file, backend, device, batch_size
class(client_type), intent(in) :: self !< An initialized SmartRedis client
character(len=*), intent(in) :: name !< The name to use to place the model
character(len=*), intent(in) :: model_file !< The file storing the model
character(len=*), intent(in) :: backend !< The name of the backend (TF, TFLITE, TORCH, ONNX)
character(len=*), intent(in) :: device !< The name of the device (CPU, GPU, GPU:0, GPU:1...)
character(len=*), intent(in) :: backend !< The name of the backend
!! (TF, TFLITE, TORCH, ONNX)
character(len=*), intent(in) :: device !< The name of the device
!! (CPU, GPU, GPU:0, GPU:1...)
integer, optional, intent(in) :: batch_size !< The batch size for model execution
integer, optional, intent(in) :: min_batch_size !< The minimum batch size for model execution
character(len=*), optional, intent(in) :: tag !< A tag to attach to the model for
!! information purposes
character(len=*), dimension(:), optional, intent(in) :: inputs !< One or more names of model input nodes (TF
!! models)
character(len=*), dimension(:), optional, intent(in) :: outputs !< One or more names of model output nodes (TF models)
character(len=*), dimension(:), optional, intent(in) :: inputs !< One or more names of model
!! input nodes (TF models)
character(len=*), dimension(:), optional, intent(in) :: outputs !< One or more names of model
!! output nodes (TF models)
integer(kind=enum_kind) :: code

code = -1
end function set_model_from_file

!> Load the machine learning model from a file and set the configuration for use in multi-GPU systems
function set_model_from_file_multigpu(self, name, model_file, backend, first_gpu, num_gpus, batch_size, min_batch_size, &
tag, inputs, outputs) result(code)
function set_model_from_file_multigpu(self, name, model_file, backend, first_gpu, num_gpus, batch_size, &
min_batch_size, tag, inputs, outputs) result(code)
class(client_type), intent(in) :: self !< An initialized SmartRedis client
character(len=*), intent(in) :: name !< The name to use to place the model
character(len=*), intent(in) :: model_file !< The file storing the model
character(len=*), intent(in) :: backend !< The name of the backend (TF, TFLITE, TORCH, ONNX)
integer, intent(in) :: first_gpu !< The first GPU (zero-based) to use with the model
character(len=*), intent(in) :: backend !< The name of the backend
!! (TF, TFLITE, TORCH, ONNX)
integer, intent(in) :: first_gpu !< The first GPU (zero-based)
!! to use with the model
integer, intent(in) :: num_gpus !< The number of GPUs to use with the model
integer, optional, intent(in) :: batch_size !< The batch size for model execution
integer, optional, intent(in) :: min_batch_size !< The minimum batch size for model execution
character(len=*), optional, intent(in) :: tag !< A tag to attach to the model for
!! information purposes
character(len=*), dimension(:), optional, intent(in) :: inputs !< One or more names of model input nodes (TF
!! models)
character(len=*), dimension(:), optional, intent(in) :: outputs !< One or more names of model output nodes (TF models)
character(len=*), dimension(:), optional, intent(in) :: inputs !< One or more names of model
!! input nodes (TF models)
character(len=*), dimension(:), optional, intent(in) :: outputs !< One or more names of model
!! output nodes (TF models)
integer(kind=enum_kind) :: code

code = -1
Expand All @@ -499,7 +505,8 @@ function set_model(self, name, model, backend, device, batch_size, min_batch_siz
character(len=*), intent(in) :: device !< The name of the device (CPU, GPU, GPU:0, GPU:1...)
integer, intent(in) :: batch_size !< The batch size for model execution
integer, intent(in) :: min_batch_size !< The minimum batch size for model execution
character(len=*), intent(in) :: tag !< A tag to attach to the model for information purposes
character(len=*), intent(in) :: tag !< A tag to attach to the model for
!! information purposes
character(len=*), dimension(:), intent(in) :: inputs !< One or more names of model input nodes (TF models)
character(len=*), dimension(:), intent(in) :: outputs !< One or more names of model output nodes (TF models)
integer(kind=enum_kind) :: code
Expand All @@ -518,7 +525,8 @@ function set_model_multigpu(self, name, model, backend, first_gpu, num_gpus, bat
integer, intent(in) :: num_gpus !< The number of GPUs to use with the model
integer, intent(in) :: batch_size !< The batch size for model execution
integer, intent(in) :: min_batch_size !< The minimum batch size for model execution
character(len=*), intent(in) :: tag !< A tag to attach to the model for information purposes
character(len=*), intent(in) :: tag !< A tag to attach to the model for
!! information purposes
character(len=*), dimension(:), intent(in) :: inputs !< One or more names of model input nodes (TF models)
character(len=*), dimension(:), intent(in) :: outputs !< One or more names of model output nodes (TF models)
integer(kind=enum_kind) :: code
Expand Down Expand Up @@ -632,8 +640,10 @@ function run_script(self, name, func, inputs, outputs) result(code)
class(client_type), intent(in) :: self !< An initialized SmartRedis client
character(len=*), intent(in) :: name !< The name to use to place the script
character(len=*), intent(in) :: func !< The name of the function in the script to call
character(len=*), dimension(:), intent(in) :: inputs !< One or more names of script input nodes (TF scripts)
character(len=*), dimension(:), intent(in) :: outputs !< One or more names of script output nodes (TF scripts)
character(len=*), dimension(:), intent(in) :: inputs !< One or more names of script
!! input nodes (TF scripts)
character(len=*), dimension(:), intent(in) :: outputs !< One or more names of script
!! output nodes (TF scripts)
integer(kind=enum_kind) :: code

code = -1
Expand All @@ -643,8 +653,10 @@ function run_script_multigpu(self, name, func, inputs, outputs, offset, first_gp
class(client_type), intent(in) :: self !< An initialized SmartRedis client
character(len=*), intent(in) :: name !< The name to use to place the script
character(len=*), intent(in) :: func !< The name of the function in the script to call
character(len=*), dimension(:), intent(in) :: inputs !< One or more names of script input nodes (TF scripts)
character(len=*), dimension(:), intent(in) :: outputs !< One or more names of script output nodes (TF scripts)
character(len=*), dimension(:), intent(in) :: inputs !< One or more names of script
!! input nodes (TF scripts)
character(len=*), dimension(:), intent(in) :: outputs !< One or more names of script
!! output nodes (TF scripts)
integer, intent(in) :: offset !< Index of the current image, such as a processor ID
!! or MPI rank
integer, intent(in) :: first_gpu !< The first GPU (zero-based) to use with the model
Expand Down Expand Up @@ -836,7 +848,8 @@ function poll_list_length(self, list_name, list_length, poll_frequency_ms, num_t
integer, intent(in ) :: list_length !< The desired length of the list
integer, intent(in ) :: poll_frequency_ms !< Frequency at which to poll the database (ms)
integer, intent(in ) :: num_tries !< Number of times to poll the database before failing
logical(kind=c_bool), intent( out) :: poll_result !< True if the list is the requested length, False if not after num_tries.
logical(kind=c_bool), intent( out) :: poll_result !< True if the list is the requested length,
!! False if not after num_tries.
integer(kind=enum_kind) :: code

code = -1
Expand All @@ -849,7 +862,8 @@ function poll_list_length_gte(self, list_name, list_length, poll_frequency_ms, n
integer, intent(in ) :: list_length !< The desired length of the list
integer, intent(in ) :: poll_frequency_ms !< Frequency at which to poll the database (ms)
integer, intent(in ) :: num_tries !< Number of times to poll the database before failing
logical(kind=c_bool), intent( out) :: poll_result !< True if the list is the requested length, False if not after num_tries.
logical(kind=c_bool), intent( out) :: poll_result !< True if the list is the requested length,
!! False if not after num_tries.
integer(kind=enum_kind) :: code

code = -1
Expand All @@ -862,7 +876,9 @@ function poll_list_length_lte(self, list_name, list_length, poll_frequency_ms, n
integer, intent(in) :: list_length !< The desired length of the list
integer, intent(in) :: poll_frequency_ms !< Frequency at which to poll the database (ms)
integer, intent(in) :: num_tries !< Number of times to poll the database before failing
logical(kind=c_bool), intent(out) :: poll_result !< True if the list is the requested length, False if not after num_tries.
logical(kind=c_bool), intent( out) :: poll_result !< True if the list is the requested length,
!! False if not after num_tries.

integer(kind=enum_kind) :: code

code = -1
Expand Down
16 changes: 7 additions & 9 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -410,14 +410,12 @@ module MOM
!! increments and priors
type(smartredis_CS_type) :: smartredis_CS !< SmartRedis control structure for online ML/AI
type(porous_barrier_ptrs) :: pbv !< porous barrier fractional cell metrics
real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NKMEM_) &
:: por_face_areaU !< fractional open area of U-faces [nondim]
real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NKMEM_) &
:: por_face_areaV !< fractional open area of V-faces [nondim]
real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NK_INTERFACE_) &
:: por_layer_widthU !< fractional open width of U-faces [nondim]
real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NK_INTERFACE_) &
:: por_layer_widthV !< fractional open width of V-faces [nondim]
real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NKMEM_) :: por_face_areaU !< fractional open area of U-faces [nondim]
real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NKMEM_) :: por_face_areaV !< fractional open area of V-faces [nondim]
real ALLOCABLE_, dimension(NIMEMB_PTR_,NJMEM_,NK_INTERFACE_) :: por_layer_widthU !< fractional open width
!! of U-faces [nondim]
real ALLOCABLE_, dimension(NIMEM_,NJMEMB_PTR_,NK_INTERFACE_) :: por_layer_widthV !< fractional open width
!! of V-faces [nondim]
type(particles), pointer :: particles => NULL() !<Lagrangian particles
type(stochastic_CS), pointer :: stoch_CS => NULL() !< a pointer to the stochastics control structure
end type MOM_control_struct
Expand Down Expand Up @@ -1221,7 +1219,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &

if (CS%useMEKE .and. CS%MEKE_in_dynamics) then
call step_forward_MEKE(CS%MEKE, h, CS%VarMix%SN_u, CS%VarMix%SN_v, &
CS%visc, CS%t_dyn_rel_adv, G, GV, US, CS%MEKE_CSp, CS%uhtr, CS%vhtr, &
CS%visc, dt, G, GV, US, CS%MEKE_CSp, CS%uhtr, CS%vhtr, &
CS%u, CS%v, CS%tv, Time_local)
endif
call disable_averaging(CS%diag)
Expand Down
Loading

0 comments on commit 4960fff

Please sign in to comment.