Skip to content

Commit

Permalink
Merge pull request #7 from CommerceGov/user/sdu/cell_measures_message
Browse files Browse the repository at this point in the history
Accepted in testing
  • Loading branch information
underwoo committed Nov 13, 2014
2 parents 574c737 + 34d1d64 commit 8cb7db2
Show file tree
Hide file tree
Showing 4 changed files with 53 additions and 46 deletions.
4 changes: 2 additions & 2 deletions diag_manager/diag_data.F90
Original file line number Diff line number Diff line change
Expand Up @@ -492,13 +492,13 @@ MODULE diag_data_mod
INTEGER :: pack
INTEGER :: pow_value !< Power value to use for mean_pow(n) calculations
CHARACTER(len=50) :: time_method ! time method field from the input file
! coordianes of the buffer and counter are (x, y, z, time-of-day)
! coordinates of the buffer and counter are (x, y, z, time-of-day)
REAL, _ALLOCATABLE, DIMENSION(:,:,:,:) :: buffer _NULL
REAL, _ALLOCATABLE, DIMENSION(:,:,:,:) :: counter _NULL
! the following two counters are used in time-averaging for some
! combination of the field options. Their size is the length of the
! diurnal axis; the counters must be tracked separately for each of
! the diurnal interval, becaus the number of time slices accumulated
! the diurnal interval, because the number of time slices accumulated
! in each can be different, depending on time step and the number of
! diurnal samples.
REAL, _ALLOCATABLE, DIMENSION(:) :: count_0d
Expand Down
2 changes: 1 addition & 1 deletion diag_manager/diag_grid.F90
Original file line number Diff line number Diff line change
Expand Up @@ -547,7 +547,7 @@ SUBROUTINE get_local_indexes(latStart, latEnd, lonStart, lonEnd,&
dists_lat(1) = ABS(diag_global_grid%glo_lat(i+1,j) - diag_global_grid%glo_lat(i,j))
count = count+1
END IF
IF ( j < dimI ) THEN
IF ( j < dimJ ) THEN
dists_lon(2) = ABS(diag_global_grid%glo_lon(i,j+1) - diag_global_grid%glo_lon(i,j))
dists_lat(2) = ABS(diag_global_grid%glo_lat(i,j+1) - diag_global_grid%glo_lat(i,j))
count = count+1
Expand Down
79 changes: 43 additions & 36 deletions diag_manager/diag_manager.F90
Original file line number Diff line number Diff line change
Expand Up @@ -560,28 +560,31 @@ INTEGER FUNCTION register_diag_field_array(module_name, field_name, axes, init_t
input_fields(register_diag_field_array)%static = .FALSE.
field = register_diag_field_array


! Verify that area and volume do not point to the same variable
IF ( PRESENT(volume).AND.PRESENT(area) ) THEN
IF ( area.EQ.volume ) THEN
CALL error_mesg ('diag_manager_mod::register_diag_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA and VOLUME CANNOT be the same variable.&
& Contact the developers.',&
& FATAL)
END IF
END IF

! Check for the existence of the area/volume field(s)
IF ( PRESENT(area) ) THEN
IF ( area < 0 ) THEN
CALL error_mesg ('diag_manager_mod::register_diag_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA measures field NOT found in diag_table',&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA measures field NOT found in diag_table.&
& Contact the model liaison.',&
& FATAL)
END IF
END IF
IF ( PRESENT(volume) ) THEN
IF ( volume < 0 ) THEN
CALL error_mesg ('diag_manager_mod::register_diag_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' VOLUME measures field NOT found in diag_table',&
& FATAL)
END IF
END IF

! Verify that area and volume do not point to the same variable
IF ( PRESENT(volume).AND.PRESENT(area) ) THEN
IF ( area.EQ.volume ) THEN
CALL error_mesg ('diag_manager_mod::register_diag_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA and VOLUME CANNOT be the same variable.&
& Contact the developers.',&
&//TRIM(module_name)//'/'// TRIM(field_name)//' VOLUME measures field NOT found in diag_table.&
& Contact the model liaison.',&
& FATAL)
END IF
END IF
Expand Down Expand Up @@ -790,28 +793,30 @@ INTEGER FUNCTION register_static_field(module_name, field_name, axes, long_name,
& TRIM(field_name)//' ALREADY registered, should not register twice', FATAL)
END IF

! Verify that area and volume do not point to the same variable
IF ( PRESENT(volume).AND.PRESENT(area) ) THEN
IF ( area.EQ.volume ) THEN
CALL error_mesg ('diag_manager_mod::register_static_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA and VOLUME CANNOT be the same variable.&
& Contact the developers.',&
& FATAL)
END IF
END IF

! Check for the existence of the area/volume field(s)
IF ( PRESENT(area) ) THEN
IF ( area < 0 ) THEN
CALL error_mesg ('diag_manager_mod::register_static_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA measures field NOT found in diag_table',&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA measures field NOT found in diag_table.&
& Contact the model liaison.n',&
& FATAL)
END IF
END IF
IF ( PRESENT(volume) ) THEN
IF ( volume < 0 ) THEN
CALL error_mesg ('diag_manager_mod::register_static_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' VOLUME measures field NOT found in diag_table',&
& FATAL)
END IF
END IF

! Verify that area and volume do not point to the same variable
IF ( PRESENT(volume).AND.PRESENT(area) ) THEN
IF ( area.EQ.volume ) THEN
CALL error_mesg ('diag_manager_mod::register_static_field', 'module/output_field '&
&//TRIM(module_name)//'/'// TRIM(field_name)//' AREA and VOLUME CANNOT be the same variable.&
& Contact the developers.',&
&//TRIM(module_name)//'/'// TRIM(field_name)//' VOLUME measures field NOT found in diag_table&
& Contact the model liaison.',&
& FATAL)
END IF
END IF
Expand Down Expand Up @@ -1101,10 +1106,10 @@ LOGICAL FUNCTION get_related_field(field, rel_field, out_field_id, out_file_id)
cm_file_num = output_fields(cm_ind)%output_file

IF ( cm_file_num.EQ.rel_file.AND.&
& (( output_fields(cm_ind)%time_method.EQ.rel_field%time_method .AND.&
& output_fields(cm_ind)%next_output.EQ.rel_field%next_output .AND.&
& output_fields(cm_ind)%last_output.EQ.rel_field%last_output ).OR.&
& ( output_fields(cm_ind)%static.OR.rel_field%static )) ) THEN
& (( (output_fields(cm_ind)%time_ops.EQV.rel_field%time_ops) .AND.&
& (output_fields(cm_ind)%next_output.EQ.rel_field%next_output) .AND.&
& (output_fields(cm_ind)%last_output.EQ.rel_field%last_output) ).OR.&
& (output_fields(cm_ind)%static.OR.rel_field%static) ) ) THEN
get_related_field = .TRUE.
out_field_id = cm_ind
out_file_id = cm_file_num
Expand All @@ -1120,12 +1125,12 @@ LOGICAL FUNCTION get_related_field(field, rel_field, out_field_id, out_file_id)

! If time_method, freq, output_units, next_output, and last_output the same, or
! the output_field is static then valid for cell_measures
IF ( ( files(cm_file_num)%output_freq.EQ.files(rel_file)%output_freq .AND.&
& files(cm_file_num)%output_units.EQ.files(cm_file_num)%output_units .AND.&
& output_fields(cm_ind)%time_method.EQ.rel_field%time_method .AND.&
& output_fields(cm_ind)%next_output.EQ.rel_field%next_output .AND.&
& output_fields(cm_ind)%last_output.EQ.rel_field%last_output ).OR.&
& output_fields(cm_ind)%static.OR.rel_field%static ) THEN
IF ( ( (files(cm_file_num)%output_freq.EQ.files(rel_file)%output_freq) .AND.&
& (files(cm_file_num)%output_units.EQ.files(rel_file)%output_units) .AND.&
& (output_fields(cm_ind)%time_ops.EQV.rel_field%time_ops) .AND.&
& (output_fields(cm_ind)%next_output.EQ.rel_field%next_output) .AND.&
& (output_fields(cm_ind)%last_output.EQ.rel_field%last_output) ).OR.&
& ( output_fields(cm_ind)%static.OR.rel_field%static ) ) THEN
get_related_field = .TRUE.
out_field_id = cm_ind
out_file_id = cm_file_num
Expand Down Expand Up @@ -1167,14 +1172,16 @@ SUBROUTINE init_field_cell_measures(output_field, area, volume, err_msg)
IF ( PRESENT(area) ) THEN
IF ( area.LE.0 ) THEN
IF ( fms_error_handler('diag_manager_mod::init_field_cell_measure',&
& 'AREA field not in diag_table', err_msg) ) RETURN
& 'AREA field not in diag_table for field '//TRIM(input_fields(output_field%input_field)%module_name)//&
& '/'//TRIM(input_fields(output_field%input_field)%field_name), err_msg) ) RETURN
END IF
END IF

IF ( PRESENT(volume) ) THEN
IF ( volume.LE.0 ) THEN
IF ( fms_error_handler('diag_manager_mod::init_field_cell_measure',&
& 'VOLUME field not in diag_table', err_msg) ) RETURN
& 'VOLUME field not in diag_table for field '//TRIM(input_fields(output_field%input_field)%module_name)//&
& '/'//TRIM(input_fields(output_field%input_field)%field_name), err_msg) ) RETURN
END IF
END IF

Expand Down
14 changes: 7 additions & 7 deletions diag_manager/diag_table.F90
Original file line number Diff line number Diff line change
Expand Up @@ -797,37 +797,37 @@ TYPE(field_description_type) FUNCTION parse_field_line(line, istat, err_msg)
IF ( SCAN(parse_field_line%module_name, UNALLOWED_ALL) > 0 ) THEN
pstat = 1
IF ( fms_error_handler('diag_table_mod::parse_field_line',&
& 'Unallowed Unallowed character in module_name in the diag_table.', err_msg) ) RETURN
& 'Unallowed character in module_name in the diag_table.', err_msg) ) RETURN
END IF
IF ( SCAN(parse_field_line%field_name, UNALLOWED_ALL) > 0 ) THEN
pstat = 1
IF ( fms_error_handler('diag_table_mod::parse_field_line',&
& 'Unallowed Unallowed character in field_name in the diag_table.', err_msg) ) RETURN
& 'Unallowed character in field_name in the diag_table.', err_msg) ) RETURN
END IF
IF ( SCAN(parse_field_line%output_name, UNALLOWED_ALL) > 0 ) THEN
pstat = 1
IF ( fms_error_handler('diag_table_mod::parse_field_line',&
& 'Unallowed Unallowed character in output_name in the diag_table.', err_msg) ) RETURN
& 'Unallowed character in output_name in the diag_table.', err_msg) ) RETURN
END IF
IF ( SCAN(parse_field_line%file_name, UNALLOWED_ALL) > 0 ) THEN
pstat = 1
IF ( fms_error_handler('diag_table_mod::parse_field_line',&
& 'Unallowed Unallowed character in file_name in the diag_table.', err_msg) ) RETURN
& 'Unallowed character in file_name in the diag_table.', err_msg) ) RETURN
END IF
IF ( SCAN(parse_field_line%time_sampling, UNALLOWED_ALL) > 0 ) THEN
pstat = 1
IF ( fms_error_handler('diag_table_mod::parse_field_line',&
& 'Unallowed Unallowed character in time_sampling in the diag_table.', err_msg) ) RETURN
& 'Unallowed character in time_sampling in the diag_table.', err_msg) ) RETURN
END IF
IF ( SCAN(parse_field_line%time_method, UNALLOWED_ALL) > 0 ) THEN
pstat = 1
IF ( fms_error_handler('diag_table_mod::parse_field_line',&
& 'Unallowed Unallowed character in time_method in the diag_table.', err_msg) ) RETURN
& 'Unallowed character in time_method in the diag_table.', err_msg) ) RETURN
END IF
IF ( SCAN(parse_field_line%spatial_ops, UNALLOWED_QTE) > 0 ) THEN
pstat = 1
IF ( fms_error_handler('diag_table_mod::parse_field_line',&
& 'Unallowed Unallowed character in spatial_ops in the diag_table.', err_msg) ) RETURN
& 'Unallowed character in spatial_ops in the diag_table.', err_msg) ) RETURN
END IF

! Fix the file name
Expand Down

0 comments on commit 8cb7db2

Please sign in to comment.