New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
sbcrnf.F90 in branches/DEV_R1821_Rivers/NEMO/OPA_SRC/SBC – NEMO

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

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

changes to include volume flux in hdivn instead of ssha, currently not working correctly

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