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

source: trunk/NEMO/OPA_SRC/SBC/sbcrnf.F90 @ 1200

Last change on this file since 1200 was 1200, checked in by rblod, 16 years ago

Adapt Agrif to the new SBC and correct several bugs for agrif (restart writing and reading), see ticket #133
Note : this fix does not work yet on NEC computerq (sxf90/360)

  • Property svn:keywords set to Id
File size: 12.4 KB
Line 
1MODULE sbcrnf
2   !!======================================================================
3   !!                       ***  MODULE  sbcrnf  ***
4   !! Ocean forcing:  river runoff
5   !!=====================================================================
6   !! History :       !  00-11  (R. Hordoir, E. Durand)  NetCDF FORMAT
7   !!            8.5  !  02-09  (G. Madec)  F90: Free form and module
8   !!            9.0  !  06-07  (G. Madec)  Surface module
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   sbc_rnf      : monthly runoffs read in a NetCDF file
13   !!   sbc_rnf_init : runoffs initialisation
14   !!   rnf_mouth    : set river mouth mask
15   !!----------------------------------------------------------------------
16   USE dom_oce         ! ocean space and time domain
17   USE phycst          ! physical constants
18   USE dom_oce         ! ocean domain variables
19   USE sbc_oce         ! surface boundary condition variables
20   USE fldread         ! ???
21   USE in_out_manager  ! I/O manager
22   USE daymod          ! calendar
23   USE iom             ! I/O module
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC sbc_rnf          ! routine call in step module
29
30   !! * namsbc_rnf namelist
31   CHARACTER(len=100), PUBLIC ::   cn_dir       = './'    !: Root directory for location of ssr files
32   LOGICAL           , PUBLIC ::   ln_rnf_emp   = .false. !: runoffs into a file to be read or already into precipitation
33   TYPE(FLD_N)       , PUBLIC ::   sn_rnf                 !: information about the runoff file to be read
34   TYPE(FLD_N)       , PUBLIC ::   sn_cnf                 !: information about the runoff mouth file to be read
35   LOGICAL           , PUBLIC ::   ln_rnf_mouth = .false. !: specific treatment in mouths vicinity
36   REAL(wp)          , PUBLIC ::   rn_hrnf      = 0.e0    !: runoffs, depth over which enhanced vertical mixing is used
37   REAL(wp)          , PUBLIC ::   rn_avt_rnf   = 0.e0    !: runoffs, value of the additional vertical mixing coef. [m2/s]
38
39   INTEGER , PUBLIC                     ::   nkrnf = 0   !: number of levels over which Kz is increased at river mouths
40   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rnfmsk      !: river mouth mask (hori.)
41   REAL(wp), PUBLIC, DIMENSION(jpk)     ::   rnfmsk_z    !: river mouth mask (vert.)
42
43   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_rnf   ! structure of input SST (file information, fields read)
44
45   !!----------------------------------------------------------------------
46   !!   OPA 9.0 , LOCEAN-IPSL (2006)
47   !! $Id$
48   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50
51CONTAINS
52
53   SUBROUTINE sbc_rnf( kt )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE sbc_rnf  ***
56      !!       
57      !! ** Purpose :   Introduce a climatological run off forcing
58      !!
59      !! ** Method  :   Set each river mouth with a monthly climatology
60      !!                provided from different data.
61      !!                CAUTION : upward water flux, runoff forced to be < 0
62      !!
63      !! ** Action  :   runoff updated runoff field at time-step kt
64      !!----------------------------------------------------------------------
65      INTEGER, INTENT(in) ::   kt          ! ocean time step
66      !
67      INTEGER  ::   ji, jj   ! dummy loop indices
68      !!----------------------------------------------------------------------
69      !                                   
70      IF( kt == nit000 )   CALL sbc_rnf_init
71
72      !                                                   !-------------------!
73      IF( .NOT. ln_rnf_emp ) THEN                         !   Update runoff   !
74         !                                                !-------------------!
75         !
76         CALL fld_read( kt, nn_fsbc, sf_rnf )   ! Read Runoffs data and provides it
77         !                                      ! at the current time-step
78
79         ! Runoff reduction only associated to the ORCA2_LIM configuration
80         ! when reading the NetCDF file runoff_1m_nomask.nc
81         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 )   THEN
82            DO jj = 1, jpj
83               DO ji = 1, jpi
84                  IF( gphit(ji,jj) > 40 .AND. gphit(ji,jj) < 65 )   sf_rnf(1)%fnow(ji,jj) = 0.85 * sf_rnf(1)%fnow(ji,jj)
85               END DO
86            END DO
87         ENDIF
88
89         ! C a u t i o n : runoff is negative and in kg/m2/s
90
91         emp (:,:) = emp (:,:) - ABS( sf_rnf(1)%fnow(:,:) )
92         emps(:,:) = emps(:,:) - ABS( sf_rnf(1)%fnow(:,:) )
93         !
94      ENDIF
95      !
96   END SUBROUTINE sbc_rnf
97
98
99   SUBROUTINE sbc_rnf_init
100      !!----------------------------------------------------------------------
101      !!                  ***  ROUTINE sbc_rnf_init  ***
102      !!
103      !! ** Purpose :   Initialisation of the runoffs if (ln_rnf=T)
104      !!
105      !! ** Method  : - read the runoff namsbc_rnf namelist
106      !!
107      !! ** Action  : - read parameters
108      !!----------------------------------------------------------------------
109      INTEGER  ::   ierror   ! temporary integer
110      !!
111      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, ln_rnf_mouth,   &
112         &                 rn_hrnf, rn_avt_rnf
113      !!----------------------------------------------------------------------
114
115      !                                   ! ============
116      !                                   !   Namelist
117      !                                   ! ============
118      ! (NB: frequency positive => hours, negative => months)
119      !            !   file    ! frequency !  variable  ! time intep !  clim  ! 'yearly' or !
120      !            !   name    !  (hours)  !   name     !   (T/F)    !  (T/F) !  'monthly'  !
121      sn_rnf = FLD_N( 'runoffs',    -1.    , 'sorunoff' ,  .TRUE.    , .true. ,   'yearly'  )
122      sn_cnf = FLD_N( 'runoffs',     0.    , 'sorunoff' ,  .FALSE.   , .true. ,   'yearly'  )
123
124      !
125      REWIND ( numnam )                         ! Read Namelist namsbc_rnf
126      READ   ( numnam, namsbc_rnf )
127
128      !                                         ! Control print
129      IF(lwp) THEN
130         WRITE(numout,*)
131         WRITE(numout,*) 'sbc_rnf : runoff '
132         WRITE(numout,*) '~~~~~~~ '
133         WRITE(numout,*) '   Namelist namsbc_rnf'
134         WRITE(numout,*) '      runoff in a file to be read                ln_rnf_emp   = ', ln_rnf_emp
135         WRITE(numout,*) '      specific river mouths treatment            ln_rnf_mouth = ', ln_rnf_mouth
136         WRITE(numout,*) '      river mouth additional Kz                  rn_avt_rnf   = ', rn_avt_rnf
137         WRITE(numout,*) '      depth of river mouth additional mixing     rn_hrnf      = ', rn_hrnf
138      ENDIF
139
140      !                                   ! ==================
141      !                                   !   Type of runoff
142      !                                   ! ==================
143      !
144      IF( ln_rnf_emp ) THEN                     ! runoffs directly provided in the precipitations
145         IF(lwp) WRITE(numout,*)
146         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations'
147         !
148      ELSE                                      ! runoffs read in a file : set sf_rnf structure
149         !
150         ALLOCATE( sf_rnf(1), STAT=ierror )
151         IF( ierror > 0 ) THEN
152            CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN
153         ENDIF
154         ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) )
155         ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) )
156
157         ! fill sf_rnf with sn_rnf and control print
158         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' )
159         !
160      ENDIF
161
162      !                                   ! ========================
163      !                                   !   River mouth vicinity
164      !                                   ! ========================
165      !
166      IF( ln_rnf_mouth ) THEN                   ! Specific treatment in vicinity of river mouths :
167         !                                      !    - Increase Kz in surface layers ( rn_hrnf > 0 )
168         !                                      !    - set to zero SSS damping (ln_ssr=T)
169         !                                      !    - mixed upstream-centered (ln_traadv_cen2=T)
170         !
171         !                                          ! Number of level over which Kz increase
172         nkrnf = 0
173         IF( rn_hrnf > 0.e0 ) THEN
174            nkrnf = 2
175            DO WHILE( nkrnf /= jpkm1 .AND. gdepw_0(nkrnf+1) < rn_hrnf )   ;   nkrnf = nkrnf + 1   ;   END DO
176            IF( ln_sco )   &
177               CALL ctl_warn( 'sbc_rnf: number of levels over which Kz is increased is computed for zco...' )
178         ENDIF
179         IF(lwp) WRITE(numout,*)
180         IF(lwp) WRITE(numout,*) '          Specific treatment used in vicinity of river mouths :'
181         IF(lwp) WRITE(numout,*) '             - Increase Kz in surface layers (if rn_hrnf > 0 )'
182         IF(lwp) WRITE(numout,*) '               by ', rn_avt_rnf,' m2/s  over ', nkrnf, ' w-levels'
183         IF(lwp) WRITE(numout,*) '             - set to zero SSS damping       (if ln_ssr=T)'
184         IF(lwp) WRITE(numout,*) '             - mixed upstream-centered       (if ln_traadv_cen2=T)'
185         !
186         CALL rnf_mouth                             ! set river mouth mask
187         !
188      ELSE                                      ! No treatment at river mouths
189         IF(lwp) WRITE(numout,*)
190         IF(lwp) WRITE(numout,*) '          No specific treatment at river mouths'
191         rnfmsk  (:,:) = 0.e0 
192         rnfmsk_z(:)   = 0.e0
193         nkrnf = 0
194      ENDIF
195
196   END SUBROUTINE sbc_rnf_init
197
198
199   SUBROUTINE rnf_mouth
200      !!----------------------------------------------------------------------
201      !!                  ***  ROUTINE rnf_mouth  ***
202      !!       
203      !! ** Purpose :   define the river mouths mask
204      !!
205      !! ** Method  :   read the river mouth mask (=0/1) in the river runoff
206      !!                climatological file. Defined a given vertical structure.
207      !!                CAUTION, the vertical structure is hard coded on the
208      !!                first 5 levels.
209      !!                This fields can be used to:
210      !!                 - set an upstream advection scheme 
211      !!                   (ln_rnf_mouth=T and ln_traadv_cen2=T)
212      !!                 - increase vertical on the top nn_krnf vertical levels
213      !!                   at river runoff input grid point (nn_krnf>=2, see step.F90)
214      !!                 - set to zero SSS restoring flux at river mouth grid points
215      !!
216      !! ** Action  :   rnfmsk   set to 1 at river runoff input, 0 elsewhere
217      !!                rnfmsk_z vertical structure
218      !!----------------------------------------------------------------------
219      USE closea, ONLY :    nclosea, clo_rnf   ! closed sea flag, rnfmsk update routine
220      !
221      INTEGER           ::   inum        ! temporary integers
222      CHARACTER(len=32) ::   cl_rnfile   ! runoff file name
223      !!----------------------------------------------------------------------
224      !
225      IF(lwp) WRITE(numout,*)
226      IF(lwp) WRITE(numout,*) 'rnf_mouth : river mouth mask'
227      IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
228
229      cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf%clname )
230      IF( .NOT. sn_cnf%ln_clim ) THEN   ;   WRITE(cl_rnfile, '(a,"_y",i4)' ) TRIM( cl_rnfile ), nyear    ! add year
231         IF( sn_cnf%cltype == 'monthly' )   WRITE(cl_rnfile, '(a,"m",i2)'  ) TRIM( cl_rnfile ), nmonth   ! add month
232      ENDIF
233 
234      ! horizontal mask (read in NetCDF file)
235      CALL iom_open ( cl_rnfile, inum )                           ! open file
236      CALL iom_get  ( inum, jpdom_data, sn_cnf%clvar, rnfmsk )    ! read the river mouth array
237      CALL iom_close( inum )                                      ! close file
238     
239      IF( nclosea == 1 )    CALL clo_rnf( rnfmsk )                ! closed sea inflow set as ruver mouth
240
241      rnfmsk_z(:)   = 0.e0                                        ! vertical structure
242      rnfmsk_z(1)   = 1.0
243      rnfmsk_z(2)   = 1.0                                         ! **********
244      rnfmsk_z(3)   = 0.5                                         ! HARD CODED on the 5 first levels
245      rnfmsk_z(4)   = 0.25                                        ! **********
246      rnfmsk_z(5)   = 0.125
247      !         
248   END SUBROUTINE rnf_mouth
249   
250   !!======================================================================
251END MODULE sbcrnf
Note: See TracBrowser for help on using the repository browser.