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

Last change on this file since 699 was 699, checked in by smasson, 17 years ago

insert revision Id

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 12.7 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 iom             ! I/O module
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
42   !! * Module variable
43   REAL(wp), DIMENSION(jpi,jpj,2) ::   &  !:
44      rnfdta               !: monthly runoff data array (kg/m2/s)
45   INTEGER  ::          &  !:
46      numrnf,           &  !: logical unit for runoff data
47      nrnf1, nrnf2         !: first and second record used
48   !!----------------------------------------------------------------------
49   !!   OPA 9.0 , LOCEAN-IPSL (2005)
50   !! $Id$
51   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
52   !!----------------------------------------------------------------------
53
54CONTAINS
55
56   SUBROUTINE flx_rnf( kt )
57      !!----------------------------------------------------------------------
58      !!                  ***  ROUTINE flx_rnf  ***
59      !!       
60      !! ** Purpose :   Introduce a climatological run off forcing
61      !!
62      !! ** Method :
63      !!      Initialze each mouth of river with a monthly climatology
64      !!      provided from different data.
65      !!     C a u t i o n : upward water flux, runoff is negative
66      !!                     set at the last loop of the routine
67      !!
68      !! ** Action :
69      !!
70      !! References :
71      !!       J. D. Milliman and R. H. Meade, 1983 : world-wide delivery
72      !!          of river sediment to the oceans, journal of geology vol 91
73      !!          pp 1-21.
74      !!       G. L. Russell and J. R. Miller, 1990 : global river runoff
75      !!          calculated from a global atmospheric general circulation
76      !!          model, journal of hydrology, 117(1990), pp 241-254.
77      !!       F. Van Der Leeden, Troise F. L., Todd D. K. : the water
78      !!          encyclopedia, second edition, lewis publishers.
79      !!       J. W. Weatherly, J. E. Walsh : The effects of precipitation
80      !!          and river runoff in a coupled ice-ocean model of Arctic
81      !!          Climate dynamics 1996 12:785,798
82      !!       Jacobs et al. 1992. J. Glaciol. 38 (130) 375-387.
83      !!
84      !! History :
85      !!        !  94-10  (G.Madec, M. Pontaud, M. Imbard)  Original code
86      !!        !  97-03  (G.Madec)  time dependent version
87      !!        !  98-06  (J.M. Molines)  exact computation of zxy
88      !!                         for months that are not 30 days
89      !!        !  98-07  (M. Imbard)  ORCA and mpp option
90      !!        !  99-08  (J.P. Boulanger H.L.Ayina)  New rivers and
91      !!                         values given in m3/s
92      !!        !  00-04  (G. Madec, K. Roberts) add antarctica ice discharge.
93      !!        !  00-11  (R. Hordoir, E. Durand)  NetCDF FORMAT
94      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
95      !!----------------------------------------------------------------------
96      !! * arguments
97      INTEGER, INTENT( in  ) ::   kt       ! ocean time step
98
99      !! * Local declarations
100# if ! defined key_coupled
101      INTEGER  ::   ji, jj                 ! dummy loop indices
102      INTEGER ::   &
103         i15 , imois , iman,            &  ! temporary integers
104         idbd, idmeom                      !    "          "
105      REAL(wp) ::   zxy
106# endif
107      INTEGER  ::   ii0, ii1, ij0, ij1     !    "          "
108      !!----------------------------------------------------------------------
109     
110      IF( kt == nit000 ) THEN
111
112         SELECT CASE ( nrunoff )
113
114         CASE ( 0 )
115            IF(lwp) WRITE(numout,*)
116            IF(lwp) WRITE(numout,*) 'flx_rnf : No runoff in this simulation (nrunoff=0)'
117            IF(lwp) WRITE(numout,*) '~~~~~~~'
118           
119         CASE ( 1 )
120            IF(lwp) WRITE(numout,*)
121            IF(lwp) WRITE(numout,*) 'flx_rnf : monthly runoff (nrunoff=1)'
122            IF(lwp) WRITE(numout,*) '~~~~~~~'
123
124         CASE ( 2 )
125            IF(lwp) WRITE(numout,*)
126            IF(lwp) WRITE(numout,*) 'flx_rnf : monthly runoff with upsteam advection'
127            IF(lwp) WRITE(numout,*) '~~~~~~~   in the vicinity of river mouths (nrunoff=2)'
128
129         CASE DEFAULT
130            WRITE(ctmp1,*) ' Error nrunoff = ', nrunoff, ' /= 0, 1 or 2'
131            CALL ctl_stop( ctmp1 )
132
133         END SELECT
134
135         ! Set runoffs and upstream coeff to zero
136         upsadv (:,:) = 0.e0
137
138      ENDIF
139
140
141      ! 1. Initialization
142      ! -----------------
143
144      IF( nrunoff == 1 .OR. nrunoff == 2 ) THEN
145# if ! defined key_coupled
146
147         ! year, month, day
148         iman  = INT( raamo )
149!!! better but change the results      i15 = INT( 2*FLOAT( nday ) / ( FLOAT( nobis(nmonth) ) + 0.5 ) )
150         i15   = nday / 16
151         imois = nmonth + i15 - 1
152         IF( imois == 0 ) imois = iman
153         ! Number of days in the month
154         IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN
155            idbd = nbiss(imois)
156         ELSEIF( nleapy > 1 ) THEN
157            idbd = nleapy
158         ELSE
159            idbd = nobis(imois)
160         ENDIF
161         ! Number of days between imois, 15 and the end of month
162         idmeom = idbd - 15
163# endif
164         
165         ! Open file
166
167         IF( kt == nit000 ) THEN
168
169            nrnf1 = 0   ! initialization
170            IF (lwp) WRITE(numout,*) 'flx_rnf : Monthly runoff'
171            CALL iom_open ( 'runoff_1m_nomask.nc', numrnf )
172           
173         ENDIF
174         
175# if ! defined key_coupled
176
177         ! 2. Read monthly file of runoff
178         ! ------------------------------
179
180         IF( kt == nit000 .OR. imois /= nrnf1 ) THEN
181
182            ! Calendar computation for interpolation
183            !     nrnf1 number of the first array record used in the simulation
184            !     nrnf2 number of the last  array record
185
186            nrnf1 = imois
187            nrnf2 = nrnf1 + 1
188            nrnf1 = MOD( nrnf1, iman )
189            IF( nrnf1 == 0 ) nrnf1 = iman
190            nrnf2 = MOD( nrnf2, iman )
191            IF( nrnf2 == 0 ) nrnf2 = iman
192           
193            IF(lwp) THEN
194               WRITE(numout,*)
195               WRITE(numout,*) ' runoff monthly field'
196               WRITE(numout,*) ' --------------------'
197               WRITE(numout,*) ' NetCDF format'
198               WRITE(numout,*)
199               WRITE(numout,*) 'first array record used nrnf1 ', nrnf1
200               WRITE(numout,*) 'last  array record used nrnf2 ', nrnf2
201               WRITE(numout,*)
202            ENDIF
203           
204            ! Read monthly runoff data in kg/m2/s
205
206            CALL iom_get ( numrnf, jpdom_data, 'sorunoff', rnfdta(:,:,1), nrnf1 )
207            CALL iom_get ( numrnf, jpdom_data, 'sorunoff', rnfdta(:,:,2), nrnf2 )
208
209         ENDIF
210
211         ! Linear interpolation and conversion in upward water flux
212         ! C a u t i o n : runoff is negative and in kg/m2/s
213
214         zxy = FLOAT( nday + idmeom - idbd * i15 ) / idbd
215
216         runoff(:,:) = -( ( 1.e0 - zxy ) * rnfdta(:,:,1) + zxy * rnfdta(:,:,2) )
217
218         ! Runoff reduction only associated to the ORCA2_LIM configuration
219         ! when reading the NetCDF file runoff_1m_nomask.nc
220         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 )   THEN
221            DO jj = 1, jpj
222               DO ji = 1, jpi
223                  IF( gphit(ji,jj) > 40 .AND. gphit(ji,jj) < 65 )   runoff(ji,jj) = 0.85 * runoff(ji,jj)
224               END DO
225            END DO
226         ENDIF
227         
228# endif
229
230      ENDIF
231
232
233      ! 3. Mixed advection scheme
234      ! -------------------------
235
236      IF( nrunoff == 2 .AND. kt == nit000 ) THEN
237
238         ! Upstream and centered scheme in the vicinity of river mouths
239
240         !  Creates the array coef that contains the coefficient to affect to
241         !  the upstream scheme. advection scheme will be:
242         !  coefr * upstream + (1- coefr) centered
243         !  coefr must be between 0 and 1.
244
245         CALL iom_get ( numrnf, jpdom_data, 'socoefr', upsrnfh )
246         
247         upsrnfz(:)   = 0.e0
248         upsrnfz(1)   = 1.0
249         upsrnfz(2)   = 1.0
250         upsrnfz(3)   = 0.5
251         upsrnfz(4)   = 0.25
252         upsrnfz(5)   = 0.125
253         
254         IF( cp_cfg == "orca" .AND. jp_cfg == 2 ) THEN
255            ! ORCA_R2 configuration : upstream scheme in the Sound Strait
256            ij0 = 116   ;   ij1 = 116
257            ii0 = 144   ;   ii1 = 144   ;   upsrnfh( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
258            ii0 = 145   ;   ii1 = 147   ;   upsrnfh( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
259            ii0 = 148   ;   ii1 = 148   ;   upsrnfh( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
260         ENDIF
261
262      ENDIF
263
264      ! Upstream and centered scheme in the vicinity of some straits
265
266      IF( kt == nit000 ) THEN
267
268         IF( cp_cfg == "orca" ) THEN
269
270            SELECT CASE ( jp_cfg )
271            !                                        ! =======================
272            CASE ( 4 )                               !  ORCA_R4 configuration
273               !                                     ! =======================
274
275               !                                          ! Gibraltar Strait
276               ii0 =  70   ;   ii1 =  71
277               ij0 =  52   ;   ij1 =  53   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
278         
279               !                                     ! =======================
280            CASE ( 2 )                               !  ORCA_R2 configuration
281               !                                     ! =======================
282
283               !                                          ! Gibraltar Strait
284               ij0 = 102   ;   ij1 = 102
285               ii0 = 138   ;   ii1 = 138   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.20
286               ii0 = 139   ;   ii1 = 139   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40
287               ii0 = 140   ;   ii1 = 140   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
288               ij0 = 101   ;   ij1 = 102
289               ii0 = 141   ;   ii1 = 141   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
290
291               !                                          ! Bab el Mandeb Strait
292               ij0 =  87   ;   ij1 =  88
293               ii0 = 164   ;   ii1 = 164   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.10
294               ij0 =  88   ;   ij1 =  88
295               ii0 = 163   ;   ii1 = 163   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
296               ii0 = 162   ;   ii1 = 162   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.40
297               ii0 = 160   ;   ii1 = 161   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
298               ij0 =  89   ;   ij1 =  89
299               ii0 = 158   ;   ii1 = 160   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
300               ij0 =  90   ;   ij1 =  90
301               ii0 = 160   ;   ii1 = 160   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.25
302
303               !                                          ! Sound Strait
304               ij0 = 116   ;   ij1 = 116
305               ii0 = 145   ;   ii1 = 147   ;   upsadv( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) ) = 0.50
306         
307            END SELECT
308
309         ENDIF
310
311      ENDIF
312     
313      ! 4. Closing all files
314      ! --------------------
315
316      IF( kt == nitend .AND. nrunoff >= 1 )   CALL iom_close( numrnf )
317
318   END SUBROUTINE flx_rnf
319
320#endif
321   !!======================================================================
322END MODULE flxrnf
Note: See TracBrowser for help on using the repository browser.