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.
sbcfwb.F90 in branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SBC/sbcfwb.F90 @ 11101

Last change on this file since 11101 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 12.1 KB
Line 
1MODULE sbcfwb
2   !!======================================================================
3   !!                       ***  MODULE  sbcfwb  ***
4   !! Ocean fluxes   : domain averaged freshwater budget
5   !!======================================================================
6   !! History :  OPA  ! 2001-02  (E. Durand)  Original code
7   !!   NEMO     1.0  ! 2002-06  (G. Madec)  F90: Free form and module
8   !!            3.0  ! 2006-08  (G. Madec)  Surface module
9   !!            3.2  ! 2009-07  (C. Talandier) emp mean s spread over erp area
10   !!            3.6  ! 2014-11  (P. Mathiot  ) add ice shelf melting
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   sbc_fwb      : freshwater budget for global ocean configurations
15   !!                  in free surface and forced mode
16   !!----------------------------------------------------------------------
17   USE oce             ! ocean dynamics and tracers
18   USE dom_oce         ! ocean space and time domain
19   USE sbc_oce         ! surface ocean boundary condition
20   USE phycst          ! physical constants
21   USE sbcrnf          ! ocean runoffs
22   USE sbcisf          ! ice shelf melting contribution
23   USE sbcssr          ! SS damping terms
24   USE in_out_manager  ! I/O manager
25   USE lib_mpp         ! distribued memory computing library
26   USE wrk_nemo        ! work arrays
27   USE timing          ! Timing
28   USE lbclnk          ! ocean lateral boundary conditions
29   USE lib_fortran
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   sbc_fwb    ! routine called by step
35
36   REAL(wp) ::   a_fwb_b   ! annual domain averaged freshwater budget
37   REAL(wp) ::   a_fwb     ! for 2 year before (_b) and before year.
38   REAL(wp) ::   fwfold    ! fwfold to be suppressed
39   REAL(wp) ::   area      ! global mean ocean surface (interior domain)
40
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43#  include "vectopt_loop_substitute.h90"
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
46   !! $Id$
47   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE sbc_fwb( kt, kn_fwb, kn_fsbc )
52      !!---------------------------------------------------------------------
53      !!                  ***  ROUTINE sbc_fwb  ***
54      !!
55      !! ** Purpose :   Control the mean sea surface drift
56      !!
57      !! ** Method  :   several ways  depending on kn_fwb
58      !!                =0 no control
59      !!                =1 global mean of emp set to zero at each nn_fsbc time step
60      !!                =2 annual global mean corrected from previous year
61      !!                =3 global mean of emp set to zero at each nn_fsbc time step
62      !!                   & spread out over erp area depending its sign
63      !! Note: if sea ice is embedded it is taken into account when computing the budget
64      !!----------------------------------------------------------------------
65      INTEGER, INTENT( in ) ::   kt       ! ocean time-step index
66      INTEGER, INTENT( in ) ::   kn_fsbc  !
67      INTEGER, INTENT( in ) ::   kn_fwb   ! ocean time-step index
68      !
69      INTEGER  ::   inum, ikty, iyear     ! local integers
70      REAL(wp) ::   z_fwf, z_fwf_nsrf, zsum_fwf, zsum_erp                ! local scalars
71      REAL(wp) ::   zsurf_neg, zsurf_pos, zsurf_tospread, zcoef          !   -      -
72      REAL(wp), POINTER, DIMENSION(:,:) ::   ztmsk_neg, ztmsk_pos, z_wgt ! 2D workspaces
73      REAL(wp), POINTER, DIMENSION(:,:) ::   ztmsk_tospread, zerp_cor    !   -      -
74      !!----------------------------------------------------------------------
75      !
76      IF( nn_timing == 1 )  CALL timing_start('sbc_fwb')
77      !
78      CALL wrk_alloc( jpi,jpj, ztmsk_neg, ztmsk_pos, ztmsk_tospread, z_wgt, zerp_cor )
79      !
80      IF( kt == nit000 ) THEN
81         IF(lwp) THEN
82            WRITE(numout,*)
83            WRITE(numout,*) 'sbc_fwb : FreshWater Budget correction'
84            WRITE(numout,*) '~~~~~~~'
85            IF( kn_fwb == 1 )   WRITE(numout,*) '          instantaneously set to zero'
86            IF( kn_fwb == 2 )   WRITE(numout,*) '          adjusted from previous year budget'
87            IF( kn_fwb == 3 )   WRITE(numout,*) '          fwf set to zero and spread out over erp area'
88            IF(lflush) CALL flush(numout)
89         ENDIF
90         !
91         IF( kn_fwb == 3 .AND. nn_sssr /= 2 )   CALL ctl_stop( 'sbc_fwb: nn_fwb = 3 requires nn_sssr = 2, we stop ' )
92         IF( kn_fwb == 3 .AND. ln_isfcav    )   CALL ctl_stop( 'sbc_fwb: nn_fwb = 3 with ln_isfcav = .TRUE. not working, we stop ' )
93         !
94         area = glob_sum( e1e2t(:,:) * tmask(:,:,1))           ! interior global domain surface
95         ! isf cavities are excluded because it can feedback to the melting with generation of inhibition of plumes
96         ! and in case of no melt, it can generate HSSW.
97         !
98#if ! defined key_lim2 &&  ! defined key_lim3 && ! defined key_cice
99         snwice_mass_b(:,:) = 0.e0               ! no sea-ice model is being used : no snow+ice mass
100         snwice_mass  (:,:) = 0.e0
101#endif
102         !
103      ENDIF
104     
105
106      SELECT CASE ( kn_fwb )
107      !
108      CASE ( 1 )                             !==  global mean fwf set to zero  ==!
109         !
110         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN
111            z_fwf = glob_sum( e1e2t(:,:) * ( emp(:,:) - rnf(:,:) + fwfisf(:,:) - snwice_fmass(:,:) ) ) / area   ! sum over the global domain
112            zcoef = z_fwf * rcp
113            emp(:,:) = emp(:,:) - z_fwf              * tmask(:,:,1)
114            qns(:,:) = qns(:,:) + zcoef * sst_m(:,:) * tmask(:,:,1) ! account for change to the heat budget due to fw correction
115         ENDIF
116         !
117      CASE ( 2 )                             !==  fwf budget adjusted from the previous year  ==!
118         !
119         IF( kt == nit000 ) THEN                      ! initialisation
120            !                                         ! Read the corrective factor on precipitations (fwfold)
121            CALL ctl_opn( inum, 'EMPave_old.dat', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
122            READ ( inum, "(24X,I8,2ES24.16)" ) iyear, a_fwb_b, a_fwb
123            CLOSE( inum )
124            fwfold = a_fwb                            ! current year freshwater budget correction
125            !                                         ! estimate from the previous year budget
126            IF(lwp)WRITE(numout,*)
127            IF(lwp)WRITE(numout,*)'sbc_fwb : year = ',iyear  , ' freshwater budget correction = ', fwfold
128            IF(lwp)WRITE(numout,*)'          year = ',iyear-1, ' freshwater budget read       = ', a_fwb
129            IF(lwp)WRITE(numout,*)'          year = ',iyear-2, ' freshwater budget read       = ', a_fwb_b
130            IF(lwp .AND. lflush) CALL flush(numout)
131         ENDIF   
132         !                                         ! Update fwfold if new year start
133         ikty = 365 * 86400 / rdttra(1)    !!bug  use of 365 days leap year or 360d year !!!!!!!
134         IF( MOD( kt, ikty ) == 0 ) THEN
135            a_fwb_b = a_fwb                           ! mean sea level taking into account the ice+snow
136                                                      ! sum over the global domain
137            a_fwb   = glob_sum( e1e2t(:,:) * ( sshn(:,:) + snwice_mass(:,:) * r1_rau0 ) )
138            a_fwb   = a_fwb * 1.e+3 / ( area * rday * 365. )     ! convert in Kg/m3/s = mm/s
139!!gm        !                                                      !!bug 365d year
140            fwfold =  a_fwb                           ! current year freshwater budget correction
141            !                                         ! estimate from the previous year budget
142         ENDIF
143         !
144         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN         ! correct the freshwater fluxes
145            zcoef = fwfold * rcp
146            emp(:,:) = emp(:,:) + fwfold             * tmask(:,:,1)
147            qns(:,:) = qns(:,:) - zcoef * sst_m(:,:) * tmask(:,:,1) ! account for change to the heat budget due to fw correction
148         ENDIF
149         !
150         IF( kt == nitend .AND. lwp ) THEN            ! save fwfold value in a file
151            CALL ctl_opn( inum, 'EMPave.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea )
152            WRITE( inum, "(24X,I8,2ES24.16)" ) nyear, a_fwb_b, a_fwb
153            CLOSE( inum )
154         ENDIF
155         !
156      CASE ( 3 )                             !==  global fwf set to zero and spread out over erp area  ==!
157         !
158         IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN
159            ztmsk_pos(:,:) = tmask_i(:,:)                      ! Select <0 and >0 area of erp
160            WHERE( erp < 0._wp )   ztmsk_pos = 0._wp
161            ztmsk_neg(:,:) = tmask_i(:,:) - ztmsk_pos(:,:)
162            !
163            zsurf_neg = glob_sum( e1e2t(:,:)*ztmsk_neg(:,:) )  ! Area filled by <0 and >0 erp
164            zsurf_pos = glob_sum( e1e2t(:,:)*ztmsk_pos(:,:) )
165            !                                                  ! fwf global mean (excluding ocean to ice/snow exchanges)
166            z_fwf     = glob_sum( e1e2t(:,:) * ( emp(:,:) - rnf(:,:) + fwfisf(:,:) - snwice_fmass(:,:) ) ) / area
167            !           
168            IF( z_fwf < 0._wp ) THEN         ! spread out over >0 erp area to increase evaporation
169                zsurf_tospread      = zsurf_pos
170                ztmsk_tospread(:,:) = ztmsk_pos(:,:)
171            ELSE                             ! spread out over <0 erp area to increase precipitation
172                zsurf_tospread      = zsurf_neg
173                ztmsk_tospread(:,:) = ztmsk_neg(:,:)
174            ENDIF
175            !
176            zsum_fwf   = glob_sum( e1e2t(:,:) * z_fwf )         ! fwf global mean over <0 or >0 erp area
177!!gm :  zsum_fwf   = z_fwf * area   ???  it is right?  I think so....
178            z_fwf_nsrf =  zsum_fwf / ( zsurf_tospread + rsmall )
179            !                                                  ! weight to respect erp field 2D structure
180            zsum_erp   = glob_sum( ztmsk_tospread(:,:) * erp(:,:) * e1e2t(:,:) )
181            z_wgt(:,:) = ztmsk_tospread(:,:) * erp(:,:) / ( zsum_erp + rsmall )
182            !                                                  ! final correction term to apply
183            zerp_cor(:,:) = -1. * z_fwf_nsrf * zsurf_tospread * z_wgt(:,:)
184            !
185!!gm   ===>>>>  lbc_lnk should be useless as all the computation is done over the whole domain !
186            CALL lbc_lnk( zerp_cor, 'T', 1. )
187            !
188            emp(:,:) = emp(:,:) + zerp_cor(:,:)
189            qns(:,:) = qns(:,:) - zerp_cor(:,:) * rcp * sst_m(:,:)  ! account for change to the heat budget due to fw correction
190            erp(:,:) = erp(:,:) + zerp_cor(:,:)
191            !
192            IF( nprint > 3 .AND. lwp ) THEN                   ! control print
193               IF( z_fwf < 0._wp ) THEN
194                  WRITE(numout,*)'   z_fwf < 0'
195                  WRITE(numout,*)'   SUM(erp+)     = ', SUM( ztmsk_tospread(:,:)*erp(:,:)*e1e2t(:,:) )*1.e-9,' Sv'
196               ELSE
197                  WRITE(numout,*)'   z_fwf >= 0'
198                  WRITE(numout,*)'   SUM(erp-)     = ', SUM( ztmsk_tospread(:,:)*erp(:,:)*e1e2t(:,:) )*1.e-9,' Sv'
199               ENDIF
200               WRITE(numout,*)'   SUM(empG)     = ', SUM( z_fwf*e1e2t(:,:) )*1.e-9,' Sv'
201               WRITE(numout,*)'   z_fwf         = ', z_fwf      ,' Kg/m2/s'
202               WRITE(numout,*)'   z_fwf_nsrf    = ', z_fwf_nsrf ,' Kg/m2/s'
203               WRITE(numout,*)'   MIN(zerp_cor) = ', MINVAL(zerp_cor) 
204               WRITE(numout,*)'   MAX(zerp_cor) = ', MAXVAL(zerp_cor) 
205               IF(lflush) CALL flush(numout)
206            ENDIF
207         ENDIF
208         !
209      CASE DEFAULT                           !==  you should never be there  ==!
210         CALL ctl_stop( 'sbc_fwb : wrong nn_fwb value for the FreshWater Budget correction, choose either 1, 2 or 3' )
211         !
212      END SELECT
213      !
214      CALL wrk_dealloc( jpi,jpj, ztmsk_neg, ztmsk_pos, ztmsk_tospread, z_wgt, zerp_cor )
215      !
216      IF( nn_timing == 1 )  CALL timing_stop('sbc_fwb')
217      !
218   END SUBROUTINE sbc_fwb
219
220   !!======================================================================
221END MODULE sbcfwb
Note: See TracBrowser for help on using the repository browser.