source: XIOS/trunk/src/test/test_client.f90 @ 545

Last change on this file since 545 was 545, checked in by rlacroix, 9 years ago

Expose the calendar operations through the Fortran interface.

  • Add arithmetic operations on the xios_duration and xios_date types:
    • xios_duration + xios_duration = xios_duration
    • xios_duration - xios_duration = xios_duration
    • scalar * xios_duration = xios_duration * scalar = xios_duration
    • - xios_duration = xios_duration
    • xios_date + xios_duration = xios_date
    • xios_date - xios_duration = xios_date
    • xios_date - xios_date = xios_duration
  • Add comparison operations on the xios_duration and xios_date types:
    • xios_duration: ==, /=
    • xios_date: ==, /=, <, <=, >, >=
  • Add a new function "xios_date_convert_to_seconds" to convert a date into the number of seconds since the time origin of the calendar
  • Define some constant durations "xios_second", "xios_minute", "xios_hour", "xios_day", "xios_month", "xios_year" et "xios_timestep" to ease the definition of new durations (for example, 10h is just 10 * xios_hour)
  • Add a new function "xios_set_calendar" so that one can manually create the calendar attached to the current context and thus use the calendar operations before calling "xios_close_context_definition". This function can accept optional parameters so that the calendar attributes (calendar_type, start_date, time_origin and timestep) can be easily overwritten. Note that you cannot define a new calendar after one was already created (either because "xios_set_calendar" or "xios_close_context_definition" was used)
  • Readd the function "xios_set_timestep" as a simplified alias of "xios_set_context_attr(context, timestep)" for the current context
  • Property copyright set to
    Software name : XIOS (Xml I/O Server)
    http://forge.ipsl.jussieu.fr/ioserver
    Creation date : January 2009
    Licence : CeCCIL version2
    see license file in root directory : Licence_CeCILL_V2-en.txt
    or http://www.cecill.info/licences/Licence_CeCILL_V2-en.html
    Holder : CEA/LSCE (Laboratoire des Sciences du CLimat et de l'Environnement)
    CNRS/IPSL (Institut Pierre Simon Laplace)
    Project Manager : Yann Meurdesoif
    yann.meurdesoif@cea.fr
File size: 3.9 KB
Line 
1PROGRAM test_client
2
3  USE xios
4  USE mod_wait
5  IMPLICIT NONE
6  INCLUDE "mpif.h"
7  INTEGER :: rank
8  INTEGER :: size
9  INTEGER :: ierr
10 
11  CHARACTER(len=*),PARAMETER :: id="client"
12  INTEGER :: comm
13  TYPE(xios_duration) :: dtime
14  TYPE(xios_date) :: date
15  TYPE(xios_context) :: ctx_hdl
16  INTEGER,PARAMETER :: ni_glo=100
17  INTEGER,PARAMETER :: nj_glo=100 
18  INTEGER,PARAMETER :: llm=5 
19  DOUBLE PRECISION  :: lval(llm)=1
20  TYPE(xios_field) :: field_hdl
21  TYPE(xios_fieldgroup) :: fieldgroup_hdl
22  TYPE(xios_file) :: file_hdl
23  LOGICAL :: ok
24 
25  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo
26  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm)
27  DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A(:,:,:), lonvalue(:) ;
28  INTEGER :: ni,ibegin,iend,nj,jbegin,jend
29  INTEGER :: i,j,l,ts,n
30
31!!! MPI Initialization
32
33  CALL MPI_INIT(ierr)
34 
35  CALL init_wait
36 
37!!! XIOS Initialization (get the local communicator)
38
39  CALL xios_initialize(id,return_comm=comm)
40
41  CALL MPI_COMM_RANK(comm,rank,ierr)
42  CALL MPI_COMM_SIZE(comm,size,ierr) 
43 
44  DO j=1,nj_glo
45    DO i=1,ni_glo
46      lon_glo(i,j)=(i-1)+(j-1)*ni_glo
47      lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
48      DO l=1,llm
49        field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo+10000*l
50      ENDDO
51    ENDDO
52  ENDDO
53  ni=ni_glo ; ibegin=1
54
55  jbegin=1
56  DO n=0,size-1
57    nj=nj_glo/size
58    IF (n<MOD(nj_glo,size)) nj=nj+1
59    IF (n==rank) exit
60    jbegin=jbegin+nj
61  ENDDO
62 
63  iend=ibegin+ni-1 ; jend=jbegin+nj-1
64
65  ALLOCATE(lon(ni,nj),lat(ni,nj),field_A(0:ni+1,-1:nj+2,llm),lonvalue(ni*nj))
66  lon(:,:)=lon_glo(ibegin:iend,jbegin:jend)
67  lat(:,:)=lat_glo(ibegin:iend,jbegin:jend)
68  field_A(1:ni,1:nj,:)=field_A_glo(ibegin:iend,jbegin:jend,:)
69 
70  CALL xios_context_initialize("test",comm)
71  CALL xios_get_handle("test",ctx_hdl)
72  CALL xios_set_current_context(ctx_hdl)
73 
74  CALL xios_set_context_attr("test",calendar_type="Gregorian") 
75  CALL xios_set_axis_attr("axis_A",size=llm ,value=lval) ;
76  CALL xios_set_domain_attr("domain_A",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj)
77  CALL xios_set_domain_attr("domain_A",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
78  CALL xios_set_domain_attr("domain_A",lonvalue=RESHAPE(lon,(/ni*nj/)),latvalue=RESHAPE(lat,(/ni*nj/)))
79  CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
80 
81  CALL xios_get_handle("field_definition",fieldgroup_hdl)
82  CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B")
83  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_B")
84 
85  CALL xios_get_handle("output",file_hdl)
86  CALL xios_add_child(file_hdl,field_hdl)
87  CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_C")
88   
89 
90  dtime%second = 3600
91  CALL xios_set_context_attr("test", timestep=dtime)
92
93  ! Create the calendar before closing the context definition
94  ! so that calendar operations can be used
95  CALL xios_set_calendar()
96  CALL xios_get_context_attr("test", time_origin=date)
97  PRINT *, "time_origin = ", date
98  dtime%timestep = 1
99  dtime = 0.5 * dtime
100  PRINT *, "duration = ", dtime
101  date = date + 3 * (dtime + dtime)
102  PRINT *, "date = time_origin + 3 * (duration + duration) = ", date
103  PRINT *, "xios_date_convert_to_seconds(date) = ", xios_date_convert_to_seconds(date)
104  PRINT *, "xios_date_convert_to_seconds(date - 2.5h) = ", xios_date_convert_to_seconds(date - 2.5 * xios_hour)
105 
106  ni=0 ; lonvalue(:)=0
107  CALL xios_get_domain_attr("domain_A",ni=ni,lonvalue=lonvalue)
108 
109  print *,"ni",ni
110  print *,"lonvalue",lonvalue ;
111
112  CALL xios_is_defined_field_attr("field_A",enabled=ok)
113  PRINT *,"field_A : attribute enabled is defined ? ",ok
114  CALL xios_close_context_definition()
115 
116  PRINT*,"field field_A is active ? ",xios_field_is_active("field_A")
117  DO ts=1,24*10
118    CALL xios_update_calendar(ts)
119    CALL xios_send_field("field_A",field_A)
120    CALL wait_us(5000) ;
121  ENDDO
122
123  CALL xios_context_finalize()
124  CALL xios_finalize()
125 
126  CALL MPI_FINALIZE(ierr)
127 
128END PROGRAM test_client
129
130
131 
132
133 
Note: See TracBrowser for help on using the repository browser.