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