Skip to content

Commit cc584db

Browse files
Merge branch 'NOAA-GFDL:dev/gfdl' into evp_in_BTCS_tmp
2 parents 5897e57 + 9b45087 commit cc584db

File tree

94 files changed

+4812
-2285
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

94 files changed

+4812
-2285
lines changed

.testing/Makefile

+3-1
Original file line numberDiff line numberDiff line change
@@ -265,10 +265,12 @@ $(BUILD)/timing/Makefile: MOM_ACFLAGS += --with-driver=timing_tests
265265

266266

267267
# Build executables
268+
.NOTPARALLEL:$(foreach e,$(UNIT_EXECS),$(BUILD)/unit/$(e))
268269
$(BUILD)/unit/test_%: $(BUILD)/unit/Makefile FORCE
269270
cd $(@D) && $(TIME) $(MAKE) $(@F) -j
270271
$(BUILD)/unit/Makefile: $(foreach e,$(UNIT_EXECS),../config_src/drivers/unit_tests/$(e).F90)
271272

273+
.NOTPARALLEL:$(foreach e,$(TIMING_EXECS),$(BUILD)/timing/$(e))
272274
$(BUILD)/timing/time_%: $(BUILD)/timing/Makefile FORCE
273275
cd $(@D) && $(TIME) $(MAKE) $(@F) -j
274276
$(BUILD)/timing/Makefile: $(foreach e,$(TIMING_EXECS),../config_src/drivers/timing_tests/$(e).F90)
@@ -649,7 +651,7 @@ $(WORK)/%/restart/ocean.stats: $(BUILD)/symmetric/MOM6 | preproc
649651
# Not a true rule; only call this after `make test` to summarize test results.
650652
.PHONY: test.summary
651653
test.summary:
652-
@./tools/report_test_results.sh $(WORK)/results
654+
./tools/report_test_results.sh $(WORK)/results
653655

654656

655657
#---

ac/configure.ac

+2-2
Original file line numberDiff line numberDiff line change
@@ -81,8 +81,8 @@ AS_IF([test "x$with_driver" != "x"],
8181

8282

8383
# Explicitly assume free-form Fortran
84-
AC_LANG(Fortran)
85-
AC_FC_SRCEXT(f90)
84+
AC_LANG([Fortran])
85+
AC_FC_SRCEXT([f90])
8686

8787

8888
# Determine MPI compiler wrappers

ac/deps/configure.fms.ac

+14-2
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,16 @@ AC_INIT(
1010
AC_CONFIG_SRCDIR([fms/fms.F90])
1111
AC_CONFIG_MACRO_DIR([m4])
1212

13+
1314
# C configuration
15+
16+
# Autoconf assumes that LDFLAGS can be passed to CFLAGS, even though this is
17+
# not valid in some compilers. This can cause basic CC tests to fail.
18+
# Since we do not link with CC, we can safely disable LDFLAGS for AC_PROG_CC.
19+
FC_LDFLAGS="$LDFLAGS"
20+
LDFLAGS=""
21+
22+
# C compiler verification
1423
AC_PROG_CC
1524
AX_MPI
1625
CC=$MPICC
@@ -55,10 +64,13 @@ AC_CHECK_FUNCS([gettid], [], [
5564
# FMS 2019.01.03 uses __APPLE__ to disable Linux CPU affinity calls.
5665
AC_CHECK_FUNCS([sched_getaffinity], [], [AC_DEFINE([__APPLE__])])
5766

67+
# Restore LDFLAGS
68+
LDFLAGS="$FC_LDFLAGS"
69+
5870

5971
# Standard Fortran configuration
60-
AC_LANG(Fortran)
61-
AC_FC_SRCEXT(f90)
72+
AC_LANG([Fortran])
73+
AC_FC_SRCEXT([f90])
6274
AC_PROG_FC
6375

6476

config_src/drivers/FMS_cap/MOM_surface_forcing_gfdl.F90

+21-7
Original file line numberDiff line numberDiff line change
@@ -635,16 +635,20 @@ subroutine convert_IOB_to_fluxes(IOB, fluxes, index_bounds, Time, valid_time, G,
635635
endif
636636

637637
! Set the wind stresses and ustar.
638-
if (associated(fluxes%ustar) .and. associated(fluxes%ustar_gustless) .and. associated(fluxes%tau_mag)) then
638+
if (associated(fluxes%ustar) .and. associated(fluxes%ustar_gustless) .and. associated(fluxes%tau_mag) &
639+
.and. associated(fluxes%tau_mag_gustless) ) then
639640
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, ustar=fluxes%ustar, &
640-
mag_tau=fluxes%tau_mag, gustless_ustar=fluxes%ustar_gustless)
641+
mag_tau=fluxes%tau_mag, gustless_ustar=fluxes%ustar_gustless, &
642+
gustless_mag_tau=fluxes%tau_mag_gustless)
641643
else
642644
if (associated(fluxes%ustar)) &
643645
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, ustar=fluxes%ustar)
644646
if (associated(fluxes%ustar_gustless)) &
645647
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, gustless_ustar=fluxes%ustar_gustless)
646648
if (associated(fluxes%tau_mag)) &
647649
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, mag_tau=fluxes%tau_mag)
650+
if (associated(fluxes%tau_mag_gustless)) &
651+
call extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, gustless_mag_tau=fluxes%tau_mag_gustless)
648652
endif
649653

