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 NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/SBC – NEMO

source: NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/OCE/SBC/sbcrnf.F90 @ 11844

Last change on this file since 11844 was 11671, checked in by acc, 5 years ago

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Final, non-substantive changes to complete this branch. These changes remove all REWIND statements on the old namelist fortran units (now character variables for internal files). These changes have been left until last since they are easily repeated via a script and it may be preferable to use the previous revision for merge purposes and reapply these last changes separately. This branch has been fully SETTE tested.

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