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 @ 1938

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

rnf has been separated from emp and emps. Also temperature and salinity of runoff can be specified, and runoff can be added to a user specified depth

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