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.
sbcrnf.F90 in branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC – NEMO

source: branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC/sbcrnf.F90 @ 2171

Last change on this file since 2171 was 2171, checked in by rfurner, 14 years ago

Some variables renamed and some calculations moved to different modules following comments from Gurvan

  • Property svn:keywords set to Id
File size: 23.2 KB
Line 
1MODULE sbcrnf
2   !!======================================================================
3   !!                       ***  MODULE  sbcrnf  ***
4   !! Ocean forcing:  river runoff
5   !!=====================================================================
6   !! History :  OPA  !  2000-11  (R. Hordoir, E. Durand)  NetCDF FORMAT
7   !!   NEMO     1.0  !  2002-09  (G. Madec)  F90: Free form and module
8   !!            3.0  !  2006-07  (G. Madec)  Surface module
9   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   sbc_rnf      : monthly runoffs read in a NetCDF file
14   !!   sbc_rnf_init : runoffs initialisation
15   !!   rnf_mouth    : set river mouth mask
16   !!----------------------------------------------------------------------
17   USE dom_oce         ! ocean space and time domain
18   USE phycst          ! physical constants
19   USE sbc_oce         ! surface boundary condition variables
20   USE fldread         ! ???
21   USE in_out_manager  ! I/O manager
22   USE iom             ! I/O module
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC sbc_rnf          ! routine call in sbcmod module
28   PUBLIC sbc_rnf_div      ! routine called in sshwzv module
29
30   !                                                      !!* namsbc_rnf namelist *
31   CHARACTER(len=100), PUBLIC ::   cn_dir       = './'    !: Root directory for location of ssr files
32   LOGICAL           , PUBLIC ::   ln_rnf_depth = .false. !: depth       river runoffs attribute specified in a file
33   LOGICAL           , PUBLIC ::   ln_rnf_temp  = .false. !: temperature river runoffs attribute specified in a file
34   LOGICAL           , PUBLIC ::   ln_rnf_sal   = .false. !: salinity    river runoffs attribute specified in a file
35   LOGICAL           , PUBLIC ::   ln_rnf_emp   = .false. !: runoffs into a file to be read or already into precipitation
36   TYPE(FLD_N)       , PUBLIC ::   sn_rnf                 !: information about the runoff file to be read
37   TYPE(FLD_N)       , PUBLIC ::   sn_cnf                 !: information about the runoff mouth file to be read
38   TYPE(FLD_N)                ::   sn_s_rnf               !: information about the salinities of runoff file to be read 
39   TYPE(FLD_N)                ::   sn_t_rnf               !: information about the temperatures of runoff file to be read 
40   TYPE(FLD_N)                ::   sn_dep_rnf             !: information about the depth which river inflow affects
41   LOGICAL           , PUBLIC ::   ln_rnf_mouth = .false. !: specific treatment in mouths vicinity
42   REAL(wp)          , PUBLIC ::   rn_hrnf      = 0.e0    !: runoffs, depth over which enhanced vertical mixing is used
43   REAL(wp)          , PUBLIC ::   rn_avt_rnf   = 0.e0    !: runoffs, value of the additional vertical mixing coef. [m2/s]
44   REAL(wp)          , PUBLIC ::   rn_rfact     = 1.e0    !: multiplicative factor for runoff
45
46   INTEGER , PUBLIC                     ::   nkrnf = 0    !: number of levels over which Kz is increased at river mouths
47   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnfmsk       !: river mouth mask (hori.)
48   REAL(wp), PUBLIC, DIMENSION(jpk)     ::   rnfmsk_z     !: river mouth mask (vert.)
49
50   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf       !: structure of input river runoff (file information, fields read)
51
52   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     !: structure of input river runoff salinity (file information, fields read) 
53   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     !: structure of input river runoff temperature (file information, fields read) 
54 
55   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   h_rnf        !: depth of runoff in m
56   INTEGER,  PUBLIC, DIMENSION(jpi,jpj) ::   nk_rnf       !: depth of runoff in model levels
57
58   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,2) ::  tsc_rnf  !: temperature & salinity content of river runoffs   [K.m/s & PSU.m/s]
59
60   INTEGER, PUBLIC                      :: jp_sal=1
61   INTEGER, PUBLIC                      :: jp_tem=2
62
63!   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnf_sal      !: salinity of river runoff
64!   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnf_tmp      !: temperature of river runoff
65 
66   INTEGER  ::  ji, jj ,jk    ! dummy loop indices 
67   INTEGER  ::  inum          ! temporary logical unit 
68 
69   !! * Substitutions 
70#  include "domzgr_substitute.h90" 
71
72   !!----------------------------------------------------------------------
73   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
74   !! $Id$
75   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
76   !!----------------------------------------------------------------------
77
78CONTAINS
79
80   SUBROUTINE sbc_rnf( kt )
81      !!----------------------------------------------------------------------
82      !!                  ***  ROUTINE sbc_rnf  ***
83      !!       
84      !! ** Purpose :   Introduce a climatological run off forcing
85      !!
86      !! ** Method  :   Set each river mouth with a monthly climatology
87      !!                provided from different data.
88      !!                CAUTION : upward water flux, runoff forced to be < 0
89      !!
90      !! ** Action  :   runoff updated runoff field at time-step kt
91      !!----------------------------------------------------------------------
92      INTEGER, INTENT(in) ::   kt          ! ocean time step
93      !!
94      INTEGER  ::   ji, jj   ! dummy loop indices
95      REAL(wp) ::   z1_rau0  ! local scalar
96      !!----------------------------------------------------------------------
97      !                                   
98      IF( kt == nit000 ) THEN 
99         CALL sbc_rnf_init                      ! Read namelist and allocate structures
100      ENDIF
101
102      !                                                   !-------------------!
103      IF( .NOT. ln_rnf_emp ) THEN                         !   Update runoff   !
104         !                                                !-------------------!
105         !
106                             CALL fld_read ( kt, nn_fsbc, sf_rnf )      ! Read Runoffs data and provide it at kt
107         IF( ln_rnf_temp )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required
108         IF( ln_rnf_sal  )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required
109
110         ! Runoff reduction only associated to the ORCA2_LIM configuration
111         ! when reading the NetCDF file runoff_1m_nomask.nc
112         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 )   THEN
113            DO jj = 1, jpj
114               DO ji = 1, jpi
115                  IF( gphit(ji,jj) > 40 .AND. gphit(ji,jj) < 65 )   sf_rnf(1)%fnow(ji,jj) = 0.85 * sf_rnf(1)%fnow(ji,jj)
116               END DO
117            END DO
118         ENDIF
119
120         ! C a u t i o n : runoff is negative and in kg/m2/s
121
122         IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
123            rnf(:,:)  = rn_rfact * ( sf_rnf(1)%fnow(:,:) ) 
124            !
125            z1_rau0 = 1.e0 / rau0
126            !                                                              ! set temperature & salinity content of runoffs
127            IF( ln_rnf_temp )   THEN                                       ! use runoffs temperature data
128               tsc_rnf(:,:,jp_tem) = ( sf_t_rnf(1)%fnow(:,:) ) * rnf(:,:) * z1_rau0
129               WHERE( sf_t_rnf(1)%fnow(:,:) == -999 )                      ! if missing data value use SST as runoffs temperature 
130                   tsc_rnf(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * z1_rau0
131               ENDWHERE
132            ELSE                                                           ! use SST as runoffs temperature
133               tsc_rnf(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * z1_rau0
134            ENDIF 
135            !                                                              ! use runoffs salinity data
136            IF( ln_rnf_sal ) tsc_rnf(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:) ) * rnf(:,:) * z1_rau0
137            !                                                              ! else use S=0 for runoffs (done one for all in the init)
138            !
139            IF( ln_rnf_temp .OR. ln_rnf_sal ) THEN                         ! runoffs as outflow: use ocean SST and SSS
140               WHERE( rnf(:,:) < 0.e0 )                                    ! example baltic model when flow is out of domain
141                  tsc_rnf(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * z1_rau0
142                  tsc_rnf(:,:,jp_sal) = sss_m(:,:) * rnf(:,:) * z1_rau0
143               ENDWHERE
144            ENDIF
145
146            CALL iom_put( "runoffs", rnf )         ! output runoffs arrays
147         ENDIF
148         !
149      ENDIF
150      !
151   END SUBROUTINE sbc_rnf
152
153   SUBROUTINE sbc_rnf_div( phdivn )
154      !!----------------------------------------------------------------------
155      !!                  ***  ROUTINE sbc_rnf  ***
156      !!       
157      !! ** Purpose :   update the horizontal divergence with the runoff inflow
158      !!
159      !! ** Method  :   
160      !!                CAUTION : rnf is positive (inflow) decreasing the
161      !!                          divergence and expressed in m/s
162      !!
163      !! ** Action  :   phdivn   decreased by the runoff inflow
164      !!----------------------------------------------------------------------
165      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   phdivn   ! horizontal divergence
166      !!
167      INTEGER  ::   ji, jj, jk   ! dummy loop indices
168      REAL(wp) ::   z1_rau0   ! local scalar
169      !!----------------------------------------------------------------------
170      !
171      z1_rau0 = 1.e0 / rau0
172      IF( ln_rnf_depth ) THEN      !==   runoff distributed over several levels   ==!
173         IF( lk_vvl ) THEN             ! variable volume case
174            DO jj = 1, jpj                   ! update the depth over which runoffs are distributed
175               DO ji = 1, jpi
176                  h_rnf(ji,jj) = 0.e0 
177                  DO jk = 1, nk_rnf(ji,jj)                           ! recalculates h_rnf to be the depth in metres
178                     h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)   ! to the bottom of the relevant grid box
179                  END DO 
180                  !                          ! apply the runoff input flow
181                  DO jk = 1, nk_rnf(ji,jj)
182                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - rnf(ji,jj) * z1_rau0 / h_rnf(ji,jj)
183                  END DO
184               END DO
185            END DO
186         ELSE                          ! constant volume case : just apply the runoff input flow
187            DO jj = 1, jpj
188               DO ji = 1, jpi
189                  DO jk = 1, nk_rnf(ji,jj)
190                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - rnf(ji,jj) * z1_rau0 / h_rnf(ji,jj)
191                  END DO
192               END DO
193            END DO
194         ENDIF
195      ELSE                       !==   runoff put only at the surface   ==!
196         phdivn(:,:,1) = phdivn(:,:,1) - rnf(:,:) * z1_rau0 / fse3t(:,:,1)
197      ENDIF
198      !
199   END SUBROUTINE sbc_rnf_div
200
201
202   SUBROUTINE sbc_rnf_init
203      !!----------------------------------------------------------------------
204      !!                  ***  ROUTINE sbc_rnf_init  ***
205      !!
206      !! ** Purpose :   Initialisation of the runoffs if (ln_rnf=T)
207      !!
208      !! ** Method  : - read the runoff namsbc_rnf namelist
209      !!
210      !! ** Action  : - read parameters
211      !!----------------------------------------------------------------------
212      CHARACTER(len=32) ::   rn_dep_file   ! runoff file name 
213      INTEGER  ::   ierror   ! temporary integer
214      !!
215      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, ln_rnf_depth, ln_rnf_temp, ln_rnf_sal,   &
216         &                 sn_rnf, sn_cnf    , sn_s_rnf    , sn_t_rnf   , sn_dep_rnf,   & 
217         &                 ln_rnf_mouth      , rn_hrnf     , rn_avt_rnf , rn_rfact 
218      !!----------------------------------------------------------------------
219
220      !                                   ! ============
221      !                                   !   Namelist
222      !                                   ! ============
223      ! (NB: frequency positive => hours, negative => months)
224      !            !   file    ! frequency !  variable  ! time intep !  clim  ! 'yearly' or ! weights  ! rotation   !
225      !            !   name    !  (hours)  !   name     !   (T/F)    !  (T/F) !  'monthly'  ! filename ! pairs      !
226      sn_rnf = FLD_N( 'runoffs',    -1     , 'sorunoff' ,  .TRUE.    , .true. ,   'yearly'  , ''       , ''         )
227      sn_cnf = FLD_N( 'runoffs',     0     , 'sorunoff' ,  .FALSE.   , .true. ,   'yearly'  , ''       , ''         )
228
229      sn_s_rnf = FLD_N( 'runoffs',  24.  , 'rosaline' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  ) 
230      sn_t_rnf = FLD_N( 'runoffs',  24.  , 'rotemper' ,  .TRUE.    , .true. ,   'yearly'  , ''    , ''  ) 
231      sn_dep_rnf = FLD_N( 'runoffs',   0.  , 'rodepth'  ,  .FALSE.   , .true. ,   'yearly'  , ''    , ''  ) 
232      !
233      REWIND ( numnam )                         ! Read Namelist namsbc_rnf
234      READ   ( numnam, namsbc_rnf )
235
236      !                                         ! Control print
237      IF(lwp) THEN
238         WRITE(numout,*)
239         WRITE(numout,*) 'sbc_rnf : runoff '
240         WRITE(numout,*) '~~~~~~~ '
241         WRITE(numout,*) '   Namelist namsbc_rnf'
242         WRITE(numout,*) '      runoff in a file to be read                ln_rnf_emp   = ', ln_rnf_emp
243         WRITE(numout,*) '      specific river mouths treatment            ln_rnf_mouth = ', ln_rnf_mouth
244         WRITE(numout,*) '      river mouth additional Kz                  rn_avt_rnf   = ', rn_avt_rnf
245         WRITE(numout,*) '      depth of river mouth additional mixing     rn_hrnf      = ', rn_hrnf
246         WRITE(numout,*) '      multiplicative factor for runoff           rn_rfact     = ', rn_rfact   
247      ENDIF
248
249      !                                   ! ==================
250      !                                   !   Type of runoff
251      !                                   ! ==================
252      !
253      IF( ln_rnf_emp ) THEN                     !==  runoffs directly provided in the precipitations  ==!
254         IF(lwp) WRITE(numout,*)
255         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations'
256         IF( ln_rnf_depth .OR. ln_rnf_temp .OR. ln_rnf_sal ) THEN
257           CALL ctl_warn( 'runoffs already included in precipitations, so runoff (T,S, depth) attributes will not be used' ) 
258           ln_rnf_depth = .FALSE.   ;   ln_rnf_temp = .FALSE.   ;   ln_rnf_sal = .FALSE.
259         ENDIF
260         !
261      ELSE                                      !==  runoffs read in a file : set sf_rnf structure  ==!
262         !
263         ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow)
264         IF(lwp) WRITE(numout,*)
265         IF(lwp) WRITE(numout,*) '          runoffs inflow read in a file'
266         IF( ierror > 0 ) THEN
267            CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN
268         ENDIF
269         ALLOCATE( sf_rnf(1)%fnow(jpi,jpj)   )   ;   ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) )
270         !                                          ! fill sf_rnf with the namelist (sn_rnf) and control print
271         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' )
272         !
273         IF( ln_rnf_temp ) THEN                     ! Create (if required) sf_t_rnf structure
274            IF(lwp) WRITE(numout,*)
275            IF(lwp) WRITE(numout,*) '          runoffs temperatures read in a file'
276            ALLOCATE( sf_t_rnf(1), STAT=ierror  )
277            IF( ierror > 0 ) THEN
278               CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_t_rnf structure' )   ;   RETURN
279            ENDIF
280            ALLOCATE( sf_t_rnf(1)%fnow(jpi,jpj)   )   ;   ALLOCATE( sf_t_rnf(1)%fdta(jpi,jpj,2) )
281            CALL fld_fill (sf_t_rnf, (/ sn_t_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' ) 
282         ENDIF
283         !
284         IF( ln_rnf_sal  ) THEN                     ! Create (if required) sf_s_rnf and sf_t_rnf structures
285            IF(lwp) WRITE(numout,*)
286            IF(lwp) WRITE(numout,*) '          runoffs salinities read in a file'
287            ALLOCATE( sf_s_rnf(1), STAT=ierror  )
288            IF( ierror > 0 ) THEN
289               CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_s_rnf structure' )   ;   RETURN
290            ENDIF
291            ALLOCATE( sf_s_rnf(1)%fnow(jpi,jpj)   )   ;   ALLOCATE( sf_s_rnf(1)%fdta(jpi,jpj,2) )
292            CALL fld_fill (sf_s_rnf, (/ sn_s_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' ) 
293         ENDIF
294
295 
296         IF ( ln_rnf_depth ) THEN                     ! depth of runoffs set from a file
297            IF(lwp) WRITE(numout,*)
298            IF(lwp) WRITE(numout,*) '          runoffs depth read in a file'
299            rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname ) 
300            CALL iom_open ( rn_dep_file, inum )                           ! open file 
301            CALL iom_get  ( inum, jpdom_data, sn_dep_rnf%clvar, h_rnf )    ! read the river mouth array 
302            CALL iom_close( inum )                                      ! close file 
303 
304            nk_rnf(:,:)=0                              ! set the number of level over which river runoffs are applied
305            DO jj=1,jpj 
306              DO ji=1,jpi 
307                IF ( h_rnf(ji,jj) > 0.e0 ) THEN 
308                  jk=2 
309                  DO WHILE ( jk/=(mbathy(ji,jj)-1) .AND. fsdept(ji,jj,jk) < h_rnf(ji,jj) );  jk=jk+1;   ENDDO 
310                  nk_rnf(ji,jj)=jk 
311                ELSE IF ( h_rnf(ji,jj) == -1   ) THEN   ;  nk_rnf(ji,jj)=1 
312                ELSE IF ( h_rnf(ji,jj) == -999 ) THEN   ;  nk_rnf(ji,jj)=mbathy(ji,jj)-1
313                ELSE IF ( h_rnf(ji,jj) /= 0 ) THEN 
314                  CALL ctl_stop( 'runoff depth not positive, and not -999 or -1, rnf value in file fort.999'  ) 
315                  WRITE(999,*) 'ji, jj, rnf(ji,jj) :', ji, jj, rnf(ji,jj) 
316                ENDIF 
317              ENDDO 
318            ENDDO 
319            DO jj=1,jpj                               ! set the associated depth
320              DO ji=1,jpi 
321                h_rnf(ji,jj)=0.e0
322                DO jk=1,nk_rnf(ji,jj)                       
323                   h_rnf(ji,jj)=h_rnf(ji,jj)+fse3t(ji,jj,jk) 
324                ENDDO
325              ENDDO
326            ENDDO
327         ELSE                                       ! runoffs applied at the surface
328            nk_rnf(:,:)=1 
329            h_rnf(:,:)=fse3t(:,:,1)
330         ENDIF 
331      !
332      ENDIF
333
334      tsc_rnf(:,:,:) = 0.e0                 ! runoffs temperature & salinty contents initilisation
335      !                                   ! ========================
336      !                                   !   River mouth vicinity
337      !                                   ! ========================
338      !
339      IF( ln_rnf_mouth ) THEN                   ! Specific treatment in vicinity of river mouths :
340         !                                      !    - Increase Kz in surface layers ( rn_hrnf > 0 )
341         !                                      !    - set to zero SSS damping (ln_ssr=T)
342         !                                      !    - mixed upstream-centered (ln_traadv_cen2=T)
343         !
344         IF ( ln_rnf_depth )   CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already',   &
345            &                                              'be spread through depth by ln_rnf_depth'               ) 
346         !
347         nkrnf = 0                                  ! Number of level over which Kz increase
348         IF( rn_hrnf > 0.e0 ) THEN
349            nkrnf = 2
350            DO WHILE( nkrnf /= jpkm1 .AND. gdepw_0(nkrnf+1) < rn_hrnf )   ;   nkrnf = nkrnf + 1   ;   END DO
351            IF( ln_sco )   &
352               CALL ctl_warn( 'sbc_rnf: number of levels over which Kz is increased is computed for zco...' )
353         ENDIF
354         IF(lwp) WRITE(numout,*)
355         IF(lwp) WRITE(numout,*) '          Specific treatment used in vicinity of river mouths :'
356         IF(lwp) WRITE(numout,*) '             - Increase Kz in surface layers (if rn_hrnf > 0 )'
357         IF(lwp) WRITE(numout,*) '               by ', rn_avt_rnf,' m2/s  over ', nkrnf, ' w-levels'
358         IF(lwp) WRITE(numout,*) '             - set to zero SSS damping       (if ln_ssr=T)'
359         IF(lwp) WRITE(numout,*) '             - mixed upstream-centered       (if ln_traadv_cen2=T)'
360         !
361         CALL rnf_mouth                             ! set river mouth mask
362         !
363      ELSE                                      ! No treatment at river mouths
364         IF(lwp) WRITE(numout,*)
365         IF(lwp) WRITE(numout,*) '          No specific treatment at river mouths'
366         rnfmsk  (:,:) = 0.e0 
367         rnfmsk_z(:)   = 0.e0
368         nkrnf = 0
369      ENDIF
370
371   END SUBROUTINE sbc_rnf_init
372
373
374   SUBROUTINE rnf_mouth
375      !!----------------------------------------------------------------------
376      !!                  ***  ROUTINE rnf_mouth  ***
377      !!       
378      !! ** Purpose :   define the river mouths mask
379      !!
380      !! ** Method  :   read the river mouth mask (=0/1) in the river runoff
381      !!                climatological file. Defined a given vertical structure.
382      !!                CAUTION, the vertical structure is hard coded on the
383      !!                first 5 levels.
384      !!                This fields can be used to:
385      !!                 - set an upstream advection scheme 
386      !!                   (ln_rnf_mouth=T and ln_traadv_cen2=T)
387      !!                 - increase vertical on the top nn_krnf vertical levels
388      !!                   at river runoff input grid point (nn_krnf>=2, see step.F90)
389      !!                 - set to zero SSS restoring flux at river mouth grid points
390      !!
391      !! ** Action  :   rnfmsk   set to 1 at river runoff input, 0 elsewhere
392      !!                rnfmsk_z vertical structure
393      !!----------------------------------------------------------------------
394      USE closea, ONLY :    clo_rnf   ! rnfmsk update routine
395      !
396      INTEGER           ::   inum        ! temporary integers
397      CHARACTER(len=32) ::   cl_rnfile   ! runoff file name
398      !!----------------------------------------------------------------------
399      !
400      IF(lwp) WRITE(numout,*)
401      IF(lwp) WRITE(numout,*) 'rnf_mouth : river mouth mask'
402      IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
403
404      cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf%clname )
405      IF( .NOT. sn_cnf%ln_clim ) THEN   ;   WRITE(cl_rnfile, '(a,"_y",i4)' ) TRIM( cl_rnfile ), nyear    ! add year
406         IF( sn_cnf%cltype == 'monthly' )   WRITE(cl_rnfile, '(a,"m",i2)'  ) TRIM( cl_rnfile ), nmonth   ! add month
407      ENDIF
408 
409      ! horizontal mask (read in NetCDF file)
410      CALL iom_open ( cl_rnfile, inum )                           ! open file
411      CALL iom_get  ( inum, jpdom_data, sn_cnf%clvar, rnfmsk )    ! read the river mouth array
412      CALL iom_close( inum )                                      ! close file
413     
414      IF( nclosea == 1 )    CALL clo_rnf( rnfmsk )                ! closed sea inflow set as ruver mouth
415
416      rnfmsk_z(:)   = 0.e0                                        ! vertical structure
417      rnfmsk_z(1)   = 1.0
418      rnfmsk_z(2)   = 1.0                                         ! **********
419      rnfmsk_z(3)   = 0.5                                         ! HARD CODED on the 5 first levels
420      rnfmsk_z(4)   = 0.25                                        ! **********
421      rnfmsk_z(5)   = 0.125
422      !         
423   END SUBROUTINE rnf_mouth
424   
425   !!======================================================================
426END MODULE sbcrnf
Note: See TracBrowser for help on using the repository browser.