Changeset 32 for XMLIO_SERVER
- Timestamp:
- 04/20/09 18:16:37 (14 years ago)
- Location:
- XMLIO_SERVER/trunk
- Files:
-
- 2 added
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
XMLIO_SERVER/trunk/configure
r30 r32 96 96 # set compiler flags 97 97 set FFLAGS="%BASE_FFLAGS" 98 set LD_FFLAGS="%BASE_LD "98 set LD_FFLAGS="%BASE_LD %MPI_LD" 99 99 set CPP_KEY="%FPP_DEF" 100 100 set INCDIR="" … … 107 107 set compile_flags=$default_compile_flags 108 108 endif 109 set FFLAGS=${FFLAGS}" "$compile_flags109 set FFLAGS=${FFLAGS}" %MPI_FFLAGS "$compile_flags 110 110 111 111 -
XMLIO_SERVER/trunk/src/IOSERVER/mod_event_client.f90
r26 r32 1 1 MODULE mod_event_client 2 2 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 4 4 USE mod_event_parameters 5 5 USE mod_ioserver_namelist … … 293 293 IF (using_server) THEN 294 294 CALL create_request(event_id_stop_ioserver) 295 is_last_request=.TRUE. 295 296 CALL Finalize_request 296 297 ELSE -
XMLIO_SERVER/trunk/src/IOSERVER/mod_global_memory.f90
r8 r32 4 4 MODULE PROCEDURE Allocate_global_memory_r8, & 5 5 Allocate_global_memory_i8, & 6 Allocate_global_memory_r4, &6 ! Allocate_global_memory_r4, & 7 7 Allocate_global_memory_i4 8 8 END INTERFACE Allocate_global_memory … … 65 65 66 66 67 SUBROUTINE Allocate_global_memory_r4(size,Pt)68 IMPLICIT NONE69 INCLUDE 'mpif.h'70 REAL(kind=4),POINTER :: Pt(:)71 INTEGER :: size72 73 POINTER (Pbuffer,MPI_Buffer(size))74 REAL(kind=4) :: MPI_Buffer75 INTEGER(KIND=MPI_ADDRESS_KIND) :: BS76 INTEGER :: ierr77 78 BS=4*size79 CALL MPI_ALLOC_MEM(BS,MPI_INFO_NULL,Pbuffer,ierr)80 CALL associate_buffer(MPI_Buffer,Pt)81 82 CONTAINS83 84 SUBROUTINE associate_buffer(MPI_buffer,Pt)85 IMPLICIT NONE86 REAL(kind=4),DIMENSION(:),target :: MPI_Buffer87 REAL(kind=4),POINTER :: Pt(:)88 Pt=>MPI_buffer89 END SUBROUTINE associate_buffer90 91 END SUBROUTINE Allocate_global_memory_r467 ! 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 92 92 93 93 -
XMLIO_SERVER/trunk/src/IOSERVER/mod_interface_ioipsl.f90
r29 r32 72 72 IF ( (pt_zoom%ni_loc == pt_zoom%ni_glo) .AND. (pt_zoom%nj_loc == pt_zoom%nj_glo) ) THEN 73 73 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, & 77 77 ioipsl_hori_id, ioipsl_file_id) 78 78 ELSE … … 80 80 CALL set_ioipsl_domain_id(pt_grid,nb_server,server_rank,ioipsl_domain_id) 81 81 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, & 84 84 ioipsl_hori_id, ioipsl_file_id,domain_id=ioipsl_domain_id) 85 85 -
XMLIO_SERVER/trunk/src/IOSERVER/mod_mpi_buffer_client.f90
r17 r32 21 21 LOGICAL,SAVE :: ok_new_request 22 22 23 LOGICAL,SAVE :: is_last_request 23 24 CONTAINS 24 25 … … 35 36 Request_pos=1 36 37 ok_new_request=.TRUE. 38 is_last_request=.FALSE. 39 37 40 CALL set_pack_buffer(MPI_Buffer,buffer_begin) 38 41 … … 94 97 ! PRINT *,"Request_pos",request_pos 95 98 ! 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) ) THEN99 IF ( nb_request_pending==1 .AND. ( (buffer_free < MPI_buffer_size * 0.4) .OR. is_last_request ) ) THEN 97 100 ok_out=.FALSE. 98 CALL Wait_us(1 )101 CALL Wait_us(10) 99 102 IF (.NOT. is_buffer_full) THEN 100 103 CALL VTb(VTbuffer_full) -
XMLIO_SERVER/trunk/src/IOSERVER/mod_wait.f90
r8 r32 9 9 10 10 11 FUNCTION Top 11 FUNCTION Top() 12 12 IMPLICIT NONE 13 13 DOUBLE PRECISION :: Top
Note: See TracChangeset
for help on using the changeset viewer.