650654
if (coupler_type_initialized(fluxes%tr_fluxes) .and. &
@@ -908,7 +912,7 @@ end subroutine convert_IOB_to_forces
908912
!! Ice_ocean_boundary_type into optional argument arrays, including changes of units, sign
909913
!! conventions, and putting the fields into arrays with MOM-standard sized halos.
910914
subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy, ustar, &
911-
gustless_ustar, mag_tau, tau_halo)
915+
gustless_ustar, mag_tau, gustless_mag_tau, tau_halo)
912916
type(ice_ocean_boundary_type), &
913917
target, intent(in) :: IOB !< An ice-ocean boundary type with fluxes to drive
914918
!! the ocean in a coupled model
@@ -931,6 +935,9 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
931935
real, dimension(SZI_(G),SZJ_(G)), &
932936
optional, intent(inout) :: mag_tau !< The magintude of the wind stress at tracer points
933937
!! including subgridscale variability and gustiness [R Z L T-2 ~> Pa]
938+
real, dimension(SZI_(G),SZJ_(G)), &
939+
optional, intent(out) :: gustless_mag_tau !< The magintude of the wind stress at tracer points
940+
!! without any contributions from gustiness [R Z L T-2 ~> Pa]
934941
integer, optional, intent(in) :: tau_halo !< The halo size of wind stresses to set, 0 by default.
935942

936943
! Local variables
@@ -947,7 +954,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
947954
real :: tau_mag ! magnitude of the wind stress [R Z L T-2 ~> Pa]
948955
real :: stress_conversion ! A unit conversion factor from Pa times any stress multiplier [R Z L T-2 Pa-1 ~> 1]
949956

950-
logical :: do_ustar, do_gustless, do_tau_mag
957+
logical :: do_ustar, do_gustless, do_tau_mag, do_gustless_tau_mag
951958
integer :: wind_stagger ! AGRID, BGRID_NE, or CGRID_NE (integers from MOM_domains)
952959
integer :: i, j, is, ie, js, je, ish, ieh, jsh, jeh, Isqh, Ieqh, Jsqh, Jeqh, i0, j0, halo
953960

@@ -960,7 +967,8 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
960967
IRho0 = US%L_to_Z / CS%Rho0
961968
stress_conversion = US%Pa_to_RLZ_T2 * CS%wind_stress_multiplier
962969

963-
do_ustar = present(ustar) ; do_gustless = present(gustless_ustar) ; do_tau_mag = present(mag_tau)
970+
do_ustar = present(ustar) ; do_gustless = present(gustless_ustar)
971+
do_tau_mag = present(mag_tau) ; do_gustless_tau_mag = present(gustless_mag_tau)
964972

965973
wind_stagger = CS%wind_stagger
966974
if ((IOB%wind_stagger == AGRID) .or. (IOB%wind_stagger == BGRID_NE) .or. &
@@ -973,7 +981,8 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
973981

974982
! Set surface momentum stress related fields as a function of staggering.
975983
if (present(taux) .or. present(tauy) .or. &
976-
((do_ustar .or. do_tau_mag .or. do_gustless) .and. .not.associated(IOB%stress_mag)) ) then
984+
((do_ustar .or. do_tau_mag .or. do_gustless .or. do_gustless_tau_mag) &
985+
.and. .not.associated(IOB%stress_mag)) ) then
977986

