source: XMLIO_SERVER/trunk/src/IOSERVER/mod_global_memory.f90 @ 8

Last change on this file since 8 was 8, checked in by ymipsl, 15 years ago

Importation des sources du serveur XMLIO

File size: 3.1 KB
Line 
1MODULE mod_global_memory
2
3  INTERFACE allocate_global_memory
4    MODULE PROCEDURE Allocate_global_memory_r8,    &
5                     Allocate_global_memory_i8,    &
6                     Allocate_global_memory_r4,    &
7                     Allocate_global_memory_i4
8  END INTERFACE Allocate_global_memory
9 
10CONTAINS
11
12  SUBROUTINE Allocate_global_memory_r8(size,Pt)
13  IMPLICIT NONE
14    INCLUDE 'mpif.h'
15    REAL(kind=8),POINTER :: Pt(:)
16    INTEGER              :: size
17
18    POINTER (Pbuffer,MPI_Buffer(size))
19    REAL(kind=8) :: MPI_Buffer
20    INTEGER(KIND=MPI_ADDRESS_KIND) :: BS 
21    INTEGER :: ierr
22   
23    BS=8*size
24    CALL MPI_ALLOC_MEM(BS,MPI_INFO_NULL,Pbuffer,ierr)
25    CALL associate_buffer(MPI_Buffer,Pt)
26 
27  CONTAINS
28 
29    SUBROUTINE associate_buffer(MPI_buffer,Pt)
30    IMPLICIT NONE
31      REAL(kind=8),DIMENSION(:),target :: MPI_Buffer
32      REAL(kind=8),POINTER             :: Pt(:)
33      Pt=>MPI_buffer
34    END SUBROUTINE associate_buffer
35 
36  END SUBROUTINE Allocate_global_memory_r8
37
38
39
40  SUBROUTINE Allocate_global_memory_i8(size,Pt)
41  IMPLICIT NONE
42    INCLUDE 'mpif.h'
43    INTEGER(kind=8),POINTER :: Pt(:)
44    INTEGER              :: size
45
46    POINTER (Pbuffer,MPI_Buffer(size))
47    INTEGER(kind=8) :: MPI_Buffer
48    INTEGER(KIND=MPI_ADDRESS_KIND) :: BS 
49    INTEGER :: ierr
50   
51    BS=8*size
52    CALL MPI_ALLOC_MEM(BS,MPI_INFO_NULL,Pbuffer,ierr)
53    CALL associate_buffer(MPI_Buffer,Pt)
54 
55  CONTAINS
56 
57    SUBROUTINE associate_buffer(MPI_buffer,Pt)
58    IMPLICIT NONE
59      INTEGER(kind=8),DIMENSION(:),target :: MPI_Buffer
60      INTEGER(kind=8),POINTER             :: Pt(:)
61      Pt=>MPI_buffer
62    END SUBROUTINE associate_buffer
63 
64  END SUBROUTINE Allocate_global_memory_i8
65 
66 
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
92
93
94
95
96  SUBROUTINE Allocate_global_memory_i4(size,Pt)
97  IMPLICIT NONE
98    INCLUDE 'mpif.h'
99    INTEGER(kind=4),POINTER :: Pt(:)
100    INTEGER              :: size
101
102    POINTER (Pbuffer,MPI_Buffer(size))
103    INTEGER(kind=4) :: MPI_Buffer
104    INTEGER(KIND=MPI_ADDRESS_KIND) :: BS 
105    INTEGER :: ierr
106   
107    BS=4*size
108    CALL MPI_ALLOC_MEM(BS,MPI_INFO_NULL,Pbuffer,ierr)
109    CALL associate_buffer(MPI_Buffer,Pt)
110 
111  CONTAINS
112 
113    SUBROUTINE associate_buffer(MPI_buffer,Pt)
114    IMPLICIT NONE
115      INTEGER(kind=4),DIMENSION(:),target :: MPI_Buffer
116      INTEGER(kind=4),POINTER             :: Pt(:)
117      Pt=>MPI_buffer
118    END SUBROUTINE associate_buffer
119 
120  END SUBROUTINE Allocate_global_memory_i4
121 
122 
123END MODULE mod_global_memory
Note: See TracBrowser for help on using the repository browser.