Ignore:
Timestamp:
01/11/17 15:14:22 (7 years ago)
Author:
mhnguyen
Message:

Merging working version of coupler

+) Add some changes of domain and axis: Retransfer the atttributes in a generic ways for each level of client (or server)
+) Remove some spoiled files from the previous commits

Test
+) No test

File:
1 edited

Legend:

Unmodified
Added
Removed
  • XIOS/dev/dev_olga/src/test/test_client.f90

    r987 r1025  
    1717  CHARACTER(len=15) :: calendar_type 
    1818  TYPE(xios_context) :: ctx_hdl 
    19   INTEGER,PARAMETER :: ni_glo=2 
    20   INTEGER,PARAMETER :: nj_glo=2 
    21   INTEGER,PARAMETER :: llm=1 
     19  INTEGER,PARAMETER :: ni_glo=4 
     20  INTEGER,PARAMETER :: nj_glo=4 
     21  INTEGER,PARAMETER :: llm=5 
    2222  DOUBLE PRECISION  :: lval(llm)=1 
    2323  TYPE(xios_field) :: field_hdl 
     
    2828  DOUBLE PRECISION,DIMENSION(ni_glo,nj_glo) :: lon_glo,lat_glo 
    2929  DOUBLE PRECISION :: field_A_glo(ni_glo,nj_glo,llm) 
    30   DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A(:,:,:), lonvalue(:,:) ; 
     30  DOUBLE PRECISION,ALLOCATABLE :: lon(:,:),lat(:,:),field_A(:,:,:), lonvalue(:,:), axisValue(:), field_domain(:,:) ; 
    3131  INTEGER :: ni,ibegin,iend,nj,jbegin,jend 
    3232  INTEGER :: i,j,l,ts,n 
     
    6666  iend=ibegin+ni-1 ; jend=jbegin+nj-1 
    6767 
    68   ALLOCATE(lon(ni,nj),lat(ni,nj),field_A(0:ni+1,-1:nj+2,llm),lonvalue(ni,nj)) 
     68  ALLOCATE(lon(ni,nj),lat(ni,nj),field_A(0:ni+1,-1:nj+2,llm),lonvalue(ni,nj), axisValue(nj), field_domain(0:ni+1,-1:nj+2)) 
    6969  lon(:,:)=lon_glo(ibegin+1:iend+1,jbegin+1:jend+1) 
    7070  lat(:,:)=lat_glo(ibegin+1:iend+1,jbegin+1:jend+1) 
    7171  field_A(1:ni,1:nj,:)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,:) 
     72  field_domain(1:ni,1:nj) = field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,1) 
     73  axisValue(1:nj)=field_A(1,1:nj,1); 
    7274 
    7375  CALL xios_context_initialize("test",comm) 
     
    7880  PRINT *, "calendar_type = ", calendar_type 
    7981 
     82  ! CALL xios_set_axis_attr("axis_A",n_glo=nj_glo ,value=axisValue, n=nj, begin=jbegin) ; 
    8083  CALL xios_set_axis_attr("axis_A",n_glo=llm ,value=lval) ; 
    8184  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') 
     
    128131 
    129132  PRINT*,"field field_A is active ? ",xios_field_is_active("field_A") 
    130   DO ts=1,24 
     133  DO ts=1,40 
    131134    CALL xios_update_calendar(ts) 
    132     CALL xios_send_field("field_A",field_A) 
     135    ! CALL xios_send_field("field_A",field_A) 
     136    ! CALL xios_send_field("field_Axis",axisValue) 
     137    ! CALL xios_send_field("field_Axis",lval) 
     138    CALL xios_send_field("field_Domain",field_domain) 
    133139    CALL wait_us(5000) ; 
    134140  ENDDO 
Note: See TracChangeset for help on using the changeset viewer.