SND@LHC Software
Loading...
Searching...
No Matches
mpdalc::mpalloc Interface Reference

allocate array More...

Public Member Functions

subroutine mpallocdvec (array, length, text)
 allocate (1D) double precision array
 
subroutine mpallocfvec (array, length, text)
 allocate (1D) single precision array
 
subroutine mpallocivec (array, length, text)
 allocate (1D) integer array
 
subroutine mpallocfarr (array, rows, cols, text)
 allocate (2D) single precision array
 
subroutine mpallociarr (array, rows, cols, text)
 allocate (2D) INTEGER(mpi) array
 
subroutine mpalloclarr (array, rows, cols, text)
 allocate (2D) large integer array
 
subroutine mpalloclist (array, length, text)
 allocate (1D) list item array
 
subroutine mpalloccvec (array, length, text)
 allocate (1D) character array
 

Detailed Description

allocate array

Definition at line 36 of file mpdalc.f90.

Member Function/Subroutine Documentation

◆ mpalloccvec()

subroutine mpdalc::mpalloc::mpalloccvec ( character, dimension(:), intent(inout), allocatable  array,
integer(mpl), intent(in)  length,
character (len=*), intent(in)  text 
)

allocate (1D) character array

Definition at line 129 of file mpdalc.f90.

130 CHARACTER, DIMENSION(:), INTENT(IN OUT), ALLOCATABLE :: array
131 INTEGER(mpl), INTENT(IN) :: length
132 CHARACTER (LEN=*), INTENT(IN) :: text
133
134 INTEGER(mpi) :: ifail
135 ALLOCATE (array(length),stat=ifail)
136 CALL mpalloccheck(ifail,(length+mpi-1)/mpi,text)

◆ mpallocdvec()

subroutine mpdalc::mpalloc::mpallocdvec ( real(mpd), dimension(:), intent(inout), allocatable  array,
integer(mpl), intent(in)  length,
character (len=*), intent(in)  text 
)

allocate (1D) double precision array

Definition at line 49 of file mpdalc.f90.

50 REAL(mpd), DIMENSION(:), INTENT(IN OUT), ALLOCATABLE :: array
51 INTEGER(mpl), INTENT(IN) :: length
52 CHARACTER (LEN=*), INTENT(IN) :: text
53
54 INTEGER(mpi) :: ifail
55 ALLOCATE (array(length),stat=ifail)
56 CALL mpalloccheck(ifail,(mpd*length)/mpi,text)

◆ mpallocfarr()

subroutine mpdalc::mpalloc::mpallocfarr ( real(mps), dimension(:,:), intent(inout), allocatable  array,
integer(mpl), intent(in)  rows,
integer(mpl), intent(in)  cols,
character (len=*), intent(in)  text 
)

allocate (2D) single precision array

Definition at line 82 of file mpdalc.f90.

83 REAL(mps), DIMENSION(:,:), INTENT(IN OUT), ALLOCATABLE :: array
84 INTEGER(mpl), INTENT(IN) :: rows
85 INTEGER(mpl), INTENT(IN) :: cols
86 CHARACTER (LEN=*), INTENT(IN) :: text
87
88 INTEGER(mpi) :: ifail
89 ALLOCATE (array(rows,cols),stat=ifail)
90 CALL mpalloccheck(ifail,(mps*rows*cols)/mpi,text)

◆ mpallocfvec()

subroutine mpdalc::mpalloc::mpallocfvec ( real(mps), dimension(:), intent(inout), allocatable  array,
integer(mpl), intent(in)  length,
character (len=*), intent(in)  text 
)

allocate (1D) single precision array

Definition at line 60 of file mpdalc.f90.

61 REAL(mps), DIMENSION(:), INTENT(IN OUT), ALLOCATABLE :: array
62 INTEGER(mpl), INTENT(IN) :: length
63 CHARACTER (LEN=*), INTENT(IN) :: text
64
65 INTEGER(mpi) :: ifail
66 ALLOCATE (array(length),stat=ifail)
67 CALL mpalloccheck(ifail,(mps*length)/mpi,text)

◆ mpallociarr()

subroutine mpdalc::mpalloc::mpallociarr ( integer(mpi), dimension(:,:), intent(inout), allocatable  array,
integer(mpl), intent(in)  rows,
integer(mpl), intent(in)  cols,
character (len=*), intent(in)  text 
)

allocate (2D) INTEGER(mpi) array

Definition at line 94 of file mpdalc.f90.

95 INTEGER(mpi), DIMENSION(:,:), INTENT(IN OUT), ALLOCATABLE :: array
96 INTEGER(mpl), INTENT(IN) :: rows
97 INTEGER(mpl), INTENT(IN) :: cols
98 CHARACTER (LEN=*), INTENT(IN) :: text
99
100 INTEGER(mpi) :: ifail
101 ALLOCATE (array(rows,cols),stat=ifail)
102 CALL mpalloccheck(ifail,rows*cols,text)

◆ mpallocivec()

subroutine mpdalc::mpalloc::mpallocivec ( integer(mpi), dimension(:), intent(inout), allocatable  array,
integer(mpl), intent(in)  length,
character (len=*), intent(in)  text 
)

allocate (1D) integer array

Definition at line 71 of file mpdalc.f90.

72 INTEGER(mpi), DIMENSION(:), INTENT(IN OUT), ALLOCATABLE :: array
73 INTEGER(mpl), INTENT(IN) :: length
74 CHARACTER (LEN=*), INTENT(IN) :: text
75
76 INTEGER(mpi) :: ifail
77 ALLOCATE (array(length),stat=ifail)
78 CALL mpalloccheck(ifail,length,text)

◆ mpalloclarr()

subroutine mpdalc::mpalloc::mpalloclarr ( integer(mpl), dimension(:,:), intent(inout), allocatable  array,
integer(mpl), intent(in)  rows,
integer(mpl), intent(in)  cols,
character (len=*), intent(in)  text 
)

allocate (2D) large integer array

Definition at line 106 of file mpdalc.f90.

107 INTEGER(mpl), DIMENSION(:,:), INTENT(IN OUT), ALLOCATABLE :: array
108 INTEGER(mpl), INTENT(IN) :: rows
109 INTEGER(mpl), INTENT(IN) :: cols
110 CHARACTER (LEN=*), INTENT(IN) :: text
111
112 INTEGER(mpi) :: ifail
113 ALLOCATE (array(rows,cols),stat=ifail)
114 CALL mpalloccheck(ifail,(mpl*rows*cols)/mpi,text)

◆ mpalloclist()

subroutine mpdalc::mpalloc::mpalloclist ( type(listitem), dimension(:), intent(inout), allocatable  array,
integer(mpl), intent(in)  length,
character (len=*), intent(in)  text 
)

allocate (1D) list item array

Definition at line 118 of file mpdalc.f90.

119 TYPE(listItem), DIMENSION(:), INTENT(IN OUT), ALLOCATABLE :: array
120 INTEGER(mpl), INTENT(IN) :: length
121 CHARACTER (LEN=*), INTENT(IN) :: text
122
123 INTEGER(mpi) :: ifail
124 ALLOCATE (array(length),stat=ifail)
125 CALL mpalloccheck(ifail,((mps+mpi)*length)/mpi,text)

The documentation for this interface was generated from the following file: