Changeset 32 for XMLIO_SERVER


Ignore:
Timestamp:
04/20/09 18:16:37 (15 years ago)
Author:
ymipsl
Message:

Portage sur Vargas + correction sur IOSERVER : finalisation de la derniÚre requÚte

Location:
XMLIO_SERVER/trunk
Files:
2 added
6 edited

Legend:

Unmodified
Added
Removed
  • XMLIO_SERVER/trunk/configure

    r30 r32  
    9696# set compiler flags 
    9797set FFLAGS="%BASE_FFLAGS" 
    98 set LD_FFLAGS="%BASE_LD" 
     98set LD_FFLAGS="%BASE_LD %MPI_LD" 
    9999set CPP_KEY="%FPP_DEF" 
    100100set INCDIR="" 
     
    107107  set compile_flags=$default_compile_flags 
    108108endif 
    109 set FFLAGS=${FFLAGS}" "$compile_flags 
     109set FFLAGS=${FFLAGS}" %MPI_FFLAGS "$compile_flags 
    110110 
    111111 
  • XMLIO_SERVER/trunk/src/IOSERVER/mod_event_client.f90

    r26 r32  
    11MODULE mod_event_client 
    22  USE mod_pack, ONLY : pack, pack_field 
    3   USE mod_mpi_buffer_client, ONLY : create_request, finalize_request 
     3  USE mod_mpi_buffer_client, ONLY : create_request, finalize_request,is_last_request 
    44  USE mod_event_parameters  
    55  USE mod_ioserver_namelist 
     
    293293    IF (using_server) THEN 
    294294      CALL create_request(event_id_stop_ioserver) 
     295      is_last_request=.TRUE. 
    295296      CALL Finalize_request 
    296297    ELSE 
  • XMLIO_SERVER/trunk/src/IOSERVER/mod_global_memory.f90

    r8 r32  
    44    MODULE PROCEDURE Allocate_global_memory_r8,    & 
    55                     Allocate_global_memory_i8,    & 
    6                      Allocate_global_memory_r4,    & 
     6!                     Allocate_global_memory_r4,    & 
    77                     Allocate_global_memory_i4 
    88  END INTERFACE Allocate_global_memory 
     
    6565   
    6666   
    67   SUBROUTINE Allocate_global_memory_r4(size,Pt) 
    68   IMPLICIT NONE 
    69     INCLUDE 'mpif.h' 
    70     REAL(kind=4),POINTER :: Pt(:) 
    71     INTEGER              :: size 
    72  
    73     POINTER (Pbuffer,MPI_Buffer(size)) 
    74     REAL(kind=4) :: MPI_Buffer 
    75     INTEGER(KIND=MPI_ADDRESS_KIND) :: BS  
    76     INTEGER :: ierr 
    77      
    78     BS=4*size 
    79     CALL MPI_ALLOC_MEM(BS,MPI_INFO_NULL,Pbuffer,ierr) 
    80     CALL associate_buffer(MPI_Buffer,Pt) 
    81    
    82   CONTAINS 
    83    
    84     SUBROUTINE associate_buffer(MPI_buffer,Pt) 
    85     IMPLICIT NONE 
    86       REAL(kind=4),DIMENSION(:),target :: MPI_Buffer 
    87       REAL(kind=4),POINTER             :: Pt(:) 
    88       Pt=>MPI_buffer 
    89     END SUBROUTINE associate_buffer 
    90    
    91   END SUBROUTINE Allocate_global_memory_r4 
     67!  SUBROUTINE Allocate_global_memory_r4(size,Pt) 
     68!  IMPLICIT NONE 
     69!    INCLUDE 'mpif.h' 
     70!    REAL(kind=4),POINTER :: Pt(:) 
     71!    INTEGER              :: size 
     72! 
     73!    POINTER (Pbuffer,MPI_Buffer(size)) 
     74!    REAL(kind=4) :: MPI_Buffer 
     75!    INTEGER(KIND=MPI_ADDRESS_KIND) :: BS  
     76!    INTEGER :: ierr 
     77!     
     78!    BS=4*size 
     79!    CALL MPI_ALLOC_MEM(BS,MPI_INFO_NULL,Pbuffer,ierr) 
     80!    CALL associate_buffer(MPI_Buffer,Pt) 
     81!   
     82!  CONTAINS 
     83!   
     84!    SUBROUTINE associate_buffer(MPI_buffer,Pt) 
     85!    IMPLICIT NONE 
     86!      REAL(kind=4),DIMENSION(:),target :: MPI_Buffer 
     87!      REAL(kind=4),POINTER             :: Pt(:) 
     88!      Pt=>MPI_buffer 
     89!    END SUBROUTINE associate_buffer 
     90!   
     91!  END SUBROUTINE Allocate_global_memory_r4 
    9292 
    9393 
  • XMLIO_SERVER/trunk/src/IOSERVER/mod_interface_ioipsl.f90

    r29 r32  
    7272        IF ( (pt_zoom%ni_loc == pt_zoom%ni_glo) .AND. (pt_zoom%nj_loc == pt_zoom%nj_glo) ) THEN  
    7373 
    74           CALL histbeg(TRIM(pt_file%name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat,  & 
    75                      pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,        &                                            & 
    76                      initial_timestep, initial_date, timestep_value,                              & 
     74          CALL histbeg(TRIM(pt_file%name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat, &  
     75                     pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,        & 
     76                     initial_timestep, initial_date, timestep_value,                               & 
    7777                     ioipsl_hori_id, ioipsl_file_id) 
    7878         ELSE                                               
     
    8080          CALL set_ioipsl_domain_id(pt_grid,nb_server,server_rank,ioipsl_domain_id) 
    8181          CALL histbeg(TRIM(pt_file%name),pt_domain%ni,pt_domain%lon, pt_domain%nj, pt_domain%lat,  & 
    82                      pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,        &                                            & 
    83                      initial_timestep, initial_date, timestep_value,                              & 
     82                     pt_zoom%ibegin_loc, pt_zoom%ni_loc,pt_zoom%jbegin_loc,pt_zoom%nj_loc,          & 
     83                     initial_timestep, initial_date, timestep_value,                                & 
    8484                     ioipsl_hori_id, ioipsl_file_id,domain_id=ioipsl_domain_id)                                               
    8585        
  • XMLIO_SERVER/trunk/src/IOSERVER/mod_mpi_buffer_client.f90

    r17 r32  
    2121  LOGICAL,SAVE :: ok_new_request 
    2222   
     23  LOGICAL,SAVE :: is_last_request 
    2324CONTAINS 
    2425 
     
    3536    Request_pos=1 
    3637    ok_new_request=.TRUE. 
     38    is_last_request=.FALSE. 
     39     
    3740    CALL set_pack_buffer(MPI_Buffer,buffer_begin) 
    3841     
     
    9497!      PRINT *,"Request_pos",request_pos 
    9598!      PRINT *,"Pos in Buffer",Pending_request(Request_pos)%Pos,"pack_pos",pack_pos 
    96       IF ( nb_request_pending==1 .AND. (buffer_free < MPI_buffer_size * 0.4) ) THEN 
     99      IF ( nb_request_pending==1 .AND. ( (buffer_free < MPI_buffer_size * 0.4) .OR. is_last_request ) ) THEN 
    97100        ok_out=.FALSE. 
    98         CALL Wait_us(1) 
     101        CALL Wait_us(10) 
    99102        IF (.NOT. is_buffer_full) THEN 
    100103          CALL VTb(VTbuffer_full) 
  • XMLIO_SERVER/trunk/src/IOSERVER/mod_wait.f90

    r8 r32  
    99 
    1010   
    11   FUNCTION Top 
     11  FUNCTION Top() 
    1212  IMPLICIT NONE 
    1313    DOUBLE PRECISION :: Top 
Note: See TracChangeset for help on using the changeset viewer.