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 @ 313

Last change on this file since 313 was 287, checked in by opalod, 19 years ago

nemo_v1_bugfix_004 : CT : - use the iman variable instead of the parameter jpmois as argument of the flinopen routine when opening the runoff_1m_nomask.nc runoff file

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