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

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

Correct incompatibilities with Agrif (easier part), see ticket #133

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