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_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 18.4 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   USE yomhook, ONLY: lhook, dr_hook
23   USE parkind1, ONLY: jprb, jpim
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   sbc_oce_alloc   ! routine called in sbcmod.F90
29   PUBLIC   sbc_tau2wnd     ! routine called in several sbc modules
30   
31   !!----------------------------------------------------------------------
32   !!           Namelist for the Ocean Surface Boundary Condition
33   !!----------------------------------------------------------------------
34   !                                   !!* namsbc namelist *
35   LOGICAL , PUBLIC ::   ln_ana         !: analytical boundary condition flag
36   LOGICAL , PUBLIC ::   ln_flx         !: flux      formulation
37   LOGICAL , PUBLIC ::   ln_blk_clio    !: CLIO bulk formulation
38   LOGICAL , PUBLIC ::   ln_blk_core    !: CORE bulk formulation
39   LOGICAL , PUBLIC ::   ln_blk_mfs     !: MFS  bulk formulation
40#if defined key_oasis3
41   LOGICAL , PUBLIC ::   lk_oasis = .TRUE.  !: OASIS used
42#else
43   LOGICAL , PUBLIC ::   lk_oasis = .FALSE. !: OASIS unused
44#endif
45   LOGICAL , PUBLIC ::   ln_cpl         !: ocean-atmosphere coupled formulation
46   LOGICAL , PUBLIC ::   ln_mixcpl      !: ocean-atmosphere forced-coupled mixed formulation
47   LOGICAL , PUBLIC ::   ln_dm2dc       !: Daily mean to Diurnal Cycle short wave (qsr)
48   LOGICAL , PUBLIC ::   ln_rnf         !: runoffs / runoff mouths
49   LOGICAL , PUBLIC ::   ln_ssr         !: Sea Surface restoring on SST and/or SSS     
50   LOGICAL , PUBLIC ::   ln_apr_dyn     !: Atmospheric pressure forcing used on dynamics (ocean & ice)
51   INTEGER , PUBLIC ::   nn_ice         !: flag for ice in the surface boundary condition (=0/1/2/3)
52   INTEGER , PUBLIC ::   nn_isf         !: flag for isf in the surface boundary condition (=0/1/2/3/4)
53   INTEGER , PUBLIC ::   nn_ice_embd    !: flag for levitating/embedding sea-ice in the ocean
54   !                                             !: =0 levitating ice (no mass exchange, concentration/dilution effect)
55   !                                             !: =1 levitating ice with mass and salt exchange but no presure effect
56   !                                             !: =2 embedded sea-ice (full salt and mass exchanges and pressure)
57   INTEGER , PUBLIC ::   nn_components  !: flag for sbc module (including sea-ice) coupling mode (see component definition below)
58   INTEGER , PUBLIC ::   nn_limflx      !: LIM3 Multi-category heat flux formulation
59   !                                             !: =-1  Use of per-category fluxes
60   !                                             !: = 0  Average per-category fluxes
61   !                                             !: = 1  Average then redistribute per-category fluxes
62   !                                             !: = 2  Redistribute a single flux over categories
63   INTEGER , PUBLIC ::   nn_fwb         !: FreshWater Budget:
64   !                                             !:  = 0 unchecked
65   !                                             !:  = 1 global mean of e-p-r set to zero at each nn_fsbc time step
66   !                                             !:  = 2 annual global mean of e-p-r set to zero
67   LOGICAL , PUBLIC ::   ln_wave        !: true if some coupling with wave model
68   LOGICAL , PUBLIC ::   ln_cdgw        !: true if neutral drag coefficient from wave model
69   LOGICAL , PUBLIC ::   ln_sdw         !: true if 3d stokes drift from wave model
70   !
71   LOGICAL , PUBLIC ::   ln_icebergs    !: Icebergs
72   !
73   INTEGER , PUBLIC ::   nn_lsm         !: Number of iteration if seaoverland is applied
74   !!----------------------------------------------------------------------
75   !!           switch definition (improve readability)
76   !!----------------------------------------------------------------------
77   INTEGER , PUBLIC, PARAMETER ::   jp_gyre    = 0        !: GYRE analytical               formulation
78   INTEGER , PUBLIC, PARAMETER ::   jp_ana     = 1        !: analytical                    formulation
79   INTEGER , PUBLIC, PARAMETER ::   jp_flx     = 2        !: flux                          formulation
80   INTEGER , PUBLIC, PARAMETER ::   jp_clio    = 3        !: CLIO bulk                     formulation
81   INTEGER , PUBLIC, PARAMETER ::   jp_core    = 4        !: CORE bulk                     formulation
82   INTEGER , PUBLIC, PARAMETER ::   jp_purecpl = 5        !: Pure ocean-atmosphere Coupled formulation
83   INTEGER , PUBLIC, PARAMETER ::   jp_mfs     = 6        !: MFS  bulk                     formulation
84   INTEGER , PUBLIC, PARAMETER ::   jp_none    = 7        !: for OPA when doing coupling via SAS module
85   INTEGER , PUBLIC, PARAMETER ::   jp_esopa   = -1       !: esopa test, ALL formulations
86   
87   !!----------------------------------------------------------------------
88   !!           component definition
89   !!----------------------------------------------------------------------
90   INTEGER , PUBLIC, PARAMETER ::   jp_iam_nemo = 0      !: Initial single executable configuration
91                                                         !  (no internal OASIS coupling)
92   INTEGER , PUBLIC, PARAMETER ::   jp_iam_opa  = 1      !: Multi executable configuration - OPA component
93                                                         !  (internal OASIS coupling)
94   INTEGER , PUBLIC, PARAMETER ::   jp_iam_sas  = 2      !: Multi executable configuration - SAS component
95                                                         !  (internal OASIS coupling)
96   !!----------------------------------------------------------------------
97   !!              Ocean Surface Boundary Condition fields
98   !!----------------------------------------------------------------------
99   INTEGER , PUBLIC ::  ncpl_qsr_freq            !: qsr coupling frequency per days from atmosphere
100   !
101   LOGICAL , PUBLIC ::   lhftau = .FALSE.        !: HF tau used in TKE: mean(stress module) - module(mean stress)
102   !!                                   !!   now    ! before   !!
103   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   utau   , utau_b   !: sea surface i-stress (ocean referential)     [N/m2]
104   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vtau   , vtau_b   !: sea surface j-stress (ocean referential)     [N/m2]
105   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   taum              !: module of sea surface stress (at T-point)    [N/m2]
106   !! wndm is used onmpute surface gases exchanges in ice-free ocean or leads
107   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wndm              !: wind speed module at T-point (=|U10m-Uoce|)  [m/s]
108   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr               !: sea heat flux:     solar                     [W/m2]
109   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns    , qns_b    !: sea heat flux: non solar                     [W/m2]
110   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsr_tot           !: total     solar heat flux (over sea and ice) [W/m2]
111   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qns_tot           !: total non solar heat flux (over sea and ice) [W/m2]
112   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp    , emp_b    !: freshwater budget: volume flux               [Kg/m2/s]
113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx    , sfx_b    !: salt flux                                    [PSU/m2/s]
114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   emp_tot           !: total E-P over ocean and ice                 [Kg/m2/s]
115   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fmmflx            !: freshwater budget: freezing/melting          [Kg/m2/s]
116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rnf    , rnf_b    !: river runoff        [Kg/m2/s] 
117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fwfisf , fwfisf_b !: ice shelf melting   [Kg/m2/s] 
118   !!
119   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  sbc_tsc, sbc_tsc_b  !: sbc content trend                      [K.m/s] jpi,jpj,jpts
120   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  qsr_hc , qsr_hc_b   !: heat content trend due to qsr flux     [K.m/s] jpi,jpj,jpk
121   !!
122   !!
123   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tprecip           !: total precipitation                          [Kg/m2/s]
124   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sprecip           !: solid precipitation                          [Kg/m2/s]
125   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fr_i              !: ice fraction = 1 - lead fraction      (between 0 to 1)
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      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
187      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
188      REAL(KIND=jprb)               :: zhook_handle
189
190      CHARACTER(LEN=*), PARAMETER :: RoutineName='SBC_OCE_ALLOC'
191
192      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
193
194      !!---------------------------------------------------------------------
195      ierr(:) = 0
196      !
197      ALLOCATE( utau(jpi,jpj) , utau_b(jpi,jpj) , taum(jpi,jpj) ,     &
198         &      vtau(jpi,jpj) , vtau_b(jpi,jpj) , wndm(jpi,jpj) , STAT=ierr(1) ) 
199         !
200      ALLOCATE( qns_tot(jpi,jpj) , qns  (jpi,jpj) , qns_b(jpi,jpj),        &
201         &      qsr_tot(jpi,jpj) , qsr  (jpi,jpj) ,                        &
202         &      emp    (jpi,jpj) , emp_b(jpi,jpj) ,                        &
203         &      sfx    (jpi,jpj) , sfx_b(jpi,jpj) , emp_tot(jpi,jpj), fmmflx(jpi,jpj), STAT=ierr(2) )
204         !
205      ALLOCATE( fwfisf  (jpi,jpj), rnf  (jpi,jpj) , sbc_tsc  (jpi,jpj,jpts) , qsr_hc  (jpi,jpj,jpk) ,     &
206         &      fwfisf_b(jpi,jpj), rnf_b(jpi,jpj) , sbc_tsc_b(jpi,jpj,jpts) , qsr_hc_b(jpi,jpj,jpk) , STAT=ierr(3) )
207         !
208      ALLOCATE( tprecip(jpi,jpj) , sprecip(jpi,jpj) , fr_i(jpi,jpj) ,     &
209#if defined key_cpl_carbon_cycle
210         &      atm_co2(jpi,jpj) ,                                        &
211#endif
212         &      ssu_m  (jpi,jpj) , sst_m(jpi,jpj) , frq_m(jpi,jpj) ,      &
213         &      ssv_m  (jpi,jpj) , sss_m(jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) )
214      ALLOCATE( greenland_icesheet_mass_array(jpi,jpj) , antarctica_icesheet_mass_array(jpi,jpj) )
215      ALLOCATE( greenland_icesheet_mask(jpi,jpj) , antarctica_icesheet_mask(jpi,jpj) )
216         !
217#if defined key_vvl
218      ALLOCATE( e3t_m(jpi,jpj) , STAT=ierr(5) )
219#endif
220         !
221      sbc_oce_alloc = MAXVAL( ierr )
222      IF( lk_mpp            )   CALL mpp_sum ( sbc_oce_alloc )
223      IF( sbc_oce_alloc > 0 )   CALL ctl_warn('sbc_oce_alloc: allocation of arrays failed')
224      !
225      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
226   END FUNCTION sbc_oce_alloc
227
228
229   SUBROUTINE sbc_tau2wnd
230      !!---------------------------------------------------------------------
231      !!                    ***  ROUTINE sbc_tau2wnd  ***
232      !!                   
233      !! ** Purpose : Estimation of wind speed as a function of wind stress   
234      !!
235      !! ** Method  : |tau|=rhoa*Cd*|U|^2
236      !!---------------------------------------------------------------------
237      USE dom_oce         ! ocean space and time domain
238      USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
239      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
240      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
241      REAL(wp) ::   ztx, zty, ztau, zcoef ! temporary variables
242      INTEGER  ::   ji, jj                ! dummy indices
243      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
244      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
245      REAL(KIND=jprb)               :: zhook_handle
246
247      CHARACTER(LEN=*), PARAMETER :: RoutineName='SBC_TAU2WND'
248
249      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
250
251      !!---------------------------------------------------------------------
252      zcoef = 0.5 / ( zrhoa * zcdrag ) 
253!CDIR NOVERRCHK
254      DO jj = 2, jpjm1
255!CDIR NOVERRCHK
256         DO ji = fs_2, fs_jpim1   ! vect. opt.
257            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
258            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
259            ztau = SQRT( ztx * ztx + zty * zty )
260            wndm(ji,jj) = SQRT ( ztau * zcoef ) * tmask(ji,jj,1)
261         END DO
262      END DO
263      CALL lbc_lnk( wndm(:,:) , 'T', 1. )
264      !
265      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
266   END SUBROUTINE sbc_tau2wnd
267
268   !!======================================================================
269END MODULE sbc_oce
Note: See TracBrowser for help on using the repository browser.