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/trunk/src/OCE/SBC – NEMO

source: NEMO/trunk/src/OCE/SBC/sbcrnf.F90 @ 12485

Last change on this file since 12485 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

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