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

source: trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90 @ 4781

Last change on this file since 4781 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

  • Property svn:keywords set to Id
File size: 26.3 KB
RevLine 
[888]1MODULE sbcrnf
2   !!======================================================================
3   !!                       ***  MODULE  sbcrnf  ***
4   !! Ocean forcing:  river runoff
5   !!=====================================================================
[2528]6   !! History :  OPA  ! 2000-11  (R. Hordoir, E. Durand)  NetCDF FORMAT
7   !!   NEMO     1.0  ! 2002-09  (G. Madec)  F90: Free form and module
[3764]8   !!            3.0  ! 2006-07  (G. Madec)  Surface module
[2528]9   !!            3.2  ! 2009-04  (B. Lemaire)  Introduce iom_put
10   !!            3.3  ! 2010-10  (R. Furner, G. Madec) runoff distributed over ocean levels
[888]11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   sbc_rnf      : monthly runoffs read in a NetCDF file
[1116]15   !!   sbc_rnf_init : runoffs initialisation
[888]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
[2715]21   USE closea          ! closed seas
[2528]22   USE fldread         ! read input field at current time step
[888]23   USE in_out_manager  ! I/O manager
24   USE iom             ! I/O module
[2715]25   USE lib_mpp         ! MPP library
[888]26
27   IMPLICIT NONE
28   PRIVATE
29
[2528]30   PUBLIC   sbc_rnf       ! routine call in sbcmod module
31   PUBLIC   sbc_rnf_div   ! routine called in sshwzv module
[2715]32   PUBLIC   sbc_rnf_alloc ! routine call in sbcmod module
[3764]33   PUBLIC   sbc_rnf_init  ! (PUBLIC for TAM)
[2715]34   !                                                     !!* namsbc_rnf namelist *
[4147]35   CHARACTER(len=100), PUBLIC ::   cn_dir          !: Root directory for location of ssr files
36   LOGICAL           , PUBLIC ::   ln_rnf_depth    !: depth       river runoffs attribute specified in a file
37   LOGICAL           , PUBLIC ::   ln_rnf_tem      !: temperature river runoffs attribute specified in a file
38   LOGICAL           , PUBLIC ::   ln_rnf_sal      !: salinity    river runoffs attribute specified in a file
39   LOGICAL           , PUBLIC ::   ln_rnf_emp      !: runoffs into a file to be read or already into precipitation
40   TYPE(FLD_N)       , PUBLIC ::   sn_rnf          !: information about the runoff file to be read
41   TYPE(FLD_N)       , PUBLIC ::   sn_cnf          !: information about the runoff mouth file to be read
42   TYPE(FLD_N)                ::   sn_s_rnf        !: information about the salinities of runoff file to be read
43   TYPE(FLD_N)                ::   sn_t_rnf        !: information about the temperatures of runoff file to be read
44   TYPE(FLD_N)                ::   sn_dep_rnf      !: information about the depth which river inflow affects
45   LOGICAL           , PUBLIC ::   ln_rnf_mouth    !: specific treatment in mouths vicinity
46   REAL(wp)          , PUBLIC ::   rn_hrnf         !: runoffs, depth over which enhanced vertical mixing is used
47   REAL(wp)          , PUBLIC ::   rn_avt_rnf      !: runoffs, value of the additional vertical mixing coef. [m2/s]
48   REAL(wp)          , PUBLIC ::   rn_rfact        !: multiplicative factor for runoff
[888]49
[2715]50   INTEGER , PUBLIC  ::   nkrnf = 0         !: nb of levels over which Kz is increased at river mouths
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rnfmsk              !: river mouth mask (hori.)
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   rnfmsk_z            !: river mouth mask (vert.)
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   h_rnf               !: depth of runoff in m
54   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   nk_rnf              !: depth of runoff in model levels
[3764]55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rnf_tsc_b, rnf_tsc  !: before and now T & S runoff contents   [K.m/s & PSU.m/s]   
[888]56
[3680]57   TYPE(FLD), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   sf_rnf       ! structure: river runoff (file information, fields read)
58   TYPE(FLD), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   sf_s_rnf     ! structure: river runoff salinity (file information, fields read) 
59   TYPE(FLD), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   sf_t_rnf     ! structure: river runoff temperature (file information, fields read) 
[2528]60 
61   !! * Substitutions 
62#  include "domzgr_substitute.h90" 
[888]63   !!----------------------------------------------------------------------
[2528]64   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[1146]65   !! $Id$
[2528]66   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[888]67   !!----------------------------------------------------------------------
68CONTAINS
69
[2715]70   INTEGER FUNCTION sbc_rnf_alloc()
71      !!----------------------------------------------------------------------
72      !!                ***  ROUTINE sbc_rnf_alloc  ***
73      !!----------------------------------------------------------------------
74      ALLOCATE( rnfmsk(jpi,jpj)         , rnfmsk_z(jpk)          ,     &
75         &      h_rnf (jpi,jpj)         , nk_rnf  (jpi,jpj)      ,     &
76         &      rnf_tsc_b(jpi,jpj,jpts) , rnf_tsc (jpi,jpj,jpts) , STAT=sbc_rnf_alloc )
77         !
78      IF( lk_mpp            )   CALL mpp_sum ( sbc_rnf_alloc )
79      IF( sbc_rnf_alloc > 0 )   CALL ctl_warn('sbc_rnf_alloc: allocation of arrays failed')
80   END FUNCTION sbc_rnf_alloc
81
[3625]82
[888]83   SUBROUTINE sbc_rnf( kt )
84      !!----------------------------------------------------------------------
85      !!                  ***  ROUTINE sbc_rnf  ***
[3764]86      !!
[888]87      !! ** Purpose :   Introduce a climatological run off forcing
88      !!
[3764]89      !! ** Method  :   Set each river mouth with a monthly climatology
[888]90      !!                provided from different data.
91      !!                CAUTION : upward water flux, runoff forced to be < 0
92      !!
93      !! ** Action  :   runoff updated runoff field at time-step kt
94      !!----------------------------------------------------------------------
95      INTEGER, INTENT(in) ::   kt          ! ocean time step
[3625]96      !
[3832]97      INTEGER  ::   ji, jj    ! dummy loop indices
98      INTEGER  ::   z_err = 0 ! dummy integer for error handling
[888]99      !!----------------------------------------------------------------------
[3764]100      !
[2528]101      IF( kt == nit000 )   CALL sbc_rnf_init                           ! Read namelist and allocate structures
102
103      !                                            ! ---------------------------------------- !
104      IF( kt /= nit000 ) THEN                      !          Swap of forcing fields          !
105         !                                         ! ---------------------------------------- !
106         rnf_b    (:,:  ) = rnf    (:,:  )               ! Swap the ocean forcing fields except at nit000
107         rnf_tsc_b(:,:,:) = rnf_tsc(:,:,:)               ! where before fields are set at the end of the routine
108         !
[1242]109      ENDIF
[888]110
111      !                                                   !-------------------!
[1116]112      IF( .NOT. ln_rnf_emp ) THEN                         !   Update runoff   !
[888]113         !                                                !-------------------!
114         !
[3764]115                             CALL fld_read ( kt, nn_fsbc, sf_rnf   )    ! Read Runoffs data and provide it at kt
[2528]116         IF( ln_rnf_tem  )   CALL fld_read ( kt, nn_fsbc, sf_t_rnf )    ! idem for runoffs temperature if required
117         IF( ln_rnf_sal  )   CALL fld_read ( kt, nn_fsbc, sf_s_rnf )    ! idem for runoffs salinity    if required
118         !
[888]119         ! Runoff reduction only associated to the ORCA2_LIM configuration
120         ! when reading the NetCDF file runoff_1m_nomask.nc
121         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 )   THEN
[2528]122            WHERE( 40._wp < gphit(:,:) .AND. gphit(:,:) < 65._wp )
123               sf_rnf(1)%fnow(:,:,1) = 0.85 * sf_rnf(1)%fnow(:,:,1)
124            END WHERE
125         ENDIF
126         !
127         IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN
128            !
[3625]129            rnf(:,:) = rn_rfact * ( sf_rnf(1)%fnow(:,:,1) )       ! updated runoff value at time step kt
130            !
[2528]131            !                                                     ! set temperature & salinity content of runoffs
132            IF( ln_rnf_tem ) THEN                                       ! use runoffs temperature data
133               rnf_tsc(:,:,jp_tem) = ( sf_t_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0
[3811]134               WHERE( sf_t_rnf(1)%fnow(:,:,1) == -999._wp )             ! if missing data value use SST as runoffs temperature
[2528]135                   rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0
136               END WHERE
137            ELSE                                                        ! use SST as runoffs temperature
138               rnf_tsc(:,:,jp_tem) = sst_m(:,:) * rnf(:,:) * r1_rau0
[3764]139            ENDIF
140            !                                                           ! use runoffs salinity data
[2528]141            IF( ln_rnf_sal )   rnf_tsc(:,:,jp_sal) = ( sf_s_rnf(1)%fnow(:,:,1) ) * rnf(:,:) * r1_rau0
142            !                                                           ! else use S=0 for runoffs (done one for all in the init)
[3832]143            IF ( ANY( rnf(:,:) < 0._wp ) ) z_err=1
144            IF(lk_mpp) CALL mpp_sum(z_err)
145            IF( z_err > 0 ) CALL ctl_stop( 'sbc_rnf : negative runnoff values exist' )
[2528]146            !
147            CALL iom_put( "runoffs", rnf )         ! output runoffs arrays
148         ENDIF
149         !
150      ENDIF
151      !
152      IF( kt == nit000 ) THEN                          !   set the forcing field at nit000 - 1    !
153         !                                             ! ---------------------------------------- !
154         IF( ln_rstart .AND.    &                               !* Restart: read in restart file
[3764]155            & iom_varid( numror, 'rnf_b', ldstop = .FALSE. ) > 0 ) THEN
[2528]156            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields red in the restart file'
157            CALL iom_get( numror, jpdom_autoglo, 'rnf_b', rnf_b )     ! before runoff
158            CALL iom_get( numror, jpdom_autoglo, 'rnf_hc_b', rnf_tsc_b(:,:,jp_tem) )   ! before heat content of runoff
159            CALL iom_get( numror, jpdom_autoglo, 'rnf_sc_b', rnf_tsc_b(:,:,jp_sal) )   ! before salinity content of runoff
160         ELSE                                                   !* no restart: set from nit000 values
161            IF(lwp) WRITE(numout,*) '          nit000-1 runoff forcing fields set to nit000'
[3764]162             rnf_b    (:,:  ) = rnf    (:,:  )
163             rnf_tsc_b(:,:,:) = rnf_tsc(:,:,:)
[2528]164         ENDIF
165      ENDIF
166      !                                                ! ---------------------------------------- !
167      IF( lrst_oce ) THEN                              !      Write in the ocean restart file     !
168         !                                             ! ---------------------------------------- !
169         IF(lwp) WRITE(numout,*)
170         IF(lwp) WRITE(numout,*) 'sbcrnf : runoff forcing fields written in ocean restart file ',   &
171            &                    'at it= ', kt,' date= ', ndastp
172         IF(lwp) WRITE(numout,*) '~~~~'
173         CALL iom_rstput( kt, nitrst, numrow, 'rnf_b' , rnf )
174         CALL iom_rstput( kt, nitrst, numrow, 'rnf_hc_b', rnf_tsc(:,:,jp_tem) )
175         CALL iom_rstput( kt, nitrst, numrow, 'rnf_sc_b', rnf_tsc(:,:,jp_sal) )
176      ENDIF
177      !
178   END SUBROUTINE sbc_rnf
179
180
181   SUBROUTINE sbc_rnf_div( phdivn )
182      !!----------------------------------------------------------------------
183      !!                  ***  ROUTINE sbc_rnf  ***
[3764]184      !!
[2528]185      !! ** Purpose :   update the horizontal divergence with the runoff inflow
186      !!
[3764]187      !! ** Method  :
188      !!                CAUTION : rnf is positive (inflow) decreasing the
[2528]189      !!                          divergence and expressed in m/s
190      !!
191      !! ** Action  :   phdivn   decreased by the runoff inflow
192      !!----------------------------------------------------------------------
[2715]193      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   phdivn   ! horizontal divergence
[2528]194      !!
195      INTEGER  ::   ji, jj, jk   ! dummy loop indices
196      REAL(wp) ::   zfact     ! local scalar
197      !!----------------------------------------------------------------------
198      !
199      zfact = 0.5_wp
200      !
201      IF( ln_rnf_depth ) THEN      !==   runoff distributed over several levels   ==!
[3764]202         IF( lk_vvl ) THEN             ! variable volume case
[2528]203            DO jj = 1, jpj                   ! update the depth over which runoffs are distributed
204               DO ji = 1, jpi
[3764]205                  h_rnf(ji,jj) = 0._wp
[2528]206                  DO jk = 1, nk_rnf(ji,jj)                           ! recalculates h_rnf to be the depth in metres
[3764]207                     h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)   ! to the bottom of the relevant grid box
208                  END DO
[2528]209                  !                          ! apply the runoff input flow
210                  DO jk = 1, nk_rnf(ji,jj)
211                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rau0 / h_rnf(ji,jj)
212                  END DO
213               END DO
214            END DO
215         ELSE                          ! constant volume case : just apply the runoff input flow
[888]216            DO jj = 1, jpj
217               DO ji = 1, jpi
[2528]218                  DO jk = 1, nk_rnf(ji,jj)
219                     phdivn(ji,jj,jk) = phdivn(ji,jj,jk) - ( rnf(ji,jj) + rnf_b(ji,jj) ) * zfact * r1_rau0 / h_rnf(ji,jj)
220                  END DO
[888]221               END DO
222            END DO
223         ENDIF
[2528]224      ELSE                       !==   runoff put only at the surface   ==!
225         IF( lk_vvl ) THEN              ! variable volume case
226            h_rnf(:,:) = fse3t(:,:,1)   ! recalculate h_rnf to be depth of top box
[1303]227         ENDIF
[2528]228         phdivn(:,:,1) = phdivn(:,:,1) - ( rnf(:,:) + rnf_b(:,:) ) * zfact * r1_rau0 / fse3t(:,:,1)
[888]229      ENDIF
230      !
[2528]231   END SUBROUTINE sbc_rnf_div
[888]232
233
[2528]234   SUBROUTINE sbc_rnf_init
[1116]235      !!----------------------------------------------------------------------
236      !!                  ***  ROUTINE sbc_rnf_init  ***
237      !!
238      !! ** Purpose :   Initialisation of the runoffs if (ln_rnf=T)
239      !!
240      !! ** Method  : - read the runoff namsbc_rnf namelist
241      !!
242      !! ** Action  : - read parameters
243      !!----------------------------------------------------------------------
[3764]244      CHARACTER(len=32) ::   rn_dep_file   ! runoff file name
[2528]245      INTEGER           ::   ji, jj, jk    ! dummy loop indices
246      INTEGER           ::   ierror, inum  ! temporary integer
[4147]247      INTEGER           ::   ios           ! Local integer output status for namelist read
[3625]248      !
[2528]249      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, ln_rnf_depth, ln_rnf_tem, ln_rnf_sal,   &
[3764]250         &                 sn_rnf, sn_cnf    , sn_s_rnf    , sn_t_rnf  , sn_dep_rnf,   &
251         &                 ln_rnf_mouth      , rn_hrnf     , rn_avt_rnf, rn_rfact
[1116]252      !!----------------------------------------------------------------------
[3625]253      !
[1116]254      !                                   ! ============
255      !                                   !   Namelist
256      !                                   ! ============
[4147]257      !
258      REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs
259      READ  ( numnam_ref, namsbc_rnf, IOSTAT = ios, ERR = 901)
260901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in reference namelist', lwp )
[1116]261
[4147]262      REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs
263      READ  ( numnam_cfg, namsbc_rnf, IOSTAT = ios, ERR = 902 )
264902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf in configuration namelist', lwp )
[4624]265      IF(lwm) WRITE ( numond, namsbc_rnf )
[1116]266      !
267      !                                         ! Control print
268      IF(lwp) THEN
269         WRITE(numout,*)
270         WRITE(numout,*) 'sbc_rnf : runoff '
271         WRITE(numout,*) '~~~~~~~ '
272         WRITE(numout,*) '   Namelist namsbc_rnf'
273         WRITE(numout,*) '      runoff in a file to be read                ln_rnf_emp   = ', ln_rnf_emp
274         WRITE(numout,*) '      specific river mouths treatment            ln_rnf_mouth = ', ln_rnf_mouth
275         WRITE(numout,*) '      river mouth additional Kz                  rn_avt_rnf   = ', rn_avt_rnf
276         WRITE(numout,*) '      depth of river mouth additional mixing     rn_hrnf      = ', rn_hrnf
[3764]277         WRITE(numout,*) '      multiplicative factor for runoff           rn_rfact     = ', rn_rfact
[1116]278      ENDIF
[3625]279      !
[1116]280      !                                   ! ==================
281      !                                   !   Type of runoff
282      !                                   ! ==================
[2715]283      !                                         !==  allocate runoff arrays
284      IF( sbc_rnf_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_rnf_alloc : unable to allocate arrays' )
[1116]285      !
[2528]286      IF( ln_rnf_emp ) THEN                     !==  runoffs directly provided in the precipitations  ==!
[1116]287         IF(lwp) WRITE(numout,*)
288         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations'
[2528]289         IF( ln_rnf_depth .OR. ln_rnf_tem .OR. ln_rnf_sal ) THEN
[3764]290           CALL ctl_warn( 'runoffs already included in precipitations, so runoff (T,S, depth) attributes will not be used' )
[2528]291           ln_rnf_depth = .FALSE.   ;   ln_rnf_tem = .FALSE.   ;   ln_rnf_sal = .FALSE.
292         ENDIF
[1116]293         !
[2528]294      ELSE                                      !==  runoffs read in a file : set sf_rnf structure  ==!
[1116]295         !
[2528]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         !                                          ! fill sf_rnf with the namelist (sn_rnf) and control print
[1133]305         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' )
[1116]306         !
[2528]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) )
[3764]316            CALL fld_fill (sf_t_rnf, (/ sn_t_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff temperature data', 'namsbc_rnf' )
[2528]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) )
[3764]328            CALL fld_fill (sf_s_rnf, (/ sn_s_rnf /), cn_dir, 'sbc_rnf_init', 'read runoff salinity data', 'namsbc_rnf' )
[2528]329         ENDIF
330         !
[3764]331         IF( ln_rnf_depth ) THEN                    ! depth of runoffs set from a file
[2528]332            IF(lwp) WRITE(numout,*)
333            IF(lwp) WRITE(numout,*) '          runoffs depth read in a file'
[3764]334            rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname )
[3832]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
[3764]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
[2528]341            !
342            nk_rnf(:,:) = 0                               ! set the number of level over which river runoffs are applied
[3764]343            DO jj = 1, jpj
344               DO ji = 1, jpi
345                  IF( h_rnf(ji,jj) > 0._wp ) THEN
346                     jk = 2
[4368]347                     DO WHILE ( jk /= mbkt(ji,jj) .AND. gdept_0(ji,jj,jk) < h_rnf(ji,jj) ) ;  jk = jk + 1 ;  END DO
[3764]348                     nk_rnf(ji,jj) = jk
349                  ELSEIF( h_rnf(ji,jj) == -1._wp   ) THEN   ;  nk_rnf(ji,jj) = 1
350                  ELSEIF( h_rnf(ji,jj) == -999._wp ) THEN   ;  nk_rnf(ji,jj) = mbkt(ji,jj)
351                  ELSE
[3832]352                     CALL ctl_stop( 'sbc_rnf_init: runoff depth not positive, and not -999 or -1, rnf value in file fort.999'  )
353                     WRITE(999,*) 'ji, jj, h_rnf(ji,jj) :', ji, jj, h_rnf(ji,jj)
[3764]354                  ENDIF
355               END DO
356            END DO
357            DO jj = 1, jpj                                ! set the associated depth
358               DO ji = 1, jpi
[2528]359                  h_rnf(ji,jj) = 0._wp
[3764]360                  DO jk = 1, nk_rnf(ji,jj)
361                     h_rnf(ji,jj) = h_rnf(ji,jj) + fse3t(ji,jj,jk)
[2528]362                  END DO
363               END DO
364            END DO
[3764]365         ELSE                                       ! runoffs applied at the surface
366            nk_rnf(:,:) = 1
[2528]367            h_rnf (:,:) = fse3t(:,:,1)
[3764]368         ENDIF
369         !
[1116]370      ENDIF
[2528]371      !
[3294]372      rnf(:,:) =  0._wp                         ! runoff initialisation
[2528]373      rnf_tsc(:,:,:) = 0._wp                    ! runoffs temperature & salinty contents initilisation
374      !
[1116]375      !                                   ! ========================
376      !                                   !   River mouth vicinity
377      !                                   ! ========================
378      !
379      IF( ln_rnf_mouth ) THEN                   ! Specific treatment in vicinity of river mouths :
380         !                                      !    - Increase Kz in surface layers ( rn_hrnf > 0 )
381         !                                      !    - set to zero SSS damping (ln_ssr=T)
382         !                                      !    - mixed upstream-centered (ln_traadv_cen2=T)
383         !
[2528]384         IF ( ln_rnf_depth )   CALL ctl_warn( 'sbc_rnf_init: increased mixing turned on but effects may already',   &
[3764]385            &                                              'be spread through depth by ln_rnf_depth'               )
[2528]386         !
387         nkrnf = 0                                  ! Number of level over which Kz increase
388         IF( rn_hrnf > 0._wp ) THEN
[1116]389            nkrnf = 2
[4292]390            DO WHILE( nkrnf /= jpkm1 .AND. gdepw_1d(nkrnf+1) < rn_hrnf )   ;   nkrnf = nkrnf + 1   ;   END DO
[3625]391            IF( ln_sco )   CALL ctl_warn( 'sbc_rnf: number of levels over which Kz is increased is computed for zco...' )
[1116]392         ENDIF
393         IF(lwp) WRITE(numout,*)
394         IF(lwp) WRITE(numout,*) '          Specific treatment used in vicinity of river mouths :'
395         IF(lwp) WRITE(numout,*) '             - Increase Kz in surface layers (if rn_hrnf > 0 )'
396         IF(lwp) WRITE(numout,*) '               by ', rn_avt_rnf,' m2/s  over ', nkrnf, ' w-levels'
397         IF(lwp) WRITE(numout,*) '             - set to zero SSS damping       (if ln_ssr=T)'
398         IF(lwp) WRITE(numout,*) '             - mixed upstream-centered       (if ln_traadv_cen2=T)'
399         !
400         CALL rnf_mouth                             ! set river mouth mask
401         !
402      ELSE                                      ! No treatment at river mouths
403         IF(lwp) WRITE(numout,*)
404         IF(lwp) WRITE(numout,*) '          No specific treatment at river mouths'
[3764]405         rnfmsk  (:,:) = 0._wp
[2528]406         rnfmsk_z(:)   = 0._wp
[1116]407         nkrnf = 0
408      ENDIF
[3625]409      !
[1116]410   END SUBROUTINE sbc_rnf_init
411
412
[888]413   SUBROUTINE rnf_mouth
414      !!----------------------------------------------------------------------
415      !!                  ***  ROUTINE rnf_mouth  ***
[3764]416      !!
[888]417      !! ** Purpose :   define the river mouths mask
418      !!
419      !! ** Method  :   read the river mouth mask (=0/1) in the river runoff
[3764]420      !!                climatological file. Defined a given vertical structure.
421      !!                CAUTION, the vertical structure is hard coded on the
[888]422      !!                first 5 levels.
423      !!                This fields can be used to:
[3764]424      !!                 - set an upstream advection scheme
[1116]425      !!                   (ln_rnf_mouth=T and ln_traadv_cen2=T)
[3764]426      !!                 - increase vertical on the top nn_krnf vertical levels
[888]427      !!                   at river runoff input grid point (nn_krnf>=2, see step.F90)
428      !!                 - set to zero SSS restoring flux at river mouth grid points
429      !!
430      !! ** Action  :   rnfmsk   set to 1 at river runoff input, 0 elsewhere
431      !!                rnfmsk_z vertical structure
432      !!----------------------------------------------------------------------
[2784]433      INTEGER            ::   inum        ! temporary integers
434      CHARACTER(len=140) ::   cl_rnfile   ! runoff file name
[888]435      !!----------------------------------------------------------------------
[3764]436      !
[888]437      IF(lwp) WRITE(numout,*)
438      IF(lwp) WRITE(numout,*) 'rnf_mouth : river mouth mask'
439      IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
[3625]440      !
[1133]441      cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf%clname )
442      IF( .NOT. sn_cnf%ln_clim ) THEN   ;   WRITE(cl_rnfile, '(a,"_y",i4)' ) TRIM( cl_rnfile ), nyear    ! add year
443         IF( sn_cnf%cltype == 'monthly' )   WRITE(cl_rnfile, '(a,"m",i2)'  ) TRIM( cl_rnfile ), nmonth   ! add month
444      ENDIF
[3625]445      !
[888]446      ! horizontal mask (read in NetCDF file)
447      CALL iom_open ( cl_rnfile, inum )                           ! open file
448      CALL iom_get  ( inum, jpdom_data, sn_cnf%clvar, rnfmsk )    ! read the river mouth array
449      CALL iom_close( inum )                                      ! close file
[3625]450      !
[3632]451      IF( nn_closea == 1 )   CALL clo_rnf( rnfmsk )               ! closed sea inflow set as ruver mouth
[3625]452      !
[3764]453      rnfmsk_z(:)   = 0._wp                                       ! vertical structure
[888]454      rnfmsk_z(1)   = 1.0
455      rnfmsk_z(2)   = 1.0                                         ! **********
456      rnfmsk_z(3)   = 0.5                                         ! HARD CODED on the 5 first levels
457      rnfmsk_z(4)   = 0.25                                        ! **********
458      rnfmsk_z(5)   = 0.125
[3764]459      !
[888]460   END SUBROUTINE rnf_mouth
[3764]461
[888]462   !!======================================================================
463END MODULE sbcrnf
Note: See TracBrowser for help on using the repository browser.