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.
flxrnf.F90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/flxrnf.F90 @ 73

Last change on this file since 73 was 73, checked in by opalod, 20 years ago

CT : BUGFIX047 : Bug correction in mpp case, initialization to zero of rnfdta and zcoefr arrays

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 14.9 KB
Line 
1MODULE flxrnf
2   !!======================================================================
3   !!                       ***  MODULE  flxrnf  ***
4   !! Ocean forcing:  runoff
5   !!=====================================================================
6#if defined key_orca_r05
7   !!----------------------------------------------------------------------
8   !!   'key_orca_r05'                               ORCA R05 configuration
9   !!----------------------------------------------------------------------
10#  include "flxrnf_ORCA_R05.h90"
11#else
12   !!----------------------------------------------------------------------
13   !!   Default option                                     Standard runoffs
14   !!----------------------------------------------------------------------
15
16   !!----------------------------------------------------------------------
17   !!   flx_rnf      : monthly runoff read in a NetCDF file
18   !!----------------------------------------------------------------------
19   !! * Modules used
20   USE dom_oce         ! ocean space and time domain
21   USE phycst          ! physical constants
22   USE in_out_manager  ! I/O manager
23   USE daymod          ! calendar
24   USE ioipsl          ! NetCDF IPSL library
25
26   IMPLICIT NONE
27   PRIVATE
28
29   !! * Routine accessibility
30   PUBLIC flx_rnf          ! routine call in step module
31
32   !! * Shared module variables
33   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  !:
34      runoff,           &  !: monthly runoff (kg/m2/s)
35      upsadv,           &  !: mixed adv scheme in straits vicinity (hori.)
36      upsrnfh              !: mixed adv scheme in runoffs vicinity (hori.)
37   REAL(wp), PUBLIC, DIMENSION(jpk) ::   &  !:
38      upsrnfz              !: mixed adv scheme in runoffs vicinity (vert.)
39   INTEGER, PUBLIC ::   &  !:
40      nrunoff =  0 ,    &  !: runoff option (namelist)
41      nrnf1, nrnf2         !: first and second record used
42
43   !! * Module variable
44   REAL(wp), DIMENSION(jpi,jpj,2) ::   &  !:
45      rnfdta               !: monthly runoff data array (kg/m2/s)
46   !!----------------------------------------------------------------------
47   !!   OPA 9.0 , LODYC-IPSL  (2003)
48   !!----------------------------------------------------------------------
49
50CONTAINS
51
52   SUBROUTINE flx_rnf( kt )
53      !!----------------------------------------------------------------------
54      !!                  ***  ROUTINE flx_rnf  ***
55      !!       
56      !! ** Purpose :   Introduce a climatological run off forcing
57      !!
58      !! ** Method :
59      !!      Initialze each mouth of river with a monthly climatology
60      !!      provided from different data.
61      !!     C a u t i o n : upward water flux, runoff is negative
62      !!                     set at the last loop of the routine
63      !!
64      !! ** Action :
65      !!
66      !! References :
67      !!       J. D. Milliman and R. H. Meade, 1983 : world-wide delivery
68      !!          of river sediment to the oceans, journal of geology vol 91
69      !!          pp 1-21.
70      !!       G. L. Russell and J. R. Miller, 1990 : global river runoff
71      !!          calculated from a global atmospheric general circulation
72      !!          model, journal of hydrology, 117(1990), pp 241-254.
73      !!       F. Van Der Leeden, Troise F. L., Todd D. K. : the water
74      !!          encyclopedia, second edition, lewis publishers.
75      !!       J. W. Weatherly, J. E. Walsh : The effects of precipitation
76      !!          and river runoff in a coupled ice-ocean model of Arctic
77      !!          Climate dynamics 1996 12:785,798
78      !!       Jacobs et al. 1992. J. Glaciol. 38 (130) 375-387.
79      !!
80      !! History :
81      !!        !  94-10  (G.Madec, M. Pontaud, M. Imbard)  Original code
82      !!        !  97-03  (G.Madec)  time dependent version
83      !!        !  98-06  (J.M. Molines)  exact computation of zxy
84      !!                         for months that are not 30 days
85      !!        !  98-07  (M. Imbard)  ORCA and mpp option
86      !!        !  99-08  (J.P. Boulanger H.L.Ayina)  New rivers and
87      !!                         values given in m3/s
88      !!        !  00-04  (G. Madec, K. Roberts) add antarctica ice discharge.
89      !!        !  00-11  (R. Hordoir, E. Durand)  NetCDF FORMAT
90      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
91      !!----------------------------------------------------------------------
92      !! * arguments
93      INTEGER, INTENT( in  ) ::   kt       ! ocean time step
94
95      !! * Local declarations
96# if ! defined key_coupled
97      INTEGER ::   &
98         i15 , imois , iman,            &  ! temporary integers
99         idbd, idmeom                      !    "          "
100      REAL(wp) ::   zxy
101# endif
102      CHARACTER (len=32) ::   &
103         clname = 'runoff_1m_nomask'       ! monthly runoff filename
104      INTEGER, PARAMETER :: jpmois = 12
105      INTEGER  ::   ji, jj                 ! dummy loop indices
106      INTEGER  ::   ipi, ipj, ipk          ! temporary integers
107      INTEGER  ::   ii0, ii1, ij0, ij1     !    "          "
108      INTEGER, DIMENSION(jpmois) ::     &
109         istep                             ! temporary workspace
110      REAL(wp) ::   zdate0, zdt            ! temporary scalars
111      REAL(wp), DIMENSION(jpk) ::       &
112         zlev                              ! temporary workspace
113      REAL(wp), DIMENSION(jpi,jpj) ::   &
114         zlon, zlat,                    &  ! temporary workspace
115         zcoefr                            ! coeff of advection link to runoff
116      !!----------------------------------------------------------------------
117     
118      IF( kt == nit000 ) THEN
119
120         SELECT CASE ( nrunoff )
121
122         CASE ( 0 )
123            IF(lwp) WRITE(numout,*)
124            IF(lwp) WRITE(numout,*) 'flx_rnf : No runoff in this simulation (nrunoff=0)'
125            IF(lwp) WRITE(numout,*) '~~~~~~~'
126           
127         CASE ( 1 )
128            IF(lwp) WRITE(numout,*)
129            IF(lwp) WRITE(numout,*) 'flx_rnf : monthly runoff (nrunoff=0)'
130            IF(lwp) WRITE(numout,*) '~~~~~~~'
131
132         CASE ( 2 )
133            IF(lwp) WRITE(numout,*)
134            IF(lwp) WRITE(numout,*) 'flx_rnf : monthly runoff with upsteam advection'
135            IF(lwp) WRITE(numout,*) '~~~~~~~   in the vicinity of river mouths (nrunoff=2)'
136
137         CASE DEFAULT
138            IF(lwp) WRITE(numout,cform_err)
139            IF(lwp) WRITE(numout,*) ' Error nrunoff = ', nrunoff, ' /= 0, 1 or 2'
140            nstop = nstop + 1
141
142         END SELECT
143
144         ! Set runoffs and upstream coeff to zero
145         runoff (:,:) = 0.e0
146         upsrnfh(:,:) = 0.e0
147         upsrnfz(:)   = 0.e0 
148         upsadv (:,:) = 0.e0
149
150      ENDIF
151
152
153      ! 1. Initialization
154      ! -----------------
155
156      IF( nrunoff == 1 .OR. nrunoff == 2 ) THEN
157# if ! defined key_coupled
158
159         ! year, month, day
160
161         iman  = jpmois
162         i15   = nday / 16
163         imois = nmonth + i15 - 1
164         IF( imois == 0 )   imois = iman
165         ! Number of days in the month
166         IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN
167            idbd = nbiss(imois)
168         ELSEIF( nleapy > 1 ) THEN
169            idbd = nleapy
170         ELSE
171            idbd = nobis(imois)
172         ENDIF
173         ! Number of days between imois, 15 and the end of month
174         idmeom = idbd - 15
175# endif
176         ipi = jpiglo
177         ipj = jpjglo
178         ipk = jpk
179         zdt = rdt
180         
181         ! Open file
182
183         IF( kt == nit000 ) THEN
184            CALL flinopen( clname, mig(1), nlci, mjg(1), nlcj,    &
185               &           .false., ipi, ipj, ipk, zlon,        &
186               &           zlat, zlev, jpmois, istep, zdate0,   &
187               &           zdt, numrnf )
188            !   Title, dimensions and tests
189# if ! defined key_coupled
190            IF( iman /= jpmois ) THEN
191               IF(lwp) WRITE(numout,*)
192               IF(lwp) WRITE(numout,*) 'problem with time coordinates'
193               IF(lwp) WRITE(numout,*) ' iman ', iman, ' jpmois ', jpmois
194               nstop = nstop + 1
195            ENDIF
196            IF(lwp) WRITE(numout,*) iman, istep, zdate0, rdt, numrnf
197            IF(lwp) WRITE(numout,*) 'numrnf=', numrnf
198            IF(lwp) WRITE(numout,*) 'jpmois=', jpmois
199            IF(lwp) WRITE(numout,*) 'zdt=', zdt
200# endif
201            IF(ipi /= jpidta .AND. ipj /= jpjdta .AND. ipk /= 1) THEN
202               IF(lwp)WRITE(numout,*) ' '
203               IF(lwp)WRITE(numout,*) 'problem with dimensions'
204               IF(lwp)WRITE(numout,*) ' ipi ', ipi, ' jpidta ', jpidta
205               IF(lwp)WRITE(numout,*) ' ipj ', ipj, ' jpjdta ', jpjdta
206               IF(lwp)WRITE(numout,*) ' ipk ', ipk, ' =? 1'
207               nstop = nstop + 1
208            ENDIF
209            IF(lwp)WRITE(numout,*) 'ipi=', ipi, ' ipj=', ipj, ' ipk=', ipk
210         ENDIF
211         
212# if ! defined key_coupled
213
214         ! 2. Read monthly file of runoff
215         ! ------------------------------
216
217         IF( kt == nit000 .OR. imois /= nrnf1 ) THEN
218
219            ! Calendar computation for interpolation
220            !     nrnf1 number of the first array record used in the simulation
221            !     nrnf2 number of the last  array record
222
223            nrnf1 = imois
224            nrnf2 = nrnf1 + 1
225            nrnf1 = MOD( nrnf1, iman )
226            IF( nrnf1 == 0 ) nrnf1 = iman
227            nrnf2 = MOD( nrnf2, iman )
228            IF( nrnf2 == 0 ) nrnf2 = iman
229           
230            IF(lwp) THEN
231               WRITE(numout,*)
232               WRITE(numout,*) ' runoff monthly field'
233               WRITE(numout,*) ' --------------------'
234               WRITE(numout,*) ' NetCDF format'
235               WRITE(numout,*)
236               WRITE(numout,*) 'first array record used nrnf1 ',nrnf1
237               WRITE(numout,*) 'last  array record used nrnf2 ',nrnf2
238               WRITE(numout,*)
239            ENDIF
240           
241            ! Read monthly runoff data in kg/m2/s
242!ibug
243            IF( kt == nit000 )   rnfdta(:,:,:) = 0.e0
244!ibug
245            CALL flinget( numrnf, 'sorunoff', jpidta, jpjdta, 1, jpmois   &
246               &        , nrnf1, nrnf1, mig(1), nlci, mjg(1), nlcj, rnfdta(1:nlci,1:nlcj,1) )
247            CALL flinget( numrnf, 'sorunoff', jpidta, jpjdta, 1, jpmois   &
248               &        , nrnf2, nrnf2, mig(1), nlci, mjg(1), nlcj, rnfdta(1:nlci,1:nlcj,2) )
249
250            IF(lwp) WRITE(numout,*)
251            IF(lwp) WRITE(numout,*) ' read runoff field ok'
252            IF(lwp) WRITE(numout,*)
253
254         ENDIF
255
256         ! Linear interpolation and conversion in upward water flux
257         ! C a u t i o n : runoff is negative and in kg/m2/s
258
259         zxy = FLOAT( nday + idmeom - idbd * i15 ) / idbd
260
261         runoff(:,:) = -( ( 1.e0 - zxy ) * rnfdta(:,:,1) + zxy * rnfdta(:,:,2) )
262
263         ! Runoff reduction
264         DO jj = 1, jpj
265            DO ji = 1, jpi
266               IF( gphit(ji,jj) > 40 .AND. gphit(ji,jj) < 65 )   runoff(ji,jj) = 0.85 * runoff(ji,jj)
267            END DO
268         END DO
269         
270# endif
271
272      ENDIF
273
274
275      ! 3. Mixed advection scheme
276      ! -------------------------
277
278      IF( nrunoff == 2 .AND. kt == nit000 ) THEN
279
280         ! Upstream and centered scheme in the vicinity of river mouths
281
282         !  Creates the array coef that contains the coefficient to affect to
283         !  the upstream scheme. advection scheme will be:
284         !  coefr * upstream + (1- coefr) centered
285         !  coefr must be between 0 and 1.
286!ibug
287         zcoefr(:,:) = 0.e0
288!ibug
289
290         CALL flinget( numrnf, 'socoefr', jpidta, jpjdta, 1, jpmois, nrnf1,   &
291            &          nrnf1, mig(1), nlci, mjg(1), nlcj, zcoefr(1:nlci,1:nlcj) )
292
293         IF(lwp) WRITE(numout,*)
294         IF(lwp) WRITE(numout,*) ' read coefr for advection ok'
295         IF(lwp) WRITE(numout,*)
296         
297         upsrnfh(:,:) = zcoefr(:,:)
298         upsrnfz(:)   = 0.e0
299         upsrnfz(1)   = 1.0
300         upsrnfz(2)   = 1.0
301         upsrnfz(3)   = 0.5
302         upsrnfz(4)   = 0.25
303         upsrnfz(5)   = 0.125
304         
305         IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN
306            ! ORCA_R2 configuration : upstream scheme in the Sound Strait
307            ij0 = 116   ;   ij1 = 116
308            ii0 = 144   ;   ii1 = 144   ;   upsrnfh( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
309            ii0 = 145   ;   ii1 = 147   ;   upsrnfh( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
310            ii0 = 148   ;   ii1 = 148   ;   upsrnfh( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
311         ENDIF
312
313      ENDIF
314
315      ! Upstream and centered scheme in the vicinity of some straits
316
317      IF( kt == nit000 ) THEN
318
319         IF( cp_cfg == "orca" ) THEN
320
321            SELECT CASE ( jp_cfg )
322            !                                        ! =======================
323            CASE ( 4 )                               !  ORCA_R4 configuration
324               !                                     ! =======================
325
326               !                                          ! Gibraltar Strait
327               ii0 =  70   ;   ii1 =  71
328               ij0 =  52   ;   ij1 =  53   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
329         
330               !                                     ! =======================
331            CASE ( 2 )                               !  ORCA_R2 configuration
332               !                                     ! =======================
333
334               !                                          ! Gibraltar Strait
335               ij0 = 102   ;   ij1 = 102
336               ii0 = 138   ;   ii1 = 138   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.20
337               ii0 = 139   ;   ii1 = 139   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40
338               ii0 = 140   ;   ii1 = 140   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
339               ij0 = 101   ;   ij1 = 102
340               ii0 = 141   ;   ii1 = 141   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
341
342               !                                          ! Bab el Mandeb Strait
343               ij0 =  87   ;   ij1 =  88
344               ii0 = 164   ;   ii1 = 164   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.10
345               ij0 =  88   ;   ij1 =  88
346               ii0 = 163   ;   ii1 = 163   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
347               ii0 = 162   ;   ii1 = 162   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40
348               ii0 = 160   ;   ii1 = 161   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
349               ij0 =  89   ;   ij1 =  89
350               ii0 = 158   ;   ii1 = 160   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
351               ij0 =  90   ;   ij1 =  90
352               ii0 = 160   ;   ii1 = 160   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
353
354               !                                          ! Sound Strait
355               ij0 = 116   ;   ij1 = 116
356               ii0 = 145   ;   ii1 = 147   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
357         
358            END SELECT
359
360         ENDIF
361
362      ENDIF
363     
364      ! 4. Closing all files
365      ! --------------------
366
367      IF( kt == nitend .AND. nrunoff >= 1 )   CALL flinclo( numrnf )
368
369   END SUBROUTINE flx_rnf
370
371#endif
372   !!======================================================================
373END MODULE flxrnf
Note: See TracBrowser for help on using the repository browser.