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.
sbc_oce.F90 in NEMO/trunk/src/OCE/SBC – NEMO

source: NEMO/trunk/src/OCE/SBC/sbc_oce.F90 @ 12606

Last change on this file since 12606 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 15.8 KB
RevLine 
[888]1MODULE sbc_oce
2   !!======================================================================
3   !!                       ***  MODULE  sbc_oce  ***
[12377]4   !! Surface module :   variables defined in core memory
[888]5   !!======================================================================
[2528]6   !! History :  3.0  ! 2006-06  (G. Madec)  Original code
7   !!             -   ! 2008-08  (G. Madec)  namsbc moved from sbcmod
8   !!            3.3  ! 2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps
9   !!             -   ! 2010-11  (G. Madec) ice-ocean stress always computed at each ocean time-step
10   !!            3.3  ! 2010-10  (J. Chanut, C. Bricaud)  add the surface pressure forcing
[12377]11   !!            4.0  ! 2012-05  (C. Rousset) add attenuation coef for use in ice model
[7646]12   !!            4.0  ! 2016-06  (L. Brodeau) new unified bulk routine (based on AeroBulk)
[12377]13   !!            4.0  ! 2019-03  (F. Lemarié, G. Samson) add compatibility with ABL mode
[888]14   !!----------------------------------------------------------------------
15
[2715]16   !!----------------------------------------------------------------------
17   !!   sbc_oce_alloc : allocation of sbc arrays
18   !!   sbc_tau2wnd   : wind speed estimated from wind stress
19   !!----------------------------------------------------------------------
20   USE par_oce        ! ocean parameters
21   USE in_out_manager ! I/O manager
22   USE lib_mpp        ! MPP library
23
[888]24   IMPLICIT NONE
25   PRIVATE
[2715]26
27   PUBLIC   sbc_oce_alloc   ! routine called in sbcmod.F90
28   PUBLIC   sbc_tau2wnd     ! routine called in several sbc modules
[12377]29
[888]30   !!----------------------------------------------------------------------
[1218]31   !!           Namelist for the Ocean Surface Boundary Condition
32   !!----------------------------------------------------------------------
[4147]33   !                                   !!* namsbc namelist *
[7646]34   LOGICAL , PUBLIC ::   ln_usr         !: user defined formulation
[4147]35   LOGICAL , PUBLIC ::   ln_flx         !: flux      formulation
[7646]36   LOGICAL , PUBLIC ::   ln_blk         !: bulk formulation
[12377]37   LOGICAL , PUBLIC ::   ln_abl         !: Atmospheric boundary layer model
[4990]38#if defined key_oasis3
[5407]39   LOGICAL , PUBLIC ::   lk_oasis = .TRUE.  !: OASIS used
[4990]40#else
[5407]41   LOGICAL , PUBLIC ::   lk_oasis = .FALSE. !: OASIS unused
[4990]42#endif
[5407]43   LOGICAL , PUBLIC ::   ln_cpl         !: ocean-atmosphere coupled formulation
44   LOGICAL , PUBLIC ::   ln_mixcpl      !: ocean-atmosphere forced-coupled mixed formulation
[4147]45   LOGICAL , PUBLIC ::   ln_dm2dc       !: Daily mean to Diurnal Cycle short wave (qsr)
[4230]46   LOGICAL , PUBLIC ::   ln_rnf         !: runoffs / runoff mouths
[12377]47   LOGICAL , PUBLIC ::   ln_ssr         !: Sea Surface restoring on SST and/or SSS
[4147]48   LOGICAL , PUBLIC ::   ln_apr_dyn     !: Atmospheric pressure forcing used on dynamics (ocean & ice)
49   INTEGER , PUBLIC ::   nn_ice         !: flag for ice in the surface boundary condition (=0/1/2/3)
[9019]50   LOGICAL , PUBLIC ::   ln_ice_embd    !: flag for levitating/embedding sea-ice in the ocean
51   !                                             !: =F levitating ice (no presure effect) with mass and salt exchanges
52   !                                             !: =T embedded sea-ice (pressure effect + mass and salt exchanges)
[12377]53   INTEGER , PUBLIC ::   nn_components  !: flag for sbc module (including sea-ice) coupling mode (see component definition below)
54   INTEGER , PUBLIC ::   nn_fwb         !: FreshWater Budget:
55   !                                             !:  = 0 unchecked
[1220]56   !                                             !:  = 1 global mean of e-p-r set to zero at each nn_fsbc time step
57   !                                             !:  = 2 annual global mean of e-p-r set to zero
[4147]58   LOGICAL , PUBLIC ::   ln_wave        !: true if some coupling with wave model
59   LOGICAL , PUBLIC ::   ln_cdgw        !: true if neutral drag coefficient from wave model
60   LOGICAL , PUBLIC ::   ln_sdw         !: true if 3d stokes drift from wave model
[9033]61   LOGICAL , PUBLIC ::   ln_tauwoc       !: true if normalized stress from wave is used
[9023]62   LOGICAL , PUBLIC ::   ln_tauw        !: true if ocean stress components from wave is used
[7646]63   LOGICAL , PUBLIC ::   ln_stcor       !: true if Stokes-Coriolis term is used
[4147]64   !
[9023]65   INTEGER , PUBLIC ::   nn_sdrift      ! type of parameterization to calculate vertical Stokes drift
66   !
[4147]67   LOGICAL , PUBLIC ::   ln_icebergs    !: Icebergs
[4161]68   !
[4990]69   INTEGER , PUBLIC ::   nn_lsm         !: Number of iteration if seaoverland is applied
[9019]70   !
71   !                                   !!* namsbc_cpl namelist *
72   INTEGER , PUBLIC ::   nn_cats_cpl    !: Number of sea ice categories over which the coupling is carried out
73
[1218]74   !!----------------------------------------------------------------------
[4990]75   !!           switch definition (improve readability)
76   !!----------------------------------------------------------------------
[7646]77   INTEGER , PUBLIC, PARAMETER ::   jp_usr     = 1        !: user defined                  formulation
[5407]78   INTEGER , PUBLIC, PARAMETER ::   jp_flx     = 2        !: flux                          formulation
[7646]79   INTEGER , PUBLIC, PARAMETER ::   jp_blk     = 3        !: bulk                          formulation
[12377]80   INTEGER , PUBLIC, PARAMETER ::   jp_abl     = 4        !: Atmospheric boundary layer    formulation
81   INTEGER , PUBLIC, PARAMETER ::   jp_purecpl = 5        !: Pure ocean-atmosphere Coupled formulation
82   INTEGER , PUBLIC, PARAMETER ::   jp_none    = 6        !: for OPA when doing coupling via SAS module
83
[4990]84   !!----------------------------------------------------------------------
[12377]85   !!           Stokes drift parametrization definition
[9023]86   !!----------------------------------------------------------------------
[9115]87   INTEGER , PUBLIC, PARAMETER ::   jp_breivik_2014 = 0     !: Breivik  2014: v_z=v_0*[exp(2*k*z)/(1-8*k*z)]
[12377]88   INTEGER , PUBLIC, PARAMETER ::   jp_li_2017      = 1     !: Li et al 2017: Stokes drift based on Phillips spectrum (Breivik 2016)
89   !  with depth averaged profile
90   INTEGER , PUBLIC, PARAMETER ::   jp_peakfr       = 2     !: Li et al 2017: using the peak wave number read from wave model instead
91   !  of the inverse depth scale
[9115]92   LOGICAL , PUBLIC            ::   ll_st_bv2014  = .FALSE. !  logical indicator, .true. if Breivik 2014 parameterisation is active.
93   LOGICAL , PUBLIC            ::   ll_st_li2017  = .FALSE. !  logical indicator, .true. if Li 2017 parameterisation is active.
94   LOGICAL , PUBLIC            ::   ll_st_bv_li   = .FALSE. !  logical indicator, .true. if either Breivik or Li parameterisation is active.
95   LOGICAL , PUBLIC            ::   ll_st_peakfr  = .FALSE. !  logical indicator, .true. if using Li 2017 with peak wave number
[9023]96
97   !!----------------------------------------------------------------------
[5407]98   !!           component definition
99   !!----------------------------------------------------------------------
[12377]100   INTEGER , PUBLIC, PARAMETER ::   jp_iam_nemo = 0      !: Initial single executable configuration
101   !  (no internal OASIS coupling)
[5407]102   INTEGER , PUBLIC, PARAMETER ::   jp_iam_opa  = 1      !: Multi executable configuration - OPA component
[12377]103   !  (internal OASIS coupling)
[5407]104   INTEGER , PUBLIC, PARAMETER ::   jp_iam_sas  = 2      !: Multi executable configuration - SAS component
[12377]105   !  (internal OASIS coupling)
[5407]106   !!----------------------------------------------------------------------
[888]107   !!              Ocean Surface Boundary Condition fields
108   !!----------------------------------------------------------------------
[12132]109   INTEGER , PUBLIC ::  ncpl_qsr_freq = 0        !: qsr coupling frequency per days from atmosphere (used by top)
[5385]110   !
[2528]111   !!                                   !!   now    ! before   !!
[2715]112   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   utau   , utau_b   !: sea surface i-stress (ocean referential)     [N/m2]
113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vtau   , vtau_b   !: sea surface j-stress (ocean referential)     [N/m2]
[12377]114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   taum              !: module of sea surface stress (at T-point)    [N/m2]
115   !! wndm is used compute surface gases exchanges in ice-free ocean or leads
[2715]116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wndm              !: wind speed module at T-point (=|U10m-Uoce|)  [m/s]
[12377]117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rhoa              !: air density at "rn_zu" m above the sea       [kg/m3]
[2715]118   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr               !: sea heat flux:     solar                     [W/m2]
119   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns    , qns_b    !: sea heat flux: non solar                     [W/m2]
120   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr_tot           !: total     solar heat flux (over sea and ice) [W/m2]
121   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns_tot           !: total non solar heat flux (over sea and ice) [W/m2]
122   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp    , emp_b    !: freshwater budget: volume flux               [Kg/m2/s]
[10882]123   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx    , sfx_b    !: salt flux                                    [PSS.kg/m2/s]
[2715]124   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp_tot           !: total E-P over ocean and ice                 [Kg/m2/s]
[4148]125   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fmmflx            !: freshwater budget: freezing/melting          [Kg/m2/s]
[12377]126   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rnf    , rnf_b    !: river runoff                                 [Kg/m2/s]
127   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fwficb , fwficb_b !: iceberg melting                              [Kg/m2/s]
[2528]128   !!
[2715]129   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  sbc_tsc, sbc_tsc_b  !: sbc content trend                      [K.m/s] jpi,jpj,jpts
130   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  qsr_hc , qsr_hc_b   !: heat content trend due to qsr flux     [K.m/s] jpi,jpj,jpk
[2528]131   !!
[4161]132   !!
[2715]133   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tprecip           !: total precipitation                          [Kg/m2/s]
134   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sprecip           !: solid precipitation                          [Kg/m2/s]
135   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fr_i              !: ice fraction = 1 - lead fraction      (between 0 to 1)
136   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   atm_co2           !: atmospheric pCO2                             [ppm]
[5407]137   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: xcplmask          !: coupling mask for ln_mixcpl (warning: allocated in sbccpl)
[888]138
[12377]139   !!---------------------------------------------------------------------
140   !! ABL Vertical Domain size
141   !!---------------------------------------------------------------------
142   INTEGER , PUBLIC            ::   jpka   = 2     !: ABL number of vertical levels (default definition)
143   INTEGER , PUBLIC            ::   jpkam1 = 1     !: jpka-1
144   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   ght_abl, ghw_abl          !: ABL geopotential height (needed for iom)
145   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   e3t_abl, e3w_abl          !: ABL vertical scale factors (needed for iom)
146
[888]147   !!----------------------------------------------------------------------
148   !!                     Sea Surface Mean fields
149   !!----------------------------------------------------------------------
150   INTEGER , PUBLIC                     ::   nn_fsbc   !: frequency of sbc computation (as well as sea-ice model)
[2715]151   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssu_m     !: mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
152   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssv_m     !: mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
153   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sst_m     !: mean (nn_fsbc time-step) surface sea temperature     [Celsius]
154   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sss_m     !: mean (nn_fsbc time-step) surface sea salinity            [psu]
155   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssh_m     !: mean (nn_fsbc time-step) sea surface height                [m]
[12377]156   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tsk_m     !: mean (nn_fsbc time-step) SKIN surface sea temp.      [Celsius]
[4990]157   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   e3t_m     !: mean (nn_fsbc time-step) sea surface layer thickness       [m]
[5407]158   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   frq_m     !: mean (nn_fsbc time-step) fraction of solar net radiation absorbed in the 1st T level [-]
[888]159
[2715]160   !! * Substitutions
[12377]161#  include "do_loop_substitute.h90"
[888]162   !!----------------------------------------------------------------------
[9598]163   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[2528]164   !! $Id$
[10068]165   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]166   !!----------------------------------------------------------------------
167CONTAINS
168
169   INTEGER FUNCTION sbc_oce_alloc()
170      !!---------------------------------------------------------------------
171      !!                  ***  FUNCTION sbc_oce_alloc  ***
172      !!---------------------------------------------------------------------
[4292]173      INTEGER :: ierr(5)
[2715]174      !!---------------------------------------------------------------------
175      ierr(:) = 0
176      !
177      ALLOCATE( utau(jpi,jpj) , utau_b(jpi,jpj) , taum(jpi,jpj) ,     &
[12377]178         &      vtau(jpi,jpj) , vtau_b(jpi,jpj) , wndm(jpi,jpj) , rhoa(jpi,jpj) , STAT=ierr(1) )
179      !
[3625]180      ALLOCATE( qns_tot(jpi,jpj) , qns  (jpi,jpj) , qns_b(jpi,jpj),        &
181         &      qsr_tot(jpi,jpj) , qsr  (jpi,jpj) ,                        &
182         &      emp    (jpi,jpj) , emp_b(jpi,jpj) ,                        &
[4148]183         &      sfx    (jpi,jpj) , sfx_b(jpi,jpj) , emp_tot(jpi,jpj), fmmflx(jpi,jpj), STAT=ierr(2) )
[12377]184      !
185      ALLOCATE( rnf  (jpi,jpj) , sbc_tsc  (jpi,jpj,jpts) , qsr_hc  (jpi,jpj,jpk) ,  &
186         &      rnf_b(jpi,jpj) , sbc_tsc_b(jpi,jpj,jpts) , qsr_hc_b(jpi,jpj,jpk) ,  &
[7788]187         &      fwficb  (jpi,jpj), fwficb_b(jpi,jpj), STAT=ierr(3) )
[12377]188      !
[2715]189      ALLOCATE( tprecip(jpi,jpj) , sprecip(jpi,jpj) , fr_i(jpi,jpj) ,     &
[12377]190         &      atm_co2(jpi,jpj) , tsk_m(jpi,jpj) ,                       &
[5407]191         &      ssu_m  (jpi,jpj) , sst_m(jpi,jpj) , frq_m(jpi,jpj) ,      &
192         &      ssv_m  (jpi,jpj) , sss_m(jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) )
[12377]193      !
[4292]194      ALLOCATE( e3t_m(jpi,jpj) , STAT=ierr(5) )
[12377]195      !
[2715]196      sbc_oce_alloc = MAXVAL( ierr )
[10425]197      CALL mpp_sum ( 'sbc_oce', sbc_oce_alloc )
[2715]198      IF( sbc_oce_alloc > 0 )   CALL ctl_warn('sbc_oce_alloc: allocation of arrays failed')
199      !
200   END FUNCTION sbc_oce_alloc
201
202
203   SUBROUTINE sbc_tau2wnd
204      !!---------------------------------------------------------------------
205      !!                    ***  ROUTINE sbc_tau2wnd  ***
206      !!
[12377]207      !! ** Purpose : Estimation of wind speed as a function of wind stress
208      !!
[2715]209      !! ** Method  : |tau|=rhoa*Cd*|U|^2
210      !!---------------------------------------------------------------------
211      USE dom_oce         ! ocean space and time domain
212      USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
213      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
214      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
215      REAL(wp) ::   ztx, zty, ztau, zcoef ! temporary variables
216      INTEGER  ::   ji, jj                ! dummy indices
217      !!---------------------------------------------------------------------
[12377]218      zcoef = 0.5 / ( zrhoa * zcdrag )
219      DO_2D_00_00
220         ztx = utau(ji-1,jj  ) + utau(ji,jj)
221         zty = vtau(ji  ,jj-1) + vtau(ji,jj)
222         ztau = SQRT( ztx * ztx + zty * zty )
223         wndm(ji,jj) = SQRT ( ztau * zcoef ) * tmask(ji,jj,1)
224      END_2D
[10425]225      CALL lbc_lnk( 'sbc_oce', wndm(:,:) , 'T', 1. )
[2715]226      !
227   END SUBROUTINE sbc_tau2wnd
228
[888]229   !!======================================================================
230END MODULE sbc_oce
Note: See TracBrowser for help on using the repository browser.