Skip to content

Commit

Permalink
Revert "feat: emc changes for mixedmode (NOAA-GFDL#857) (NOAA-GFDL#898)…
Browse files Browse the repository at this point in the history
…" (NOAA-GFDL#914)

This reverts commit 516a5ef.
  • Loading branch information
rem1776 authored Feb 17, 2022
1 parent b6b9554 commit 6c3d531
Show file tree
Hide file tree
Showing 11 changed files with 1,095 additions and 3,944 deletions.
2 changes: 0 additions & 2 deletions CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -100,8 +100,6 @@ list(APPEND fms_fortran_src_files
column_diagnostics/column_diagnostics.F90
constants/constants.F90
constants/fmsconstants.F90
constants4/constants4.F90
constants4/fmsconstants4.F90
coupler/atmos_ocean_fluxes.F90
coupler/coupler_types.F90
coupler/ensemble_manager.F90
Expand Down
176 changes: 0 additions & 176 deletions constants4/constants4.F90

This file was deleted.

32 changes: 0 additions & 32 deletions constants4/fmsconstants4.F90

This file was deleted.

24 changes: 4 additions & 20 deletions diag_manager/diag_axis.F90
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,7 @@ MODULE diag_axis_mod
INTEGER FUNCTION diag_axis_init(name, DATA, units, cart_name, long_name, direction,&
& set_name, edges, Domain, Domain2, DomainU, aux, req, tile_count, domain_position )
CHARACTER(len=*), INTENT(in) :: name !< Short name for axis
CLASS(*), DIMENSION(:), INTENT(in) :: DATA !< Array of coordinate values
REAL, DIMENSION(:), INTENT(in) :: DATA !< Array of coordinate values
CHARACTER(len=*), INTENT(in) :: units !< Units for the axis
CHARACTER(len=*), INTENT(in) :: cart_name !< Cartesian axis ("X", "Y", "Z", "T")
CHARACTER(len=*), INTENT(in), OPTIONAL :: long_name !< Long name for the axis.
Expand Down Expand Up @@ -231,15 +231,7 @@ INTEGER FUNCTION diag_axis_init(name, DATA, units, cart_name, long_name, directi

! Initialize Axes(diag_axis_init)
Axes(diag_axis_init)%name = TRIM(name)
SELECT TYPE (DATA)
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 = 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)
END SELECT
Axes(diag_axis_init)%data = DATA(1:axlen)
Axes(diag_axis_init)%units = units
Axes(diag_axis_init)%length = axlen
Axes(diag_axis_init)%set = set
Expand Down Expand Up @@ -468,7 +460,7 @@ SUBROUTINE get_diag_axis(id, name, units, long_name, cart_name,&
INTEGER, INTENT(out) :: direction !< Direction of data. (See <TT>@ref diag_axis_init</TT> for a description of
!! allowed values)
INTEGER, INTENT(out) :: edges !< Axis ID for the previously defined "edges axis".
CLASS(*), DIMENSION(:), INTENT(out) :: DATA !< Array of coordinate values for this axis.
REAL, DIMENSION(:), INTENT(out) :: DATA !< Array of coordinate values for this axis.
INTEGER, INTENT(out), OPTIONAL :: num_attributes
TYPE(diag_atttype), ALLOCATABLE, DIMENSION(:), INTENT(out), OPTIONAL :: attributes
INTEGER, INTENT(out), OPTIONAL :: domain_position
Expand All @@ -489,15 +481,7 @@ SUBROUTINE get_diag_axis(id, name, units, long_name, cart_name,&
! <ERROR STATUS="FATAL">array data is too small.</ERROR>
CALL error_mesg('diag_axis_mod::get_diag_axis', 'array data is too small', FATAL)
ELSE
SELECT TYPE (DATA)
TYPE IS (real(kind=r4_kind))
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
CALL error_mesg('diag_axis_mod::get_diag_axis',&
& 'The axis data is not one of the supported types of real(kind=4) or real(kind=8)', FATAL)
END SELECT
DATA(1:Axes(id)%length) = Axes(id)%data(1:Axes(id)%length)
END IF
IF ( PRESENT(num_attributes) ) THEN
num_attributes = Axes(id)%num_attributes
Expand Down
Loading

0 comments on commit 6c3d531

Please sign in to comment.