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

Last change on this file since 1242 was 1242, checked in by rblod, 15 years ago

Fix runtime issues with AGRIF on NEC and add the ability to run without sea-ice on the fine grid hierarchy

  • Property svn:keywords set to Id
File size: 12.6 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      INTEGER  ::   ierror   ! temporary integer
69      !!----------------------------------------------------------------------
70      !                                   
71      IF( kt == nit000 ) THEN 
72         IF( .NOT. ln_rnf_emp ) THEN
73            ALLOCATE( sf_rnf(1), STAT=ierror )
74            IF( ierror > 0 ) THEN
75               CALL ctl_stop( 'sbc_rnf: unable to allocate sf_rnf structure' )   ;   RETURN
76            ENDIF
77            ALLOCATE( sf_rnf(1)%fnow(jpi,jpj) )
78            ALLOCATE( sf_rnf(1)%fdta(jpi,jpj,2) )
79         ENDIF
80         CALL sbc_rnf_init(sf_rnf)
81      ENDIF
82
83      !                                                   !-------------------!
84      IF( .NOT. ln_rnf_emp ) THEN                         !   Update runoff   !
85         !                                                !-------------------!
86         !
87         CALL fld_read( kt, nn_fsbc, sf_rnf )   ! Read Runoffs data and provides it
88         !                                      ! at the current time-step
89
90         ! Runoff reduction only associated to the ORCA2_LIM configuration
91         ! when reading the NetCDF file runoff_1m_nomask.nc
92         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 )   THEN
93            DO jj = 1, jpj
94               DO ji = 1, jpi
95                  IF( gphit(ji,jj) > 40 .AND. gphit(ji,jj) < 65 )   sf_rnf(1)%fnow(ji,jj) = 0.85 * sf_rnf(1)%fnow(ji,jj)
96               END DO
97            END DO
98         ENDIF
99
100         ! C a u t i o n : runoff is negative and in kg/m2/s
101
102         emp (:,:) = emp (:,:) - ABS( sf_rnf(1)%fnow(:,:) )
103         emps(:,:) = emps(:,:) - ABS( sf_rnf(1)%fnow(:,:) )
104         !
105      ENDIF
106      !
107   END SUBROUTINE sbc_rnf
108
109
110   SUBROUTINE sbc_rnf_init( sf_rnf )
111      !!----------------------------------------------------------------------
112      !!                  ***  ROUTINE sbc_rnf_init  ***
113      !!
114      !! ** Purpose :   Initialisation of the runoffs if (ln_rnf=T)
115      !!
116      !! ** Method  : - read the runoff namsbc_rnf namelist
117      !!
118      !! ** Action  : - read parameters
119      !!----------------------------------------------------------------------
120      TYPE(FLD), INTENT(inout), DIMENSION(:) :: sf_rnf   ! input data
121      !!
122      NAMELIST/namsbc_rnf/ cn_dir, ln_rnf_emp, sn_rnf, sn_cnf, ln_rnf_mouth,   &
123         &                 rn_hrnf, rn_avt_rnf
124      !!----------------------------------------------------------------------
125
126      !                                   ! ============
127      !                                   !   Namelist
128      !                                   ! ============
129      ! (NB: frequency positive => hours, negative => months)
130      !            !   file    ! frequency !  variable  ! time intep !  clim  ! 'yearly' or !
131      !            !   name    !  (hours)  !   name     !   (T/F)    !  (T/F) !  'monthly'  !
132      sn_rnf = FLD_N( 'runoffs',    -1.    , 'sorunoff' ,  .TRUE.    , .true. ,   'yearly'  )
133      sn_cnf = FLD_N( 'runoffs',     0.    , 'sorunoff' ,  .FALSE.   , .true. ,   'yearly'  )
134
135      !
136      REWIND ( numnam )                         ! Read Namelist namsbc_rnf
137      READ   ( numnam, namsbc_rnf )
138
139      !                                         ! Control print
140      IF(lwp) THEN
141         WRITE(numout,*)
142         WRITE(numout,*) 'sbc_rnf : runoff '
143         WRITE(numout,*) '~~~~~~~ '
144         WRITE(numout,*) '   Namelist namsbc_rnf'
145         WRITE(numout,*) '      runoff in a file to be read                ln_rnf_emp   = ', ln_rnf_emp
146         WRITE(numout,*) '      specific river mouths treatment            ln_rnf_mouth = ', ln_rnf_mouth
147         WRITE(numout,*) '      river mouth additional Kz                  rn_avt_rnf   = ', rn_avt_rnf
148         WRITE(numout,*) '      depth of river mouth additional mixing     rn_hrnf      = ', rn_hrnf
149      ENDIF
150
151      !                                   ! ==================
152      !                                   !   Type of runoff
153      !                                   ! ==================
154      !
155      IF( ln_rnf_emp ) THEN                     ! runoffs directly provided in the precipitations
156         IF(lwp) WRITE(numout,*)
157         IF(lwp) WRITE(numout,*) '          runoffs directly provided in the precipitations'
158         !
159      ELSE                                      ! runoffs read in a file : set sf_rnf structure
160         !
161         ! sf_rnf already allocated in main routine
162         ! fill sf_rnf with sn_rnf and control print
163         CALL fld_fill( sf_rnf, (/ sn_rnf /), cn_dir, 'sbc_rnf_init', 'read runoffs data', 'namsbc_rnf' )
164         !
165      ENDIF
166
167      !                                   ! ========================
168      !                                   !   River mouth vicinity
169      !                                   ! ========================
170      !
171      IF( ln_rnf_mouth ) THEN                   ! Specific treatment in vicinity of river mouths :
172         !                                      !    - Increase Kz in surface layers ( rn_hrnf > 0 )
173         !                                      !    - set to zero SSS damping (ln_ssr=T)
174         !                                      !    - mixed upstream-centered (ln_traadv_cen2=T)
175         !
176         !                                          ! Number of level over which Kz increase
177         nkrnf = 0
178         IF( rn_hrnf > 0.e0 ) THEN
179            nkrnf = 2
180            DO WHILE( nkrnf /= jpkm1 .AND. gdepw_0(nkrnf+1) < rn_hrnf )   ;   nkrnf = nkrnf + 1   ;   END DO
181            IF( ln_sco )   &
182               CALL ctl_warn( 'sbc_rnf: number of levels over which Kz is increased is computed for zco...' )
183         ENDIF
184         IF(lwp) WRITE(numout,*)
185         IF(lwp) WRITE(numout,*) '          Specific treatment used in vicinity of river mouths :'
186         IF(lwp) WRITE(numout,*) '             - Increase Kz in surface layers (if rn_hrnf > 0 )'
187         IF(lwp) WRITE(numout,*) '               by ', rn_avt_rnf,' m2/s  over ', nkrnf, ' w-levels'
188         IF(lwp) WRITE(numout,*) '             - set to zero SSS damping       (if ln_ssr=T)'
189         IF(lwp) WRITE(numout,*) '             - mixed upstream-centered       (if ln_traadv_cen2=T)'
190         !
191         CALL rnf_mouth                             ! set river mouth mask
192         !
193      ELSE                                      ! No treatment at river mouths
194         IF(lwp) WRITE(numout,*)
195         IF(lwp) WRITE(numout,*) '          No specific treatment at river mouths'
196         rnfmsk  (:,:) = 0.e0 
197         rnfmsk_z(:)   = 0.e0
198         nkrnf = 0
199      ENDIF
200
201   END SUBROUTINE sbc_rnf_init
202
203
204   SUBROUTINE rnf_mouth
205      !!----------------------------------------------------------------------
206      !!                  ***  ROUTINE rnf_mouth  ***
207      !!       
208      !! ** Purpose :   define the river mouths mask
209      !!
210      !! ** Method  :   read the river mouth mask (=0/1) in the river runoff
211      !!                climatological file. Defined a given vertical structure.
212      !!                CAUTION, the vertical structure is hard coded on the
213      !!                first 5 levels.
214      !!                This fields can be used to:
215      !!                 - set an upstream advection scheme 
216      !!                   (ln_rnf_mouth=T and ln_traadv_cen2=T)
217      !!                 - increase vertical on the top nn_krnf vertical levels
218      !!                   at river runoff input grid point (nn_krnf>=2, see step.F90)
219      !!                 - set to zero SSS restoring flux at river mouth grid points
220      !!
221      !! ** Action  :   rnfmsk   set to 1 at river runoff input, 0 elsewhere
222      !!                rnfmsk_z vertical structure
223      !!----------------------------------------------------------------------
224      USE closea, ONLY :    nclosea, clo_rnf   ! closed sea flag, rnfmsk update routine
225      !
226      INTEGER           ::   inum        ! temporary integers
227      CHARACTER(len=32) ::   cl_rnfile   ! runoff file name
228      !!----------------------------------------------------------------------
229      !
230      IF(lwp) WRITE(numout,*)
231      IF(lwp) WRITE(numout,*) 'rnf_mouth : river mouth mask'
232      IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
233
234      cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf%clname )
235      IF( .NOT. sn_cnf%ln_clim ) THEN   ;   WRITE(cl_rnfile, '(a,"_y",i4)' ) TRIM( cl_rnfile ), nyear    ! add year
236         IF( sn_cnf%cltype == 'monthly' )   WRITE(cl_rnfile, '(a,"m",i2)'  ) TRIM( cl_rnfile ), nmonth   ! add month
237      ENDIF
238 
239      ! horizontal mask (read in NetCDF file)
240      CALL iom_open ( cl_rnfile, inum )                           ! open file
241      CALL iom_get  ( inum, jpdom_data, sn_cnf%clvar, rnfmsk )    ! read the river mouth array
242      CALL iom_close( inum )                                      ! close file
243     
244      IF( nclosea == 1 )    CALL clo_rnf( rnfmsk )                ! closed sea inflow set as ruver mouth
245
246      rnfmsk_z(:)   = 0.e0                                        ! vertical structure
247      rnfmsk_z(1)   = 1.0
248      rnfmsk_z(2)   = 1.0                                         ! **********
249      rnfmsk_z(3)   = 0.5                                         ! HARD CODED on the 5 first levels
250      rnfmsk_z(4)   = 0.25                                        ! **********
251      rnfmsk_z(5)   = 0.125
252      !         
253   END SUBROUTINE rnf_mouth
254   
255   !!======================================================================
256END MODULE sbcrnf
Note: See TracBrowser for help on using the repository browser.