source: XIOS/dev/dev_trunk_omp/src/test/test_omp.f90 @ 1679

Last change on this file since 1679 was 1679, checked in by yushan, 5 years ago

MARK: Dynamic workflow graph developement. Branch up to date with trunk @1676. Using vis.js

File size: 7.0 KB
Line 
1PROGRAM test_omp
2
3  USE xios
4  USE mod_wait
5  use omp_lib
6  IMPLICIT NONE
7  INCLUDE "mpif.h"
8  INTEGER :: rank
9  INTEGER :: size
10  INTEGER :: ierr
11
12  CHARACTER(len=*),PARAMETER :: id="client"
13  INTEGER :: comm
14  TYPE(xios_duration) :: dtime
15  CHARACTER(len=20) :: dtime_str
16  TYPE(xios_date) :: date
17  CHARACTER(len=20) :: date_str
18  CHARACTER(len=15) :: calendar_type
19  TYPE(xios_context) :: ctx_hdl
20  INTEGER,PARAMETER :: ni_glo=100
21  INTEGER,PARAMETER :: nj_glo=100
22  INTEGER,PARAMETER :: llm=5
23  DOUBLE PRECISION  :: lval(llm)=1, scalar = 5
24  TYPE(xios_field) :: field_hdl
25  TYPE(xios_fieldgroup) :: fieldgroup_hdl
26  TYPE(xios_file) :: file_hdl
27  LOGICAL :: ok
28
29  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo
30  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm)
31  DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A(:,:,:), lonvalue(:,:), axisValue(:), field_domain(:,:)
32  INTEGER :: ni,ibegin,iend,nj,jbegin,jend
33  INTEGER :: i,j,l,ts,n, provided
34
35  integer :: num_args, ix, nb_servers
36  character(len=12), dimension(:), allocatable :: args
37
38  num_args = command_argument_count()
39  if(num_args<1) then
40    print*, "please give the number of servers as input argument."
41    call abort
42  endif
43
44  allocate(args(num_args))  ! I've omitted checking the return status of the allocation
45
46  do ix = 1, num_args
47    call get_command_argument(ix,args(ix))
48    ! now parse the argument as you wish
49  end do
50
51  READ(args(1),*) nb_servers
52
53!!! MPI Initialization   
54
55    CALL MPI_INIT_THREAD(3, provided, ierr)
56    if(provided .NE. 3) then
57      print*, "provided thread level = ", provided
58      call MPI_Abort()
59    endif
60
61    CALL init_wait
62
63    CALL MPI_COMM_RANK(MPI_COMM_WORLD,rank,ierr)
64    CALL MPI_COMM_SIZE(MPI_COMM_WORLD,size,ierr)
65    if(rank < size-nb_servers) then
66
67    !$omp parallel default(firstprivate)
68 
69    CALL xios_initialize(id,return_comm=comm)
70 
71    CALL MPI_COMM_RANK(comm,rank,ierr)
72    CALL MPI_COMM_SIZE(comm,size,ierr)
73
74    size = size*omp_get_num_threads()
75    rank = rank*omp_get_num_threads() + omp_get_thread_num()
76
77    DO j=1,nj_glo
78      DO i=1,ni_glo
79        lon_glo(i,j)=(i-1)+(j-1)*ni_glo
80        lat_glo(i,j)=1000+(i-1)+(j-1)*ni_glo
81        DO l=1,llm
82          field_A_glo(i,j,l)=(i-1)+(j-1)*ni_glo*100+10000*l
83        ENDDO
84      ENDDO
85    ENDDO
86    ni=ni_glo ; ibegin=0
87
88    jbegin=0
89    DO n=0,size-1
90      nj=nj_glo/size
91      IF (n<MOD(nj_glo,size)) nj=nj+1
92      IF (n==rank) exit
93      jbegin=jbegin+nj
94    ENDDO
95
96    iend=ibegin+ni-1 ; jend=jbegin+nj-1
97
98    !ALLOCATE(lon(ni,nj),lat(ni,nj),field_A(0:ni+1,-1:nj+2,llm),lonvalue(ni,nj))
99    !lon(:,:)=lon_glo(ibegin+1:iend+1,jbegin+1:jend+1)
100    !lat(:,:)=lat_glo(ibegin+1:iend+1,jbegin+1:jend+1)
101    !field_A(1:ni,1:nj,:)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,:)
102   
103    ALLOCATE(lon(ni,nj),lat(ni,nj),field_A(0:ni+1,-1:nj+2,llm),lonvalue(ni,nj), axisValue(nj_glo), field_domain(0:ni+1,-1:nj+2))
104    lon(:,:)=lon_glo(ibegin+1:iend+1,jbegin+1:jend+1)
105    lat(:,:)=lat_glo(ibegin+1:iend+1,jbegin+1:jend+1)
106    field_A(1:ni,1:nj,:)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,:)
107    field_domain(1:ni,1:nj) = field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,1)
108    axisValue(1:nj_glo)=field_A_glo(1,1:nj_glo,1);
109 
110
111
112    CALL xios_context_initialize("test",comm)
113    CALL xios_get_handle("test",ctx_hdl)
114    CALL xios_set_current_context(ctx_hdl)
115 
116    CALL xios_get_calendar_type(calendar_type)
117    PRINT *, "calendar_type = ", calendar_type
118
119    CALL xios_set_axis_attr("axis_A",n_glo=llm ,value=lval) ;
120    CALL xios_set_domain_attr("domain_A",ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, ni=ni,jbegin=jbegin,nj=nj,type='curvilinear')
121    CALL xios_set_domain_attr("domain_A",data_dim=2, data_ibegin=-1, data_ni=ni+2, data_jbegin=-2, data_nj=nj+4)
122    CALL xios_set_domain_attr("domain_A",lonvalue_2D=lon,latvalue_2D=lat)
123    CALL xios_set_fieldgroup_attr("field_definition",enabled=.TRUE.)
124    !print*, "test block OK", rank, size
125
126    !CALL xios_get_handle("field_definition",fieldgroup_hdl)
127    !CALL xios_add_child(fieldgroup_hdl,field_hdl,"field_B")
128    !CALL xios_set_attr(field_hdl,field_ref="field_A",name="field_B")
129
130    !CALL xios_get_handle("output",file_hdl)
131    !CALL xios_add_child(file_hdl,field_hdl)
132    !CALL xios_set_attr(field_hdl,field_ref="field_A_zoom",name="field_C")
133
134    dtime%second = 3600
135    CALL xios_set_timestep(dtime)
136    !print*, "xios_set_timestep OK", rank, size   
137
138   ! The calendar is created as soon as the calendar type is defined. This way
139   ! calendar operations can be used before the context definition is closed
140   CALL xios_get_time_origin(date)
141   PRINT *, "--> year length = ", xios_get_year_length_in_seconds(date%year)
142   PRINT *, "--> day length = ", xios_get_day_length_in_seconds()
143   CALL xios_date_convert_to_string(date, date_str)
144   PRINT *, "time_origin = ", date_str
145   PRINT *, "xios_date_get_second_of_year(time_origin) = ", xios_date_get_second_of_year(date)
146   PRINT *, "xios_date_get_day_of_year(time_origin) = ", xios_date_get_day_of_year(date)
147   PRINT *, "xios_date_get_fraction_of_year(time_origin) = ", xios_date_get_fraction_of_year(date)
148   PRINT *, "xios_date_get_second_of_day(time_origin) = ", xios_date_get_second_of_day(date)
149   PRINT *, "xios_date_get_fraction_of_day(time_origin) = ", xios_date_get_fraction_of_day(date)
150   dtime%timestep = 1
151   dtime = 0.5 * dtime
152   CALL xios_duration_convert_to_string(dtime, dtime_str)
153   PRINT *, "duration = ", dtime_str
154   date = date + 3 * (dtime + dtime)
155   CALL xios_date_convert_to_string(date, date_str)
156   PRINT *, "date = time_origin + 3 * (duration + duration) = ", date_str
157   PRINT *, "xios_date_convert_to_seconds(date) = ", xios_date_convert_to_seconds(date)
158   PRINT *, "xios_date_convert_to_seconds(date - 2.5h) = ", xios_date_convert_to_seconds(date - 2.5 * xios_hour)
159
160   ni=0 ; lonvalue(:,:)=0;
161   CALL xios_get_domain_attr("domain_A",ni=ni,lonvalue_2D=lonvalue)
162   !print *,"ni",ni
163   !print *,"lonvalue",lonvalue;
164
165   CALL xios_is_defined_field_attr("field_A",enabled=ok)
166   PRINT *,"field_A : attribute enabled is defined ? ",ok 
167   CALL xios_close_context_definition()
168
169   PRINT*,"field field_A is active ? ",xios_field_is_active("field_A")
170
171   DO ts=1,4
172    CALL xios_update_calendar(ts)
173    CALL xios_send_field("field_A",field_A)
174    CALL xios_send_field("field_B",field_A)
175    CALL xios_send_field("field_C",field_A)
176    !CALL xios_send_field("field_Axis",axisValue)
177    ! CALL xios_send_field("field_Axis",lval)
178    !CALL xios_send_field("field_Domain",field_domain)
179    !CALL xios_send_field("field_Scalar",scalar)
180    CALL wait_us(5000)
181   ENDDO
182
183    CALL xios_context_finalize()
184    !print*, "xios_context_finalize OK", rank, size
185
186    CALL xios_finalize()
187    print*, "xios finalize OK", rank, size
188
189    DEALLOCATE(lon, lat, field_A, lonvalue, axisValue, field_domain)
190    !$omp master
191    !call MPI_Barrier(comm)
192    CALL MPI_COMM_FREE(comm, ierr)
193    !$omp end master
194
195    !$omp barrier
196
197
198
199  !$omp end parallel
200
201
202    else
203
204    CALL xios_init_server
205    print *, "Server : xios_finalize ", rank
206 
207    endif
208   
209
210  CALL MPI_FINALIZE(ierr)
211
212END PROGRAM test_omp
213
214
215
216
217
Note: See TracBrowser for help on using the repository browser.