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 branches/UKMO/dev_r5518_GO6_package_FOAMv14_sit/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GO6_package_FOAMv14_sit/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

Last change on this file was 11939, checked in by dcarneir, 4 years ago

Changing GO6 package to include sea ice thickness DA

File size: 18.0 KB
Line 
1MODULE 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   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   sbc_oce_alloc : allocation of sbc arrays
16   !!   sbc_tau2wnd   : wind speed estimated from wind stress
17   !!----------------------------------------------------------------------
18   USE par_oce        ! ocean parameters
19   USE in_out_manager ! I/O manager
20   USE lib_mpp        ! MPP library
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   sbc_oce_alloc   ! routine called in sbcmod.F90
26   PUBLIC   sbc_tau2wnd     ! routine called in several sbc modules
27   
28   !!----------------------------------------------------------------------
29   !!           Namelist for the Ocean Surface Boundary Condition
30   !!----------------------------------------------------------------------
31   !                                   !!* namsbc namelist *
32   LOGICAL , PUBLIC ::   ln_ana         !: analytical boundary condition flag
33   LOGICAL , PUBLIC ::   ln_flx         !: flux      formulation
34   LOGICAL , PUBLIC ::   ln_blk_clio    !: CLIO bulk formulation
35   LOGICAL , PUBLIC ::   ln_blk_core    !: CORE bulk formulation
36   LOGICAL , PUBLIC ::   ln_blk_mfs     !: MFS  bulk formulation
37#if defined key_oasis3
38   LOGICAL , PUBLIC ::   lk_oasis = .TRUE.  !: OASIS used
39#else
40   LOGICAL , PUBLIC ::   lk_oasis = .FALSE. !: OASIS unused
41#endif
42   LOGICAL , PUBLIC ::   ln_cpl         !: ocean-atmosphere coupled formulation
43   LOGICAL , PUBLIC ::   ln_mixcpl      !: ocean-atmosphere forced-coupled mixed formulation
44   LOGICAL , PUBLIC ::   ln_dm2dc       !: Daily mean to Diurnal Cycle short wave (qsr)
45   LOGICAL , PUBLIC ::   ln_rnf         !: runoffs / runoff mouths
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   INTEGER , PUBLIC ::   nn_isf         !: flag for isf in the surface boundary condition (=0/1/2/3/4)
50   INTEGER , PUBLIC ::   nn_ice_embd    !: flag for levitating/embedding sea-ice in the ocean
51   !                                             !: =0 levitating ice (no mass exchange, concentration/dilution effect)
52   !                                             !: =1 levitating ice with mass and salt exchange but no presure effect
53   !                                             !: =2 embedded sea-ice (full salt and mass exchanges and pressure)
54   INTEGER , PUBLIC ::   nn_components  !: flag for sbc module (including sea-ice) coupling mode (see component definition below)
55   INTEGER , PUBLIC ::   nn_limflx      !: LIM3 Multi-category heat flux formulation
56   !                                             !: =-1  Use of per-category fluxes
57   !                                             !: = 0  Average per-category fluxes
58   !                                             !: = 1  Average then redistribute per-category fluxes
59   !                                             !: = 2  Redistribute a single flux over categories
60   INTEGER , PUBLIC ::   nn_fwb         !: FreshWater Budget:
61   !                                             !:  = 0 unchecked
62   !                                             !:  = 1 global mean of e-p-r set to zero at each nn_fsbc time step
63   !                                             !:  = 2 annual global mean of e-p-r set to zero
64   LOGICAL , PUBLIC ::   ln_wave        !: true if some coupling with wave model
65   LOGICAL , PUBLIC ::   ln_cdgw        !: true if neutral drag coefficient from wave model
66   LOGICAL , PUBLIC ::   ln_sdw         !: true if 3d stokes drift from wave model
67   !
68   LOGICAL , PUBLIC ::   ln_icebergs    !: Icebergs
69   !
70   INTEGER , PUBLIC ::   nn_lsm         !: Number of iteration if seaoverland is applied
71   !!----------------------------------------------------------------------
72   !!           switch definition (improve readability)
73   !!----------------------------------------------------------------------
74   INTEGER , PUBLIC, PARAMETER ::   jp_gyre    = 0        !: GYRE analytical               formulation
75   INTEGER , PUBLIC, PARAMETER ::   jp_ana     = 1        !: analytical                    formulation
76   INTEGER , PUBLIC, PARAMETER ::   jp_flx     = 2        !: flux                          formulation
77   INTEGER , PUBLIC, PARAMETER ::   jp_clio    = 3        !: CLIO bulk                     formulation
78   INTEGER , PUBLIC, PARAMETER ::   jp_core    = 4        !: CORE bulk                     formulation
79   INTEGER , PUBLIC, PARAMETER ::   jp_purecpl = 5        !: Pure ocean-atmosphere Coupled formulation
80   INTEGER , PUBLIC, PARAMETER ::   jp_mfs     = 6        !: MFS  bulk                     formulation
81   INTEGER , PUBLIC, PARAMETER ::   jp_none    = 7        !: for OPA when doing coupling via SAS module
82   INTEGER , PUBLIC, PARAMETER ::   jp_esopa   = -1       !: esopa test, ALL formulations
83   
84   !!----------------------------------------------------------------------
85   !!           component definition
86   !!----------------------------------------------------------------------
87   INTEGER , PUBLIC, PARAMETER ::   jp_iam_nemo = 0      !: Initial single executable configuration
88                                                         !  (no internal OASIS coupling)
89   INTEGER , PUBLIC, PARAMETER ::   jp_iam_opa  = 1      !: Multi executable configuration - OPA component
90                                                         !  (internal OASIS coupling)
91   INTEGER , PUBLIC, PARAMETER ::   jp_iam_sas  = 2      !: Multi executable configuration - SAS component
92                                                         !  (internal OASIS coupling)
93   !!----------------------------------------------------------------------
94   !!              Ocean Surface Boundary Condition fields
95   !!----------------------------------------------------------------------
96   INTEGER , PUBLIC ::  ncpl_qsr_freq            !: qsr coupling frequency per days from atmosphere
97   !
98   LOGICAL , PUBLIC ::   lhftau = .FALSE.        !: HF tau used in TKE: mean(stress module) - module(mean stress)
99   !!                                   !!   now    ! before   !!
100   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   utau   , utau_b   !: sea surface i-stress (ocean referential)     [N/m2]
101   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vtau   , vtau_b   !: sea surface j-stress (ocean referential)     [N/m2]
102   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   taum              !: module of sea surface stress (at T-point)    [N/m2]
103   !! wndm is used onmpute surface gases exchanges in ice-free ocean or leads
104   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wndm              !: wind speed module at T-point (=|U10m-Uoce|)  [m/s]
105   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr               !: sea heat flux:     solar                     [W/m2]
106   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns    , qns_b    !: sea heat flux: non solar                     [W/m2]
107   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr_tot           !: total     solar heat flux (over sea and ice) [W/m2]
108   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns_tot           !: total non solar heat flux (over sea and ice) [W/m2]
109   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp    , emp_b    !: freshwater budget: volume flux               [Kg/m2/s]
110   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx    , sfx_b    !: salt flux                                    [PSU/m2/s]
111   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp_tot           !: total E-P over ocean and ice                 [Kg/m2/s]
112   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fmmflx            !: freshwater budget: freezing/melting          [Kg/m2/s]
113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rnf    , rnf_b    !: river runoff        [Kg/m2/s] 
114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fwfisf , fwfisf_b !: ice shelf melting   [Kg/m2/s] 
115   !!
116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  sbc_tsc, sbc_tsc_b  !: sbc content trend                      [K.m/s] jpi,jpj,jpts
117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  qsr_hc , qsr_hc_b   !: heat content trend due to qsr flux     [K.m/s] jpi,jpj,jpk
118   !!
119   !!
120   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tprecip           !: total precipitation                          [Kg/m2/s]
121   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sprecip           !: solid precipitation                          [Kg/m2/s]
122   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fr_i              !: ice fraction = 1 - lead fraction      (between 0 to 1)
123   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   thick_i           !: ice thickness [m]
124   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   thick_s           !: snow depth [m]
125   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vol_i             !: ice volume [m3]
126#if defined key_cpl_carbon_cycle
127   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   atm_co2           !: atmospheric pCO2                             [ppm]
128#endif
129   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: xcplmask          !: coupling mask for ln_mixcpl (warning: allocated in sbccpl)
130   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   greenland_icesheet_mass_array, greenland_icesheet_mask
131   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   antarctica_icesheet_mass_array, antarctica_icesheet_mask
132
133   !!----------------------------------------------------------------------
134   !!                     Sea Surface Mean fields
135   !!----------------------------------------------------------------------
136   INTEGER , PUBLIC                     ::   nn_fsbc   !: frequency of sbc computation (as well as sea-ice model)
137   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssu_m     !: mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
138   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssv_m     !: mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
139   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sst_m     !: mean (nn_fsbc time-step) surface sea temperature     [Celsius]
140   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sss_m     !: mean (nn_fsbc time-step) surface sea salinity            [psu]
141   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ssh_m     !: mean (nn_fsbc time-step) sea surface height                [m]
142   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   e3t_m     !: mean (nn_fsbc time-step) sea surface layer thickness       [m]
143   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   frq_m     !: mean (nn_fsbc time-step) fraction of solar net radiation absorbed in the 1st T level [-]
144   
145   !!----------------------------------------------------------------------
146   !!  Surface scalars of total ice sheet mass for Greenland and Antarctica,
147   !! passed from atmosphere to be converted to dvol and hence a freshwater
148   !! flux  by using old values. New values are saved in the dump, to become
149   !! old values next coupling timestep. Freshwater fluxes split between
150   !! sub iceshelf melting and iceberg calving, scalled to flux per second
151   !!----------------------------------------------------------------------
152   
153   REAL(wp), PUBLIC  :: greenland_icesheet_mass, greenland_icesheet_mass_rate_of_change, greenland_icesheet_timelapsed 
154   REAL(wp), PUBLIC  :: antarctica_icesheet_mass, antarctica_icesheet_mass_rate_of_change, antarctica_icesheet_timelapsed
155
156   ! sbccpl namelist parameters associated with icesheet freshwater input code. Included here rather than in sbccpl.F90 to
157   ! avoid circular dependencies.
158   INTEGER, PUBLIC     ::   nn_coupled_iceshelf_fluxes     ! =0 : total freshwater input from iceberg calving and ice shelf basal melting
159                                                           ! taken from climatologies used (no action in coupling routines).
160                                                           ! =1 :  use rate of change of mass of Greenland and Antarctic icesheets to set the
161                                                           ! combined magnitude of the iceberg calving and iceshelf melting freshwater fluxes.
162                                                           ! =2 :  specify constant freshwater inputs in this namelist to set the combined
163                                                           ! magnitude of iceberg calving and iceshelf melting freshwater fluxes.
164   LOGICAL, PUBLIC     ::   ln_iceshelf_init_atmos         ! If true force ocean to initialise iceshelf masses from atmospheric values rather
165                                                           ! than values in ocean restart (applicable if nn_coupled_iceshelf_fluxes=1).
166   REAL(wp), PUBLIC    ::   rn_greenland_total_fw_flux    ! Constant total rate of freshwater input (kg/s) for Greenland (if nn_coupled_iceshelf_fluxes=2)
167   REAL(wp), PUBLIC    ::   rn_greenland_calving_fraction  ! Set fraction of total freshwater flux for iceberg calving - remainder goes to iceshelf melting.
168   REAL(wp), PUBLIC    ::   rn_antarctica_total_fw_flux   ! Constant total rate of freshwater input (kg/s) for Antarctica (if nn_coupled_iceshelf_fluxes=2)
169   REAL(wp), PUBLIC    ::   rn_antarctica_calving_fraction ! Set fraction of total freshwater flux for iceberg calving - remainder goes to iceshelf melting.
170   REAL(wp), PUBLIC    ::   rn_iceshelf_fluxes_tolerance   ! Absolute tolerance for detecting differences in icesheet masses.
171
172   !! * Substitutions
173#  include "vectopt_loop_substitute.h90"
174   !!----------------------------------------------------------------------
175   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
176   !! $Id$
177   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
178   !!----------------------------------------------------------------------
179CONTAINS
180
181   INTEGER FUNCTION sbc_oce_alloc()
182      !!---------------------------------------------------------------------
183      !!                  ***  FUNCTION sbc_oce_alloc  ***
184      !!---------------------------------------------------------------------
185      INTEGER :: ierr(5)
186      !!---------------------------------------------------------------------
187      ierr(:) = 0
188      !
189      ALLOCATE( utau(jpi,jpj) , utau_b(jpi,jpj) , taum(jpi,jpj) ,     &
190         &      vtau(jpi,jpj) , vtau_b(jpi,jpj) , wndm(jpi,jpj) , STAT=ierr(1) ) 
191         !
192      ALLOCATE( qns_tot(jpi,jpj) , qns  (jpi,jpj) , qns_b(jpi,jpj),        &
193         &      qsr_tot(jpi,jpj) , qsr  (jpi,jpj) ,                        &
194         &      emp    (jpi,jpj) , emp_b(jpi,jpj) ,                        &
195         &      sfx    (jpi,jpj) , sfx_b(jpi,jpj) , emp_tot(jpi,jpj), fmmflx(jpi,jpj), STAT=ierr(2) )
196         !
197      ALLOCATE( fwfisf  (jpi,jpj), rnf  (jpi,jpj) , sbc_tsc  (jpi,jpj,jpts) , qsr_hc  (jpi,jpj,jpk) ,     &
198         &      fwfisf_b(jpi,jpj), rnf_b(jpi,jpj) , sbc_tsc_b(jpi,jpj,jpts) , qsr_hc_b(jpi,jpj,jpk) , STAT=ierr(3) )
199         !
200      ALLOCATE( tprecip(jpi,jpj) , sprecip(jpi,jpj) , fr_i(jpi,jpj) ,     &
201         & thick_i(jpi,jpj) , thick_s(jpi,jpj) , vol_i(jpi,jpj) ,         & 
202#if defined key_cpl_carbon_cycle
203         &      atm_co2(jpi,jpj) ,                                        &
204#endif
205         &      ssu_m  (jpi,jpj) , sst_m(jpi,jpj) , frq_m(jpi,jpj) ,      &
206         &      ssv_m  (jpi,jpj) , sss_m(jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) )
207      ALLOCATE( greenland_icesheet_mass_array(jpi,jpj) , antarctica_icesheet_mass_array(jpi,jpj) )
208      ALLOCATE( greenland_icesheet_mask(jpi,jpj) , antarctica_icesheet_mask(jpi,jpj) )
209         !
210#if defined key_vvl
211      ALLOCATE( e3t_m(jpi,jpj) , STAT=ierr(5) )
212#endif
213         !
214      sbc_oce_alloc = MAXVAL( ierr )
215      IF( lk_mpp            )   CALL mpp_sum ( sbc_oce_alloc )
216      IF( sbc_oce_alloc > 0 )   CALL ctl_warn('sbc_oce_alloc: allocation of arrays failed')
217      !
218   END FUNCTION sbc_oce_alloc
219
220
221   SUBROUTINE sbc_tau2wnd
222      !!---------------------------------------------------------------------
223      !!                    ***  ROUTINE sbc_tau2wnd  ***
224      !!                   
225      !! ** Purpose : Estimation of wind speed as a function of wind stress   
226      !!
227      !! ** Method  : |tau|=rhoa*Cd*|U|^2
228      !!---------------------------------------------------------------------
229      USE dom_oce         ! ocean space and time domain
230      USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
231      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
232      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
233      REAL(wp) ::   ztx, zty, ztau, zcoef ! temporary variables
234      INTEGER  ::   ji, jj                ! dummy indices
235      !!---------------------------------------------------------------------
236      zcoef = 0.5 / ( zrhoa * zcdrag ) 
237!CDIR NOVERRCHK
238      DO jj = 2, jpjm1
239!CDIR NOVERRCHK
240         DO ji = fs_2, fs_jpim1   ! vect. opt.
241            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
242            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
243            ztau = SQRT( ztx * ztx + zty * zty )
244            wndm(ji,jj) = SQRT ( ztau * zcoef ) * tmask(ji,jj,1)
245         END DO
246      END DO
247      CALL lbc_lnk( wndm(:,:) , 'T', 1. )
248      !
249   END SUBROUTINE sbc_tau2wnd
250
251   !!======================================================================
252END MODULE sbc_oce
Note: See TracBrowser for help on using the repository browser.