SURFEX v8.1
General documentation of Surfex
trip_xios_init.F90
Go to the documentation of this file.
1 SUBROUTINE trip_xios_init(TPG,KLOCAL_COMM,KLON,KLAT,KYEAR,KMONTH,KDAY,PTIME)
2 !!
3 !!
4 !! PURPOSE
5 !! --------
6 !!
7 !! Initialize Xios context and declare Trip domain to XIOS
8 !!
9 !!
10 !! METHOD
11 !! ------
12 !!
13 !!
14 !! EXTERNAL
15 !! --------
16 !!
17 !! XIOS library
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !! Y.Meurdesoif, 2015 : XIOS ....
23 !!
24 !!
25 !! AUTHOR
26 !! ------
27 !!
28 !! S.Senesi - CNRM
29 !!
30 !! MODIFICATION
31 !! --------------
32 !!
33 !! Original 10/2016
34 !! S.Sénési 08/11/16 : interface to XIOS
35 !!
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 USE modd_trip_par, ONLY : xundef
43 USE modd_trip_grid, ONLY : trip_grid_t
44 !
45 USE modi_get_lonlat_trip
46 !
47 #ifdef WXIOS
48 USE xios
49 #endif
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 Declarations of arguments
57 ! -------------------------
58 !
59 TYPE(trip_grid_t), INTENT(INOUT) :: TPG
60 INTEGER, INTENT(IN) :: KLOCAL_COMM ! value of local communicator
61 INTEGER, INTENT(IN) :: KLON ! Number of longitude
62 INTEGER, INTENT(IN) :: KLAT ! Number of latittude
63 INTEGER, INTENT(IN) :: KYEAR !date UTC
64 INTEGER, INTENT(IN) :: KMONTH !date UTC
65 INTEGER, INTENT(IN) :: KDAY !date UTC
66 REAL , INTENT(IN) :: PTIME ! current time (s)
67 !
68 !* 0.2 Declarations of local variables
69 ! -------------------------------
70 !
71 REAL, DIMENSION(:),ALLOCATABLE :: ZLON
72 REAL, DIMENSION(:),ALLOCATABLE :: ZLAT
73 !
74 #ifdef WXIOS
75 INTEGER :: IREFYEAR
76 TYPE(xios_duration) :: DTIME
77 TYPE(xios_date) :: TDATE
78 #endif
79 INTEGER :: NHOURS,NMINUTES,NSECONDS
80 !
81 REAL(KIND=JPRB) :: ZHOOK_HANDLE
82 !
83 !-------------------------------------------------------------------------------
84 !
85 IF (lhook) CALL dr_hook('TRIP_XIOS_INIT',0,zhook_handle)
86 !
87 #ifdef WXIOS
88 !
89  CALL xios_context_initialize(cmodel_name,klocal_comm)
90  CALL xios_set_current_context(cmodel_name)
91 !
92 nhours=int(ptime/3600)
93 nminutes=int((ptime - nhours*3600)/60)
94 nseconds=int(ptime - nhours*3600 -nminutes*60)
95 IF (.NOT.(xios_getvar('ref_year',irefyear))) irefyear=1850
96  CALL xios_define_calendar("Gregorian", &
97  start_date=xios_date(kyear,kmonth,kday,nhours,nminutes,nseconds), &
98  time_origin=xios_date(irefyear,1,1,0,0,0))
99 !
100 dtime%SECOND=xtstep_diag
101 !
102  CALL xios_set_timestep(dtime)
103 !
104  CALL xios_set_domain_attr("trip_grid",data_dim=2,type="rectilinear")
105  CALL xios_set_domain_attr("trip_grid",ni_glo=klon,ni=klon,ibegin=0)
106  CALL xios_set_domain_attr("trip_grid",nj_glo=klat,nj=klat,jbegin=0)
107 !
108 ALLOCATE(zlon(klon),zlat(klat))
109 zlon(:)=xundef ; zlat(:)=xundef
110  CALL get_lonlat_trip(tpg, klon,klat,zlon,zlat)
111  CALL xios_set_domain_attr("trip_grid",lonvalue_1d=zlon,latvalue_1d=zlat)
112 DEALLOCATE(zlon,zlat)
113 !
114  CALL xios_close_context_definition()
115 !
116 #endif
117 !
118 IF (lhook) CALL dr_hook('TRIP_XIOS_INIT',1,zhook_handle)
119 !
120 !-------------------------------------------------------------------------------
121 END SUBROUTINE trip_xios_init
subroutine trip_xios_init(TPG, KLOCAL_COMM, KLON, KLAT, KYEAR, KMONTH, KDAY, PTIME)
character(len=6) cmodel_name
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine get_lonlat_trip(TPG, KLON, KLAT, PLON, PLAT)
real, save xundef