source: XIOS/xios_training/hands-on-6/TP_src/test_tp6.f90 @ 2046

Last change on this file since 2046 was 2046, checked in by ymipsl, 3 years ago
File size: 2.0 KB
Line 
1PROGRAM test_tp6
2
3  USE xios
4  IMPLICIT NONE
5  INCLUDE "mpif.h"
6  INTEGER :: rank
7  INTEGER :: size
8  INTEGER :: ierr
9
10  CHARACTER(len=*),PARAMETER :: id="client"
11  INTEGER :: comm
12  TYPE(xios_duration) :: dtime
13  TYPE(xios_date) :: date
14  CHARACTER(len=20) :: date_str
15  INTEGER :: ni_glo
16  INTEGER :: nj_glo
17
18  INTEGER :: i,j,l
19
20  CHARACTER(len=20) :: domain_type
21  DOUBLE PRECISION, ALLOCATABLE :: lonvalue(:)
22  DOUBLE PRECISION, ALLOCATABLE :: latvalue(:)
23
24  DOUBLE PRECISION, ALLOCATABLE :: temp(:,:)
25  INTEGER :: ts
26
27  INTEGER :: ni, ibegin, nj, jbegin
28  real :: ri, rj
29
30  CALL MPI_INIT(ierr)
31
32
33
34  CALL xios_initialize(id,return_comm=comm)
35
36  CALL MPI_COMM_RANK(comm,rank,ierr)
37  CALL MPI_COMM_SIZE(comm,size,ierr)
38
39 
40  CALL xios_context_initialize("test",comm)
41 
42 
43 
44  dtime%hour = 1
45  CALL xios_set_timestep(dtime)
46
47
48 
49  CALL xios_get_domain_attr("domain", type = domain_type)
50  CALL xios_get_domain_attr("domain", ni_glo = ni_glo, nj_glo=nj_glo)
51 
52  ni = ni_glo/size
53  ibegin = rank*ni
54  nj = nj_glo
55  jbegin=0
56
57  CALL xios_set_domain_attr("domain", ni=ni, ibegin=ibegin, nj=nj, jbegin=jbegin) 
58  ALLOCATE(lonvalue(ni))
59  ALLOCATE(latvalue(nj))
60
61  DO i=1,ni 
62    lonvalue(i) = -180 + (rank*ni+i) * 360/ni_glo
63  ENDDO
64 
65  DO j=1, nj
66    latvalue(j) = -90 + j * 180/nj_glo
67  ENDDO
68
69  CALL xios_set_domain_attr("domain", lonvalue_1d=lonvalue,latvalue_1d=latvalue)
70
71
72  ALLOCATE(temp(ni, nj))
73
74
75  CALL xios_close_context_definition()
76 
77  call random_seed()
78
79  DO ts=1,480
80    CALL xios_update_calendar(ts)
81
82    call random_number(ri)
83    call random_number(rj)
84
85    if ((MOD(ts,24) .LE. 12) .AND. (MOD(ts,24) .GE. 1)) then
86      temp(:,:) = MOD(ts,24)+ri
87    else if (MOD(ts,24) .EQ. 0) then
88      temp(:,:) = 0+rj
89    else
90      temp(:,:) = 24-MOD(ts,24)
91    endif
92
93    CALL xios_send_field("temp", temp)
94  ENDDO
95  CALL xios_context_finalize()
96
97  DEALLOCATE(lonvalue)
98  DEALLOCATE(latvalue)
99  DEALLOCATE(temp)
100
101  CALL MPI_COMM_FREE(comm, ierr)
102
103  CALL xios_finalize()
104
105  CALL MPI_FINALIZE(ierr)
106
107END PROGRAM test_tp6
108
Note: See TracBrowser for help on using the repository browser.