SURFEX v8.1
General documentation of Surfex
set_axis.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 SUBROUTINE set_axis(HNAME, PVALUE ,CDPOSITIVE, KSIZE, CDUNITS, PBOUNDS)
6 !!
7 !!
8 !! PURPOSE
9 !! --------
10 !!
11 !! Declare a Surfex axis to XIOS
12 !!
13 !!
14 !! IMPLICIT ARGUMENTS :
15 !! --------------------
16 !!
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !! XIOS LIBRARY
22 !!
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !! XIOS Reference guide - Yann Meurdesoif - 10/10/2014 -
28 !! svn co -r 515 http://forge.ipsl.jussieu.fr/ioserver/svn/XIOS/branchs/xios-1.0 <dir> ; cd <dir>/doc ; ....
29 !!
30 !! AUTHOR
31 !! ------
32 !!
33 !! S.Sénési, CNRM
34 !!
35 !! MODIFICATION
36 !! --------------
37 !!
38 !! Original 08/2015
39 !!
40 !-------------------------------------------------------------------------------
41 !
42 !* 0. DECLARATIONS
43 ! ------------
44 !
45 USE yomhook ,ONLY : lhook, dr_hook
46 USE parkind1 ,ONLY : jprb
47 USE modi_abor1_sfx
48 !
49 USE modd_xios, ONLY : lxios
50 #ifdef WXIOS
51 USE xios, ONLY : xios_get_handle, xios_add_child, xios_set_axis_attr, xios_axisgroup, xios_axis
52 #endif
53 !
54 !
55 IMPLICIT NONE
56 !
57 ! Arguments
58 !
59  CHARACTER(LEN=*), INTENT(IN) :: HNAME ! axis name
60 REAL,DIMENSION(:),INTENT(IN), OPTIONAL :: PVALUE ! axis coordinate values array
61  CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: CDPOSITIVE ! 'up' or 'down', if axis is vertical
62 INTEGER , INTENT(IN), OPTIONAL :: KSIZE ! size of the axis (when values are not provided)
63  CHARACTER(LEN=*), INTENT(IN), OPTIONAL :: CDUNITS ! Units for the values
64 REAL,DIMENSION(:,:),INTENT(IN),OPTIONAL :: PBOUNDS ! coordinate bounds array (should be (2,:))
65 !
66 ! Local variables
67 !
68 #ifdef WXIOS
69 TYPE(xios_axisgroup) :: axisgroup_hdl
70 TYPE(xios_axis) :: axis_hdl
71 #endif
72 !
73 INTEGER :: I
74 REAL(KIND=JPRB), DIMENSION(:),ALLOCATABLE :: ZAXIS
75 REAL(KIND=JPRB) :: ZHOOK_HANDLE
76 !
77 IF (lhook) CALL dr_hook('SET_AXIS',0,zhook_handle)
78 !
79 IF (lxios) THEN
80 #ifdef WXIOS
81 !
82 !$OMP SINGLE
83 
84  CALL xios_get_handle("axis_definition",axisgroup_hdl)
85  CALL xios_add_child(axisgroup_hdl,axis_hdl,hname)
86  IF (PRESENT(pvalue)) THEN
87  CALL xios_set_axis_attr(hname, VALUE=pvalue, n_glo=SIZE(pvalue))
88  IF (PRESENT(pbounds)) THEN
89  CALL xios_set_axis_attr(hname, bounds=pbounds)
90  ENDIF
91  IF (PRESENT(cdunits)) THEN
92  CALL xios_set_axis_attr(hname, unit=cdunits)
93  ENDIF
94  ELSE
95  IF (PRESENT(ksize)) THEN
96  ALLOCATE(zaxis(ksize))
97  zaxis=(/(i, i=1,ksize)/)
98  CALL xios_set_axis_attr(hname, VALUE=zaxis, n_glo=ksize)
99  DEALLOCATE(zaxis)
100  ELSE
101  CALL abor1_sfx('SET_AXIS : MUST PROVIDE PVALUE OR KSIZE FOR'//trim(hname))
102  ENDIF
103  ENDIF
104  IF (PRESENT(cdpositive)) THEN
105  CALL xios_set_axis_attr(hname, positive=cdpositive)
106  ENDIF
107 
108 !$OMP END SINGLE
109 !
110 #endif
111 ENDIF
112 !-------------------------------------------------------------------------------
113 IF (lhook) CALL dr_hook('SET_AXIS',1,zhook_handle)
114 !
115 END SUBROUTINE set_axis
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
logical lxios
Definition: modd_xios.F90:41
subroutine set_axis(HNAME, PVALUE, CDPOSITIVE, KSIZE, CDUNITS, PBOUNDS)
Definition: set_axis.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15