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_2_2/NEMOTAM/OPATAM_SRC – NEMO

source: branches/TAM_V3_2_2/NEMOTAM/OPATAM_SRC/gridrandom.F90 @ 3317

Last change on this file since 3317 was 2578, checked in by rblod, 13 years ago

first import of NEMOTAM 3.2.2

File size: 18.3 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      ELSEIF ( cd_type == 'S' ) THEN
119         CALL lbc_lnk( pt2d, 'S', 1.0 )
120               
121      ENDIF
122           
123   END SUBROUTINE grid_2d_ran
124         
125   SUBROUTINE grid_3d_ran( kseed, pt3d, cd_type, pmean, pstd )
126      !!----------------------------------------------------------------------
127      !!               ***  ROUTINE grid_3d_ran ***
128      !!         
129      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian noise.
130      !!
131      !! ** Method  : The value of kseed is the seed for the random number
132      !!              generator. On the first call to "grid_3d_ran" it should
133      !!              be set to a large negative number.
134      !!
135      !!              Apply the appropriate grid-point mask and lateral
136      !!              boundary conditions before exiting.
137      !!
138      !! ** Action  :
139      !!
140      !! References :
141      !!
142      !! History :
143      !!        !  07-11  (A. Weaver) 
144      !!----------------------------------------------------------------------
145      !! * Modules used
146
147      !! * Arguments
148      INTEGER, INTENT(INOUT) :: &
149         & kseed       ! Seed for random number generator
150      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
151         & pt3d        ! 3D field
152      REAL(wp), INTENT(IN) :: &
153         & pmean, &    ! Mean of noise
154         & pstd        ! Standard deviation of noise
155 
156      !! * Local declarations
157      CHARACTER(LEN=1), INTENT(IN) ::   &
158         & cd_type     ! Nature of pt3d grid-point
159                       !   = T , U  or V  grid-point
160      INTEGER  :: &
161         & ji, &
162         & jj, &
163         & jk
164
165      !--------------------------------------------------------------------
166      ! Fill in the 3D field with Gaussian noise
167      !--------------------------------------------------------------------
168
169      DO jk = 1, jpk
170         DO jj = 1, jpj
171            DO ji = 1, jpi
172               pt3d(ji,jj,jk) = gaustb( kseed, pstd, pmean )
173            END DO
174         END DO
175      END DO
176
177      !--------------------------------------------------------------------
178      ! Apply masks and lateral boundary conditions
179      !--------------------------------------------------------------------
180
181      IF ( cd_type == 'T' ) THEN
182
183         pt3d(:,:,:) = pt3d(:,:,:) * tmask(:,:,:)
184         CALL lbc_lnk( pt3d, 'T',  1.0 )
185         
186      ELSEIF ( cd_type == 'U' ) THEN
187           
188         pt3d(:,:,:) = pt3d(:,:,:) * umask(:,:,:)
189         CALL lbc_lnk( pt3d, 'U', -1.0 )
190           
191      ELSEIF ( cd_type == 'V' ) THEN
192         
193         pt3d(:,:,:) = pt3d(:,:,:) * vmask(:,:,:)
194         CALL lbc_lnk( pt3d, 'V', -1.0 )
195
196      ELSEIF ( cd_type == 'S' ) THEN
197         CALL lbc_lnk( pt3d, 'S', 1.0 )
198
199      ENDIF
200
201   END SUBROUTINE grid_3d_ran
202     
203   SUBROUTINE grid_2d_ran_2d( kseed, pt2d, cd_type, pmean, pstd )
204      !!----------------------------------------------------------------------
205      !!               ***  ROUTINE grid_2d_ran_2d ***
206      !!         
207      !! ** Purpose : Fill a 2D (surface) array with uncorrelated Gaussian
208      !!              noise.
209      !!
210      !! ** Method  : The value of kseed is the seed for the random number
211      !!              generator. On the first call to "grid_2d_ran_2d" it
212      !!              should be set to a large negative number.
213      !!             
214      !!              This version has a 2D seed array to allow reproducible
215      !!              results for parallel execution.
216      !!
217      !!              The kseed array should be be initialized with a MPP
218      !!              independent way. The mig, mjg values of each grid point
219      !!              can be used.
220      !!
221      !!              Apply the appropriate grid-point mask and lateral
222      !!              boundary conditions before exiting.
223      !!
224      !! ** Action  :
225      !!
226      !! References :
227      !!
228      !! History :
229      !!        !  07-07  (K. Mogensen) NEMOVAR version
230      !!        !  07-11  (A. Weaver) Treat one array only
231      !!----------------------------------------------------------------------
232      !! * Modules used
233
234      !! * Arguments
235      INTEGER, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
236         & kseed       ! Seed for random number generator
237      REAL, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
238         & pt2d        ! 2D field
239      REAL(wp), INTENT(IN) :: &
240         & pmean, &    ! Mean of noise
241         & pstd        ! Standard deviation of noise
242
243      !! * Local declarations
244      CHARACTER(LEN=1), INTENT(IN) ::   &
245         & cd_type     ! Nature of pt2d grid-point
246                       !   = T , U  or V  grid-point
247      INTEGER :: &
248         & ji, &
249         & jj
250
251      !--------------------------------------------------------------------
252      ! Fill in the 2D field with Gaussian noise
253      !--------------------------------------------------------------------
254
255      DO jj = 1, jpj
256         DO ji = 1, jpi
257            pt2d(ji,jj) = gaustb_2d( ji, jj, kseed, pstd, pmean )
258         END DO
259      END DO
260
261      !--------------------------------------------------------------------
262      ! Apply masks and lateral boundary conditions
263      !--------------------------------------------------------------------
264
265      IF ( cd_type == 'T' ) THEN
266 
267         pt2d(:,:) = pt2d(:,:) * tmask(:,:,1)
268         CALL lbc_lnk( pt2d, 'T',  1.0 )
269
270      ELSEIF ( cd_type == 'U' ) THEN
271
272         pt2d(:,:) = pt2d(:,:) * umask(:,:,1)
273         CALL lbc_lnk( pt2d, 'U', -1.0 )
274
275      ELSEIF ( cd_type == 'V' ) THEN
276
277         pt2d(:,:) = pt2d(:,:) * vmask(:,:,1)
278         CALL lbc_lnk( pt2d, 'V', -1.0 )
279
280      ELSEIF ( cd_type == 'S' ) THEN
281         CALL lbc_lnk( pt2d, 'S', 1.0 )     
282         
283      ENDIF
284           
285   END SUBROUTINE grid_2d_ran_2d
286         
287   SUBROUTINE grid_3d_ran_2d( kseed, pt3d, cd_type, pmean, pstd )
288      !!----------------------------------------------------------------------
289      !!               ***  ROUTINE grid_3d_ran_2d ***
290      !!         
291      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian noise.
292      !!
293      !! ** Method  : The value of kseed is the seed for the random number
294      !!              generator. On the first call to "grid_3d_ran_2d" it
295      !!              should be set to a large negative number.
296      !!             
297      !!              This version has a 2D seed array to allow reproducible
298      !!              results for parallel execution.
299      !!             
300      !!              The kseed array should be be initialized with a MPP
301      !!              independent way. The mig, mjg values of each grid point
302      !!              can be used.
303      !!
304      !!              Apply the appropriate grid-point mask and lateral
305      !!              boundary conditions before exiting.
306      !!
307      !! ** Action  :
308      !!
309      !! References :
310      !!
311      !! History :
312      !!        !  07-07  (K. Mogensen) NEMOVAR version
313      !!        !  07-11  (A. Weaver) Treat one array only
314      !!----------------------------------------------------------------------
315      !! * Modules used
316
317      !! * Arguments
318      INTEGER, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
319         & kseed       ! Seed for random number generator
320      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
321         & pt3d        ! 3D field
322      REAL(wp), INTENT(IN) :: &
323         & pmean, &    ! Mean of noise
324         & pstd        ! Standard deviation of noise
325 
326      !! * Local declarations
327      CHARACTER(LEN=1), INTENT(IN) ::   &
328         & cd_type     ! Nature of pt3d grid-point
329                       !   = T , U  or V  grid-point
330      INTEGER  :: &
331         & ji, &
332         & jj, &
333         & jk
334
335      !--------------------------------------------------------------------
336      ! Fill in the 3D field with Gaussian noise
337      !--------------------------------------------------------------------
338
339      DO jk = 1, jpk
340         DO jj = 1, jpj
341            DO ji = 1, jpi
342               pt3d(ji,jj,jk) = gaustb_2d( ji, jj, kseed, pstd, pmean )
343            END DO
344         END DO
345      END DO
346
347      !--------------------------------------------------------------------
348      ! Apply masks and lateral boundary conditions
349      !--------------------------------------------------------------------
350
351      IF ( cd_type == 'T' ) THEN
352
353         pt3d(:,:,:) = pt3d(:,:,:) * tmask(:,:,:)
354         CALL lbc_lnk( pt3d, 'T',  1.0 )
355         
356      ELSEIF ( cd_type == 'U' ) THEN
357           
358         pt3d(:,:,:) = pt3d(:,:,:) * umask(:,:,:)
359         CALL lbc_lnk( pt3d, 'U', -1.0 )
360           
361      ELSEIF ( cd_type == 'V' ) THEN
362         
363         pt3d(:,:,:) = pt3d(:,:,:) * vmask(:,:,:)
364         CALL lbc_lnk( pt3d, 'V', -1.0 )
365
366      ELSEIF ( cd_type == 'S' ) THEN
367         CALL lbc_lnk( pt3d, 'S', 1.0 )   
368 
369      ENDIF
370
371   END SUBROUTINE grid_3d_ran_2d
372
373   SUBROUTINE grid_write_seed( cdfilename, kseed )
374      !!----------------------------------------------------------------------
375      !!               ***  ROUTINE grid_write_seed ***
376      !!         
377      !! ** Purpose : Write output 2d seed array
378      !!
379      !! ** Method  : IOM
380      !!
381      !! ** Action  :
382      !!
383      !! References :
384      !!
385      !! History :
386      !!        !  07-07  (K. Mogensen)  Original code based on iniwrk.F
387      !!----------------------------------------------------------------------
388      !! * Modules used
389      !! * Arguments
390      CHARACTER(LEN=*), INTENT(IN) :: &
391         & cdfilename  ! File to be written
392      INTEGER, INTENT(IN), DIMENSION(jpi,jpj) :: &
393         & kseed       ! Seed array
394      !! * Local declarations
395      INTEGER :: &
396         & inum
397
398      ! Open the file
399
400      CALL iom_open( TRIM(cdfilename), inum, ldwrt = .TRUE., kiolib = jprstlib)
401
402      ! Write the seed
403   
404      CALL iom_rstput( 0, 0, inum, 'seed' , REAL(kseed) )
405     
406      ! Close the file
407
408      CALL iom_close( inum )
409     
410   END SUBROUTINE grid_write_seed
411
412   SUBROUTINE grid_2d_rd_sd_loc( kseed, pt2d, cd_type, pmean, pstd )
413      !!----------------------------------------------------------------------
414      !!               ***  ROUTINE grid_2d_rd_sd ***
415      !!         
416      !! ** Purpose : Fill a 2D (surface) array with uncorrelated Gaussian
417      !!              noise.
418      !!
419      !! ** Method  : The value of kseed is an integer from which a seed is
420      !!              generated for the random number
421      !!              and then call grid_random routine
422      !!
423      !!              Apply the appropriate grid-point mask and lateral
424      !!              boundary conditions before exiting.
425      !!
426      !! ** Action  :
427      !!
428      !! References :
429      !!
430      !! History :
431      !!        !  09-07  (F. Vigilant) 
432      !!----------------------------------------------------------------------
433      !! * Modules used
434      USE par_oce       , ONLY: & ! Ocean space and time domain variables
435         & jpiglo
436      !! * Arguments
437      INTEGER, INTENT(IN) :: &
438         & kseed       ! Seed for random number generator
439      REAL, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
440         & pt2d        ! 2D field
441      REAL(wp), INTENT(IN) :: &
442         & pmean, &    ! Mean of noise
443         & pstd        ! Standard deviation of noise
444
445      !! * Local declarations
446      CHARACTER(LEN=1), INTENT(IN) ::   &
447         & cd_type     ! Nature of pt2d grid-point
448                       !   = T , U  or V  grid-point
449      INTEGER, DIMENSION(jpi,jpj) :: &
450         & iseed_2d             ! 2D seed for the random number generator
451      INTEGER :: &
452         & ji, &
453         & jj
454
455      !--------------------------------------------------------------------
456      ! Generate the seed
457      !--------------------------------------------------------------------
458      DO jj = 1, jpj
459         DO ji = 1, jpi
460            iseed_2d(ji,jj) = - ( kseed + &
461               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
462         END DO
463      END DO
464
465      !--------------------------------------------------------------------
466      ! Generate the noise
467      !--------------------------------------------------------------------
468      CALL grid_random( iseed_2d, pt2d, cd_type, pmean, pstd )
469           
470   END SUBROUTINE grid_2d_rd_sd_loc
471
472   SUBROUTINE grid_3d_rd_sd_loc( kseed, pt3d, cd_type, pmean, pstd )
473      !!----------------------------------------------------------------------
474      !!               ***  ROUTINE grid_3d_rd_sd ***
475      !!         
476      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian
477      !!              noise.
478      !!
479      !! ** Method  : The value of kseed is an integer from which a seed is
480      !!              generated for the random number
481      !!              and then call grid_random routine
482      !!
483      !!              Apply the appropriate grid-point mask and lateral
484      !!              boundary conditions before exiting.
485      !!
486      !! ** Action  :
487      !!
488      !! References :
489      !!
490      !! History :
491      !!        !  09-07  (F. Vigilant) 
492      !!----------------------------------------------------------------------
493      !! * Modules used
494      USE par_oce       , ONLY: & ! Ocean space and time domain variables
495         & jpiglo
496      !! * Arguments
497      INTEGER, INTENT(IN) :: &
498         & kseed       ! Seed for random number generator
499      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
500         & pt3d        ! 3D field
501      REAL(wp), INTENT(IN) :: &
502         & pmean, &    ! Mean of noise
503         & pstd        ! Standard deviation of noise
504
505      !! * Local declarations
506      CHARACTER(LEN=1), INTENT(IN) ::   &
507         & cd_type     ! Nature of pt2d grid-point
508                       !   = T , U  or V  grid-point
509      INTEGER, DIMENSION(jpi,jpj) :: &
510         & iseed_2d             ! 2D seed for the random number generator
511      INTEGER :: &
512         & ji, &
513         & jj
514
515      !--------------------------------------------------------------------
516      ! Generate the seed
517      !--------------------------------------------------------------------
518      DO jj = 1, jpj
519         DO ji = 1, jpi
520            iseed_2d(ji,jj) = - ( kseed + &
521               &                  mig(ji) + ( mjg(jj) - 1 ) * jpiglo )
522         END DO
523      END DO
524
525      !--------------------------------------------------------------------
526      ! Generate the noise
527      !--------------------------------------------------------------------
528      CALL grid_random( iseed_2d, pt3d, cd_type, pmean, pstd )
529           
530   END SUBROUTINE grid_3d_rd_sd_loc
531
532
533END MODULE gridrandom
Note: See TracBrowser for help on using the repository browser.