source: XIOS/xios_training/hands-on-8/test_tp8.f90 @ 2045

Last change on this file since 2045 was 2045, checked in by ymipsl, 3 years ago

Add source hand-on and doc for training
YM

File size: 2.0 KB
Line 
1PROGRAM test_tp8
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  INTEGER,PARAMETER :: seed = 86456
29  real :: ri,rj
30
31  CALL MPI_INIT(ierr)
32
33  CALL xios_initialize(id,return_comm=comm)
34
35  CALL MPI_COMM_RANK(comm,rank,ierr)
36  CALL MPI_COMM_SIZE(comm,size,ierr)
37
38 
39  CALL xios_context_initialize("test",comm)
40 
41 
42  dtime%hour = 1
43  CALL xios_set_timestep(dtime)
44
45
46 
47  CALL xios_get_domain_attr("domain", type = domain_type)
48  CALL xios_get_domain_attr("domain", ni_glo = ni_glo, nj_glo=nj_glo)
49 
50  ni = ni_glo/size
51  ibegin = rank*ni
52  nj = nj_glo
53  jbegin=0
54
55  CALL xios_set_domain_attr("domain", ni=ni, ibegin=ibegin, nj=nj, jbegin=jbegin) 
56  ALLOCATE(lonvalue(ni))
57  ALLOCATE(latvalue(nj))
58
59  DO i=1,ni 
60    lonvalue(i) = -180 + (rank*ni+i) * 360/ni_glo
61  ENDDO
62 
63  DO j=1, nj
64    latvalue(j) = -90 + j * 180/nj_glo
65  ENDDO
66
67  CALL xios_set_domain_attr("domain", lonvalue_1d=lonvalue,latvalue_1d=latvalue)
68
69
70  ALLOCATE(temp(ni, nj))
71
72
73  CALL xios_close_context_definition()
74 
75  call random_seed()
76
77  DO ts=1,480
78    CALL xios_update_calendar(ts)
79
80    call random_number(ri)
81    call random_number(rj)
82
83    if ((MOD(ts,24) .LE. 12) .AND. (MOD(ts,24) .GE. 1)) then
84      temp(:,:) = MOD(ts,24)+ri
85    else if (MOD(ts,24) .EQ. 0) then
86      temp(:,:) = 0+rj
87    else
88      temp(:,:) = 24-MOD(ts,24)
89    endif
90
91    CALL xios_send_field("temp", temp)
92  ENDDO
93  CALL xios_context_finalize()
94
95  DEALLOCATE(lonvalue)
96  DEALLOCATE(latvalue)
97  DEALLOCATE(temp)
98
99  CALL MPI_COMM_FREE(comm, ierr)
100
101  CALL xios_finalize()
102
103  CALL MPI_FINALIZE(ierr)
104
105END PROGRAM test_tp8
106
Note: See TracBrowser for help on using the repository browser.