MODULE sbcmod !!====================================================================== !! *** MODULE sbcmod *** !! Surface module : provide to the ocean its surface boundary condition !!====================================================================== !! History : 3.0 ! 2006-07 (G. Madec) Original code !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! sbc_init : read namsbc namelist !! sbc : surface ocean momentum, heat and freshwater boundary conditions !!---------------------------------------------------------------------- USE oce ! ocean dynamics and tracers USE dom_oce ! ocean space and time domain USE daymod ! calendar USE phycst ! physical constants USE ice_oce ! sea-ice model : LIM USE sbc_oce ! Surface boundary condition: ocean fields USE sbcssm ! surface boundary condition: sea-surface mean variables USE sbcana ! surface boundary condition: analytical formulation USE sbcflx ! surface boundary condition: flux formulation USE sbcblk_clio ! surface boundary condition: bulk formulation : CLIO USE sbcblk_core ! surface boundary condition: bulk formulation : CORE USE sbcice_if ! surface boundary condition: ice-if sea-ice model USE sbcice_lim ! surface boundary condition: LIM 3.0 sea-ice model USE sbcice_lim_2 ! surface boundary condition: LIM 2.0 sea-ice model USE sbccpl ! surface boundary condition: coupled florulation USE sbcssr ! surface boundary condition: sea surface restoring USE sbcrnf ! surface boundary condition: runoffs USE sbcfwb ! surface boundary condition: freshwater budget USE closea ! closed sea USE prtctl ! Print control (prt_ctl routine) USE restart ! ocean restart USE iom USE in_out_manager ! I/O manager IMPLICIT NONE PRIVATE PUBLIC sbc ! routine called by step.F90 !! * namsbc namelist (public variables) LOGICAL , PUBLIC :: ln_ana = .FALSE. !: analytical boundary condition flag LOGICAL , PUBLIC :: ln_flx = .FALSE. !: flux formulation LOGICAL , PUBLIC :: ln_blk_clio = .FALSE. !: CLIO bulk formulation LOGICAL , PUBLIC :: ln_blk_core = .FALSE. !: CORE bulk formulation LOGICAL , PUBLIC :: ln_cpl = .FALSE. !: coupled formulation (overwritten by key_sbc_coupled ) LOGICAL , PUBLIC :: ln_dm2dc = .FALSE. !: Daily mean to Diurnal Cycle short wave (qsr) LOGICAL , PUBLIC :: ln_rnf = .FALSE. !: runoffs / runoff mouths LOGICAL , PUBLIC :: ln_ssr = .FALSE. !: Sea Surface restoring on SST and/or SSS INTEGER , PUBLIC :: nn_ice = 0 !: flag on ice in the surface boundary condition (=0/1/2) INTEGER , PUBLIC :: nn_fwb = 0 !: type of FreshWater Budget control (=0/1/2) INTEGER :: nn_ico_cpl = 0 !: ice-ocean coupling indicator ! ! = 0 LIM-3 old case ! ! = 1 stresses computed using now ocean velocity ! ! = 2 combination of 0 and 1 cases INTEGER :: nsbc ! type of surface boundary condition (deduced from namsbc informations) INTEGER :: nice ! type of ice in the surface boundary condition (deduced from namsbc informations) !! * Substitutions # include "domzgr_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008) !! $Id: $ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE sbc_init !!--------------------------------------------------------------------- !! *** ROUTINE sbc_init *** !! !! ** Purpose : Initialisation of the ocean surface boundary computation !! !! ** Method : Read the namsbc namelist and set derived parameters !! !! ** Action : - read namsbc parameters !! - nsbc: type of sbc !!---------------------------------------------------------------------- INTEGER :: icpt ! temporary integer !! NAMELIST/namsbc/ nn_fsbc, ln_ana, ln_flx, ln_blk_clio, ln_blk_core, ln_cpl, & & nn_ice , ln_dm2dc, ln_rnf, ln_ssr, nn_fwb, nn_ico_cpl !!---------------------------------------------------------------------- IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'sbc_init : surface boundary condition setting' WRITE(numout,*) '~~~~~~~~ ' ENDIF REWIND ( numnam ) ! Read Namelist namsbc READ ( numnam, namsbc ) ! overwrite namelist parameter using CPP key information !!gmhere no overwrite, test all option via namelist change: require more incore memory !!gm IF( lk_sbc_cpl ) THEN ; ln_cpl = .TRUE. ; ELSE ; ln_cpl = .FALSE. ; ENDIF IF( lk_lim2 ) nn_ice = 2 IF( lk_lim3 ) nn_ice = 3 IF( cp_cfg == 'gyre' ) THEN ln_ana = .TRUE. nn_ice = 0 ENDIF ! Control print IF(lwp) THEN WRITE(numout,*) ' Namelist namsbc (overwritten using CPP key defined)' WRITE(numout,*) ' frequency update of sbc (and ice) nn_fsbc = ', nn_fsbc WRITE(numout,*) ' Type of sbc : ' WRITE(numout,*) ' analytical formulation ln_ana = ', ln_ana WRITE(numout,*) ' flux formulation ln_flx = ', ln_flx WRITE(numout,*) ' CLIO bulk formulation ln_blk_clio = ', ln_blk_clio WRITE(numout,*) ' CLIO bulk formulation ln_blk_core = ', ln_blk_core WRITE(numout,*) ' coupled formulation (T if key_sbc_cpl) ln_cpl = ', ln_cpl WRITE(numout,*) ' Misc. options of sbc : ' WRITE(numout,*) ' ice management in the sbc (=0/1/2/3) nn_ice = ', nn_ice WRITE(numout,*) ' ice-ocean stress computation (=0/1/2) nn_ico_cpl = ', nn_ico_cpl WRITE(numout,*) ' daily mean to diurnal cycle qsr ln_dm2dc = ', ln_dm2dc WRITE(numout,*) ' runoff / runoff mouths ln_rnf = ', ln_rnf WRITE(numout,*) ' Sea Surface Restoring on SST and/or SSS ln_ssr = ', ln_ssr WRITE(numout,*) ' FreshWater Budget control (=0/1/2) nn_fwb = ', nn_fwb WRITE(numout,*) ' closed sea (=0/1) (set in namdom) nclosea = ', nclosea ENDIF IF( .NOT. ln_rnf ) nn_runoff = 0 ! no runoff, or runoff mouths IF( nn_ice == 0 ) fr_i(:,:) = 0.e0 ! no ice in the domain, ice fraction is always zero ! Check consistancy !!gm mixture of real and integer : coding to be changed.... IF( nn_ice == 2 ) THEN IF( MOD( nitend - nit000 + 1, nn_fsbc) /= 0 ) THEN WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') is NOT a multiple of nn_fsbc (', nn_fsbc, ')' CALL ctl_stop( ctmp1, 'Impossible to do proper restart files' ) ENDIF IF( MOD( nstock, nn_fsbc) /= 0 ) THEN WRITE(ctmp1,*) 'nstock (' , nstock , ') is NOT a multiple of nn_fsbc (', nn_fsbc, ')' CALL ctl_stop( ctmp1, 'Impossible to do proper restart files' ) ENDIF ENDIF IF( MOD( rday, nn_fsbc*rdt ) /= 0 ) CALL ctl_warn( 'nn_fsbc is NOT a multiple of the number of time steps in a day' ) IF( nn_ice == 2 .AND. .NOT.( ln_blk_clio .OR. ln_blk_core ) ) & & CALL ctl_stop( 'sbc_init: sea-ice model requires a bulk formulation' ) ! Choice of the Surface Boudary Condition (set nsbc) icpt = 0 IF( ln_ana ) THEN ; nsbc = 1 ; icpt = icpt + 1 ; ENDIF ! analytical formulation IF( ln_flx ) THEN ; nsbc = 2 ; icpt = icpt + 1 ; ENDIF ! flux formulation IF( ln_blk_clio ) THEN ; nsbc = 3 ; icpt = icpt + 1 ; ENDIF ! CLIO bulk formulation IF( ln_blk_core ) THEN ; nsbc = 4 ; icpt = icpt + 1 ; ENDIF ! CORE bulk formulation IF( ln_cpl ) THEN ; nsbc = 5 ; icpt = icpt + 1 ; ENDIF ! Coupled formulation IF( cp_cfg == 'gyre') THEN ; nsbc = 0 ; ENDIF ! GYRE analytical formulation IF( lk_esopa ) nsbc = -1 ! esopa test, ALL formulations IF( icpt /= 1 .AND. .NOT.lk_esopa ) THEN WRITE(numout,*) WRITE(numout,*) ' E R R O R in setting the sbc, one and only one namelist/CPP key option ' WRITE(numout,*) ' must be choosen. You choose ', icpt, ' option(s)' WRITE(numout,*) ' We stop' nstop = nstop + 1 ENDIF IF(lwp) THEN WRITE(numout,*) IF( nsbc == -1 ) WRITE(numout,*) ' ESOPA test All surface boundary conditions' IF( nsbc == 0 ) WRITE(numout,*) ' GYRE analytical formulation' IF( nsbc == 1 ) WRITE(numout,*) ' analytical formulation' IF( nsbc == 2 ) WRITE(numout,*) ' flux formulation' IF( nsbc == 3 ) WRITE(numout,*) ' CLIO bulk formulation' IF( nsbc == 4 ) WRITE(numout,*) ' CORE bulk formulation' IF( nsbc == 5 ) WRITE(numout,*) ' coupled formulation' ENDIF ! END SUBROUTINE sbc_init SUBROUTINE sbc( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE sbc *** !! !! ** Purpose : provide at each time-step the ocean surface boundary !! condition (momentum, heat and freshwater fluxes) !! !! ** Method : blah blah to be written ????????? !! CAUTION : never mask the surface stress field (tke sbc) !! !! ** Action : - set the ocean surface boundary condition, i.e. !! utau, vtau, qns, qsr, emp, emps, qrp, erp !! - updte the ice fraction : fr_i !!---------------------------------------------------------------------- INTEGER, INTENT(in) :: kt ! ocean time step !!--------------------------------------------------------------------- IF( kt == nit000 ) CALL sbc_init ! Read namsbc namelist : surface module ! ocean to sbc mean sea surface variables (ss._m) ! --------------------------------------- CALL sbc_ssm( kt ) ! sea surface mean currents (at U- and V-points), ! ! temperature and salinity (at T-point) over nf_sbc time-step ! ! (i.e. sst_m, sss_m, ssu_m, ssv_m) ! sbc formulation ! --------------- SELECT CASE( nsbc ) ! Compute ocean surface boundary condition ! ! (i.e. utau,vtau, qns, qsr, emp, emps) CASE( 0 ) ; CALL sbc_gyre ( kt ) ! analytical formulation : GYRE configuration CASE( 1 ) ; CALL sbc_ana ( kt ) ! analytical formulation : uniform sbc CASE( 2 ) ; CALL sbc_flx ( kt ) ! flux formulation CASE( 3 ) ; CALL sbc_blk_clio( kt ) ! bulk formulation : CLIO for the ocean CASE( 4 ) ; CALL sbc_blk_core( kt ) ! bulk formulation : CORE for the ocean CASE( 5 ) ; CALL sbc_cpl ( kt ) ! coupled formulation CASE( -1 ) CALL sbc_ana ( kt ) ! ESOPA, test ALL the formulations CALL sbc_gyre ( kt ) CALL sbc_flx ( kt ) CALL sbc_blk_clio( kt ) CALL sbc_blk_core( kt ) CALL sbc_cpl ( kt ) END SELECT ! Misc. Options ! ------------- !!gm IF( ln_dm2dc ) CALL sbc_dcy( kt ) ! Daily mean qsr distributed over the Diurnal Cycle SELECT CASE( nn_ice ) ! Update heat and freshwater fluxes over ice-covered areas CASE( 1 ) ; CALL sbc_ice_if ( kt ) ! Ice-cover climatology ("Ice-if" model) ! CASE( 2 ) ; CALL sbc_ice_lim_2( kt, nsbc ) ! LIM 2.0 ice model ! CASE( 3 ) ; CALL sbc_ice_lim ( kt, nsbc, nn_ico_cpl) ! LIM 3.0 ice model END SELECT IF( ln_ssr ) CALL sbc_ssr( kt ) ! add SST/SSS damping term IF( ln_rnf ) CALL sbc_rnf( kt ) ! add runoffs to fresh water fluxes IF( nn_fwb /= 0 ) CALL sbc_fwb( kt, nn_fwb, nn_fsbc ) ! control the freshwater budget IF( nclosea == 1 ) CALL sbc_clo( kt ) ! treatment of closed sea in the model domain ! ! (update freshwater fluxes) ! IF(ln_ctl) THEN ! print mean trends (used for debugging) CALL prt_ctl(tab2d_1=fr_i , clinfo1=' fr_i - : ', mask1=tmask, ovlap=1 ) CALL prt_ctl(tab2d_1=emp , clinfo1=' emp - : ', mask1=tmask, ovlap=1 ) CALL prt_ctl(tab2d_1=emps , clinfo1=' emps - : ', mask1=tmask, ovlap=1 ) CALL prt_ctl(tab2d_1=qns , clinfo1=' qns - : ', mask1=tmask, ovlap=1 ) CALL prt_ctl(tab2d_1=qsr , clinfo1=' qsr - : ', mask1=tmask, ovlap=1 ) CALL prt_ctl(tab3d_1=tmask , clinfo1=' tmask : ', mask1=tmask, ovlap=1, kdim=jpk ) CALL prt_ctl(tab3d_1=tn , clinfo1=' sst - : ', mask1=tmask, ovlap=1, kdim=1 ) CALL prt_ctl(tab3d_1=sn , clinfo1=' sss - : ', mask1=tmask, ovlap=1, kdim=1 ) CALL prt_ctl(tab2d_1=utau , clinfo1=' utau - : ', mask1=umask, & & tab2d_2=vtau , clinfo2=' vtau - : ', mask2=vmask, ovlap=1 ) ENDIF ! END SUBROUTINE sbc !!====================================================================== END MODULE sbcmod