MODULE diag_axis_mod
!
! Seth Underwood
!
! diag_axis_mod is an integral part
! of diag_manager_mod. It helps to create axis IDs
! that are used in register_diag_field.
!
! Users first create axis ID by calling
! diag_axis_init, then use this axis ID in
! register_diag_field.
!
USE mpp_domains_mod, ONLY: domain1d, domain2d, mpp_get_compute_domain,&
& mpp_get_domain_components, null_domain1d, null_domain2d,&
& OPERATOR(.NE.), mpp_get_global_domain, mpp_get_domain_name
USE fms_mod, ONLY: error_mesg, write_version_number, lowercase, uppercase, FATAL
USE diag_data_mod, ONLY: diag_axis_type, max_subaxes, max_axes,&
& max_num_axis_sets
IMPLICIT NONE
PRIVATE
PUBLIC diag_axis_init, get_diag_axis, get_domain1d, get_domain2d,&
& get_axis_length, get_axis_global_length, diag_subaxes_init,&
& get_diag_axis_cart, get_diag_axis_data, max_axes, get_axis_aux,&
& get_tile_count, get_axes_shift, get_diag_axis_name,&
& get_axis_num, get_diag_axis_domain_name
! Module variables
! Parameters
CHARACTER(len=128), PARAMETER :: version =&
& '$Id: diag_axis.F90,v 1.1.1.2 2012-11-16 16:00:09 atrayano Exp $'
CHARACTER(len=128), PARAMETER :: tagname =&
& '$Name: Heracles-2_1 $'
! counter of number of axes defined
INTEGER, DIMENSION(:), ALLOCATABLE :: num_subaxes
INTEGER :: num_def_axes = 0
! storage for axis set names
CHARACTER(len=128), DIMENSION(:), ALLOCATABLE, SAVE :: Axis_sets
INTEGER :: num_axis_sets = 0
! ---- global storage for all defined axes ----
TYPE(diag_axis_type), ALLOCATABLE, SAVE :: Axes(:)
LOGICAL :: module_is_initialized = .FALSE.
CONTAINS
!
!
! Initialize the axis, and return the axis ID.
!
!
! INTEGER FUNCTION diag_axis_init(name, data, units, cart_name, long_name,
! direction, set_name, edges, Domain, Domain2, aux, tile_count)
!
!
! diag_axis_init initializes an axis and returns the axis ID that
! is to be used with register_diag_field. This function also
! increments the axis counter and fills in the axes
!
! Short name for axis
! Array of coordinate values
! Units for the axis
!
! Cartesian axis ("X", "Y", "Z", "T")
!
!
! Indicates the direction of the axis:
!
! - Up if +1
! - Down if -1
! - Neither up or down if 0
!
!
!
! Long name for the axis.
!
!
! Axis ID for the previously defined "edges axis"
!
!
!
!
! Auxiliary name, can only be geolon_t or geolat_t
!
!
INTEGER FUNCTION diag_axis_init(name, DATA, units, cart_name, long_name, direction,&
& set_name, edges, Domain, Domain2, aux, tile_count)
CHARACTER(len=*), INTENT(in) :: name
REAL, DIMENSION(:), INTENT(in) :: DATA
CHARACTER(len=*), INTENT(in) :: units
CHARACTER(len=*), INTENT(in) :: cart_name
CHARACTER(len=*), INTENT(in), OPTIONAL :: long_name, set_name
INTEGER, INTENT(in), OPTIONAL :: direction, edges
TYPE(domain1d), INTENT(in), OPTIONAL :: Domain
TYPE(domain2d), INTENT(in), OPTIONAL :: Domain2
CHARACTER(len=*), INTENT(in), OPTIONAL :: aux
INTEGER, INTENT(in), OPTIONAL :: tile_count
TYPE(domain1d) :: domain_x, domain_y
INTEGER :: ierr, axlen
INTEGER :: i, set, tile
INTEGER :: isc, iec, isg, ieg
CHARACTER(len=128) :: emsg
IF ( .NOT.module_is_initialized ) THEN
CALL write_version_number( version, tagname )
ENDIF
IF ( PRESENT(tile_count)) THEN
tile = tile_count
ELSE
tile = 1
END IF
! Allocate the axes
IF (.NOT. ALLOCATED(Axis_sets)) ALLOCATE(Axis_sets(max_num_axis_sets))
IF (.NOT. ALLOCATED(Axes)) ALLOCATE(Axes(max_axes))
IF (.NOT. ALLOCATED(num_subaxes)) THEN
ALLOCATE(num_subaxes(max_axes))
num_subaxes = 0
END IF
!---- is there an axis set? ----
IF ( PRESENT(set_name) ) THEN
set = get_axis_set_num (set_name)
!---- add new set name ----
IF (set == 0) THEN
num_axis_sets = num_axis_sets + 1
IF ( num_axis_sets > max_num_axis_sets ) THEN
WRITE (emsg, FMT='("num_axis_sets (",I2,") exceeds max_num_axis_sets (",I2,"). ")')&
& num_axis_sets, max_num_axis_sets
!
! num_axis_sets () exceeds max_num_axis_sets().
! Increase max_num_axis_sets via diag_manager_nml.
!
CALL error_mesg('diag_axis_mod::diag_axis_init',&
& TRIM(emsg)//' Increase max_num_axis_sets via diag_manager_nml.', FATAL)
END IF
set = num_axis_sets
Axis_sets(set) = set_name
END IF
ELSE
set = 0
END IF
!---- see if axis already exists --
! if this is time axis, return the ID of a previously defined
! if this is spatial axis, FATAL error
DO i = 1, num_def_axes
IF ( TRIM(name) == Axes(i)%name ) THEN
IF ( TRIM(name) == 'Stations' .OR. TRIM(name) == 'Levels') THEN
diag_axis_init = i
RETURN
ELSE IF ( set == Axes(i)%set ) THEN
IF ( TRIM(lowercase(name)) == 'time' .OR.&
& TRIM(lowercase(cart_name)) == 't' .OR.&
& TRIM(lowercase(name)) == 'nv' .OR.&
& TRIM(lowercase(cart_name)) == 'n' ) THEN
diag_axis_init = i
RETURN
ELSE IF ( (lowercase(cart_name) /= 'x' .AND. lowercase(cart_name) /= 'y')&
& .OR. tile /= Axes(i)%tile_count) THEN
! axis_name and axis_set already exist.
CALL error_mesg('diag_axis_mod::diag_axis_init',&
& 'axis_name '//TRIM(name)//' and axis_set already exist.', FATAL)
END IF
END IF
END IF
END DO
!---- register axis ----
num_def_axes = num_def_axes + 1
! max_axes exceeded, increase it via diag_manager_nml
IF (num_def_axes > max_axes) CALL error_mesg ('diag_axis_mod::diag_axis_init',&
& 'max_axes exceeded, increase via diag_manager_nml', FATAL)
diag_axis_init = num_def_axes
!---- check and then save cart_name name ----
IF ( TRIM(uppercase(cart_name)) == 'X' .OR.&
& TRIM(uppercase(cart_name)) == 'Y' .OR.&
& TRIM(uppercase(cart_name)) == 'Z' .OR.&
& TRIM(uppercase(cart_name)) == 'T' .OR.&
& TRIM(uppercase(cart_name)) == 'N' ) THEN
Axes(diag_axis_init)%cart_name = TRIM(uppercase(cart_name))
ELSE
! Invalid cart_name name.
CALL error_mesg('diag_axis_mod::diag_axis_init', 'Invalid cart_name name.', FATAL)
END IF
!---- allocate storage for coordinate values of axis ----
IF ( Axes(diag_axis_init)%cart_name == 'T' ) THEN
axlen = 0
ELSE
axlen = SIZE(DATA(:))
END IF
ALLOCATE ( Axes(diag_axis_init)%data(1:axlen) )
! Initialize Axes(diag_axis_init)
Axes(diag_axis_init)%name = TRIM(name)
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
! start and end are used in subaxes information only
Axes(diag_axis_init)%start = -1
Axes(diag_axis_init)%end = -1
Axes(diag_axis_init)%subaxis_name = ""
Axes(diag_axis_init)%shift = 0
IF ( PRESENT(long_name) ) THEN
Axes(diag_axis_init)%long_name = long_name
ELSE
Axes(diag_axis_init)%long_name = name
END IF
IF ( PRESENT(aux) ) THEN
Axes(diag_axis_init)%aux = TRIM(aux)
ELSE
Axes(diag_axis_init)%aux = 'none'
END IF
!---- axis direction (-1, 0, or +1) ----
IF ( PRESENT(direction) )THEN
IF ( ABS(direction) /= 1 .AND. direction /= 0 )&
! direction must be 0, +1, or -1
& CALL error_mesg('diag_axis_mod::diag_axis_init', 'direction must be 0, +1 or -1', FATAL)
Axes(diag_axis_init)%direction = direction
ELSE
Axes(diag_axis_init)%direction = 0
END IF
!---- domain2d type ----
IF ( PRESENT(Domain2) .AND. PRESENT(Domain)) THEN
! Presence of both Domain and Domain2 at the same time is prohibited
CALL error_mesg('diag_axis_mod::diag_axis_init',&
& 'Presence of both Domain and Domain2 at the same time is prohibited', FATAL)
ELSE IF ( PRESENT(Domain2) .OR. PRESENT(Domain)) THEN
IF ( Axes(diag_axis_init)%cart_name /= 'X' .AND. Axes(diag_axis_init)%cart_name /= 'Y') THEN
! Domain must not be present for an axis which is not in the X or Y direction.
CALL error_mesg('diag_axis_mod::diag_axis_init',&
& 'Domain must not be present for an axis which is not in the X or Y direction', FATAL)
END IF
END IF
Axes(diag_axis_init)%tile_count = tile
IF ( PRESENT(Domain2) ) THEN
Axes(diag_axis_init)%Domain2 = Domain2
CALL mpp_get_domain_components(Domain2, domain_x, domain_y, tile_count=tile_count)
IF ( Axes(diag_axis_init)%cart_name == 'X' ) Axes(diag_axis_init)%Domain = domain_x
IF ( Axes(diag_axis_init)%cart_name == 'Y' ) Axes(diag_axis_init)%Domain = domain_y
ELSE IF ( PRESENT(Domain)) THEN
!---- domain1d type ----
Axes(diag_axis_init)%Domain2 = null_domain2d ! needed since not 2-D domain
Axes(diag_axis_init)%Domain = Domain
ELSE
Axes(diag_axis_init)%Domain2 = null_domain2d
Axes(diag_axis_init)%Domain = null_domain1d
END IF
!--- set up the shift value for x-y axis
IF ( Axes(diag_axis_init)%Domain .NE. null_domain1d ) THEN
CALL mpp_get_compute_domain(Axes(diag_axis_init)%Domain, isc, iec)
CALL mpp_get_global_domain(Axes(diag_axis_init)%Domain, isg, ieg)
IF ( Axes(diag_axis_init)%length == ieg - isg + 2 ) THEN
Axes(diag_axis_init)%shift = 1
END IF
END IF
!---- have axis edges been defined ? ----
Axes(diag_axis_init)%edges = 0
IF (PRESENT(edges) ) THEN
IF ( edges > 0 .AND. edges < num_def_axes ) THEN
ierr=0
IF ( Axes(edges)%cart_name /= Axes(diag_axis_init)%cart_name) ierr=1
IF ( Axes(edges)%length /= Axes(diag_axis_init)%length+1 ) ierr=ierr+2
IF ( Axes(edges)%set /= Axes(diag_axis_init)%set ) ierr=ierr+4
IF ( ierr > 0 ) THEN
! Edges axis does not match axis (code ).
WRITE (emsg,'("Edges axis does not match axis (code ",I1,").")') ierr
CALL error_mesg('diag_axis_mod::diag_axis_init', emsg, FATAL)
END IF
Axes(diag_axis_init)%edges = edges
ELSE
! Edges axis is not defined.
CALL error_mesg('diag_axis_mod::diag_axis_init', 'Edges axis is not defined', FATAL)
END IF
END IF
! Module is now initialized
module_is_initialized = .TRUE.
END FUNCTION diag_axis_init
!
!
!
! Create a subaxis on a parent axis.
!
!
! INTEGER FUNCTION diag_subaxes_init(axis, subdata, start_indx, end_indx,
! domain_1d, domain_2d)
!
!
! Given the ID of a parent axis, create a subaxis and fill it with data,
! and return the ID of the corresponding subaxis.
!
! The subaxis is defined on the parent axis from start_indx
! to end_indx.
!
! ID of the parent axis
! Data of the subaxis
! Start index of the subaxis
! End index of the subaxis
!
!
INTEGER FUNCTION diag_subaxes_init(axis, subdata, start_indx, end_indx, domain_2d)
INTEGER, INTENT(in) :: axis
REAL, DIMENSION(:), INTENT(in) :: subdata
INTEGER, INTENT(in) :: start_indx
INTEGER, INTENT(in) :: end_indx
TYPE(domain2d), INTENT(in), OPTIONAL :: domain_2d
INTEGER :: i, nsub_axis, direction
INTEGER :: xbegin, xend, ybegin, yend
INTEGER :: ad_xbegin, ad_xend, ad_ybegin, ad_yend
CHARACTER(len=128) :: name, nsub_name
CHARACTER(len=128) :: units
CHARACTER(len=128) :: cart_name
CHARACTER(len=128) :: long_name
CHARACTER(len=128) :: emsg
LOGICAL :: subaxis_set, hasDomain
! there may be more than 1 subaxis on a parent axis, check for redundancy
nsub_axis = 0
subaxis_set = .FALSE.
IF ( PRESENT(domain_2d) ) THEN
hasDomain = .TRUE.
CALL mpp_get_compute_domain(domain_2d, xbegin, xend, ybegin, yend)
ELSE
hasDomain = .FALSE.
END IF
sa_search: DO i = 1, num_subaxes(axis)
IF ( start_indx == Axes(axis)%start(i) .AND. end_indx == Axes(axis)%end(i) ) THEN
IF ( hasDomain ) THEN
CALL mpp_get_compute_domain(Axes(axis)%subaxis_domain2(i), ad_xbegin, ad_xend, ad_ybegin, ad_yend)
IF ( .NOT.((xbegin == ad_xbegin .AND. xend == ad_xend) .AND.&
& (ybegin == ad_ybegin .AND. yend == ad_yend)) ) THEN
CYCLE sa_search
END IF
END IF
nsub_axis = i
subaxis_set = .TRUE. !subaxis already exists
name = TRIM(Axes(axis)%subaxis_name(nsub_axis))
EXIT sa_search
END IF
END DO sa_search
IF ( nsub_axis == 0 ) THEN ! create new subaxis
num_subaxes(axis) = num_subaxes(axis) + 1
IF (num_subaxes(axis) > max_subaxes) THEN
! max_subaxes (value ) is too small. Consider increasing max_subaxes.
WRITE (emsg,'("max_subaxes (value ",I4,") is too small. Consider increasing max_subaxes.")') max_subaxes
CALL error_mesg('diag_axis_mod::diag_subaxes_init', emsg, FATAL)
END IF
nsub_axis = num_subaxes(axis)
Axes(axis)%start(nsub_axis) = start_indx
Axes(axis)%end(nsub_axis) = end_indx
if ( hasDomain ) Axes(axis)%subaxis_domain2(nsub_axis) = domain_2d
END IF
! Create new name for the subaxis from name of parent axis
! If subaxis already exists, get the index and return
IF(subaxis_set) THEN
IF ( Axes(axis)%set > 0 ) THEN
diag_subaxes_init = get_axis_num(name, set_name=TRIM(Axis_sets(Axes(axis)%set)))
ELSE
diag_subaxes_init = get_axis_num(name)
END IF
ELSE
! get a new index for subaxis
!::sdu:: Need a check to allow larger numbers in the index number.
WRITE (nsub_name,'(I2.2)') nsub_axis
name = TRIM(Axes(axis)%name)//'_sub'//TRIM(nsub_name)
Axes(axis)%subaxis_name(nsub_axis) = name
long_name = TRIM(Axes(axis)%long_name)
units = TRIM(Axes(axis)%units)
cart_name = TRIM(Axes(axis)%cart_name)
direction = Axes(axis)%direction
IF (Axes(axis)%set > 0) THEN
diag_subaxes_init = diag_axis_init (TRIM(name), subdata, TRIM(units), TRIM(cart_name), TRIM(long_name),&
& set_name=TRIM(Axis_sets(Axes(axis)%set)), direction=direction, Domain2=domain_2d)
ELSE
diag_subaxes_init = diag_axis_init (TRIM(name), subdata, TRIM(units), TRIM(cart_name), TRIM(long_name),&
& direction=direction, Domain2=domain_2d)
END IF
END IF
END FUNCTION diag_subaxes_init
!
!
!
! Return information about the axis with index ID
!
!
! SUBROUTINE get_diag_axis(id, name, units, long_name, cart_name,
! direction, edges, Domain, data)
!
!
! Return information about the axis with index ID
!
! Axis ID
! Short name for axis
! Units for axis
! Long name for axis
!
! Cartesian axis ("x", "y", "z", "t").
!
!
! Direction of data. (See diag_axis_init for a description of
! allowed values)
!
!
! Axis ID for the previously defined "edges axis".
!
!
!
! Array of coordinate values for this axis.
!
SUBROUTINE get_diag_axis(id, name, units, long_name, cart_name,&
& direction, edges, Domain, DATA)
CHARACTER(len=*), INTENT(out) :: name, units, long_name, cart_name
INTEGER, INTENT(in) :: id
TYPE(domain1d), INTENT(out) :: Domain
INTEGER, INTENT(out) :: direction, edges
REAL, DIMENSION(:), INTENT(out) :: DATA
CALL valid_id_check(id, 'get_diag_axis')
name = Axes(id)%name
units = Axes(id)%units
long_name = Axes(id)%long_name
cart_name = Axes(id)%cart_name
direction = Axes(id)%direction
edges = Axes(id)%edges
Domain = Axes(id)%Domain
IF ( Axes(id)%length > SIZE(DATA(:)) ) THEN
! array data is too small.
CALL error_mesg('diag_axis_mod::get_diag_axis', 'array data is too small', FATAL)
ELSE
DATA(1:Axes(id)%length) = Axes(id)%data
END IF
END SUBROUTINE get_diag_axis
!
!
!
! Return the axis cartesian.
!
!
! SUBROUTINE get_diag_axis_cart(id, cart_name)
!
!
! Return the axis cartesian ('X', 'Y', 'Z' or 'T') for the axis ID given.
!
! Axis ID
! Cartesian axis
SUBROUTINE get_diag_axis_cart(id, cart_name)
INTEGER, INTENT(in) :: id
CHARACTER(len=*), INTENT(out) :: cart_name
CALL valid_id_check(id, 'get_diag_axis_cart')
cart_name = Axes(id)%cart_name
END SUBROUTINE get_diag_axis_cart
!
!
!
! Return the axis data.
!
!
! SUBROUTINE get_diag_axis_data(id, data)
!
!
! Return the axis data for the axis ID given.
!
! Axis ID
! Axis data
SUBROUTINE get_diag_axis_data(id, DATA)
INTEGER, INTENT(in) :: id
REAL, DIMENSION(:), INTENT(out) :: DATA
CALL valid_id_check(id, 'get_diag_axis_data')
IF (Axes(id)%length > SIZE(DATA(:))) THEN
! array data is too small
CALL error_mesg('diag_axis_mod::get_diag_axis_data', 'array data is too small', FATAL)
ELSE
DATA(1:Axes(id)%length) = Axes(id)%data
END IF
END SUBROUTINE get_diag_axis_data
!
!
!
! Return the short name of the axis.
!
!
! SUBROUTINE get_diag_axis_name (id, name)
!
!
! Return the short name for the axis ID given.
!
! Axis ID
! Axis short name
SUBROUTINE get_diag_axis_name(id, name)
INTEGER , INTENT(in) :: id
CHARACTER(len=*), INTENT(out) :: name
CALL valid_id_check(id, 'get_diag_axis_name')
name = Axes(id)%name
END SUBROUTINE get_diag_axis_name
!
!
!
! Return the name of the axis' domain
!
!
! SUBROUTINE get_diag_axis_domain_name(id, name)
!
!
! Retruns the name of the axis' domain.
!
! Axis ID
! Axis' domain name
SUBROUTINE get_diag_axis_domain_name(id, name)
INTEGER, INTENT(in) :: id
CHARACTER(len=*), INTENT(out) :: name
CALL valid_id_check(id, 'get_diag_axis_domain_name')
name = mpp_get_domain_name(Axes(id)%domain2)
END SUBROUTINE get_diag_axis_domain_name
!
!
!
! Return the length of the axis.
!
!
! INTEGER FUNCTION get_axis_length(id)
!
!
! Return the length of the axis ID given.
!
! Axis ID
INTEGER FUNCTION get_axis_length(id)
INTEGER, INTENT(in) :: id
INTEGER :: length
CALL valid_id_check(id, 'get_axis_length')
IF ( Axes(id)%Domain .NE. null_domain1d ) THEN
CALL mpp_get_compute_domain(Axes(id)%Domain,size=length)
!---one extra point is needed for some case. ( like symmetry domain )
get_axis_length = length + Axes(id)%shift
ELSE
get_axis_length = Axes(id)%length
END IF
END FUNCTION get_axis_length
!
!
!
! Return the auxiliary name for the axis.
!
!
! CHARACTER(len=128) FUNCTION get_axis_aux(id)
!
!
! Returns the auxiliary name for the axis. The only possible values for
! the auxiliary names is geolon_t or geolat_t.
!
! Axis ID
CHARACTER(len=138) FUNCTION get_axis_aux(id)
INTEGER, INTENT(in) :: id
CALL valid_id_check(id, 'get_axis_aux')
get_axis_aux = Axes(id)%aux
END FUNCTION get_axis_aux
!
!
!
! Return the global length of the axis.
!
!
! INTEGER FUNCTION get_axis_global_length (id)
!
!
! Returns the global length of the axis ID given.
!
! Axis ID
INTEGER FUNCTION get_axis_global_length(id)
INTEGER, INTENT(in) :: id
CALL valid_id_check(id, 'get_axis_global_length')
get_axis_global_length = Axes(id)%length
END FUNCTION get_axis_global_length
!
!
!
! Return the tile count for the axis.
!
!
! INTEGER FUNCTION get_tile_count (ids)
!
!
! Return the tile count for the axis IDs given.
!
!
! Axis IDs. Possible dimensions: 1 <= size(ids(:)) <= 4.
!
INTEGER FUNCTION get_tile_count(ids)
INTEGER, DIMENSION(:), INTENT(in) :: ids
INTEGER :: i, id, flag
IF ( SIZE(ids(:)) < 1 ) THEN
! input argument has incorrect size.
CALL error_mesg('diag_axis_mod::get_tile_count', 'input argument has incorrect size', FATAL)
END IF
get_tile_count = 1
flag = 0
DO i = 1, SIZE(ids(:))
id = ids(i)
CALL valid_id_check(id, 'get_tile_count')
IF ( Axes(id)%cart_name == 'X' .OR. &
Axes(id)%cart_name == 'Y' ) flag = flag + 1
! --- both x/y axes found ---
IF ( flag == 2 ) THEN
get_tile_count = Axes(id)%tile_count
EXIT
END IF
END DO
END FUNCTION get_tile_count
!
!
!
! Return the 1D domain.
!
!
! TYPE(domain1d) FUNCTION get_domain1d(id)
!
!
! Retrun the 1D domain for the axis ID given.
!
! Axis ID
TYPE(domain1d) FUNCTION get_domain1d(id)
INTEGER, INTENT(in) :: id
CALL valid_id_check(id, 'get_domain1d')
IF (Axes(id)%Domain .NE. NULL_DOMAIN1D) THEN
get_domain1d = Axes(id)%Domain
ELSE
get_domain1d = NULL_DOMAIN1D
ENDIF
END FUNCTION get_domain1d
!
!
!
! Return the 2D domain.
!
!
! TYPE(domain2d) FUNCTION get_domain2d(ids)
!
!
! Return the 2D domain for the axis IDs given.
!
!
! Axis IDs. Possible dimensions: 1 <= size(ids(:)) <= 4.
!
TYPE(domain2d) FUNCTION get_domain2d(ids)
INTEGER, DIMENSION(:), INTENT(in) :: ids
INTEGER :: i, id, flag
IF ( SIZE(ids(:)) < 1 ) THEN
! input argument has incorrect size.
CALL error_mesg('diag_axis_mod::get_domain2d', 'input argument has incorrect size', FATAL)
END IF
get_domain2d = null_domain2d
flag = 0
DO i = 1, SIZE(ids(:))
id = ids(i)
CALL valid_id_check(id, 'get_domain2d')
IF ( Axes(id)%cart_name == 'X' .OR. Axes(id)%cart_name == 'Y' ) flag = flag + 1
! --- both x/y axes found ---
IF ( flag == 2 ) THEN
IF (Axes(id)%Domain2 .NE. NULL_DOMAIN2D) get_domain2d = Axes(id)%Domain2
EXIT
END IF
END DO
END FUNCTION get_domain2d
!
!
!
! Return the value of the shift.
!
!
! SUBROUTINE get_axes_shift(ids, ishift, jshift)
!
!
! Return the value of the shift for the axis IDs given.
!
!
! Axis IDs. Possible dimensions: 1 <= size(ids(:)) <= 4
!
! X shift value.
! Y shift value.
SUBROUTINE get_axes_shift(ids, ishift, jshift)
INTEGER, DIMENSION(:), INTENT(in) :: ids
INTEGER, INTENT(out) :: ishift, jshift
INTEGER :: i, id
!-- get the value of the shift.
ishift = 0
jshift = 0
DO i = 1, SIZE(ids(:))
id = ids(i)
CALL valid_id_check(id, 'get_axes_shift')
SELECT CASE (Axes(id)%cart_name)
CASE ( 'X' )
ishift = Axes(id)%shift
CASE ( 'Y' )
jshift = Axes(id)%shift
END SELECT
END DO
END SUBROUTINE get_axes_shift
!
!
!
!
! Returns index into axis table corresponding to a given axis name.
!
!
! INTEGER FUNCTION get_axis_num(axis_name, set_name)
!
!
! Returns index into axis table corresponding to a given axis name.
!
! Axis name.
! Set name.
INTEGER FUNCTION get_axis_num(axis_name, set_name)
CHARACTER(len=*), INTENT(in) :: axis_name
CHARACTER(len=*), INTENT(in), OPTIONAL :: set_name
INTEGER :: set, n
IF ( PRESENT(set_name) ) THEN
set = get_axis_set_num (TRIM(set_name))
ELSE
set = 0
END IF
get_axis_num = 0
DO n = 1, num_def_axes
IF ( TRIM(axis_name) == TRIM(Axes(n)%name) .AND. Axes(n)%set == set ) THEN
get_axis_num = n
RETURN
END IF
END DO
END FUNCTION get_axis_num
!
!
!
!
!
! Returns index in axis set table corresponding to a given axis set name.
!
!
! INTEGER FUNCTION get_axis_set_num(set_name)
!
!
! Returns index in axis set table corresponding to a given axis set name.
!
! Set name.
INTEGER FUNCTION get_axis_set_num (set_name)
CHARACTER(len=*), INTENT(in) :: set_name
INTEGER :: iset
get_axis_set_num = 0
DO iset = 1, num_axis_sets
IF ( set_name == Axis_sets(iset) ) THEN
get_axis_set_num = iset
RETURN
END IF
END DO
END FUNCTION get_axis_set_num
!
!
!
!
!
! Check to see if the axis id is a vaild id.
!
!
! SUBROUTINE valid_id_check(id, routine_name)
!
!
! Check to see if the given axis id is a valid id. If the axis id is invalid,
! call a FATAL error. If the ID is valid, just return.
!
! Axis id to check for validity
! Name of the subroutine checking for a valid axis id.
SUBROUTINE valid_id_check(id, routine_name)
INTEGER, INTENT(in) :: id
CHARACTER(len=*), INTENT(in) :: routine_name
CHARACTER(len=5) :: emsg
IF ( id < 1 .OR. id > num_def_axes) THEN
!
! Illegal value for axis used (value ).
!
WRITE (emsg, '(I2)') id
CALL error_mesg('diag_axis_mod::'//TRIM(routine_name),&
& 'Illegal value for axis_id used (value '//TRIM(emsg)//').', FATAL)
END IF
END SUBROUTINE valid_id_check
!
!
END MODULE diag_axis_mod