New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
gridrandom.F90 in branches/TAM_V3_0/NEMOTAM/OPATAM_SRC – NEMO

source: branches/TAM_V3_0/NEMOTAM/OPATAM_SRC/gridrandom.F90 @ 2587

Last change on this file since 2587 was 1885, checked in by rblod, 14 years ago

add TAM sources

File size: 18.0 KB
Line 
1MODULE gridrandom
2   !!======================================================================
3   !!                       *** MODULE gridrandom ***
4   !!
5   !! NEMOVAR: Construct gridded random noise fields
6   !!======================================================================
7   !!----------------------------------------------------------------------
8   !! grid_2d_ran     : Fill a 2D array with uncorrelated Gaussian noise
9   !!                   using a constant seed
10   !! grid_3d_ran     : Fill a 3D array with uncorrelated Gaussian noise
11   !!                   using a constant seed
12   !! grid_2d_ran_2d  : Fill a 2D array with uncorrelated Gaussian noise
13   !!                   using a 2D seed array (for MPP)
14   !! grid_3d_ran_2d  : Fill a 3D array with uncorrelated Gaussian noise
15   !!                   using a 2D seed array (for MPP)
16   !! grid_write_seed : Write out the 2D seed array for the random number
17   !!                   generator
18   !!----------------------------------------------------------------------
19   !! * Modules used
20   USE par_kind       ! Kind variables
21   USE dom_oce        ! Domain variables
22   USE in_out_manager ! I/O stuff
23   USE iom            ! I/O manager
24   USE ran_num        ! Random number routines
25   USE lbclnk         ! Boundary conditions and halos
26
27   IMPLICIT NONE
28
29   INTERFACE grid_random
30      MODULE PROCEDURE grid_2d_ran, grid_3d_ran, &
31         &             grid_2d_ran_2d, grid_3d_ran_2d
32   END INTERFACE
33
34   INTERFACE grid_rd_sd
35      MODULE PROCEDURE grid_2d_rd_sd_loc,  &
36         &             grid_3d_rd_sd_loc
37   END INTERFACE
38
39   !! * Routine accessibility
40   PRIVATE
41
42   PUBLIC &
43      & grid_random,      &
44      & grid_write_seed,  &
45      & grid_rd_sd
46
47CONTAINS
48
49   SUBROUTINE grid_2d_ran( kseed, pt2d, cd_type, pmean, pstd )
50      !!----------------------------------------------------------------------
51      !!               ***  ROUTINE grid_2d_ran ***
52      !!         
53      !! ** Purpose : Fill a 2D (surface) array with uncorrelated Gaussian
54      !!              noise.
55      !!
56      !! ** Method  : The value of kseed is the seed for the random number
57      !!              generator. On the first call to "grid_2d_ran" it should
58      !!              be set to a large negative number.
59      !!
60      !!              Apply the appropriate grid-point mask and lateral
61      !!              boundary conditions before exiting.
62      !!
63      !! ** Action  :
64      !!
65      !! References :
66      !!
67      !! History :
68      !!        !  07-11  (A. Weaver) 
69      !!----------------------------------------------------------------------
70      !! * Modules used
71
72      !! * Arguments
73      INTEGER, INTENT(INOUT) :: &
74         & kseed       ! Seed for random number generator
75      REAL, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
76         & pt2d        ! 2D field
77      REAL(wp), INTENT(IN) :: &
78         & pmean, &    ! Mean of noise
79         & pstd        ! Standard deviation of noise
80
81      !! * Local declarations
82      CHARACTER(LEN=1), INTENT(IN) ::   &
83         & cd_type     ! Nature of pt2d grid-point
84                       !   = T , U  or V  grid-point
85      INTEGER :: &
86         & ji, &
87         & jj
88
89      !--------------------------------------------------------------------
90      ! Fill in the 2D field with Gaussian noise
91      !--------------------------------------------------------------------
92
93      DO jj = 1, jpj
94         DO ji = 1, jpi
95            pt2d(ji,jj) = gaustb( kseed, pstd, pmean )
96         END DO
97      END DO
98
99      !--------------------------------------------------------------------
100      ! Apply masks and lateral boundary conditions
101      !--------------------------------------------------------------------
102
103      IF ( cd_type == 'T' ) THEN
104 
105         pt2d(:,:) = pt2d(:,:) * tmask(:,:,1)
106         CALL lbc_lnk( pt2d, 'T',  1.0 )
107
108      ELSEIF ( cd_type == 'U' ) THEN
109
110         pt2d(:,:) = pt2d(:,:) * umask(:,:,1)
111         CALL lbc_lnk( pt2d, 'U', -1.0 )
112
113      ELSEIF ( cd_type == 'V' ) THEN
114
115         pt2d(:,:) = pt2d(:,:) * vmask(:,:,1)
116         CALL lbc_lnk( pt2d, 'V', -1.0 )
117               
118      ENDIF
119           
120   END SUBROUTINE grid_2d_ran
121         
122   SUBROUTINE grid_3d_ran( kseed, pt3d, cd_type, pmean, pstd )
123      !!----------------------------------------------------------------------
124      !!               ***  ROUTINE grid_3d_ran ***
125      !!         
126      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian noise.
127      !!
128      !! ** Method  : The value of kseed is the seed for the random number
129      !!              generator. On the first call to "grid_3d_ran" it should
130      !!              be set to a large negative number.
131      !!
132      !!              Apply the appropriate grid-point mask and lateral
133      !!              boundary conditions before exiting.
134      !!
135      !! ** Action  :
136      !!
137      !! References :
138      !!
139      !! History :
140      !!        !  07-11  (A. Weaver) 
141      !!----------------------------------------------------------------------
142      !! * Modules used
143
144      !! * Arguments
145      INTEGER, INTENT(INOUT) :: &
146         & kseed       ! Seed for random number generator
147      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
148         & pt3d        ! 3D field
149      REAL(wp), INTENT(IN) :: &
150         & pmean, &    ! Mean of noise
151         & pstd        ! Standard deviation of noise
152 
153      !! * Local declarations
154      CHARACTER(LEN=1), INTENT(IN) ::   &
155         & cd_type     ! Nature of pt3d grid-point
156                       !   = T , U  or V  grid-point
157      INTEGER  :: &
158         & ji, &
159         & jj, &
160         & jk
161
162      !--------------------------------------------------------------------
163      ! Fill in the 3D field with Gaussian noise
164      !--------------------------------------------------------------------
165
166      DO jk = 1, jpk
167         DO jj = 1, jpj
168            DO ji = 1, jpi
169               pt3d(ji,jj,jk) = gaustb( kseed, pstd, pmean )
170            END DO
171         END DO
172      END DO
173
174      !--------------------------------------------------------------------
175      ! Apply masks and lateral boundary conditions
176      !--------------------------------------------------------------------
177
178      IF ( cd_type == 'T' ) THEN
179
180         pt3d(:,:,:) = pt3d(:,:,:) * tmask(:,:,:)
181         CALL lbc_lnk( pt3d, 'T',  1.0 )
182         
183      ELSEIF ( cd_type == 'U' ) THEN
184           
185         pt3d(:,:,:) = pt3d(:,:,:) * umask(:,:,:)
186         CALL lbc_lnk( pt3d, 'U', -1.0 )
187           
188      ELSEIF ( cd_type == 'V' ) THEN
189         
190         pt3d(:,:,:) = pt3d(:,:,:) * vmask(:,:,:)
191         CALL lbc_lnk( pt3d, 'V', -1.0 )
192
193      ENDIF
194
195   END SUBROUTINE grid_3d_ran
196     
197   SUBROUTINE grid_2d_ran_2d( kseed, pt2d, cd_type, pmean, pstd )
198      !!----------------------------------------------------------------------
199      !!               ***  ROUTINE grid_2d_ran_2d ***
200      !!         
201      !! ** Purpose : Fill a 2D (surface) array with uncorrelated Gaussian
202      !!              noise.
203      !!
204      !! ** Method  : The value of kseed is the seed for the random number
205      !!              generator. On the first call to "grid_2d_ran_2d" it
206      !!              should be set to a large negative number.
207      !!             
208      !!              This version has a 2D seed array to allow reproducible
209      !!              results for parallel execution.
210      !!
211      !!              The kseed array should be be initialized with a MPP
212      !!              independent way. The mig, mjg values of each grid point
213      !!              can be used.
214      !!
215      !!              Apply the appropriate grid-point mask and lateral
216      !!              boundary conditions before exiting.
217      !!
218      !! ** Action  :
219      !!
220      !! References :
221      !!
222      !! History :
223      !!        !  07-07  (K. Mogensen) NEMOVAR version
224      !!        !  07-11  (A. Weaver) Treat one array only
225      !!----------------------------------------------------------------------
226      !! * Modules used
227
228      !! * Arguments
229      INTEGER, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
230         & kseed       ! Seed for random number generator
231      REAL, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
232         & pt2d        ! 2D field
233      REAL(wp), INTENT(IN) :: &
234         & pmean, &    ! Mean of noise
235         & pstd        ! Standard deviation of noise
236
237      !! * Local declarations
238      CHARACTER(LEN=1), INTENT(IN) ::   &
239         & cd_type     ! Nature of pt2d grid-point
240                       !   = T , U  or V  grid-point
241      INTEGER :: &
242         & ji, &
243         & jj
244
245      !--------------------------------------------------------------------
246      ! Fill in the 2D field with Gaussian noise
247      !--------------------------------------------------------------------
248
249      DO jj = 1, jpj
250         DO ji = 1, jpi
251            pt2d(ji,jj) = gaustb_2d( ji, jj, kseed, pstd, pmean )
252         END DO
253      END DO
254
255      !--------------------------------------------------------------------
256      ! Apply masks and lateral boundary conditions
257      !--------------------------------------------------------------------
258
259      IF ( cd_type == 'T' ) THEN
260 
261         pt2d(:,:) = pt2d(:,:) * tmask(:,:,1)
262         CALL lbc_lnk( pt2d, 'T',  1.0 )
263
264      ELSEIF ( cd_type == 'U' ) THEN
265
266         pt2d(:,:) = pt2d(:,:) * umask(:,:,1)
267         CALL lbc_lnk( pt2d, 'U', -1.0 )
268
269      ELSEIF ( cd_type == 'V' ) THEN
270
271         pt2d(:,:) = pt2d(:,:) * vmask(:,:,1)
272         CALL lbc_lnk( pt2d, 'V', -1.0 )
273               
274      ENDIF
275           
276   END SUBROUTINE grid_2d_ran_2d
277         
278   SUBROUTINE grid_3d_ran_2d( kseed, pt3d, cd_type, pmean, pstd )
279      !!----------------------------------------------------------------------
280      !!               ***  ROUTINE grid_3d_ran_2d ***
281      !!         
282      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian noise.
283      !!
284      !! ** Method  : The value of kseed is the seed for the random number
285      !!              generator. On the first call to "grid_3d_ran_2d" it
286      !!              should be set to a large negative number.
287      !!             
288      !!              This version has a 2D seed array to allow reproducible
289      !!              results for parallel execution.
290      !!             
291      !!              The kseed array should be be initialized with a MPP
292      !!              independent way. The mig, mjg values of each grid point
293      !!              can be used.
294      !!
295      !!              Apply the appropriate grid-point mask and lateral
296      !!              boundary conditions before exiting.
297      !!
298      !! ** Action  :
299      !!
300      !! References :
301      !!
302      !! History :
303      !!        !  07-07  (K. Mogensen) NEMOVAR version
304      !!        !  07-11  (A. Weaver) Treat one array only
305      !!----------------------------------------------------------------------
306      !! * Modules used
307
308      !! * Arguments
309      INTEGER, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
310         & kseed       ! Seed for random number generator
311      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
312         & pt3d        ! 3D field
313      REAL(wp), INTENT(IN) :: &
314         & pmean, &    ! Mean of noise
315         & pstd        ! Standard deviation of noise
316 
317      !! * Local declarations
318      CHARACTER(LEN=1), INTENT(IN) ::   &
319         & cd_type     ! Nature of pt3d grid-point
320                       !   = T , U  or V  grid-point
321      INTEGER  :: &
322         & ji, &
323         & jj, &
324         & jk
325
326      !--------------------------------------------------------------------
327      ! Fill in the 3D field with Gaussian noise
328      !--------------------------------------------------------------------
329
330      DO jk = 1, jpk
331         DO jj = 1, jpj
332            DO ji = 1, jpi
333               pt3d(ji,jj,jk) = gaustb_2d( ji, jj, kseed, pstd, pmean )
334            END DO
335         END DO
336      END DO
337
338      !--------------------------------------------------------------------
339      ! Apply masks and lateral boundary conditions
340      !--------------------------------------------------------------------
341
342      IF ( cd_type == 'T' ) THEN
343
344         pt3d(:,:,:) = pt3d(:,:,:) * tmask(:,:,:)
345         CALL lbc_lnk( pt3d, 'T',  1.0 )
346         
347      ELSEIF ( cd_type == 'U' ) THEN
348           
349         pt3d(:,:,:) = pt3d(:,:,:) * umask(:,:,:)
350         CALL lbc_lnk( pt3d, 'U', -1.0 )
351           
352      ELSEIF ( cd_type == 'V' ) THEN
353         
354         pt3d(:,:,:) = pt3d(:,:,:) * vmask(:,:,:)
355         CALL lbc_lnk( pt3d, 'V', -1.0 )
356     
357      ENDIF
358
359   END SUBROUTINE grid_3d_ran_2d
360
361   SUBROUTINE grid_write_seed( cdfilename, kseed )
362      !!----------------------------------------------------------------------
363      !!               ***  ROUTINE grid_write_seed ***
364      !!         
365      !! ** Purpose : Write output 2d seed array
366      !!
367      !! ** Method  : IOM
368      !!
369      !! ** Action  :
370      !!
371      !! References :
372      !!
373      !! History :
374      !!        !  07-07  (K. Mogensen)  Original code based on iniwrk.F
375      !!----------------------------------------------------------------------
376      !! * Modules used
377      !! * Arguments
378      CHARACTER(LEN=*), INTENT(IN) :: &
379         & cdfilename  ! File to be written
380      INTEGER, INTENT(IN), DIMENSION(jpi,jpj) :: &
381         & kseed       ! Seed array
382      !! * Local declarations
383      INTEGER :: &
384         & inum
385
386      ! Open the file
387
388      CALL iom_open( TRIM(cdfilename), inum, ldwrt = .TRUE., kiolib = jprstlib)
389
390      ! Write the seed
391   
392      CALL iom_rstput( 0, 0, inum, 'seed' , REAL(kseed) )
393     
394      ! Close the file
395
396      CALL iom_close( inum )
397     
398   END SUBROUTINE grid_write_seed
399
400   SUBROUTINE grid_2d_rd_sd_loc( kseed, pt2d, cd_type, pmean, pstd )
401      !!----------------------------------------------------------------------
402      !!               ***  ROUTINE grid_2d_rd_sd ***
403      !!         
404      !! ** Purpose : Fill a 2D (surface) array with uncorrelated Gaussian
405      !!              noise.
406      !!
407      !! ** Method  : The value of kseed is an integer from which a seed is
408      !!              generated for the random number
409      !!              and then call grid_random routine
410      !!
411      !!              Apply the appropriate grid-point mask and lateral
412      !!              boundary conditions before exiting.
413      !!
414      !! ** Action  :
415      !!
416      !! References :
417      !!
418      !! History :
419      !!        !  09-07  (F. Vigilant) 
420      !!----------------------------------------------------------------------
421      !! * Modules used
422      USE par_oce       , ONLY: & ! Ocean space and time domain variables
423         & jpiglo
424      !! * Arguments
425      INTEGER, INTENT(IN) :: &
426         & kseed       ! Seed for random number generator
427      REAL, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
428         & pt2d        ! 2D field
429      REAL(wp), INTENT(IN) :: &
430         & pmean, &    ! Mean of noise
431         & pstd        ! Standard deviation of noise
432
433      !! * Local declarations
434      CHARACTER(LEN=1), INTENT(IN) ::   &
435         & cd_type     ! Nature of pt2d grid-point
436                       !   = T , U  or V  grid-point
437      INTEGER, DIMENSION(jpi,jpj) :: &
438         & iseed_2d             ! 2D seed for the random number generator
439      INTEGER :: &
440         & ji, &
441         & jj
442
443      !--------------------------------------------------------------------
444      ! Generate the seed
445      !--------------------------------------------------------------------
446      DO jj = 1, jpj
447         DO ji = 1, jpi
448            iseed_2d(ji,jj) = - ( kseed + &
449               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
450         END DO
451      END DO
452
453      !--------------------------------------------------------------------
454      ! Generate the noise
455      !--------------------------------------------------------------------
456      CALL grid_random( iseed_2d, pt2d, cd_type, pmean, pstd )
457           
458   END SUBROUTINE grid_2d_rd_sd_loc
459
460   SUBROUTINE grid_3d_rd_sd_loc( kseed, pt3d, cd_type, pmean, pstd )
461      !!----------------------------------------------------------------------
462      !!               ***  ROUTINE grid_3d_rd_sd ***
463      !!         
464      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian
465      !!              noise.
466      !!
467      !! ** Method  : The value of kseed is an integer from which a seed is
468      !!              generated for the random number
469      !!              and then call grid_random routine
470      !!
471      !!              Apply the appropriate grid-point mask and lateral
472      !!              boundary conditions before exiting.
473      !!
474      !! ** Action  :
475      !!
476      !! References :
477      !!
478      !! History :
479      !!        !  09-07  (F. Vigilant) 
480      !!----------------------------------------------------------------------
481      !! * Modules used
482      USE par_oce       , ONLY: & ! Ocean space and time domain variables
483         & jpiglo
484      !! * Arguments
485      INTEGER, INTENT(IN) :: &
486         & kseed       ! Seed for random number generator
487      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
488         & pt3d        ! 3D field
489      REAL(wp), INTENT(IN) :: &
490         & pmean, &    ! Mean of noise
491         & pstd        ! Standard deviation of noise
492
493      !! * Local declarations
494      CHARACTER(LEN=1), INTENT(IN) ::   &
495         & cd_type     ! Nature of pt2d grid-point
496                       !   = T , U  or V  grid-point
497      INTEGER, DIMENSION(jpi,jpj) :: &
498         & iseed_2d             ! 2D seed for the random number generator
499      INTEGER :: &
500         & ji, &
501         & jj
502
503      !--------------------------------------------------------------------
504      ! Generate the seed
505      !--------------------------------------------------------------------
506      DO jj = 1, jpj
507         DO ji = 1, jpi
508            iseed_2d(ji,jj) = - ( kseed + &
509               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
510         END DO
511      END DO
512
513      !--------------------------------------------------------------------
514      ! Generate the noise
515      !--------------------------------------------------------------------
516      CALL grid_random( iseed_2d, pt3d, cd_type, pmean, pstd )
517           
518   END SUBROUTINE grid_3d_rd_sd_loc
519
520
521END MODULE gridrandom
Note: See TracBrowser for help on using the repository browser.