ROMS
Loading...
Searching...
No Matches
memory.F File Reference
#include "cppdefs.h"
Include dependency graph for memory.F:

Go to the source code of this file.

Functions/Subroutines

subroutine memory
 

Function/Subroutine Documentation

◆ memory()

subroutine memory

Definition at line 2 of file memory.F.

3!
4!git $Id$
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2025 The ROMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.md !
9!=======================================================================
10! !
11! This routine computes and report estimates of dynamic memory and !
12! automatic memory requirements for current application. !
13! !
14! The dynamical memory is that associated with the ocean state arrays,!
15! and it is allocated at runtime, and it is persistent until the ROMS !
16! termination of the execution. !
17! !
18! The automatic arrays appear in subroutines and functions for !
19! temporary local computations. They are created on entry to the !
20! subroutine for intermediate computations and disappear on exit. !
21! The automatic arrays (meaning non-static) are either allocated on !
22! heap or stack memory. !
23! !
24!=======================================================================
25!
26 USE mod_param
27 USE mod_parallel
28 USE mod_iounits
29!
30#ifdef DISTRIBUTE
31 USE distribute_mod, ONLY : mp_collect
32#endif
33 USE mod_netcdf, ONLY : matts, mdims, mvars, nvard, nvara
35!
36 implicit none
37!
38! Local variable declarations.
39!
40 integer :: ng, tile
41 integer :: IminS, ImaxS, JminS, JmaxS
42 integer :: Nlevels, Ntiles
43!
44 real(r8) :: Avalue, bytefac, megabytefac, size1d, size2d
45 real(r8) :: sumAsize, sumBsize, sumDsize
46 real(r8) :: totalAsize, totalBsize, totalDsize
47!
48 real(r8), parameter :: spv = 0.0_r8
49!
50#ifdef DISTRIBUTE
51 real(r8), allocatable :: Bwrk(:), Dwrk(:)
52!
53#endif
54 real(r8), allocatable :: Asize(:,:) ! automatic arrays
55 real(r8), allocatable :: Bsize(:,:) ! automatic mpi-buffers
56 real(r8), allocatable :: Dsize(:,:) ! dynamic array
57 real(r8), allocatable :: IOsize(:,:) ! NetCDF I/O
58!
59!-----------------------------------------------------------------------
60! Report estimate of dynamic memory and automatic memory requirements.
61!-----------------------------------------------------------------------
62!
63! If ROMS array have not been allocated, skip report.
64
65 IF (.not.lallocatedmemory) RETURN
66!
67! Allocate and initialize.
68!
69!$OMP MASTER
70 ntiles=maxval(ntilei)*maxval(ntilej)-1
71 IF (.not.allocated(asize)) THEN
72 allocate ( asize(0:ntiles,ngrids) )
73 asize=spv
74 END IF
75 IF (.not.allocated(bsize)) THEN
76 allocate ( bsize(0:ntiles,ngrids) )
77 bsize=spv
78 END IF
79 IF (.not.allocated(dsize)) THEN
80 allocate ( dsize(0:ntiles,ngrids) )
81 dsize=spv
82 END IF
83 IF (.not.allocated(iosize)) THEN
84 allocate ( iosize(0:ntiles,ngrids) )
85 iosize=spv
86 END IF
87#ifdef DISTRIBUTE
88 IF (.not.allocated(bwrk)) THEN
89 allocate ( bwrk(ntiles+1) )
90 END IF
91 IF (.not.allocated(dwrk)) THEN
92 allocate ( dwrk(ntiles+1) )
93 END IF
94#endif
95!
96! Determine size floating-point arrays in bytes. We could use the
97! Fortran 2008 standard function STORAGE_SIZE. However since ROMS
98! is double-precision by default, we just set its value to 64 bits
99! or 8 bytes (1 byte = 8 bits). The number of array elements is
100! multiplied by the megabytes factor.
101!
102 bytefac=real(kind(bytefac),r8) ! r8 kind in bytes
103 megabytefac=bytefac*1.0e-6_r8 ! 1 Mb = 1.0E+6 bytes (SI units)
104!
105! Add static memory requirements for processing NetCDF data. The
106! variables are declared in "mod_netcdf". Notice that a single
107! character has a size of eight bits (1 byte).
108!
109 dmem(1)=dmem(1)+real(matts,r8) ! att_kind
110 dmem(1)=dmem(1)+2.0_r8*real(mdims,r8) ! dim_id,dim_size
111 dmem(1)=dmem(1)+5.0_r8*real(mvars,r8) ! var_*
112 dmem(1)=dmem(1)+real(nvard*mvars,r8) ! var_dim
113 dmem(1)=dmem(1)+2.0_r8*real(nvard,r8) ! var_Dids,var_Dsize
114 dmem(1)=dmem(1)+2.0_r8*real(nvara,r8) ! var_Aint,var_Afloat
115 dmem(1)=dmem(1)+0.125_r8*real(40*matts,r8) ! att_name
116 dmem(1)=dmem(1)+0.125_r8*real(40*mdims,r8) ! dim_name
117 dmem(1)=dmem(1)+0.125_r8*real(40*mvars,r8) ! dim_name
118 dmem(1)=dmem(1)+0.125_r8*real(40*nvara,r8) ! var_Aname
119 dmem(1)=dmem(1)+0.125_r8*real(40*nvard,r8) ! var_Dname
120 dmem(1)=dmem(1)+0.125_r8*real(1024*nvara,r8) ! var_Achar
121!
122! Estimate automatic memory requirements (megabytes) by looking at the
123! routines that use it most, like step2d, step3d_t, or NetCDF I/O.
124! (see memory.txt for more information).
125!
126 DO ng=1,ngrids
127 DO tile=0,ntilei(ng)*ntilej(ng)-1
128#ifdef NESTING
129 imins=bounds(ng)%Istr(tile)-4
130 imaxs=bounds(ng)%Iend(tile)+3
131 jmins=bounds(ng)%Jstr(tile)-4
132 jmaxs=bounds(ng)%Jend(tile)+3
133#else
134 imins=bounds(ng)%Istr(tile)-3
135 imaxs=bounds(ng)%Iend(tile)+3
136 jmins=bounds(ng)%Jstr(tile)-3
137 jmaxs=bounds(ng)%Jend(tile)+3
138#endif
139 size1d=real((imaxs-imins+1),r8)
140 size2d=real((imaxs-imins+1)*(jmaxs-jmins+1),r8)
141#ifdef SOLVE3D
142 asize(tile,ng)=megabytefac* &
143 & (4.0_r8*size1d*real(n(ng)+1,r8)+ &
144 & 7.0_r8*size2d+ &
145 & 5.0_r8*size2d*real(n(ng),r8)+ &
146 & 1.0_r8*size2d*real(n(ng)*nt(ng),r8))
147# if !(defined PARALLEL_IO && defined DISTRIBUTE)
148# ifdef INLINE_2DIO
149 nlevels=1
150# else
151 nlevels=n(ng)+1
152# endif
153 iosize(tile,ng)=megabytefac*2.0_r8* &
154 & real(2+(lm(ng)+2)*(mm(ng)+2)*(nlevels),r8)
155# else
156 iosize(tile,ng)=megabytefac* &
157 & real(2+(lm(ng)+2)*(mm(ng)+2)*(n(ng)+1),r8)
158# endif
159#else
160 asize(tile,ng)=megabytefac* &
161 & (38.0_r8*size2d)
162 iosize(tile,ng)=megabytefac* &
163 & real(2+(lm(ng)+2)*(mm(ng)+2),r8)
164#endif
165 END DO
166 END DO
167!
168! Determine total maximum value of dynamic-memory and automatic-memory
169! requirements, and convert number of array elements to megabytes.
170!
171#ifdef DISTRIBUTE
172 bwrk=spv
173 dwrk=spv
174 DO ng=1,ngrids
175 bwrk(myrank+1)=bmemmax(ng)*1.0e-6_r8 ! already in bytes
176 dwrk(myrank+1)=megabytefac*dmem(ng)
177 CALL mp_collect (ng, inlm, numthreads, spv, bwrk)
178 CALL mp_collect (ng, inlm, numthreads, spv, dwrk)
179 bsize(myrank,ng)=bwrk(myrank+1)
180 dsize(myrank,ng)=dwrk(myrank+1)
181 bwrk=spv
182 dwrk=spv
183 END DO
184#else
185 dsize(0:numthreads-1,1:ngrids)=spv
186 DO ng=1,ngrids
187 dsize(0,ng)=megabytefac*dmem(ng)
188 END DO
189#endif
190!
191! Report dynamic and automatic memory requirements.
192!
193 IF (master) THEN
194 WRITE (stdout,"(/,80('>'))")
195 totalasize=0.0_r8
196 totalbsize=0.0_r8
197 totaldsize=0.0_r8
198 DO ng=1,ngrids
199 sumasize=0.0_r8
200 sumbsize=0.0_r8
201 sumdsize=0.0_r8
202#ifdef SOLVE3D
203 WRITE (stdout,10) ng, lm(ng), mm(ng), n(ng), &
204 & ntilei(ng), ntilej(ng)
205#else
206 WRITE (stdout,10) ng, lm(ng), mm(ng), &
207 & ntilei(ng), ntilej(ng)
208#endif
209 DO tile=0,ntilei(ng)*ntilej(ng)-1
210 avalue=max(asize(tile,ng), bsize(tile,ng), iosize(tile,ng))
211 sumasize=sumasize+avalue
212 sumbsize=sumbsize+bsize(tile,ng)
213 sumdsize=sumdsize+dsize(tile,ng)
214 WRITE (stdout,20) tile, dsize(tile,ng), avalue, &
215#ifdef DISTRIBUTE
216 & dsize(tile,ng)+avalue, bsize(tile,ng)
217#else
218 & dsize(tile,ng)+avalue
219#endif
220 END DO
221 totalasize=totalasize+sumasize
222 totalbsize=totalbsize+sumbsize
223 totaldsize=totaldsize+sumdsize
224 IF (ngrids.gt.1) THEN
225 WRITE (stdout,30) ' SUM', sumdsize, sumasize, &
226#ifdef DISTRIBUTE
227 & sumasize+sumdsize, sumbsize
228#else
229 & sumasize+sumdsize
230#endif
231 ELSE
232 WRITE (stdout,30) 'TOTAL', sumdsize, sumasize, &
233#ifdef DISTRIBUTE
234 & sumasize+sumdsize, sumbsize
235#else
236 & sumasize+sumdsize
237#endif
238 END IF
239 END DO
240 IF (ngrids.gt.1) THEN
241 WRITE (stdout,30) 'TOTAL', totaldsize, totalasize, &
242#ifdef DISTRIBUTE
243 & totalasize+totaldsize, totalbsize
244#else
245 & totalasize+totaldsize
246#endif
247 END IF
248 WRITE (stdout,"(/,80('<'))")
249 END IF
250!
251! Deallocate dynamic and automatic memory local arrays.
252!
253 IF (allocated(asize)) deallocate ( asize )
254 IF (allocated(bsize)) deallocate ( bsize )
255 IF (allocated(dsize)) deallocate ( dsize )
256 IF (allocated(iosize)) deallocate ( iosize )
257!$OMP END MASTER
258!$OMP BARRIER
259!
260#ifdef SOLVE3D
261 10 FORMAT (/,' Dynamic and Automatic memory (MB) usage for Grid ', &
262 & i2.2,':',2x,i0,'x',i0,'x',i0,2x,'tiling: ',i0,'x',i0, &
263 & /,/,5x,'tile',10x,'Dynamic',8x,'Automatic', &
264 & 12x,'USAGE', &
265# ifdef DISTRIBUTE
266 & 6x,'MPI-Buffers', &
267# endif
268 & /)
269#else
270 10 FORMAT (/,' Dynamic and Automatic memory (MB) usage for Grid ', &
271 & i2.2,':',2x,i0,'x',i0,2x,'tiling: ',i0,'x',i0, &
272 & /,/,5x,'tile',10x,'Dynamic',8x,'Automatic', &
273 & 12x,'USAGE', &
274# ifdef DISTRIBUTE
275 & 6x,'MPI-Buffers', &
276# endif
277 & /)
278#endif
279 20 FORMAT (4x,i5,4(4x,f13.2))
280 30 FORMAT (/,4x,a,4(4x,f13.2))
281!
282 RETURN
integer stdout
integer, parameter mdims
Definition mod_netcdf.F:143
integer, parameter nvara
Definition mod_netcdf.F:146
integer, parameter nvard
Definition mod_netcdf.F:145
integer, parameter mvars
Definition mod_netcdf.F:144
integer, parameter matts
Definition mod_netcdf.F:142
integer numthreads
logical master
integer, parameter inlm
Definition mod_param.F:662
integer, dimension(:), allocatable n
Definition mod_param.F:479
type(t_bounds), dimension(:), allocatable bounds
Definition mod_param.F:232
real(r8), dimension(:), allocatable dmem
Definition mod_param.F:137
integer, dimension(:), allocatable lm
Definition mod_param.F:455
integer ngrids
Definition mod_param.F:113
real(r8), dimension(:), allocatable bmemmax
Definition mod_param.F:132
integer, dimension(:), allocatable ntilei
Definition mod_param.F:677
integer, dimension(:), allocatable nt
Definition mod_param.F:489
integer, dimension(:), allocatable mm
Definition mod_param.F:456
integer, dimension(:), allocatable ntilej
Definition mod_param.F:678
logical lallocatedmemory

References mod_param::bmemmax, mod_param::bounds, mod_param::dmem, mod_param::inlm, mod_scalars::lallocatedmemory, mod_param::lm, mod_parallel::master, mod_netcdf::matts, mod_netcdf::mdims, mod_param::mm, mod_netcdf::mvars, mod_parallel::myrank, mod_param::n, mod_param::ngrids, mod_param::nt, mod_param::ntilei, mod_param::ntilej, mod_parallel::numthreads, mod_netcdf::nvara, mod_netcdf::nvard, and mod_iounits::stdout.

Referenced by roms_kernel_mod::roms_finalize(), roms_kernel_mod::roms_run(), and roms_kernel_mod::roms_run().

Here is the caller graph for this function: