Skip to content

Commit

Permalink
Address GFDL reviewer's comments (#13)
Browse files Browse the repository at this point in the history
* Modify codes for r8-r4 conversion to remove compiler warnings
  • Loading branch information
MinsukJi-NOAA authored Jan 14, 2022
1 parent 0747a61 commit 754f7e4
Show file tree
Hide file tree
Showing 6 changed files with 185 additions and 185 deletions.
4 changes: 2 additions & 2 deletions diag_manager/diag_axis.F90
Original file line number Diff line number Diff line change
Expand Up @@ -235,7 +235,7 @@ INTEGER FUNCTION diag_axis_init(name, DATA, units, cart_name, long_name, directi
TYPE IS (real(kind=r4_kind))
Axes(diag_axis_init)%data = DATA(1:axlen)
TYPE IS (real(kind=r8_kind))
Axes(diag_axis_init)%data = DATA(1:axlen)
Axes(diag_axis_init)%data = real(DATA(1:axlen))
CLASS DEFAULT
CALL error_mesg('diag_axis_mod::diag_axis_init',&
& 'The axis data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down Expand Up @@ -491,7 +491,7 @@ SUBROUTINE get_diag_axis(id, name, units, long_name, cart_name,&
ELSE
SELECT TYPE (DATA)
TYPE IS (real(kind=r4_kind))
DATA(1:Axes(id)%length) = Axes(id)%data(1:Axes(id)%length)
DATA(1:Axes(id)%length) = real(Axes(id)%data(1:Axes(id)%length), kind=r4_kind)
TYPE IS (real(kind=r8_kind))
DATA(1:Axes(id)%length) = Axes(id)%data(1:Axes(id)%length)
CLASS DEFAULT
Expand Down
12 changes: 6 additions & 6 deletions diag_manager/diag_grid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@ SUBROUTINE diag_grid_init(domain, glo_lat, glo_lon, aglo_lat, aglo_lon)
TYPE IS (real(kind=r4_kind))
diag_global_grid%aglo_lat = TRANSPOSE(aglo_lat)
TYPE IS (real(kind=r8_kind))
diag_global_grid%aglo_lat = TRANSPOSE(aglo_lat)
diag_global_grid%aglo_lat = TRANSPOSE(real(aglo_lat))
CLASS DEFAULT
CALL error_mesg('diag_grid_mod::diag_grid_init',&
& 'The a-grid latitude data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -268,7 +268,7 @@ SUBROUTINE diag_grid_init(domain, glo_lat, glo_lon, aglo_lat, aglo_lon)
TYPE IS (real(kind=r4_kind))
diag_global_grid%aglo_lon = TRANSPOSE(aglo_lon)
TYPE IS (real(kind=r8_kind))
diag_global_grid%aglo_lon = TRANSPOSE(aglo_lon)
diag_global_grid%aglo_lon = TRANSPOSE(real(aglo_lon))
CLASS DEFAULT
CALL error_mesg('diag_grid_mod::diag_grid_init',&
& 'The a-grid longitude data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -278,7 +278,7 @@ SUBROUTINE diag_grid_init(domain, glo_lat, glo_lon, aglo_lat, aglo_lon)
TYPE IS (real(kind=r4_kind))
diag_global_grid%aglo_lat = aglo_lat
TYPE IS (real(kind=r8_kind))
diag_global_grid%aglo_lat = aglo_lat
diag_global_grid%aglo_lat = real(aglo_lat)
CLASS DEFAULT
CALL error_mesg('diag_grid_mod::diag_grid_init',&
& 'The a-grid latitude data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -288,7 +288,7 @@ SUBROUTINE diag_grid_init(domain, glo_lat, glo_lon, aglo_lat, aglo_lon)
TYPE IS (real(kind=r4_kind))
diag_global_grid%aglo_lon = aglo_lon
TYPE IS (real(kind=r8_kind))
diag_global_grid%aglo_lon = aglo_lon
diag_global_grid%aglo_lon = real(aglo_lon)
CLASS DEFAULT
CALL error_mesg('diag_grid_mod::diag_grid_init',&
& 'The a-grid longitude data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -299,7 +299,7 @@ SUBROUTINE diag_grid_init(domain, glo_lat, glo_lon, aglo_lat, aglo_lon)
TYPE IS (real(kind=r4_kind))
diag_global_grid%glo_lat = glo_lat
TYPE IS (real(kind=r8_kind))
diag_global_grid%glo_lat = glo_lat
diag_global_grid%glo_lat = real(glo_lat)
CLASS DEFAULT
CALL error_mesg('diag_grid_mod::diag_grid_init',&
& 'The grid latitude data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -309,7 +309,7 @@ SUBROUTINE diag_grid_init(domain, glo_lat, glo_lon, aglo_lat, aglo_lon)
TYPE IS (real(kind=r4_kind))
diag_global_grid%glo_lon = glo_lon
TYPE IS (real(kind=r8_kind))
diag_global_grid%glo_lon = glo_lon
diag_global_grid%glo_lon = real(glo_lon)
CLASS DEFAULT
CALL error_mesg('diag_grid_mod::diag_grid_init',&
& 'The grid longitude data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down
38 changes: 19 additions & 19 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -622,8 +622,8 @@ INTEGER FUNCTION register_static_field(module_name, field_name, axes, long_name,
INTEGER, OPTIONAL, INTENT(in) :: volume !< Field ID for the volume field associated with this field
CHARACTER(len=*), OPTIONAL, INTENT(in) :: realm !< String to set as the value to the modeling_realm attribute

REAL :: missing_value_use
REAL, DIMENSION(2) :: range_use
REAL :: missing_value_use !< Local copy of missing_value
REAL, DIMENSION(2) :: range_use !< Local copy of range
INTEGER :: field, num_axes, j, out_num, k
INTEGER, DIMENSION(3) :: siz, local_siz, local_start, local_end ! indices of local domain of global axes
INTEGER :: tile, file_num
Expand All @@ -646,7 +646,7 @@ INTEGER FUNCTION register_static_field(module_name, field_name, axes, long_name,
TYPE IS (real(kind=r4_kind))
missing_value_use = missing_value
TYPE IS (real(kind=r8_kind))
missing_value_use = missing_value
missing_value_use = real(missing_value)
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::register_static_field',&
& 'The missing_value is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down Expand Up @@ -809,7 +809,7 @@ INTEGER FUNCTION register_static_field(module_name, field_name, axes, long_name,
TYPE IS (real(kind=r4_kind))
range_use = range
TYPE IS (real(kind=r8_kind))
range_use = range
range_use = real(range)
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::register_static_field',&
& 'The range is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down Expand Up @@ -1286,7 +1286,7 @@ LOGICAL FUNCTION send_data_0d(diag_field_id, field, time, err_msg)
TYPE(time_type), INTENT(in), OPTIONAL :: time
CHARACTER(len=*), INTENT(out), OPTIONAL :: err_msg

REAL :: field_out(1, 1, 1)
REAL :: field_out(1, 1, 1) !< Local copy of field

! If diag_field_id is < 0 it means that this field is not registered, simply return
IF ( diag_field_id <= 0 ) THEN
Expand All @@ -1299,7 +1299,7 @@ LOGICAL FUNCTION send_data_0d(diag_field_id, field, time, err_msg)
TYPE IS (real(kind=r4_kind))
field_out(1, 1, 1) = field
TYPE IS (real(kind=r8_kind))
field_out(1, 1, 1) = field
field_out(1, 1, 1) = real(field)
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::send_data_0d',&
& 'The field is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -1319,8 +1319,8 @@ LOGICAL FUNCTION send_data_1d(diag_field_id, field, time, is_in, mask, rmask, ie
LOGICAL, INTENT(in), DIMENSION(:), OPTIONAL :: mask
CHARACTER(len=*), INTENT(out), OPTIONAL :: err_msg

REAL, DIMENSION(SIZE(field(:)), 1, 1) :: field_out
LOGICAL, DIMENSION(SIZE(field(:)), 1, 1) :: mask_out
REAL, DIMENSION(SIZE(field(:)), 1, 1) :: field_out !< Local copy of field
LOGICAL, DIMENSION(SIZE(field(:)), 1, 1) :: mask_out !< Local copy of mask

! If diag_field_id is < 0 it means that this field is not registered, simply return
IF ( diag_field_id <= 0 ) THEN
Expand All @@ -1333,7 +1333,7 @@ LOGICAL FUNCTION send_data_1d(diag_field_id, field, time, is_in, mask, rmask, ie
TYPE IS (real(kind=r4_kind))
field_out(:, 1, 1) = field
TYPE IS (real(kind=r8_kind))
field_out(:, 1, 1) = field
field_out(:, 1, 1) = real(field)
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::send_data_1d',&
& 'The field is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -1349,9 +1349,9 @@ LOGICAL FUNCTION send_data_1d(diag_field_id, field, time, is_in, mask, rmask, ie
IF ( PRESENT(rmask) ) THEN
SELECT TYPE (rmask)
TYPE IS (real(kind=r4_kind))
WHERE (rmask < 0.5) mask_out(:, 1, 1) = .FALSE.
WHERE (rmask < 0.5_r4_kind) mask_out(:, 1, 1) = .FALSE.
TYPE IS (real(kind=r8_kind))
WHERE (rmask < 0.5) mask_out(:, 1, 1) = .FALSE.
WHERE (rmask < 0.5_r8_kind) mask_out(:, 1, 1) = .FALSE.
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::send_data_1d',&
& 'The rmask is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down Expand Up @@ -1388,8 +1388,8 @@ LOGICAL FUNCTION send_data_2d(diag_field_id, field, time, is_in, js_in, &
CLASS(*), INTENT(in), DIMENSION(:,:),OPTIONAL :: rmask
CHARACTER(len=*), INTENT(out), OPTIONAL :: err_msg

REAL, DIMENSION(SIZE(field,1),SIZE(field,2),1) :: field_out
LOGICAL, DIMENSION(SIZE(field,1),SIZE(field,2),1) :: mask_out
REAL, DIMENSION(SIZE(field,1),SIZE(field,2),1) :: field_out !< Local copy of field
LOGICAL, DIMENSION(SIZE(field,1),SIZE(field,2),1) :: mask_out !< Local copy of mask

! If diag_field_id is < 0 it means that this field is not registered, simply return
IF ( diag_field_id <= 0 ) THEN
Expand All @@ -1402,7 +1402,7 @@ LOGICAL FUNCTION send_data_2d(diag_field_id, field, time, is_in, js_in, &
TYPE IS (real(kind=r4_kind))
field_out(:, :, 1) = field
TYPE IS (real(kind=r8_kind))
field_out(:, :, 1) = field
field_out(:, :, 1) = real(field)
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::send_data_2d',&
& 'The field is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -1418,9 +1418,9 @@ LOGICAL FUNCTION send_data_2d(diag_field_id, field, time, is_in, js_in, &
IF ( PRESENT(rmask) ) THEN
SELECT TYPE (rmask)
TYPE IS (real(kind=r4_kind))
WHERE ( rmask < 0.5 ) mask_out(:, :, 1) = .FALSE.
WHERE ( rmask < 0.5_r4_kind ) mask_out(:, :, 1) = .FALSE.
TYPE IS (real(kind=r8_kind))
WHERE ( rmask < 0.5 ) mask_out(:, :, 1) = .FALSE.
WHERE ( rmask < 0.5_r8_kind ) mask_out(:, :, 1) = .FALSE.
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::send_data_2d',&
& 'The rmask is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down Expand Up @@ -1631,7 +1631,7 @@ LOGICAL FUNCTION send_data_3d(diag_field_id, field, time, is_in, js_in, ks_in, &
CHARACTER(len=256) :: err_msg_local
CHARACTER(len=128) :: error_string, error_string1

REAL, ALLOCATABLE, DIMENSION(:,:,:) :: field_out
REAL, ALLOCATABLE, DIMENSION(:,:,:) :: field_out !< Local copy of field

! If diag_field_id is < 0 it means that this field is not registered, simply return
IF ( diag_field_id <= 0 ) THEN
Expand Down Expand Up @@ -1666,7 +1666,7 @@ LOGICAL FUNCTION send_data_3d(diag_field_id, field, time, is_in, js_in, ks_in, &
TYPE IS (real(kind=r4_kind))
field_out = field
TYPE IS (real(kind=r8_kind))
field_out = field
field_out = real(field)
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::send_data_3d',&
& 'The field is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down Expand Up @@ -1800,7 +1800,7 @@ LOGICAL FUNCTION send_data_3d(diag_field_id, field, time, is_in, js_in, ks_in, &
TYPE IS (real(kind=r4_kind))
weight1 = weight
TYPE IS (real(kind=r8_kind))
weight1 = weight
weight1 = real(weight)
CLASS DEFAULT
CALL error_mesg ('diag_manager_mod::send_data_3d',&
& 'The weight is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down
8 changes: 4 additions & 4 deletions diag_manager/diag_util.F90
Original file line number Diff line number Diff line change
Expand Up @@ -643,8 +643,8 @@ SUBROUTINE log_diag_field_info(module_name, field_name, axes, long_name, units,&
CHARACTER(len=1) :: sep = '|'
CHARACTER(len=256) :: axis_name, axes_list
INTEGER :: i
REAL :: missing_value_use
REAL, DIMENSION(2) :: range_use
REAL :: missing_value_use !< Local copy of missing_value
REAL, DIMENSION(2) :: range_use !< Local copy of range

IF ( .NOT.do_diag_field_log ) RETURN
IF ( mpp_pe().NE.mpp_root_pe() ) RETURN
Expand Down Expand Up @@ -682,7 +682,7 @@ SUBROUTINE log_diag_field_info(module_name, field_name, axes, long_name, units,&
TYPE IS (real(kind=r4_kind))
missing_value_use = missing_value
TYPE IS (real(kind=r8_kind))
missing_value_use = missing_value
missing_value_use = real(missing_value)
CLASS DEFAULT
CALL error_mesg ('diag_util_mod::log_diag_field_info',&
& 'The missing_value is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand All @@ -698,7 +698,7 @@ SUBROUTINE log_diag_field_info(module_name, field_name, axes, long_name, units,&
TYPE IS (real(kind=r4_kind))
range_use = range
TYPE IS (real(kind=r8_kind))
range_use = range
range_use = real(range)
CLASS DEFAULT
CALL error_mesg ('diag_util_mod::log_diag_field_info',&
& 'The range is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
Expand Down
Loading

0 comments on commit 754f7e4

Please sign in to comment.