sbcana.F90 17 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332
  1. MODULE sbcana
  2. !!======================================================================
  3. !! *** MODULE sbcana ***
  4. !! Ocean forcing: analytical momentum, heat and freshwater forcings
  5. !!=====================================================================
  6. !! History : 3.0 ! 2006-06 (G. Madec) Original code
  7. !! 3.2 ! 2009-07 (G. Madec) Style only
  8. !!----------------------------------------------------------------------
  9. !!----------------------------------------------------------------------
  10. !! sbc_ana : set an analytical ocean forcing
  11. !! sbc_gyre : set the GYRE configuration analytical forcing
  12. !!----------------------------------------------------------------------
  13. USE oce ! ocean dynamics and tracers
  14. USE dom_oce ! ocean space and time domain
  15. USE sbc_oce ! Surface boundary condition: ocean fields
  16. USE phycst ! physical constants
  17. USE in_out_manager ! I/O manager
  18. USE lib_mpp ! distribued memory computing library
  19. USE lbclnk ! ocean lateral boundary conditions (or mpp link)
  20. USE lib_fortran
  21. IMPLICIT NONE
  22. PRIVATE
  23. PUBLIC sbc_ana ! routine called in sbcmod module
  24. PUBLIC sbc_gyre ! routine called in sbcmod module
  25. ! !!* Namelist namsbc_ana *
  26. INTEGER :: nn_tau000 ! nb of time-step during which the surface stress
  27. ! ! increase from 0 to its nominal value
  28. REAL(wp) :: rn_utau0 ! constant wind stress value in i-direction
  29. REAL(wp) :: rn_vtau0 ! constant wind stress value in j-direction
  30. REAL(wp) :: rn_qns0 ! non solar heat flux
  31. REAL(wp) :: rn_qsr0 ! solar heat flux
  32. REAL(wp) :: rn_emp0 ! net freshwater flux
  33. !! * Substitutions
  34. # include "domzgr_substitute.h90"
  35. # include "vectopt_loop_substitute.h90"
  36. !!----------------------------------------------------------------------
  37. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  38. !! $Id: sbcana.F90 4624 2014-04-28 12:09:03Z acc $
  39. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  40. !!----------------------------------------------------------------------
  41. CONTAINS
  42. SUBROUTINE sbc_ana( kt )
  43. !!---------------------------------------------------------------------
  44. !! *** ROUTINE sbc_ana ***
  45. !!
  46. !! ** Purpose : provide at each time-step the ocean surface boundary
  47. !! condition, i.e. the momentum, heat and freshwater fluxes.
  48. !!
  49. !! ** Method : Constant and uniform surface forcing specified from
  50. !! namsbc_ana namelist parameters. All the fluxes are time
  51. !! independant except the stresses which increase from zero
  52. !! during the first nn_tau000 time-step
  53. !!
  54. !! ** Action : - set the ocean surface boundary condition, i.e.
  55. !! utau, vtau, taum, wndm, qns, qsr, emp, sfx
  56. !!----------------------------------------------------------------------
  57. INTEGER, INTENT(in) :: kt ! ocean time step
  58. !
  59. INTEGER :: ios ! local integer
  60. REAL(wp) :: zrhoa = 1.22_wp ! air density kg/m3
  61. REAL(wp) :: zcdrag = 1.5e-3_wp ! drag coefficient
  62. REAL(wp) :: zfact, ztx ! local scalars
  63. REAL(wp) :: zcoef, zty, zmod ! - -
  64. !!
  65. NAMELIST/namsbc_ana/ nn_tau000, rn_utau0, rn_vtau0, rn_qns0, rn_qsr0, rn_emp0
  66. !!---------------------------------------------------------------------
  67. !
  68. IF( kt == nit000 ) THEN
  69. !
  70. REWIND( numnam_ref ) ! Namelist namsbc_ana in reference namelist : Analytical surface fluxes
  71. READ ( numnam_ref, namsbc_ana, IOSTAT = ios, ERR = 901)
  72. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in reference namelist', lwp )
  73. REWIND( numnam_cfg ) ! Namelist namsbc_ana in configuration namelist : Analytical surface fluxes
  74. READ ( numnam_cfg, namsbc_ana, IOSTAT = ios, ERR = 902 )
  75. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_ana in configuration namelist', lwp )
  76. IF(lwm) WRITE ( numond, namsbc_ana )
  77. !
  78. IF(lwp) WRITE(numout,*)' '
  79. IF(lwp) WRITE(numout,*)' sbc_ana : Constant surface fluxes read in namsbc_ana namelist'
  80. IF(lwp) WRITE(numout,*)' ~~~~~~~ '
  81. IF(lwp) WRITE(numout,*)' spin up of the stress nn_tau000 = ', nn_tau000, ' time-steps'
  82. IF(lwp) WRITE(numout,*)' constant i-stress rn_utau0 = ', rn_utau0 , ' N/m2'
  83. IF(lwp) WRITE(numout,*)' constant j-stress rn_vtau0 = ', rn_vtau0 , ' N/m2'
  84. IF(lwp) WRITE(numout,*)' non solar heat flux rn_qns0 = ', rn_qns0 , ' W/m2'
  85. IF(lwp) WRITE(numout,*)' solar heat flux rn_qsr0 = ', rn_qsr0 , ' W/m2'
  86. IF(lwp) WRITE(numout,*)' net heat flux rn_emp0 = ', rn_emp0 , ' Kg/m2/s'
  87. !
  88. nn_tau000 = MAX( nn_tau000, 1 ) ! must be >= 1
  89. !
  90. utau(:,:) = rn_utau0
  91. vtau(:,:) = rn_vtau0
  92. taum(:,:) = SQRT ( rn_utau0 * rn_utau0 + rn_vtau0 * rn_vtau0 )
  93. wndm(:,:) = SQRT ( taum(1,1) / ( zrhoa * zcdrag ) )
  94. !
  95. emp (:,:) = rn_emp0
  96. sfx (:,:) = 0.0_wp
  97. qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp ! including heat content associated with mass flux at SST
  98. qsr (:,:) = rn_qsr0
  99. !
  100. ENDIF
  101. IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN
  102. !
  103. IF( kt <= nn_tau000 ) THEN ! Increase the stress to its nominal value
  104. ! ! during the first nn_tau000 time-steps
  105. zfact = 0.5 * ( 1. - COS( rpi * REAL( kt, wp ) / REAL( nn_tau000, wp ) ) )
  106. zcoef = 1. / ( zrhoa * zcdrag )
  107. ztx = zfact * rn_utau0
  108. zty = zfact * rn_vtau0
  109. zmod = SQRT( ztx * ztx + zty * zty )
  110. utau(:,:) = ztx
  111. vtau(:,:) = zty
  112. taum(:,:) = zmod
  113. zmod = SQRT( zmod * zcoef )
  114. wndm(:,:) = zmod
  115. ENDIF
  116. ! ! update heat and fresh water fluxes
  117. ! ! as they may have been changed by sbcssr module
  118. emp (:,:) = rn_emp0 ! NB: qns changes with SST if emp /= 0
  119. sfx (:,:) = 0._wp
  120. qns (:,:) = rn_qns0 - emp(:,:) * sst_m(:,:) * rcp
  121. qsr (:,:) = rn_qsr0
  122. !
  123. ENDIF
  124. !
  125. END SUBROUTINE sbc_ana
  126. SUBROUTINE sbc_gyre( kt )
  127. !!---------------------------------------------------------------------
  128. !! *** ROUTINE sbc_ana ***
  129. !!
  130. !! ** Purpose : provide at each time-step the GYRE surface boundary
  131. !! condition, i.e. the momentum, heat and freshwater fluxes.
  132. !!
  133. !! ** Method : analytical seasonal cycle for GYRE configuration.
  134. !! CAUTION : never mask the surface stress field !
  135. !!
  136. !! ** Action : - set the ocean surface boundary condition, i.e.
  137. !! utau, vtau, taum, wndm, qns, qsr, emp, sfx
  138. !!
  139. !! Reference : Hazeleger, W., and S. Drijfhout, JPO, 30, 677-695, 2000.
  140. !!----------------------------------------------------------------------
  141. INTEGER, INTENT(in) :: kt ! ocean time step
  142. !!
  143. INTEGER :: ji, jj ! dummy loop indices
  144. INTEGER :: zyear0 ! initial year
  145. INTEGER :: zmonth0 ! initial month
  146. INTEGER :: zday0 ! initial day
  147. INTEGER :: zday_year0 ! initial day since january 1st
  148. REAL(wp) :: ztau , ztau_sais ! wind intensity and of the seasonal cycle
  149. REAL(wp) :: ztime ! time in hour
  150. REAL(wp) :: ztimemax , ztimemin ! 21th June, and 21th decem. if date0 = 1st january
  151. REAL(wp) :: ztimemax1, ztimemin1 ! 21th June, and 21th decem. if date0 = 1st january
  152. REAL(wp) :: ztimemax2, ztimemin2 ! 21th June, and 21th decem. if date0 = 1st january
  153. REAL(wp) :: ztaun ! intensity
  154. REAL(wp) :: zemp_s, zemp_n, zemp_sais, ztstar
  155. REAL(wp) :: zcos_sais1, zcos_sais2, ztrp, zconv, t_star
  156. REAL(wp) :: zsumemp, zsurf
  157. REAL(wp) :: zrhoa = 1.22 ! Air density kg/m3
  158. REAL(wp) :: zcdrag = 1.5e-3 ! drag coefficient
  159. REAL(wp) :: ztx, zty, zmod, zcoef ! temporary variables
  160. REAL(wp) :: zyydd ! number of days in one year
  161. !!---------------------------------------------------------------------
  162. zyydd = REAL(nyear_len(1),wp)
  163. ! ---------------------------- !
  164. ! heat and freshwater fluxes !
  165. ! ---------------------------- !
  166. !same temperature, E-P as in HAZELEGER 2000
  167. zyear0 = ndate0 / 10000 ! initial year
  168. zmonth0 = ( ndate0 - zyear0 * 10000 ) / 100 ! initial month
  169. zday0 = ndate0 - zyear0 * 10000 - zmonth0 * 100 ! initial day betwen 1 and 30
  170. zday_year0 = ( zmonth0 - 1 ) * 30.+zday0 ! initial day betwen 1 and 360
  171. ! current day (in hours) since january the 1st of the current year
  172. ztime = REAL( kt ) * rdt / (rmmss * rhhmm) & ! total incrementation (in hours)
  173. & - (nyear - 1) * rjjhh * zyydd ! minus years since beginning of experiment (in hours)
  174. ztimemax1 = ((5.*30.)+21.)* 24. ! 21th june at 24h in hours
  175. ztimemin1 = ztimemax1 + rjjhh * zyydd / 2 ! 21th december in hours
  176. ztimemax2 = ((6.*30.)+21.)* 24. ! 21th july at 24h in hours
  177. ztimemin2 = ztimemax2 - rjjhh * zyydd / 2 ! 21th january in hours
  178. ! ! NB: rjjhh * zyydd / 4 = one seasonal cycle in hours
  179. ! amplitudes
  180. zemp_S = 0.7 ! intensity of COS in the South
  181. zemp_N = 0.8 ! intensity of COS in the North
  182. zemp_sais = 0.1
  183. zTstar = 28.3 ! intemsity from 28.3 a -5 deg
  184. ! 1/2 period between 21th June and 21th December and between 21th July and 21th January
  185. zcos_sais1 = COS( (ztime - ztimemax1) / (ztimemin1 - ztimemax1) * rpi )
  186. zcos_sais2 = COS( (ztime - ztimemax2) / (ztimemax2 - ztimemin2) * rpi )
  187. ztrp= - 40.e0 ! retroaction term on heat fluxes (W/m2/K)
  188. zconv = 3.16e-5 ! convertion factor: 1 m/yr => 3.16e-5 mm/s
  189. DO jj = 1, jpj
  190. DO ji = 1, jpi
  191. ! domain from 15 deg to 50 deg between 27 and 28 degC at 15N, -3
  192. ! and 13 degC at 50N 53.5 + or - 11 = 1/4 period :
  193. ! 64.5 in summer, 42.5 in winter
  194. t_star = zTstar * ( 1 + 1. / 50. * zcos_sais2 ) &
  195. & * COS( rpi * (gphit(ji,jj) - 5.) &
  196. & / ( 53.5 * ( 1 + 11 / 53.5 * zcos_sais2 ) * 2.) )
  197. ! 23.5 deg : tropics
  198. qsr (ji,jj) = 230 * COS( 3.1415 * ( gphit(ji,jj) - 23.5 * zcos_sais1 ) / ( 0.9 * 180 ) )
  199. qns (ji,jj) = ztrp * ( tsb(ji,jj,1,jp_tem) - t_star ) - qsr(ji,jj)
  200. IF( gphit(ji,jj) >= 14.845 .AND. 37.2 >= gphit(ji,jj) ) THEN ! zero at 37.8 deg, max at 24.6 deg
  201. emp (ji,jj) = zemp_S * zconv &
  202. & * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (24.6 - 37.2) ) &
  203. & * ( 1 - zemp_sais / zemp_S * zcos_sais1)
  204. ELSE
  205. emp (ji,jj) = - zemp_N * zconv &
  206. & * SIN( rpi / 2 * (gphit(ji,jj) - 37.2) / (46.8 - 37.2) ) &
  207. & * ( 1 - zemp_sais / zemp_N * zcos_sais1 )
  208. ENDIF
  209. END DO
  210. END DO
  211. ! Compute the emp flux such as its integration on the whole domain at each time is zero
  212. IF( nbench /= 1 ) THEN
  213. zsumemp = GLOB_SUM( emp(:,:) )
  214. zsurf = GLOB_SUM( tmask(:,:,1) )
  215. ! Default GYRE configuration
  216. zsumemp = zsumemp / zsurf
  217. ELSE
  218. ! Benchmark GYRE configuration (to allow the bit to bit comparison between Mpp/Mono case)
  219. zsumemp = 0.e0 ; zsurf = 0.e0
  220. ENDIF
  221. ! freshwater (mass flux) and update of qns with heat content of emp
  222. emp (:,:) = emp(:,:) - zsumemp * tmask(:,:,1) ! freshwater flux (=0 in domain average)
  223. sfx (:,:) = 0.0_wp ! no salt flux
  224. qns (:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp ! evap and precip are at SST
  225. ! ---------------------------- !
  226. ! momentum fluxes !
  227. ! ---------------------------- !
  228. ! same wind as in Wico
  229. !test date0 : ndate0 = 010203
  230. zyear0 = ndate0 / 10000
  231. zmonth0 = ( ndate0 - zyear0 * 10000 ) / 100
  232. zday0 = ndate0 - zyear0 * 10000 - zmonth0 * 100
  233. !Calculates nday_year, day since january 1st
  234. zday_year0 = (zmonth0-1)*30.+zday0
  235. !accumulates days of previous months of this year
  236. ! day (in hours) since january the 1st
  237. ztime = FLOAT( kt ) * rdt / (rmmss * rhhmm) & ! incrementation in hour
  238. & - (nyear - 1) * rjjhh * zyydd ! - nber of hours the precedent years
  239. ztimemax = ((5.*30.)+21.)* 24. ! 21th june in hours
  240. ztimemin = ztimemax + rjjhh * zyydd / 2 ! 21th december in hours
  241. ! ! NB: rjjhh * zyydd / 4 = 1 seasonal cycle in hours
  242. ! mean intensity at 0.105 ; srqt(2) because projected with 45deg angle
  243. ztau = 0.105 / SQRT( 2. )
  244. ! seasonal oscillation intensity
  245. ztau_sais = 0.015
  246. ztaun = ztau - ztau_sais * COS( (ztime - ztimemax) / (ztimemin - ztimemax) * rpi )
  247. DO jj = 1, jpj
  248. DO ji = 1, jpi
  249. ! domain from 15deg to 50deg and 1/2 period along 14deg
  250. ! so 5/4 of half period with seasonal cycle
  251. utau(ji,jj) = - ztaun * SIN( rpi * (gphiu(ji,jj) - 15.) / (29.-15.) )
  252. vtau(ji,jj) = ztaun * SIN( rpi * (gphiv(ji,jj) - 15.) / (29.-15.) )
  253. END DO
  254. END DO
  255. ! module of wind stress and wind speed at T-point
  256. zcoef = 1. / ( zrhoa * zcdrag )
  257. !CDIR NOVERRCHK
  258. DO jj = 2, jpjm1
  259. !CDIR NOVERRCHK
  260. DO ji = fs_2, fs_jpim1 ! vect. opt.
  261. ztx = utau(ji-1,jj ) + utau(ji,jj)
  262. zty = vtau(ji ,jj-1) + vtau(ji,jj)
  263. zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
  264. taum(ji,jj) = zmod
  265. wndm(ji,jj) = SQRT( zmod * zcoef )
  266. END DO
  267. END DO
  268. CALL lbc_lnk( taum(:,:), 'T', 1. ) ; CALL lbc_lnk( wndm(:,:), 'T', 1. )
  269. ! ---------------------------------- !
  270. ! control print at first time-step !
  271. ! ---------------------------------- !
  272. IF( kt == nit000 .AND. lwp ) THEN
  273. WRITE(numout,*)
  274. WRITE(numout,*)'sbc_gyre : analytical surface fluxes for GYRE configuration'
  275. WRITE(numout,*)'~~~~~~~~ '
  276. WRITE(numout,*)' nyear = ', nyear
  277. WRITE(numout,*)' nmonth = ', nmonth
  278. WRITE(numout,*)' nday = ', nday
  279. WRITE(numout,*)' nday_year = ', nday_year
  280. WRITE(numout,*)' ztime = ', ztime
  281. WRITE(numout,*)' ztimemax = ', ztimemax
  282. WRITE(numout,*)' ztimemin = ', ztimemin
  283. WRITE(numout,*)' ztimemax1 = ', ztimemax1
  284. WRITE(numout,*)' ztimemin1 = ', ztimemin1
  285. WRITE(numout,*)' ztimemax2 = ', ztimemax2
  286. WRITE(numout,*)' ztimemin2 = ', ztimemin2
  287. WRITE(numout,*)' zyear0 = ', zyear0
  288. WRITE(numout,*)' zmonth0 = ', zmonth0
  289. WRITE(numout,*)' zday0 = ', zday0
  290. WRITE(numout,*)' zday_year0 = ', zday_year0
  291. WRITE(numout,*)' zyydd = ', zyydd
  292. WRITE(numout,*)' zemp_S = ', zemp_S
  293. WRITE(numout,*)' zemp_N = ', zemp_N
  294. WRITE(numout,*)' zemp_sais = ', zemp_sais
  295. WRITE(numout,*)' zTstar = ', zTstar
  296. WRITE(numout,*)' zsumemp = ', zsumemp
  297. WRITE(numout,*)' zsurf = ', zsurf
  298. WRITE(numout,*)' ztrp = ', ztrp
  299. WRITE(numout,*)' zconv = ', zconv
  300. WRITE(numout,*)' ndastp = ', ndastp
  301. WRITE(numout,*)' adatrj = ', adatrj
  302. ENDIF
  303. !
  304. END SUBROUTINE sbc_gyre
  305. !!======================================================================
  306. END MODULE sbcana