Ignore:
Timestamp:
01/25/17 16:25:17 (7 years ago)
Author:
yushan
Message:

initialize the branch

File:
1 edited

Legend:

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

    r794 r1037  
    3535 
    3636  CALL MPI_INIT(ierr) 
    37  
    3837  CALL init_wait 
    39  
    40 !!! XIOS Initialization (get the local communicator) 
    41  
     38   
    4239  CALL xios_initialize(id,return_comm=comm) 
     40   
     41  print*, "test_client xios_initialize OK" 
    4342 
    4443  CALL MPI_COMM_RANK(comm,rank,ierr) 
     44  print*, "test_client MPI_COMM_RANK OK" 
    4545  CALL MPI_COMM_SIZE(comm,size,ierr) 
     46   
    4647 
    4748  DO j=1,nj_glo 
     
    7071  lat(:,:)=lat_glo(ibegin+1:iend+1,jbegin+1:jend+1) 
    7172  field_A(1:ni,1:nj,:)=field_A_glo(ibegin+1:iend+1,jbegin+1:jend+1,:) 
     73   
     74  CALL xios_context_initialize("test",comm) 
    7275 
    73   CALL xios_context_initialize("test",comm) 
    7476  CALL xios_get_handle("test",ctx_hdl) 
     77  print*, "Client xios_get_handle OK" 
    7578  CALL xios_set_current_context(ctx_hdl) 
    76  
     79  print*, "Client xios_set_current_handle OK"   
     80   
     81   
     82   
     83   
    7784  CALL xios_get_calendar_type(calendar_type) 
    7885  PRINT *, "calendar_type = ", calendar_type 
     
    9198  CALL xios_add_child(file_hdl,field_hdl) 
    9299  CALL xios_set_attr(field_hdl,field_ref="field_A_zoom",name="field_C") 
    93  
     100   
    94101  dtime%second = 3600 
    95102  CALL xios_set_timestep(dtime) 
     103  print*, "Client xios_set_timestep OK"   
    96104 
    97105  ! The calendar is created as soon as the calendar type is defined. This way 
     
    119127  ni=0 ; lonvalue(:,:)=0; 
    120128  CALL xios_get_domain_attr("domain_A",ni=ni,lonvalue_2D=lonvalue) 
    121  
    122129  print *,"ni",ni 
    123   print *,"lonvalue",lonvalue; 
     130  !print *,"lonvalue",lonvalue; 
    124131 
    125132  CALL xios_is_defined_field_attr("field_A",enabled=ok) 
    126133  PRINT *,"field_A : attribute enabled is defined ? ",ok 
     134   
    127135  CALL xios_close_context_definition() 
     136  print*, "xios_close_context_definition OK"   
    128137 
    129138  PRINT*,"field field_A is active ? ",xios_field_is_active("field_A") 
    130   DO ts=1,24*10 
     139  !DO ts=1,24*10 
     140  DO ts=1,24 
    131141    CALL xios_update_calendar(ts) 
     142    print*, "xios_update_calendar OK, ts = ", ts 
    132143    CALL xios_send_field("field_A",field_A) 
    133     CALL wait_us(5000) ; 
     144    print*, "xios_send_field OK, ts = ", ts 
     145    CALL wait_us(5000) 
    134146  ENDDO 
     147   
    135148 
    136149  CALL xios_context_finalize() 
     150  print*, "xios_context_finalize OK"   
    137151 
    138152  DEALLOCATE(lon, lat, field_A, lonvalue) 
Note: See TracChangeset for help on using the changeset viewer.