MODULE sbcfwb !!====================================================================== !! *** MODULE sbcfwb *** !! Ocean fluxes : domain averaged freshwater budget !!====================================================================== !! History : 8.2 ! 01-02 (E. Durand) Original code !! 8.5 ! 02-06 (G. Madec) F90: Free form and module !! 9.0 ! 06-08 (G. Madec) Surface module !! 9.2 ! 09-07 (C. Talandier) emp mean s spread over erp area !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! sbc_fwb : freshwater budget for global ocean configurations !! in free surface and forced mode !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers USE dom_oce ! ocean space and time domain USE sbc_oce ! surface ocean boundary condition USE phycst ! physical constants USE sbcrnf ! ocean runoffs USE sbcssr ! SS damping terms USE in_out_manager ! I/O manager USE lib_mpp ! distribued memory computing library USE lbclnk ! ocean lateral boundary conditions IMPLICIT NONE PRIVATE PUBLIC sbc_fwb ! routine called by step REAL(wp) :: a_fwb_b ! annual domain averaged freshwater budget REAL(wp) :: a_fwb ! for 2 year before (_b) and before year. REAL(wp) :: empold ! empold to be suppressed REAL(wp) :: area ! global mean ocean surface (interior domain) REAL(wp), DIMENSION(jpi,jpj) :: e1e2_i ! area of the interior domain (e1t*e2t*tmask_i) !! * Substitutions # include "domzgr_substitute.h90" # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2006) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE sbc_fwb( kt, kn_fwb, kn_fsbc ) !!--------------------------------------------------------------------- !! *** ROUTINE sbc_fwb *** !! !! ** Purpose : Control the mean sea surface drift !! !! ** Method : several ways depending on kn_fwb !! =0 no control !! =1 global mean of emp set to zero at each nn_fsbc time step !! =2 annual global mean corrected from previous year !! =3 global mean of emp set to zero at each nn_fsbc time step !! & spread out over erp area depending its sign !!---------------------------------------------------------------------- INTEGER, INTENT( in ) :: kt ! ocean time-step index INTEGER, INTENT( in ) :: kn_fsbc ! INTEGER, INTENT( in ) :: kn_fwb ! ocean time-step index !! INTEGER :: inum ! temporary logical unit INTEGER :: ikty, iyear ! REAL(wp) :: z_emp, z_emp_nsrf ! temporary scalars REAL(wp) :: zsurf_neg, zsurf_pos, zsurf_tospread REAL(wp), DIMENSION(jpi,jpj) :: ztmsk_neg, ztmsk_pos, ztmsk_tospread REAL(wp), DIMENSION(jpi,jpj) :: z_wgt, zerp_cor !!---------------------------------------------------------------------- ! IF( kt == nit000 ) THEN ! IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'sbc_fwb : FreshWater Budget correction' WRITE(numout,*) '~~~~~~~' IF( kn_fwb == 1 ) WRITE(numout,*) ' instantaneously set to zero' IF( kn_fwb == 2 ) WRITE(numout,*) ' adjusted from previous year budget' IF( kn_fwb == 3 ) WRITE(numout,*) ' emp set to zero and spread out over erp area' ! IF( kn_fwb == 3 .AND. nn_sssr /= 2 ) & & CALL ctl_stop( 'The option nn_fwb = 3 must be associated to nn_sssr = 2 ' ) ENDIF ! e1e2_i(:,:) = e1t(:,:) * e2t(:,:) * tmask_i(:,:) area = SUM( e1e2_i(:,:) ) IF( lk_mpp ) CALL mpp_sum( area ) ! sum over the global domain ! ENDIF SELECT CASE ( kn_fwb ) ! CASE ( 0 ) WRITE(ctmp1,*)'sbc_fwb : nn_fwb = ', kn_fwb, ' is not yet associated to an option, choose either 1/2' CALL ctl_stop( ctmp1 ) ! ! CASE ( 1 ) ! global mean emp set to zero IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN z_emp = SUM( e1e2_i(:,:) * emp(:,:) ) / area IF( lk_mpp ) CALL mpp_sum( z_emp ) ! sum over the global domain emp (:,:) = emp (:,:) - z_emp emps(:,:) = emps(:,:) - z_emp ENDIF ! CASE ( 2 ) ! emp budget adjusted from the previous year ! initialisation IF( kt == nit000 ) THEN ! Read the corrective factor on precipitations (empold) CALL ctl_opn( inum, 'EMPave_old.dat', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) READ ( inum, "(24X,I8,2ES24.16)" ) iyear, a_fwb_b, a_fwb CLOSE( inum ) empold = a_fwb ! current year freshwater budget correction ! ! estimate from the previous year budget IF(lwp)WRITE(numout,*) IF(lwp)WRITE(numout,*)'sbc_fwb : year = ',iyear , ' freshwater budget correction = ', empold IF(lwp)WRITE(numout,*)' year = ',iyear-1, ' freshwater budget read = ', a_fwb IF(lwp)WRITE(numout,*)' year = ',iyear-2, ' freshwater budget read = ', a_fwb_b ENDIF ! ! Update empold if new year start ikty = 365 * 86400 / rdttra(1) !!bug use of 365 days leap year or 360d year !!!!!!! IF( MOD( kt, ikty ) == 0 ) THEN a_fwb_b = a_fwb a_fwb = SUM( e1e2_i(:,:) * sshn(:,:) ) IF( lk_mpp ) CALL mpp_sum( a_fwb ) ! sum over the global domain a_fwb = a_fwb * 1.e+3 / ( area * 86400. * 365. ) ! convert in Kg/m3/s = mm/s !!gm ! !!bug 365d year empold = a_fwb ! current year freshwater budget correction ! ! estimate from the previous year budget ENDIF ! ! correct the freshwater fluxes IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN emp (:,:) = emp (:,:) + empold emps(:,:) = emps(:,:) + empold ENDIF ! ! save empold value in a file IF( kt == nitend .AND. lwp ) THEN CALL ctl_opn( inum, 'EMPave.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea ) WRITE( inum, "(24X,I8,2ES24.16)" ) nyear, a_fwb_b, a_fwb CLOSE( inum ) ENDIF ! CASE ( 3 ) ! global emp set to zero and spread out over erp area ! IF( MOD( kt-1, kn_fsbc ) == 0 ) THEN ! Select <0 and >0 area of erp ztmsk_pos(:,:) = tmask_i(:,:) WHERE( erp < 0.e0 ) ztmsk_pos = 0.e0 ztmsk_neg(:,:) = tmask_i(:,:) - ztmsk_pos(:,:) ! Area filled by <0 and >0 erp zsurf_neg = SUM( e1e2_i(:,:)*ztmsk_neg(:,:) ) zsurf_pos = SUM( e1e2_i(:,:)*ztmsk_pos(:,:) ) ! emp global mean z_emp = SUM( e1e2_i(:,:) * emp(:,:) ) / area ! IF( lk_mpp ) CALL mpp_sum( z_emp ) IF( z_emp < 0.e0 ) THEN ! to spread out over >0 erp area to increase evaporation damping process zsurf_tospread = zsurf_pos ztmsk_tospread(:,:) = ztmsk_pos(:,:) ELSE ! to spread out over <0 erp area to increase precipitation damping process zsurf_tospread = zsurf_neg ztmsk_tospread(:,:) = ztmsk_neg(:,:) ENDIF ! emp global mean over <0 or >0 erp area z_emp_nsrf = SUM( e1e2_i(:,:) * z_emp ) / ( zsurf_tospread + rsmall ) ! weight to respect erp field 2D structure z_wgt(:,:) = ztmsk_tospread(:,:) * erp(:,:) / ( SUM( ztmsk_tospread(:,:) * erp(:,:) * e1e2_i(:,:) ) + rsmall ) ! final correction term to apply zerp_cor(:,:) = -1. * z_emp_nsrf * zsurf_tospread * z_wgt(:,:) CALL lbc_lnk( zerp_cor, 'T', 1. ) emp (:,:) = emp (:,:) + zerp_cor(:,:) emps(:,:) = emps(:,:) + zerp_cor(:,:) erp (:,:) = erp (:,:) + zerp_cor(:,:) IF( nprint == 1 .AND. lwp ) THEN IF( z_emp < 0.e0 ) THEN WRITE(numout,*)' z_emp < 0' WRITE(numout,*)' SUM(erp+) = ', SUM( ztmsk_tospread(:,:)*erp(:,:)*e1e2_i(:,:) )*1.e-3,' m3.s-1' ELSE WRITE(numout,*)' z_emp >= 0' WRITE(numout,*)' SUM(erp-) = ', SUM( ztmsk_tospread(:,:)*erp(:,:)*e1e2_i(:,:) )*1.e-3,' m3.s-1' ENDIF WRITE(numout,*)' SUM(empG) = ', SUM( z_emp*e1e2_i(:,:) )*1.e-3,' m3.s-1' WRITE(numout,*)' z_emp = ', z_emp ,' mm.s-1' WRITE(numout,*)' z_emp_nsrf = ', z_emp_nsrf ,' mm.s-1' WRITE(numout,*)' MIN(zerp_cor) = ', MINVAL(zerp_cor) WRITE(numout,*)' MAX(zerp_cor) = ', MAXVAL(zerp_cor) ENDIF ! ENDIF ! CASE DEFAULT ! you should never be there WRITE(ctmp1,*)'sbc_fwb : nn_fwb = ', kn_fwb, ' is not permitted for the FreshWater Budget correction, choose either 1/2' CALL ctl_stop( ctmp1 ) ! END SELECT ! END SUBROUTINE sbc_fwb !!====================================================================== END MODULE sbcfwb