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/UKMO/dev_r5518_test_GO6_package_update/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_test_GO6_package_update/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90 @ 7877

Last change on this file since 7877 was 7877, checked in by frrh, 7 years ago

Merge missing swathe of revisions from branches/2015/nemo_v3_6_STABLE/NEMOGCM
using the command:
svn merge -r6424:6477 svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/nemo_v3_6_STABLE/NEMOGCM

Note: this required manual conflict resolution of the content of NEMOGCM/TOOLS/SIREN/src/docsrc/
since the existing contenets of those directories in the package branch are not consistent
with the contents of branches/2015/nemo_v3_6_STABLE at revision 6424. (This should be an
incidental matter as the content in question only relates to documentation of NEMO tools
and is not relevant to NEMO source code.)

File size: 28.9 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   !!            3.3  ! 2010-10  (R. Furner, G. Madec) runoff distributed over ocean levels
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   sbc_rnf      : monthly runoffs read in a NetCDF file
15   !!   sbc_rnf_init : runoffs initialisation
16   !!   rnf_mouth    : set river mouth mask
17   !!----------------------------------------------------------------------
18   USE dom_oce         ! ocean space and time domain
19   USE phycst          ! physical constants
20   USE sbc_oce         ! surface boundary condition variables
21   USE sbcisf          ! PM we could remove it I think
22   USE closea          ! closed seas
23   USE fldread         ! read input field at current time step
24   USE in_out_manager  ! I/O manager
25   USE iom             ! I/O module
26   USE lib_mpp         ! MPP library
27   USE eosbn2
28   USE wrk_nemo        ! Memory allocation
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   sbc_rnf       ! routine call in sbcmod module
34   PUBLIC   sbc_rnf_div   ! routine called in divcurl module
35   PUBLIC   sbc_rnf_alloc ! routine call in sbcmod module
36   PUBLIC   sbc_rnf_init  ! (PUBLIC for TAM)
37   !                                                     !!* namsbc_rnf namelist *
38   CHARACTER(len=100)         ::   cn_dir          !: Root directory for location of rnf files
39   LOGICAL                    ::   ln_rnf_depth      !: depth       river runoffs attribute specified in a file
40   LOGICAL                    ::   ln_rnf_depth_ini  !: depth       river runoffs  computed at the initialisation
41   REAL(wp)                   ::   rn_rnf_max        !: maximum value of the runoff climatologie ( ln_rnf_depth_ini = .true )
42   REAL(wp)                   ::   rn_dep_max        !: depth over which runoffs is spread ( ln_rnf_depth_ini = .true )
43   INTEGER                    ::   nn_rnf_depth_file !: create (=1) a runoff depth file or not (=0)
44   LOGICAL                    ::   ln_rnf_tem      !: temperature river runoffs attribute specified in a file
45   LOGICAL           , PUBLIC ::   ln_rnf_sal      !: salinity    river runoffs attribute specified in a file
46   TYPE(FLD_N)       , PUBLIC ::   sn_rnf          !: information about the runoff file to be read
47   TYPE(FLD_N)                ::   sn_cnf          !: information about the runoff mouth file to be read
48   TYPE(FLD_N)                ::   sn_s_rnf        !: information about the salinities of runoff file to be read
49   TYPE(FLD_N)                ::   sn_t_rnf        !: information about the temperatures of runoff file to be read
50   TYPE(FLD_N)                ::   sn_dep_rnf      !: information about the depth which river inflow affects
51   LOGICAL           , PUBLIC ::   ln_rnf_mouth    !: specific treatment in mouths vicinity
52   REAL(wp)                   ::   rn_hrnf         !: runoffs, depth over which enhanced vertical mixing is used
53   REAL(wp)          , PUBLIC ::   rn_avt_rnf      !: runoffs, value of the additional vertical mixing coef. [m2/s]
54   REAL(wp)          , PUBLIC ::   rn_rfact        !: multiplicative factor for runoff
55
56   LOGICAL           , PUBLIC ::   l_rnfcpl = .false.       ! runoffs recieved from oasis
57
58   INTEGER , PUBLIC  ::   nkrnf = 0         !: nb of levels over which Kz is increased at river mouths
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rnfmsk              !: river mouth mask (hori.)
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   rnfmsk_z            !: river mouth mask (vert.)
61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   h_rnf               !: depth of runoff in m
62   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nk_rnf              !: depth of runoff in model levels
63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rnf_tsc_b, rnf_tsc  !: before and now T & S runoff contents   [K.m/s & PSU.m/s]   
64
65   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_rnf       ! structure: river runoff (file information, fields read)
66   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     ! structure: river runoff salinity (file information, fields read) 
67   TYPE(FLD),        ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     ! structure: river runoff temperature (file information, fields read) 
68 
69   !! * Substitutions 
70#  include "domzgr_substitute.h90" 
71   !!----------------------------------------------------------------------
72   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
73   !! $Id$
74   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
75   !!----------------------------------------------------------------------
76CONTAINS
77
78   INTEGER FUNCTION sbc_rnf_alloc()
79      !!----------------------------------------------------------------------
80      !!                ***  ROUTINE sbc_rnf_alloc  ***
81      !!----------------------------------------------------------------------
82      ALLOCATE( rnfmsk(jpi,jpj)         , rnfmsk_z(jpk)          ,     &
83         &      h_rnf (jpi,jpj)         , nk_rnf  (jpi,jpj)      ,     &
84         &      rnf_tsc_b(jpi,jpj,jpts) , rnf_tsc (jpi,jpj,jpts) , STAT=sbc_rnf_alloc )
85         !
86      IF( lk_mpp            )   CALL mpp_sum ( sbc_rnf_alloc )
87      IF( sbc_rnf_alloc > 0 )   CALL ctl_warn('sbc_rnf_alloc: allocation of arrays failed')
88   END FUNCTION sbc_rnf_alloc
89
90
91   SUBROUTINE sbc_rnf( kt )
92      !!----------------------------------------------------------------------
93      !!                  ***  ROUTINE sbc_rnf  ***
94      !!
95      !! ** Purpose :   Introduce a climatological run off forcing
96      !!
97      !! ** Method  :   Set each river mouth with a monthly climatology
98      !!                provided from different data.
99      !!                CAUTION : upward water flux, runoff forced to be < 0
100      !!
101      !! ** Action  :   runoff updated runoff field at time-step kt
102      !!----------------------------------------------------------------------
103      INTEGER, INTENT(in) ::   kt          ! ocean time step
104      !
105      INTEGER  ::   ji, jj    ! dummy loop indices
106      INTEGER  ::   z_err = 0 ! dummy integer for error handling
107      !!----------------------------------------------------------------------
108      REAL(wp), DIMENSION(:,:), POINTER       ::   ztfrz   ! freezing point used for temperature correction
109      !
110      CALL wrk_alloc( jpi,jpj, ztfrz)
111      !
112      !                                            !-------------------!
113      !                                            !   Update runoff   !
114      !                                            !-------------------!
115      !
116      IF( .NOT. l_rnfcpl )   CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt
117      IF(   ln_rnf_tem   )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required
118      IF(   ln_rnf_sal   )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required
119      !
120      IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN
121         !
122         IF( .NOT. l_rnfcpl )   rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) )       ! updated runoff value at time step kt
123         !
124         !                                                     ! set temperature & salinity content of runoffs
125         IF( ln_rnf_tem ) THEN                                       ! use runoffs temperature data
126            rnf_tsc(:,:,jp_tem) = ( sf_t_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0
127            WHERE( sf_t_rnf(1)%fnow(:,:,1) == -999._wp )             ! if missing data value use SST as runoffs temperature
128               rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0
129            END WHERE
130            WHERE( sf_t_rnf(1)%fnow(:,:,1) == -222._wp )             ! where fwf comes from melting of ice shelves or iceberg
131               ztfrz(:,:) = -1.9 !tfreez( sss_m(:,:) ) !PM to be discuss (trouble if sensitivity study)
132               rnf_tsc(:,:,jp_tem) = ztfrz(:,:) * rnf(:,:) * r1_rau0 - rnf(:,:) * lfusisf * r1_rau0_rcp
133            END WHERE
134         ELSE                                                        ! use SST as runoffs temperature
135            rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0
136         ENDIF
137         !                                                           ! use runoffs salinity data
138         IF( ln_rnf_sal )   rnf_tsc(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0
139         !                                                           ! else use S=0 for runoffs (done one for all in the init)
140         CALL iom_put( "runoffs", rnf )         ! output runoffs arrays
141      ENDIF
142      !
143      !                                                ! ---------------------------------------- !
144      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    !
145         !                                             ! ---------------------------------------- !
146         IF( ln_rstart .AND.    &                               !* Restart: read in restart file
147            & iom_varid( numror, 'rnf_b', ldstop = .FALSE. ) > 0 ) THEN
148            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields red in the restart file'
149            CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b )     ! before runoff
150            CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem) )   ! before heat content of runoff
151            CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal) )   ! before salinity content of runoff
152         ELSE                                                   !* no restart: set from nit000 values
153            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields set to nit000'
154            rnf_b    (:,:  ) = rnf    (:,:  )
155            rnf_tsc_b(:,:,:) = rnf_tsc(:,:,:)
156         ENDIF
157      ENDIF
158      !                                                ! ---------------------------------------- !
159      IF( lrst_oce ) THEN                              !      Write in the ocean restart file     !
160         !                                             ! ---------------------------------------- !
161         IF(lwp) WRITE(numout,*)
162         IF(lwp) WRITE(numout,*) 'sbcrnf : runoff forcing fields written in ocean restart file ',   &
163            &                    'at it= ', kt,' date= ', ndastp
164         IF(lwp) WRITE(numout,*) '~~~~'
165         CALL iom_rstput( kt, nitrst, numrow, 'rnf_b' , rnf )
166         CALL iom_rstput( kt, nitrst, numrow, 'rnf_hc_b', rnf_tsc(:,:,jp_tem) )
167         CALL iom_rstput( kt, nitrst, numrow, 'rnf_sc_b', rnf_tsc(:,:,jp_sal) )
168      ENDIF
169      !
170      CALL wrk_dealloc( jpi,jpj, ztfrz)
171      !
172   END SUBROUTINE sbc_rnf
173
174
175   SUBROUTINE sbc_rnf_div( phdivn )
176      !!----------------------------------------------------------------------
177      !!                  ***  ROUTINE sbc_rnf  ***
178      !!
179      !! ** Purpose :   update the horizontal divergence with the runoff inflow
180      !!
181      !! ** Method  :
182      !!                CAUTION : rnf is positive (inflow) decreasing the
183      !!                          divergence and expressed in m/s
184      !!
185      !! ** Action  :   phdivn   decreased by the runoff inflow
186      !!----------------------------------------------------------------------
187      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   phdivn   ! horizontal divergence
188      !!
189      INTEGER  ::   ji, jj, jk   ! dummy loop indices
190      REAL(wp) ::   zfact     ! local scalar
191      !!----------------------------------------------------------------------
192      !
193      zfact = 0.5_wp
194      !
195      IF( ln_rnf_depth .OR. ln_rnf_depth_ini ) THEN      !==   runoff distributed over several levels   ==!
196         IF( lk_vvl ) THEN             ! variable volume case
197            DO jj = 1, jpj                   ! update the depth over which runoffs are distributed
198               DO ji = 1, jpi
199                  h_rnf(ji,jj) = 0._wp
200                  DO jk = 1, nk_rnf(ji,jj)                           ! recalculates h_rnf to be the depth in metres
201                     h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)   ! to the bottom of the relevant grid box
202                  END DO
203                  !                          ! apply the runoff input flow
204                  DO jk = 1, nk_rnf(ji,jj)
205                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rau0 / h_rnf(ji,jj)
206                  END DO
207               END DO
208            END DO
209         ELSE                          ! constant volume case : just apply the runoff input flow
210            DO jj = 1, jpj
211               DO ji = 1, jpi
212                  DO jk = 1, nk_rnf(ji,jj)
213                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rau0 / h_rnf(ji,jj)
214                  END DO
215               END DO
216            END DO
217         ENDIF
218      ELSE                       !==   runoff put only at the surface   ==!
219         IF( lk_vvl ) THEN              ! variable volume case
220            h_rnf(:,:) = fse3t(:,:,1)   ! recalculate h_rnf to be depth of top box
221         ENDIF
222         phdivn(:,:,1) = phdivn(:,:,1) - ( rnf(:,:) + rnf_b(:,:) ) * zfact * r1_rau0 / fse3t(:,:,1)
223      ENDIF
224      !
225   END SUBROUTINE sbc_rnf_div
226
227
228   SUBROUTINE sbc_rnf_init
229      !!----------------------------------------------------------------------
230      !!                  ***  ROUTINE sbc_rnf_init  ***
231      !!
232      !! ** Purpose :   Initialisation of the runoffs if (ln_rnf=T)
233      !!
234      !! ** Method  : - read the runoff namsbc_rnf namelist
235      !!
236      !! ** Action  : - read parameters
237      !!----------------------------------------------------------------------
238      CHARACTER(len=32) ::   rn_dep_file   ! runoff file name
239      INTEGER           ::   ji, jj, jk, jm    ! dummy loop indices
240      INTEGER           ::   ierror, inum  ! temporary integer
241      INTEGER           ::   ios           ! Local integer output status for namelist read
242      INTEGER           ::   nbrec         ! temporary integer
243      REAL(wp)          ::   zacoef 
244      REAL(wp), DIMENSION(12)                 :: zrec             ! times records
245      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zrnfcl   
246      REAL(wp), DIMENSION(:,:  ), ALLOCATABLE :: zrnf
247      !
248      NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal,   &
249         &                 sn_rnf, sn_cnf    , sn_s_rnf    , sn_t_rnf  , sn_dep_rnf,   &
250         &                 ln_rnf_mouth      , rn_hrnf     , rn_avt_rnf, rn_rfact,     &
251         &                 ln_rnf_depth_ini  , rn_dep_max  , rn_rnf_max, nn_rnf_depth_file
252      !!----------------------------------------------------------------------
253      !
254      !                                         !==  allocate runoff arrays
255      IF( sbc_rnf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_rnf_alloc : unable to allocate arrays' )
256      !
257      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths
258         ln_rnf_mouth  = .FALSE.                   ! default definition needed for example by sbc_ssr or by tra_adv_muscl
259         nkrnf         = 0
260         rnf     (:,:) = 0.0_wp
261         rnf_b   (:,:) = 0.0_wp
262         rnfmsk  (:,:) = 0.0_wp
263         rnfmsk_z(:)   = 0.0_wp
264         RETURN
265      ENDIF
266      !
267      !                                   ! ============
268      !                                   !   Namelist
269      !                                   ! ============
270      !
271      REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs
272      READ  ( numnam_ref, namsbc_rnf, IOSTAT = ios, ERR = 901)
273901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in reference namelist', lwp )
274
275      REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs
276      READ  ( numnam_cfg, namsbc_rnf, IOSTAT = ios, ERR = 902 )
277902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in configuration namelist', lwp )
278      IF(lwm) WRITE ( numond, namsbc_rnf )
279      !
280      !                                         ! Control print
281      IF(lwp) THEN
282         WRITE(numout,*)
283         WRITE(numout,*) 'sbc_rnf : runoff '
284         WRITE(numout,*) '~~~~~~~ '
285         WRITE(numout,*) '   Namelist namsbc_rnf'
286         WRITE(numout,*) '      specific river mouths treatment            ln_rnf_mouth = ', ln_rnf_mouth
287         WRITE(numout,*) '      river mouth additional Kz                  rn_avt_rnf   = ', rn_avt_rnf
288         WRITE(numout,*) '      depth of river mouth additional mixing     rn_hrnf      = ', rn_hrnf
289         WRITE(numout,*) '      multiplicative factor for runoff           rn_rfact     = ', rn_rfact
290      ENDIF
291      !                                   ! ==================
292      !                                   !   Type of runoff
293      !                                   ! ==================
294      !
295      IF( .NOT. l_rnfcpl ) THEN                   
296         ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow)
297         IF(lwp) WRITE(numout,*)
298         IF(lwp) WRITE(numout,*) '          runoffs inflow read in a file'
299         IF( ierror > 0 ) THEN
300            CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN
301         ENDIF
302         ALLOCATE( sf_rnf(1)%fnow(jpi,jpj,1)   )
303         IF( sn_rnf%ln_tint ) ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,1,2) )
304         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' )
305      ENDIF
306      !
307      IF( ln_rnf_tem ) THEN                      ! Create (if required) sf_t_rnf structure
308         IF(lwp) WRITE(numout,*)
309         IF(lwp) WRITE(numout,*) '          runoffs temperatures read in a file'
310         ALLOCATE( sf_t_rnf(1), STAT=ierror  )
311         IF( ierror > 0 ) THEN
312            CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_t_rnf structure' )   ;   RETURN
313         ENDIF
314         ALLOCATE( sf_t_rnf(1)%fnow(jpi,jpj,1)   )
315         IF( sn_t_rnf%ln_tint ) ALLOCATE( sf_t_rnf(1)%fdta(jpi,jpj,1,2) )
316         CALL fld_fill (sf_t_rnf, (/ sn_t_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )
317      ENDIF
318      !
319      IF( ln_rnf_sal  ) THEN                     ! Create (if required) sf_s_rnf and sf_t_rnf structures
320         IF(lwp) WRITE(numout,*)
321         IF(lwp) WRITE(numout,*) '          runoffs salinities read in a file'
322         ALLOCATE( sf_s_rnf(1), STAT=ierror  )
323         IF( ierror > 0 ) THEN
324            CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_s_rnf structure' )   ;   RETURN
325         ENDIF
326         ALLOCATE( sf_s_rnf(1)%fnow(jpi,jpj,1)   )
327         IF( sn_s_rnf%ln_tint ) ALLOCATE( sf_s_rnf(1)%fdta(jpi,jpj,1,2) )
328         CALL fld_fill (sf_s_rnf, (/ sn_s_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' )
329      ENDIF
330      !
331      IF( ln_rnf_depth ) THEN                    ! depth of runoffs set from a file
332         IF(lwp) WRITE(numout,*)
333         IF(lwp) WRITE(numout,*) '          runoffs depth read in a file'
334         rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )
335         IF( .NOT. sn_dep_rnf%ln_clim ) THEN   ;   WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear    ! add year
336            IF( sn_dep_rnf%cltype == 'monthly' )   WRITE(rn_dep_file, '(a,"m",i2)'  ) TRIM( rn_dep_file ), nmonth   ! add month
337         ENDIF
338         CALL iom_open ( rn_dep_file, inum )                           ! open file
339         CALL iom_get  ( inum, jpdom_data, sn_dep_rnf%clvar, h_rnf )   ! read the river mouth array
340         CALL iom_close( inum )                                        ! close file
341         !
342         nk_rnf(:,:) = 0                               ! set the number of level over which river runoffs are applied
343         DO jj = 1, jpj
344            DO ji = 1, jpi
345               IF( h_rnf(ji,jj) > 0._wp ) THEN
346                  jk = 2
347                  DO WHILE ( jk /= mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ;  jk = jk + 1
348                  END DO
349                  nk_rnf(ji,jj) = jk
350               ELSEIF( h_rnf(ji,jj) == -1._wp   ) THEN   ;  nk_rnf(ji,jj) = 1
351               ELSEIF( h_rnf(ji,jj) == -999._wp ) THEN   ;  nk_rnf(ji,jj) = mbkt(ji,jj)
352               ELSE
353                  CALL ctl_stop( 'sbc_rnf_init: runoff depth not positive, and not -999 or -1, rnf value in file fort.999'  )
354                  WRITE(999,*) 'ji, jj, h_rnf(ji,jj) :', ji, jj, h_rnf(ji,jj)
355               ENDIF
356            END DO
357         END DO
358         DO jj = 1, jpj                                ! set the associated depth
359            DO ji = 1, jpi
360               h_rnf(ji,jj) = 0._wp
361               DO jk = 1, nk_rnf(ji,jj)
362                  h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)
363               END DO
364            END DO
365         END DO
366         !
367      ELSE IF( ln_rnf_depth_ini ) THEN           ! runoffs applied at the surface
368         !
369         IF(lwp) WRITE(numout,*)
370         IF(lwp) WRITE(numout,*) '    depth of runoff computed once from max value of runoff'
371         IF(lwp) WRITE(numout,*) '    max value of the runoff climatologie (over global domain) rn_rnf_max = ', rn_rnf_max
372         IF(lwp) WRITE(numout,*) '    depth over which runoffs is spread                        rn_dep_max = ', rn_dep_max
373         IF(lwp) WRITE(numout,*) '     create (=1) a runoff depth file or not (=0)      nn_rnf_depth_file  = ', nn_rnf_depth_file
374
375         CALL iom_open( TRIM( sn_rnf%clname ), inum )    !  open runoff file
376         CALL iom_gettime( inum, zrec, kntime=nbrec)
377         ALLOCATE( zrnfcl(jpi,jpj,nbrec) )     ;      ALLOCATE( zrnf(jpi,jpj) )
378         DO jm = 1, nbrec
379            CALL iom_get( inum, jpdom_data, TRIM( sn_rnf%clvar ), zrnfcl(:,:,jm), jm )
380         END DO
381         CALL iom_close( inum )
382         zrnf(:,:) = MAXVAL( zrnfcl(:,:,:), DIM=3 )   !  maximum value in time
383         DEALLOCATE( zrnfcl )
384         !
385         h_rnf(:,:) = 1.
386         !
387         zacoef = rn_dep_max / rn_rnf_max            ! coef of linear relation between runoff and its depth (150m for max of runoff)
388         !
389         WHERE( zrnf(:,:) > 0._wp )  h_rnf(:,:) = zacoef * zrnf(:,:)   ! compute depth for all runoffs
390         !
391         DO jj = 1, jpj                     ! take in account min depth of ocean rn_hmin
392            DO ji = 1, jpi
393               IF( zrnf(ji,jj) > 0._wp ) THEN
394                  jk = mbkt(ji,jj)
395                  h_rnf(ji,jj) = MIN( h_rnf(ji,jj), gdept_0(ji,jj,jk ) )
396               ENDIF
397            END DO
398         END DO
399         !
400         nk_rnf(:,:) = 0                       ! number of levels on which runoffs are distributed
401         DO jj = 1, jpj
402            DO ji = 1, jpi
403               IF( zrnf(ji,jj) > 0._wp ) THEN
404                  jk = 2
405                  DO WHILE ( jk /= mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ;  jk = jk + 1
406                  END DO
407                  nk_rnf(ji,jj) = jk
408               ELSE
409                  nk_rnf(ji,jj) = 1
410               ENDIF
411            END DO
412         END DO
413         !
414         DEALLOCATE( zrnf )
415         !
416         DO jj = 1, jpj                                ! set the associated depth
417            DO ji = 1, jpi
418               h_rnf(ji,jj) = 0._wp
419               DO jk = 1, nk_rnf(ji,jj)
420                  h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)
421               END DO
422            END DO
423         END DO
424         !
425         IF( nn_rnf_depth_file == 1 ) THEN      !  save  output nb levels for runoff
426            IF(lwp) WRITE(numout,*) '              create runoff depht file'
427            CALL iom_open  ( TRIM( sn_dep_rnf%clname ), inum, ldwrt = .TRUE., kiolib = jprstlib )
428            CALL iom_rstput( 0, 0, inum, 'rodepth', h_rnf )
429            CALL iom_close ( inum )
430         ENDIF
431      ELSE                                       ! runoffs applied at the surface
432         nk_rnf(:,:) = 1
433         h_rnf (:,:) = fse3t(:,:,1)
434      ENDIF
435      !
436      rnf(:,:) =  0._wp                         ! runoff initialisation
437      rnf_tsc(:,:,:) = 0._wp                    ! runoffs temperature & salinty contents initilisation
438      !
439      !                                   ! ========================
440      !                                   !   River mouth vicinity
441      !                                   ! ========================
442      !
443      IF( ln_rnf_mouth ) THEN                   ! Specific treatment in vicinity of river mouths :
444         !                                      !    - Increase Kz in surface layers ( rn_hrnf > 0 )
445         !                                      !    - set to zero SSS damping (ln_ssr=T)
446         !                                      !    - mixed upstream-centered (ln_traadv_cen2=T)
447         !
448         IF ( ln_rnf_depth )   CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already',   &
449            &                                              'be spread through depth by ln_rnf_depth'               )
450         !
451         nkrnf = 0                                  ! Number of level over which Kz increase
452         IF( rn_hrnf > 0._wp ) THEN
453            nkrnf = 2
454            DO WHILE( nkrnf /= jpkm1 .AND. gdepw_1d(nkrnf+1) < rn_hrnf )   ;   nkrnf = nkrnf + 1
455            END DO
456            IF( ln_sco )   CALL ctl_warn( 'sbc_rnf: number of levels over which Kz is increased is computed for zco...' )
457         ENDIF
458         IF(lwp) WRITE(numout,*)
459         IF(lwp) WRITE(numout,*) '          Specific treatment used in vicinity of river mouths :'
460         IF(lwp) WRITE(numout,*) '             - Increase Kz in surface layers (if rn_hrnf > 0 )'
461         IF(lwp) WRITE(numout,*) '               by ', rn_avt_rnf,' m2/s  over ', nkrnf, ' w-levels'
462         IF(lwp) WRITE(numout,*) '             - set to zero SSS damping       (if ln_ssr=T)'
463         IF(lwp) WRITE(numout,*) '             - mixed upstream-centered       (if ln_traadv_cen2=T)'
464         !
465         CALL rnf_mouth                             ! set river mouth mask
466         !
467      ELSE                                      ! No treatment at river mouths
468         IF(lwp) WRITE(numout,*)
469         IF(lwp) WRITE(numout,*) '          No specific treatment at river mouths'
470         rnfmsk  (:,:) = 0._wp
471         rnfmsk_z(:)   = 0._wp
472         nkrnf = 0
473      ENDIF
474      !
475   END SUBROUTINE sbc_rnf_init
476
477
478   SUBROUTINE rnf_mouth
479      !!----------------------------------------------------------------------
480      !!                  ***  ROUTINE rnf_mouth  ***
481      !!
482      !! ** Purpose :   define the river mouths mask
483      !!
484      !! ** Method  :   read the river mouth mask (=0/1) in the river runoff
485      !!                climatological file. Defined a given vertical structure.
486      !!                CAUTION, the vertical structure is hard coded on the
487      !!                first 5 levels.
488      !!                This fields can be used to:
489      !!                 - set an upstream advection scheme
490      !!                   (ln_rnf_mouth=T and ln_traadv_cen2=T)
491      !!                 - increase vertical on the top nn_krnf vertical levels
492      !!                   at river runoff input grid point (nn_krnf>=2, see step.F90)
493      !!                 - set to zero SSS restoring flux at river mouth grid points
494      !!
495      !! ** Action  :   rnfmsk   set to 1 at river runoff input, 0 elsewhere
496      !!                rnfmsk_z vertical structure
497      !!----------------------------------------------------------------------
498      INTEGER            ::   inum        ! temporary integers
499      CHARACTER(len=140) ::   cl_rnfile   ! runoff file name
500      !!----------------------------------------------------------------------
501      !
502      IF(lwp) WRITE(numout,*)
503      IF(lwp) WRITE(numout,*) 'rnf_mouth : river mouth mask'
504      IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
505      !
506      cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf%clname )
507      IF( .NOT. sn_cnf%ln_clim ) THEN   ;   WRITE(cl_rnfile, '(a,"_y",i4)' ) TRIM( cl_rnfile ), nyear    ! add year
508         IF( sn_cnf%cltype == 'monthly' )   WRITE(cl_rnfile, '(a,"m",i2)'  ) TRIM( cl_rnfile ), nmonth   ! add month
509      ENDIF
510      !
511      ! horizontal mask (read in NetCDF file)
512      CALL iom_open ( cl_rnfile, inum )                           ! open file
513      CALL iom_get  ( inum, jpdom_data, sn_cnf%clvar, rnfmsk )    ! read the river mouth array
514      CALL iom_close( inum )                                      ! close file
515      !
516      IF( nn_closea == 1 )   CALL clo_rnf( rnfmsk )               ! closed sea inflow set as ruver mouth
517      !
518      rnfmsk_z(:)   = 0._wp                                       ! vertical structure
519      rnfmsk_z(1)   = 1.0
520      rnfmsk_z(2)   = 1.0                                         ! **********
521      rnfmsk_z(3)   = 0.5                                         ! HARD CODED on the 5 first levels
522      rnfmsk_z(4)   = 0.25                                        ! **********
523      rnfmsk_z(5)   = 0.125
524      !
525   END SUBROUTINE rnf_mouth
526
527   !!======================================================================
528END MODULE sbcrnf
Note: See TracBrowser for help on using the repository browser.