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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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 
Note: See TracChangeset for help on using the changeset viewer.