978987
if (wind_stagger == BGRID_NE) then
979988
taux_in_B(:,:) = 0.0 ; tauy_in_B(:,:) = 0.0
@@ -1053,7 +1062,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
10531062
endif ! endif for extracting wind stress fields with various staggerings
10541063
endif
10551064

1056-
if (do_ustar .or. do_tau_mag .or. do_gustless) then
1065+
if (do_ustar .or. do_tau_mag .or. do_gustless .or. do_gustless_tau_mag) then
10571066
! Set surface friction velocity directly or as a function of staggering.
10581067
! ustar is required for the bulk mixed layer formulation and other turbulent mixing
10591068
! parametizations. The background gustiness (for example with a relatively small value
@@ -1071,6 +1080,8 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
10711080
endif
10721081
if (do_tau_mag) &
10731082
mag_tau(i,j) = gustiness + US%Pa_to_RLZ_T2*IOB%stress_mag(i-i0,j-j0)
1083+
if (do_gustless_tau_mag) &
1084+
gustless_mag_tau(i,j) = US%Pa_to_RLZ_T2*IOB%stress_mag(i-i0,j-j0)
10741085
if (do_ustar) &
10751086
ustar(i,j) = sqrt(gustiness*IRho0 + IRho0*US%Pa_to_RLZ_T2*IOB%stress_mag(i-i0,j-j0))
10761087
enddo ; enddo ; endif
@@ -1097,6 +1108,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
10971108
endif
10981109
if (do_ustar) ustar(i,j) = sqrt(gustiness*IRho0 + IRho0 * tau_mag)
10991110
if (do_tau_mag) mag_tau(i,j) = gustiness + tau_mag
1111+
if (do_gustless_tau_mag) gustless_mag_tau(i,j) = tau_mag
11001112
if (CS%answer_date < 20190101) then
11011113
if (do_gustless) gustless_ustar(i,j) = sqrt(US%L_to_Z*tau_mag / CS%Rho0)
11021114
else
@@ -1110,6 +1122,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
11101122
if (CS%read_gust_2d .and. (G%mask2dT(i,j) > 0.0)) gustiness = CS%gust(i,j)
11111123
if (do_ustar) ustar(i,j) = sqrt(gustiness*IRho0 + IRho0 * tau_mag)
11121124
if (do_tau_mag) mag_tau(i,j) = gustiness + tau_mag
1125+
if (do_gustless_tau_mag) gustless_mag_tau(i,j) = tau_mag
11131126
if (CS%answer_date < 20190101) then
11141127
if (do_gustless) gustless_ustar(i,j) = sqrt(US%L_to_Z*tau_mag / CS%Rho0)
11151128
else
@@ -1132,6 +1145,7 @@ subroutine extract_IOB_stresses(IOB, index_bounds, Time, G, US, CS, taux, tauy,
11321145

11331146
if (do_ustar) ustar(i,j) = sqrt(gustiness*IRho0 + IRho0 * tau_mag)
11341147
if (do_tau_mag) mag_tau(i,j) = gustiness + tau_mag
1148+
if (do_gustless_tau_mag) gustless_mag_tau(i,j) = tau_mag
11351149
if (CS%answer_date < 20190101) then
11361150
if (do_gustless) gustless_ustar(i,j) = sqrt(US%L_to_Z*tau_mag / CS%Rho0)
11371151
else
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,100 @@
1+
program time_MOM_remapping
2+
3+
! This file is part of MOM6. See LICENSE.md for the license.
4+
5+
use MOM_remapping, only : remapping_CS
6+
use MOM_remapping, only : initialize_remapping
7+
use MOM_remapping, only : remapping_core_h
8+
9+
implicit none
10+
11+
type(remapping_CS) :: CS
12+
integer, parameter :: nk=75, nij=20*20, nits=10, nsamp=100, nschemes = 2
13+
character(len=10) :: scheme_labels(nschemes)
14+
real, dimension(nschemes) :: timings ! Time for nits of nij calls for each scheme [s]
15+
real, dimension(nschemes) :: tmean ! Mean time for a call [s]
16+
real, dimension(nschemes) :: tstd ! Standard deviation of time for a call [s]
17+
real, dimension(nschemes) :: tmin ! Shortest time for a call [s]
18+
real, dimension(nschemes) :: tmax ! Longest time for a call [s]
19+
real, dimension(:,:), allocatable :: u0, u1 ! Source/target values [arbitrary but same units as each other]
20+
real, dimension(:,:), allocatable :: h0, h1 ! Source target thicknesses [0..1]
21+
real :: start, finish ! Times [s]
22+
real :: h0sum, h1sum ! Totals of h0 and h1 [nondim]
23+
integer :: ij, k, isamp, iter, ischeme ! Indices and counters
24+
integer :: seed_size ! Number of integers used by seed
25+
integer, allocatable :: seed(:) ! Random number seed
26+
27+
! Set seed for random numbers
28+
call random_seed(size=seed_size)
29+
allocate( seed(seed_Size) )
30+
seed(:) = 102030405
31+
call random_seed(put=seed)
32+
33+
scheme_labels(1) = 'PCM'
34+
scheme_labels(2) = 'PLM'
35+
36+
! Set up some test data (note: using k,i indexing rather than i,k)
37+
allocate( u0(nk,nij), h0(nk,nij), u1(nk,nij), h1(nk,nij) )
38+
call random_number(u0) ! In range 0-1
39+
call random_number(h0) ! In range 0-1
40+
call random_number(h1) ! In range 0-1
41+
do ij = 1, nij
42+
h0(:,ij) = max(0., h0(:,ij) - 0.05) ! Make 5% of values equal to zero
43+
h1(:,ij) = max(0., h1(:,ij) - 0.05) ! Make 5% of values equal to zero
44+
h0sum = h0(1,ij)
45+
h1sum = h1(1,ij)
46+
do k = 2, nk
47+
h0sum = h0sum + h0(k,ij)
48+
h1sum = h1sum + h1(k,ij)
49+
enddo
50+
h0(:,ij) = h0(:,ij) / h0sum
51+
h1(:,ij) = h1(:,ij) / h1sum
52+
enddo
53+
54+
! Loop over many samples of timing loop to collect statistics
55+
tmean(:) = 0.
56+
tstd(:) = 0.
57+
tmin(:) = 1.e9
58+
tmax(:) = 0.
59+
do isamp = 1, nsamp
60+
! Time reconstruction + remapping
61+
do ischeme = 1, nschemes
62+
call initialize_remapping(CS, remapping_scheme=trim(scheme_labels(ischeme)))
63+
call cpu_time(start)
64+
do iter = 1, nits ! Make many passes to reduce sampling error
65+
do ij = 1, nij ! Calling nij times to make similar to cost in MOM_ALE()
66+
call remapping_core_h(CS, nk, h0(:,ij), u0(:,ij), nk, h1(:,ij), u1(:,ij))
67+
enddo
68+
enddo
69+
call cpu_time(finish)
70+
timings(ischeme) = (finish-start)/real(nits*nij) ! Average time per call
71+
enddo
72+
tmean(:) = tmean(:) + timings(:)
73+
tstd(:) = tstd(:) + timings(:)**2 ! tstd contains sum of squares here
74+
tmin(:) = min( tmin(:), timings(:) )
75+
tmax(:) = max( tmax(:), timings(:) )
76+
enddo
77+
tmean(:) = tmean(:) / real(nsamp) ! convert to mean
78+
tstd(:) = tstd(:) / real(nsamp) ! convert to mean of squares
79+
tstd(:) = tstd(:) - tmean(:)**2 ! convert to variance
80+
tstd(:) = sqrt( tstd(:) * real(nsamp) / real(nsamp-1) ) ! convert to standard deviation
81+
82+
83+
! Display results in YAML
84+
write(*,'(a)') "{"
85+
do ischeme = 1, nschemes
86+
write(*,"(2x,5a)") '"MOM_remapping remapping_core_h(remapping_scheme=', &
87+
trim(scheme_labels(ischeme)), ')": {'
88+
write(*,"(4x,a,1pe11.4,',')") '"min": ',tmin(ischeme)
89+
write(*,"(4x,a,1pe11.4,',')") '"mean":',tmean(ischeme)
90+
write(*,"(4x,a,1pe11.4,',')") '"std": ',tstd(ischeme)
91+
write(*,"(4x,a,i7,',')") '"n_samples": ',nsamp
92+
if (ischeme.ne.nschemes) then
93+
write(*,"(4x,a,1pe11.4,'},')") '"max": ',tmax(ischeme)
94+
else
95+
write(*,"(4x,a,1pe11.4,'}')") '"max": ',tmax(ischeme)
96+
endif
97+
enddo
98+
write(*,'(a)') "}"
99+
100+
end program time_MOM_remapping
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
program test_MOM_remapping
2+
3+
use MOM_remapping, only : remapping_unit_tests
4+
5+
if (remapping_unit_tests(.true.)) stop 1
6+
7+
end program test_MOM_remapping

config_src/external/GFDL_ocean_BGC/generic_tracer_utils.F90

+2-1
Original file line numberDiff line numberDiff line change
@@ -99,8 +99,9 @@ module g_tracer_utils
9999
contains
100100

101101
!> Unknown
102-
subroutine g_tracer_flux_init(g_tracer)
102+
subroutine g_tracer_flux_init(g_tracer, verbosity)
103103
type(g_tracer_type), pointer :: g_tracer !< Pointer to this tracer node
104+
integer, optional, intent(in) :: verbosity !< A 0-9 integer indicating a level of verbosity
104105
end subroutine g_tracer_flux_init
105106

106107
!> Unknown

config_src/external/drifters/MOM_particles_types.F90

+5-4
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module particles_types_mod
33

44
! This file is part of MOM6. See LICENSE.md for the license.
55

6+
use, intrinsic :: iso_fortran_env, only : int64
67
use MOM_grid, only : ocean_grid_type
78
use MOM_domains, only: domain2D
89

@@ -75,7 +76,7 @@ module particles_types_mod
7576
real :: vvel_old !< Previous meridional velocity component (m/s)
7677
integer :: year !< Year of this record
7778
integer :: particle_num !< Current particle number
78-
integer(kind=8) :: id = -1 !< Particle Identifier
79+
integer(kind=int64) :: id = -1 !< Particle Identifier
7980
type(xyt), pointer :: next=>null() !< Pointer to the next position in the list
8081
end type xyt
8182

@@ -98,8 +99,8 @@ module particles_types_mod
9899
real :: start_day !< origination position (degrees) and day
99100
integer :: start_year !< origination year
100101
real :: halo_part !< equal to zero for particles on the computational domain, and 1 for particles on the halo
101-
integer(kind=8) :: id !< particle identifier
102-
integer(kind=8) :: drifter_num !< particle identifier
102+
integer(kind=int64) :: id !< particle identifier
103+
integer(kind=int64) :: drifter_num !< particle identifier
103104
integer :: ine !< nearest i-index in NE direction (for convenience)
104105
integer :: jne !< nearest j-index in NE direction (for convenience)
105106
real :: xi !< non-dimensional x-coordinate within current cell (0..1)
@@ -147,7 +148,7 @@ module particles_types_mod
147148
logical :: ignore_traj=.False. !< If true, then model does not write trajectory data at all
148149
logical :: use_new_predictive_corrective =.False. !< Flag to use Bob's predictive corrective particle scheme
149150
!Added by Alon
150-
integer(kind=8) :: debug_particle_with_id = -1 !< If positive, monitors a part with this id
151+
integer(kind=int64) :: debug_particle_with_id = -1 !< If positive, monitors a part with this id
151152
type(buffer), pointer :: obuffer_n=>null() !< Buffer for outgoing parts to the north
152153
type(buffer), pointer :: ibuffer_n=>null() !< Buffer for incoming parts from the north
153154
type(buffer), pointer :: obuffer_s=>null() !< Buffer for outgoing parts to the south

config_src/infra/FMS1/MOM_diag_manager_infra.F90

+3-2
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module MOM_diag_manager_infra
88

99
! This file is part of MOM6. See LICENSE.md for the license.
1010

11+
use, intrinsic :: iso_fortran_env, only : real64
1112
use diag_axis_mod, only : fms_axis_init=>diag_axis_init
1213
use diag_axis_mod, only : fms_get_diag_axis_name => get_diag_axis_name
1314
use diag_axis_mod, only : EAST, NORTH
@@ -359,7 +360,7 @@ end function send_data_infra_3d
359360
logical function send_data_infra_2d_r8(diag_field_id, field, is_in, ie_in, js_in, je_in, &
360361
time, mask, rmask, weight, err_msg)
361362
integer, intent(in) :: diag_field_id !< The diagnostic manager identifier for this field
362-
real(kind=8), dimension(:,:), intent(in) :: field !< A 2-d array of values being recorded
363+
real(kind=real64), dimension(:,:), intent(in) :: field !< A 2-d array of values being recorded
363364
integer, optional, intent(in) :: is_in !< The starting i-index for the data being recorded
364365
integer, optional, intent(in) :: ie_in !< The end i-index for the data being recorded
365366
integer, optional, intent(in) :: js_in !< The starting j-index for the data being recorded
@@ -382,7 +383,7 @@ end function send_data_infra_2d_r8
382383
logical function send_data_infra_3d_r8(diag_field_id, field, is_in, ie_in, js_in, je_in, ks_in, ke_in, &
383384
time, mask, rmask, weight, err_msg)
384385
integer, intent(in) :: diag_field_id !< The diagnostic manager identifier for this field
385-
real(kind=8), dimension(:,:,:), intent(in) :: field !< A rank 1 array of floating point values being recorded
386+
real(kind=real64), dimension(:,:,:), intent(in) :: field !< A rank 1 array of floating point values being recorded
386387
integer, optional, intent(in) :: is_in !< The starting i-index for the data being recorded
387388
integer, optional, intent(in) :: ie_in !< The end i-index for the data being recorded
388389
integer, optional, intent(in) :: js_in !< The starting j-index for the data being recorded

config_src/infra/FMS2/MOM_diag_manager_infra.F90

+3-2
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module MOM_diag_manager_infra
88

99
! This file is part of MOM6. See LICENSE.md for the license.
1010

11+
use, intrinsic :: iso_fortran_env, only : real64
1112
use diag_axis_mod, only : fms_axis_init=>diag_axis_init
1213
use diag_axis_mod, only : fms_get_diag_axis_name => get_diag_axis_name
1314
use diag_axis_mod, only : EAST, NORTH
@@ -361,7 +362,7 @@ end function send_data_infra_3d
361362
logical function send_data_infra_2d_r8(diag_field_id, field, is_in, ie_in, js_in, je_in, &
362363
time, mask, rmask, weight, err_msg)
363364
integer, intent(in) :: diag_field_id !< The diagnostic manager identifier for this field
364-
real(kind=8), dimension(:,:), intent(in) :: field !< A 2-d array of values being recorded
365+
real(kind=real64), dimension(:,:), intent(in) :: field !< A 2-d array of values being recorded
365366
integer, optional, intent(in) :: is_in !< The starting i-index for the data being recorded
366367
integer, optional, intent(in) :: ie_in !< The end i-index for the data being recorded
367368
integer, optional, intent(in) :: js_in !< The starting j-index for the data being recorded
@@ -384,7 +385,7 @@ end function send_data_infra_2d_r8
384385
logical function send_data_infra_3d_r8(diag_field_id, field, is_in, ie_in, js_in, je_in, ks_in, ke_in, &
385386
time, mask, rmask, weight, err_msg)
386387
integer, intent(in) :: diag_field_id !< The diagnostic manager identifier for this field
387-
real(kind=8), dimension(:,:,:), intent(in) :: field !< A rank 1 array of floating point values being recorded
388+
real(kind=real64), dimension(:,:,:), intent(in) :: field !< A rank 1 array of floating point values being recorded
388389
integer, optional, intent(in) :: is_in !< The starting i-index for the data being recorded
389390
integer, optional, intent(in) :: ie_in !< The end i-index for the data being recorded
390391
integer, optional, intent(in) :: js_in !< The starting j-index for the data being recorded

0 commit comments

Comments
 (0)