sbc_oce.F90 15 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215
  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. !!----------------------------------------------------------------------
  13. !!----------------------------------------------------------------------
  14. !! sbc_oce_alloc : allocation of sbc arrays
  15. !! sbc_tau2wnd : wind speed estimated from wind stress
  16. !!----------------------------------------------------------------------
  17. USE par_oce ! ocean parameters
  18. USE in_out_manager ! I/O manager
  19. USE lib_mpp ! MPP library
  20. IMPLICIT NONE
  21. PRIVATE
  22. PUBLIC sbc_oce_alloc ! routine called in sbcmod.F90
  23. PUBLIC sbc_tau2wnd ! routine called in several sbc modules
  24. !!----------------------------------------------------------------------
  25. !! Namelist for the Ocean Surface Boundary Condition
  26. !!----------------------------------------------------------------------
  27. ! !!* namsbc namelist *
  28. LOGICAL , PUBLIC :: ln_ana !: analytical boundary condition flag
  29. LOGICAL , PUBLIC :: ln_flx !: flux formulation
  30. LOGICAL , PUBLIC :: ln_blk_clio !: CLIO bulk formulation
  31. LOGICAL , PUBLIC :: ln_blk_core !: CORE bulk formulation
  32. LOGICAL , PUBLIC :: ln_blk_mfs !: MFS bulk formulation
  33. #if defined key_oasis3
  34. LOGICAL , PUBLIC :: lk_oasis = .TRUE. !: OASIS used
  35. #else
  36. LOGICAL , PUBLIC :: lk_oasis = .FALSE. !: OASIS unused
  37. #endif
  38. LOGICAL , PUBLIC :: ln_cpl !: ocean-atmosphere coupled formulation
  39. LOGICAL , PUBLIC :: ln_mixcpl !: ocean-atmosphere forced-coupled mixed formulation
  40. LOGICAL , PUBLIC :: ln_dm2dc !: Daily mean to Diurnal Cycle short wave (qsr)
  41. LOGICAL , PUBLIC :: ln_rnf !: runoffs / runoff mouths
  42. LOGICAL , PUBLIC :: ln_ssr !: Sea Surface restoring on SST and/or SSS
  43. LOGICAL , PUBLIC :: ln_apr_dyn !: Atmospheric pressure forcing used on dynamics (ocean & ice)
  44. INTEGER , PUBLIC :: nn_ice !: flag for ice in the surface boundary condition (=0/1/2/3)
  45. INTEGER , PUBLIC :: nn_isf !: flag for isf in the surface boundary condition (=0/1/2/3/4)
  46. INTEGER , PUBLIC :: nn_ice_embd !: flag for levitating/embedding sea-ice in the ocean
  47. ! !: =0 levitating ice (no mass exchange, concentration/dilution effect)
  48. ! !: =1 levitating ice with mass and salt exchange but no presure effect
  49. ! !: =2 embedded sea-ice (full salt and mass exchanges and pressure)
  50. INTEGER , PUBLIC :: nn_components !: flag for sbc module (including sea-ice) coupling mode (see component definition below)
  51. INTEGER , PUBLIC :: nn_limflx !: LIM3 Multi-category heat flux formulation
  52. ! !: =-1 Use of per-category fluxes
  53. ! !: = 0 Average per-category fluxes
  54. ! !: = 1 Average then redistribute per-category fluxes
  55. ! !: = 2 Redistribute a single flux over categories
  56. INTEGER , PUBLIC :: nn_fwb !: FreshWater Budget:
  57. ! !: = 0 unchecked
  58. ! !: = 1 global mean of e-p-r set to zero at each nn_fsbc time step
  59. ! !: = 2 annual global mean of e-p-r set to zero
  60. LOGICAL , PUBLIC :: ln_wave !: true if some coupling with wave model
  61. LOGICAL , PUBLIC :: ln_cdgw !: true if neutral drag coefficient from wave model
  62. LOGICAL , PUBLIC :: ln_sdw !: true if 3d stokes drift from wave model
  63. !
  64. LOGICAL , PUBLIC :: ln_icebergs !: Icebergs
  65. !
  66. INTEGER , PUBLIC :: nn_lsm !: Number of iteration if seaoverland is applied
  67. !!----------------------------------------------------------------------
  68. !! switch definition (improve readability)
  69. !!----------------------------------------------------------------------
  70. INTEGER , PUBLIC, PARAMETER :: jp_gyre = 0 !: GYRE analytical formulation
  71. INTEGER , PUBLIC, PARAMETER :: jp_ana = 1 !: analytical formulation
  72. INTEGER , PUBLIC, PARAMETER :: jp_flx = 2 !: flux formulation
  73. INTEGER , PUBLIC, PARAMETER :: jp_clio = 3 !: CLIO bulk formulation
  74. INTEGER , PUBLIC, PARAMETER :: jp_core = 4 !: CORE bulk formulation
  75. INTEGER , PUBLIC, PARAMETER :: jp_purecpl = 5 !: Pure ocean-atmosphere Coupled formulation
  76. INTEGER , PUBLIC, PARAMETER :: jp_mfs = 6 !: MFS bulk formulation
  77. INTEGER , PUBLIC, PARAMETER :: jp_none = 7 !: for OPA when doing coupling via SAS module
  78. INTEGER , PUBLIC, PARAMETER :: jp_esopa = -1 !: esopa test, ALL formulations
  79. !!----------------------------------------------------------------------
  80. !! component definition
  81. !!----------------------------------------------------------------------
  82. INTEGER , PUBLIC, PARAMETER :: jp_iam_nemo = 0 !: Initial single executable configuration
  83. ! (no internal OASIS coupling)
  84. INTEGER , PUBLIC, PARAMETER :: jp_iam_opa = 1 !: Multi executable configuration - OPA component
  85. ! (internal OASIS coupling)
  86. INTEGER , PUBLIC, PARAMETER :: jp_iam_sas = 2 !: Multi executable configuration - SAS component
  87. ! (internal OASIS coupling)
  88. !!----------------------------------------------------------------------
  89. !! Ocean Surface Boundary Condition fields
  90. !!----------------------------------------------------------------------
  91. INTEGER , PUBLIC :: ncpl_qsr_freq !: qsr coupling frequency per days from atmosphere
  92. !
  93. LOGICAL , PUBLIC :: lhftau = .FALSE. !: HF tau used in TKE: mean(stress module) - module(mean stress)
  94. !! !! now ! before !!
  95. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: utau , utau_b !: sea surface i-stress (ocean referential) [N/m2]
  96. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: vtau , vtau_b !: sea surface j-stress (ocean referential) [N/m2]
  97. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: taum !: module of sea surface stress (at T-point) [N/m2]
  98. !! wndm is used onmpute surface gases exchanges in ice-free ocean or leads
  99. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: wndm !: wind speed module at T-point (=|U10m-Uoce|) [m/s]
  100. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qsr !: sea heat flux: solar [W/m2]
  101. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qns , qns_b !: sea heat flux: non solar [W/m2]
  102. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qsr_tot !: total solar heat flux (over sea and ice) [W/m2]
  103. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qns_tot !: total non solar heat flux (over sea and ice) [W/m2]
  104. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: emp , emp_b !: freshwater budget: volume flux [Kg/m2/s]
  105. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: sfx , sfx_b !: salt flux [PSU/m2/s]
  106. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: emp_tot !: total E-P over ocean and ice [Kg/m2/s]
  107. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fmmflx !: freshwater budget: freezing/melting [Kg/m2/s]
  108. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: rnf , rnf_b !: river runoff [Kg/m2/s]
  109. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fwfisf , fwfisf_b !: ice shelf melting [Kg/m2/s]
  110. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fwficb , fwficb_b !: iceberg melting [Kg/m2/s]
  111. !!
  112. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: sbc_tsc, sbc_tsc_b !: sbc content trend [K.m/s] jpi,jpj,jpts
  113. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qsr_hc , qsr_hc_b !: heat content trend due to qsr flux [K.m/s] jpi,jpj,jpk
  114. !!
  115. !!
  116. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tprecip !: total precipitation [Kg/m2/s]
  117. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: sprecip !: solid precipitation [Kg/m2/s]
  118. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fr_i !: ice fraction = 1 - lead fraction (between 0 to 1)
  119. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: atm_co2 !: atmospheric pCO2 [ppm]
  120. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: xcplmask !: coupling mask for ln_mixcpl (warning: allocated in sbccpl)
  121. !!----------------------------------------------------------------------
  122. !! Sea Surface Mean fields
  123. !!----------------------------------------------------------------------
  124. INTEGER , PUBLIC :: nn_fsbc !: frequency of sbc computation (as well as sea-ice model)
  125. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ssu_m !: mean (nn_fsbc time-step) surface sea i-current (U-point) [m/s]
  126. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ssv_m !: mean (nn_fsbc time-step) surface sea j-current (V-point) [m/s]
  127. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: sst_m !: mean (nn_fsbc time-step) surface sea temperature [Celsius]
  128. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: sss_m !: mean (nn_fsbc time-step) surface sea salinity [psu]
  129. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ssh_m !: mean (nn_fsbc time-step) sea surface height [m]
  130. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: e3t_m !: mean (nn_fsbc time-step) sea surface layer thickness [m]
  131. REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: frq_m !: mean (nn_fsbc time-step) fraction of solar net radiation absorbed in the 1st T level [-]
  132. !! * Substitutions
  133. # include "vectopt_loop_substitute.h90"
  134. !!----------------------------------------------------------------------
  135. !! NEMO/OPA 4.0 , NEMO Consortium (2011)
  136. !! $Id: sbc_oce.F90 4990 2014-12-15 16:42:49Z timgraham $
  137. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  138. !!----------------------------------------------------------------------
  139. CONTAINS
  140. INTEGER FUNCTION sbc_oce_alloc()
  141. !!---------------------------------------------------------------------
  142. !! *** FUNCTION sbc_oce_alloc ***
  143. !!---------------------------------------------------------------------
  144. INTEGER :: ierr(5)
  145. !!---------------------------------------------------------------------
  146. ierr(:) = 0
  147. !
  148. ALLOCATE( utau(jpi,jpj) , utau_b(jpi,jpj) , taum(jpi,jpj) , &
  149. & vtau(jpi,jpj) , vtau_b(jpi,jpj) , wndm(jpi,jpj) , STAT=ierr(1) )
  150. !
  151. ALLOCATE( qns_tot(jpi,jpj) , qns (jpi,jpj) , qns_b(jpi,jpj), &
  152. & qsr_tot(jpi,jpj) , qsr (jpi,jpj) , &
  153. & emp (jpi,jpj) , emp_b(jpi,jpj) , &
  154. & sfx (jpi,jpj) , sfx_b(jpi,jpj) , emp_tot(jpi,jpj), fmmflx(jpi,jpj), STAT=ierr(2) )
  155. !
  156. ALLOCATE( fwfisf (jpi,jpj), rnf (jpi,jpj) , sbc_tsc (jpi,jpj,jpts) , qsr_hc (jpi,jpj,jpk) , &
  157. & fwfisf_b(jpi,jpj), rnf_b(jpi,jpj) , sbc_tsc_b(jpi,jpj,jpts) , qsr_hc_b(jpi,jpj,jpk) , &
  158. & fwficb (jpi,jpj), fwficb_b(jpi,jpj), STAT=ierr(3) )
  159. !
  160. ALLOCATE( tprecip(jpi,jpj) , sprecip(jpi,jpj) , fr_i(jpi,jpj) , &
  161. & atm_co2(jpi,jpj) , &
  162. & ssu_m (jpi,jpj) , sst_m(jpi,jpj) , frq_m(jpi,jpj) , &
  163. & ssv_m (jpi,jpj) , sss_m(jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) )
  164. !
  165. #if defined key_vvl
  166. ALLOCATE( e3t_m(jpi,jpj) , STAT=ierr(5) )
  167. #endif
  168. !
  169. sbc_oce_alloc = MAXVAL( ierr )
  170. IF( lk_mpp ) CALL mpp_sum ( sbc_oce_alloc )
  171. IF( sbc_oce_alloc > 0 ) CALL ctl_warn('sbc_oce_alloc: allocation of arrays failed')
  172. !
  173. END FUNCTION sbc_oce_alloc
  174. SUBROUTINE sbc_tau2wnd
  175. !!---------------------------------------------------------------------
  176. !! *** ROUTINE sbc_tau2wnd ***
  177. !!
  178. !! ** Purpose : Estimation of wind speed as a function of wind stress
  179. !!
  180. !! ** Method : |tau|=rhoa*Cd*|U|^2
  181. !!---------------------------------------------------------------------
  182. USE dom_oce ! ocean space and time domain
  183. USE lbclnk ! ocean lateral boundary conditions (or mpp link)
  184. REAL(wp) :: zrhoa = 1.22 ! Air density kg/m3
  185. REAL(wp) :: zcdrag = 1.5e-3 ! drag coefficient
  186. REAL(wp) :: ztx, zty, ztau, zcoef ! temporary variables
  187. INTEGER :: ji, jj ! dummy indices
  188. !!---------------------------------------------------------------------
  189. zcoef = 0.5 / ( zrhoa * zcdrag )
  190. !CDIR NOVERRCHK
  191. DO jj = 2, jpjm1
  192. !CDIR NOVERRCHK
  193. DO ji = fs_2, fs_jpim1 ! vect. opt.
  194. ztx = utau(ji-1,jj ) + utau(ji,jj)
  195. zty = vtau(ji ,jj-1) + vtau(ji,jj)
  196. ztau = SQRT( ztx * ztx + zty * zty )
  197. wndm(ji,jj) = SQRT ( ztau * zcoef ) * tmask(ji,jj,1)
  198. END DO
  199. END DO
  200. CALL lbc_lnk( wndm(:,:) , 'T', 1. )
  201. !
  202. END SUBROUTINE sbc_tau2wnd
  203. !!======================================================================
  204. END MODULE sbc_oce