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/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC – NEMO

source: branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC/gridrandom.F90 @ 3611

Last change on this file since 3611 was 3611, checked in by pabouttier, 11 years ago

Add TAM code and ORCA2_TAM configuration - see Ticket #1007

  • Property svn:executable set to *
File size: 9.8 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   END INTERFACE
32
33   INTERFACE grid_rd_sd
34      MODULE PROCEDURE grid_2d_rd_sd_loc,  &
35         &             grid_3d_rd_sd_loc
36   END INTERFACE
37
38   !! * Routine accessibility
39   PRIVATE
40
41   PUBLIC &
42      & grid_random,      &
43      & grid_rd_sd
44
45CONTAINS
46
47   SUBROUTINE grid_2d_ran( pt2d, cd_type, pmean, pstd )
48      !!----------------------------------------------------------------------
49      !!               ***  ROUTINE grid_2d_ran ***
50      !!         
51      !! ** Purpose : Fill a 2D (surface) array with uncorrelated Gaussian
52      !!              noise.
53      !!
54      !! ** Method  : The value of kseed is the seed for the random number
55      !!              generator. On the first call to "grid_2d_ran" it should
56      !!              be set to a large negative number.
57      !!
58      !!              Apply the appropriate grid-point mask and lateral
59      !!              boundary conditions before exiting.
60      !!
61      !! ** Action  :
62      !!
63      !! References :
64      !!
65      !! History :
66      !!        !  07-11  (A. Weaver) 
67      !!----------------------------------------------------------------------
68      !! * Modules used
69
70      !! * Arguments
71      REAL, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
72         & pt2d        ! 2D field
73      REAL(wp), INTENT(IN) :: &
74         & pmean, &    ! Mean of noise
75         & pstd        ! Standard deviation of noise
76
77      !! * Local declarations
78      CHARACTER(LEN=1), INTENT(IN) ::   &
79         & cd_type     ! Nature of pt2d grid-point
80                       !   = T , U  or V  grid-point
81      INTEGER :: &
82         & ji, &
83         & jj
84
85      !--------------------------------------------------------------------
86      ! Fill in the 2D field with Gaussian noise
87      !--------------------------------------------------------------------
88
89      DO jj = 1, jpj
90         DO ji = 1, jpi
91            pt2d(ji,jj) = gaustb( pstd, pmean )
92         END DO
93      END DO
94
95      !--------------------------------------------------------------------
96      ! Apply masks and lateral boundary conditions
97      !--------------------------------------------------------------------
98
99      IF ( cd_type == 'T' ) THEN
100 
101         pt2d(:,:) = pt2d(:,:) * tmask(:,:,1)
102         CALL lbc_lnk( pt2d, 'T',  1.0 )
103
104      ELSEIF ( cd_type == 'U' ) THEN
105
106         pt2d(:,:) = pt2d(:,:) * umask(:,:,1)
107         CALL lbc_lnk( pt2d, 'U', -1.0 )
108
109      ELSEIF ( cd_type == 'V' ) THEN
110
111         pt2d(:,:) = pt2d(:,:) * vmask(:,:,1)
112         CALL lbc_lnk( pt2d, 'V', -1.0 )
113
114      ELSEIF ( cd_type == 'S' ) THEN
115         CALL lbc_lnk( pt2d, 'S', 1.0 )
116               
117      ENDIF
118           
119   END SUBROUTINE grid_2d_ran
120         
121   SUBROUTINE grid_3d_ran( pt3d, cd_type, pmean, pstd )
122      !!----------------------------------------------------------------------
123      !!               ***  ROUTINE grid_3d_ran ***
124      !!         
125      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian noise.
126      !!
127      !! ** Method  : The value of kseed is the seed for the random number
128      !!              generator. On the first call to "grid_3d_ran" it should
129      !!              be set to a large negative number.
130      !!
131      !!              Apply the appropriate grid-point mask and lateral
132      !!              boundary conditions before exiting.
133      !!
134      !! ** Action  :
135      !!
136      !! References :
137      !!
138      !! History :
139      !!        !  07-11  (A. Weaver) 
140      !!----------------------------------------------------------------------
141      !! * Modules used
142
143      !! * Arguments
144      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
145         & pt3d        ! 3D field
146      REAL(wp), INTENT(IN) :: &
147         & pmean, &    ! Mean of noise
148         & pstd        ! Standard deviation of noise
149 
150      !! * Local declarations
151      CHARACTER(LEN=1), INTENT(IN) ::   &
152         & cd_type     ! Nature of pt3d grid-point
153                       !   = T , U  or V  grid-point
154      INTEGER  :: &
155         & ji, &
156         & jj, &
157         & jk
158
159      !--------------------------------------------------------------------
160      ! Fill in the 3D field with Gaussian noise
161      !--------------------------------------------------------------------
162
163      DO jk = 1, jpk
164         DO jj = 1, jpj
165            DO ji = 1, jpi
166               pt3d(ji,jj,jk) = gaustb( pstd, pmean )
167            END DO
168         END DO
169      END DO
170
171      !--------------------------------------------------------------------
172      ! Apply masks and lateral boundary conditions
173      !--------------------------------------------------------------------
174
175      IF ( cd_type == 'T' ) THEN
176
177         pt3d(:,:,:) = pt3d(:,:,:) * tmask(:,:,:)
178         CALL lbc_lnk( pt3d, 'T',  1.0 )
179         
180      ELSEIF ( cd_type == 'U' ) THEN
181           
182         pt3d(:,:,:) = pt3d(:,:,:) * umask(:,:,:)
183         CALL lbc_lnk( pt3d, 'U', -1.0 )
184           
185      ELSEIF ( cd_type == 'V' ) THEN
186         
187         pt3d(:,:,:) = pt3d(:,:,:) * vmask(:,:,:)
188         CALL lbc_lnk( pt3d, 'V', -1.0 )
189
190      ELSEIF ( cd_type == 'S' ) THEN
191         CALL lbc_lnk( pt3d, 'S', 1.0 )
192
193      ENDIF
194
195   END SUBROUTINE grid_3d_ran
196     
197   SUBROUTINE grid_2d_rd_sd_loc( pt2d, cd_type, pmean, pstd )
198      !!----------------------------------------------------------------------
199      !!               ***  ROUTINE grid_2d_rd_sd ***
200      !!         
201      !! ** Purpose : Fill a 2D (surface) array with uncorrelated Gaussian
202      !!              noise.
203      !!
204      !! ** Method  : The value of kseed is an integer from which a seed is
205      !!              generated for the random number
206      !!              and then call grid_random routine
207      !!
208      !!              Apply the appropriate grid-point mask and lateral
209      !!              boundary conditions before exiting.
210      !!
211      !! ** Action  :
212      !!
213      !! References :
214      !!
215      !! History :
216      !!        !  09-07  (F. Vigilant) 
217      !!----------------------------------------------------------------------
218      !! * Modules used
219      USE par_oce       , ONLY: & ! Ocean space and time domain variables
220         & jpiglo
221      !! * Arguments
222      REAL, INTENT(INOUT), DIMENSION(jpi,jpj) :: &
223         & pt2d        ! 2D field
224      REAL(wp), INTENT(IN) :: &
225         & pmean, &    ! Mean of noise
226         & pstd        ! Standard deviation of noise
227
228      !! * Local declarations
229      CHARACTER(LEN=1), INTENT(IN) ::   &
230         & cd_type     ! Nature of pt2d grid-point
231                       !   = T , U  or V  grid-point
232      INTEGER :: &
233         & ji, &
234         & jj
235
236      !--------------------------------------------------------------------
237      ! Generate the noise
238      !--------------------------------------------------------------------
239      CALL grid_random( pt2d, cd_type, pmean, pstd )
240           
241   END SUBROUTINE grid_2d_rd_sd_loc
242
243   SUBROUTINE grid_3d_rd_sd_loc( pt3d, cd_type, pmean, pstd )
244      !!----------------------------------------------------------------------
245      !!               ***  ROUTINE grid_3d_rd_sd ***
246      !!         
247      !! ** Purpose : Fill a 3D array with uncorrelated Gaussian
248      !!              noise.
249      !!
250      !! ** Method  : The value of kseed is an integer from which a seed is
251      !!              generated for the random number
252      !!              and then call grid_random routine
253      !!
254      !!              Apply the appropriate grid-point mask and lateral
255      !!              boundary conditions before exiting.
256      !!
257      !! ** Action  :
258      !!
259      !! References :
260      !!
261      !! History :
262      !!        !  09-07  (F. Vigilant) 
263      !!----------------------------------------------------------------------
264      !! * Modules used
265      USE par_oce       , ONLY: & ! Ocean space and time domain variables
266         & jpiglo
267      !! * Arguments
268      REAL, INTENT(INOUT), DIMENSION(jpi,jpj,jpk) :: &
269         & pt3d        ! 3D field
270      REAL(wp), INTENT(IN) :: &
271         & pmean, &    ! Mean of noise
272         & pstd        ! Standard deviation of noise
273
274      !! * Local declarations
275      CHARACTER(LEN=1), INTENT(IN) ::   &
276         & cd_type     ! Nature of pt2d grid-point
277                       !   = T , U  or V  grid-point
278      INTEGER :: &
279         & ji, &
280         & jj
281
282
283      !--------------------------------------------------------------------
284      ! Generate the noise
285      !--------------------------------------------------------------------
286      CALL grid_random( pt3d, cd_type, pmean, pstd )
287           
288   END SUBROUTINE grid_3d_rd_sd_loc
289
290
291END MODULE gridrandom
Note: See TracBrowser for help on using the repository browser.