sbcflx.F90 9.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180
  1. MODULE sbcflx
  2. !!======================================================================
  3. !! *** MODULE sbcflx ***
  4. !! Ocean forcing: momentum, heat and freshwater flux formulation
  5. !!=====================================================================
  6. !! History : 1.0 ! 2006-06 (G. Madec) Original code
  7. !! 3.3 ! 2010-10 (S. Masson) add diurnal cycle
  8. !!----------------------------------------------------------------------
  9. !!----------------------------------------------------------------------
  10. !! namflx : flux formulation namlist
  11. !! sbc_flx : flux formulation as ocean surface boundary condition (forced mode, fluxes read in NetCDF files)
  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 sbcdcy ! surface boundary condition: diurnal cycle on qsr
  17. USE phycst ! physical constants
  18. USE fldread ! read input fields
  19. USE iom ! IOM library
  20. USE in_out_manager ! I/O manager
  21. USE lib_mpp ! distribued memory computing library
  22. USE lbclnk ! ocean lateral boundary conditions (or mpp link)
  23. IMPLICIT NONE
  24. PRIVATE
  25. PUBLIC sbc_flx ! routine called by step.F90
  26. INTEGER , PARAMETER :: jpfld = 5 ! maximum number of files to read
  27. INTEGER , PARAMETER :: jp_utau = 1 ! index of wind stress (i-component) file
  28. INTEGER , PARAMETER :: jp_vtau = 2 ! index of wind stress (j-component) file
  29. INTEGER , PARAMETER :: jp_qtot = 3 ! index of total (non solar+solar) heat file
  30. INTEGER , PARAMETER :: jp_qsr = 4 ! index of solar heat file
  31. INTEGER , PARAMETER :: jp_emp = 5 ! index of evaporation-precipation file
  32. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf ! structure of input fields (file informations, fields read)
  33. !! * Substitutions
  34. # include "domzgr_substitute.h90"
  35. # include "vectopt_loop_substitute.h90"
  36. !!----------------------------------------------------------------------
  37. !! NEMO/OPA 3.3 , NEMO-consortium (2010)
  38. !! $Id: sbcflx.F90 4990 2014-12-15 16:42:49Z timgraham $
  39. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  40. !!----------------------------------------------------------------------
  41. CONTAINS
  42. SUBROUTINE sbc_flx( kt )
  43. !!---------------------------------------------------------------------
  44. !! *** ROUTINE sbc_flx ***
  45. !!
  46. !! ** Purpose : provide at each time step the surface ocean fluxes
  47. !! (momentum, heat, freshwater and runoff)
  48. !!
  49. !! ** Method : - READ each fluxes in NetCDF files:
  50. !! i-component of the stress utau (N/m2)
  51. !! j-component of the stress vtau (N/m2)
  52. !! net downward heat flux qtot (watt/m2)
  53. !! net downward radiative flux qsr (watt/m2)
  54. !! net upward freshwater (evapo - precip) emp (kg/m2/s)
  55. !!
  56. !! CAUTION : - never mask the surface stress fields
  57. !! - the stress is assumed to be in the (i,j) mesh referential
  58. !!
  59. !! ** Action : update at each time-step
  60. !! - utau, vtau i- and j-component of the wind stress
  61. !! - taum wind stress module at T-point
  62. !! - wndm 10m wind module at T-point
  63. !! - qns non solar heat flux including heat flux due to emp
  64. !! - qsr solar heat flux
  65. !! - emp upward mass flux (evap. - precip.)
  66. !! - sfx salt flux; set to zero at nit000 but possibly non-zero
  67. !! if ice is present (computed in limsbc(_2).F90)
  68. !!----------------------------------------------------------------------
  69. INTEGER, INTENT(in) :: kt ! ocean time step
  70. !!
  71. INTEGER :: ji, jj, jf ! dummy indices
  72. INTEGER :: ierror ! return error code
  73. INTEGER :: ios ! Local integer output status for namelist read
  74. REAL(wp) :: zfact ! temporary scalar
  75. REAL(wp) :: zrhoa = 1.22 ! Air density kg/m3
  76. REAL(wp) :: zcdrag = 1.5e-3 ! drag coefficient
  77. REAL(wp) :: ztx, zty, zmod, zcoef ! temporary variables
  78. !!
  79. CHARACTER(len=100) :: cn_dir ! Root directory for location of flx files
  80. TYPE(FLD_N), DIMENSION(jpfld) :: slf_i ! array of namelist information structures
  81. TYPE(FLD_N) :: sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp ! informations about the fields to be read
  82. NAMELIST/namsbc_flx/ cn_dir, sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp
  83. !!---------------------------------------------------------------------
  84. !
  85. IF( kt == nit000 ) THEN ! First call kt=nit000
  86. ! set file information
  87. REWIND( numnam_ref ) ! Namelist namsbc_flx in reference namelist : Files for fluxes
  88. READ ( numnam_ref, namsbc_flx, IOSTAT = ios, ERR = 901)
  89. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in reference namelist', lwp )
  90. REWIND( numnam_cfg ) ! Namelist namsbc_flx in configuration namelist : Files for fluxes
  91. READ ( numnam_cfg, namsbc_flx, IOSTAT = ios, ERR = 902 )
  92. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in configuration namelist', lwp )
  93. IF(lwm) WRITE ( numond, namsbc_flx )
  94. !
  95. ! ! check: do we plan to use ln_dm2dc with non-daily forcing?
  96. IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 ) &
  97. & CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' )
  98. !
  99. ! ! store namelist information in an array
  100. slf_i(jp_utau) = sn_utau ; slf_i(jp_vtau) = sn_vtau
  101. slf_i(jp_qtot) = sn_qtot ; slf_i(jp_qsr ) = sn_qsr
  102. slf_i(jp_emp ) = sn_emp
  103. !
  104. ALLOCATE( sf(jpfld), STAT=ierror ) ! set sf structure
  105. IF( ierror > 0 ) THEN
  106. CALL ctl_stop( 'sbc_flx: unable to allocate sf structure' ) ; RETURN
  107. ENDIF
  108. DO ji= 1, jpfld
  109. ALLOCATE( sf(ji)%fnow(jpi,jpj,1) )
  110. IF( slf_i(ji)%ln_tint ) ALLOCATE( sf(ji)%fdta(jpi,jpj,1,2) )
  111. END DO
  112. ! ! fill sf with slf_i and control print
  113. CALL fld_fill( sf, slf_i, cn_dir, 'sbc_flx', 'flux formulation for ocean surface boundary condition', 'namsbc_flx' )
  114. !
  115. sfx(:,:) = 0.0_wp ! salt flux due to freezing/melting (non-zero only if ice is present; set in limsbc(_2).F90)
  116. !
  117. ENDIF
  118. CALL fld_read( kt, nn_fsbc, sf ) ! input fields provided at the current time-step
  119. IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN ! update ocean fluxes at each SBC frequency
  120. IF( ln_dm2dc ) THEN ; qsr(:,:) = sbc_dcy( sf(jp_qsr)%fnow(:,:,1) ) ! modify now Qsr to include the diurnal cycle
  121. ELSE ; qsr(:,:) = sf(jp_qsr)%fnow(:,:,1)
  122. ENDIF
  123. !CDIR COLLAPSE
  124. DO jj = 1, jpj ! set the ocean fluxes from read fields
  125. DO ji = 1, jpi
  126. utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1)
  127. vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1)
  128. qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj,1) - sf(jp_qsr)%fnow(ji,jj,1)
  129. emp (ji,jj) = sf(jp_emp )%fnow(ji,jj,1)
  130. END DO
  131. END DO
  132. ! ! add to qns the heat due to e-p
  133. qns(:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp ! mass flux is at SST
  134. !
  135. ! ! module of wind stress and wind speed at T-point
  136. zcoef = 1. / ( zrhoa * zcdrag )
  137. !CDIR NOVERRCHK
  138. DO jj = 2, jpjm1
  139. !CDIR NOVERRCHK
  140. DO ji = fs_2, fs_jpim1 ! vect. opt.
  141. ztx = utau(ji-1,jj ) + utau(ji,jj)
  142. zty = vtau(ji ,jj-1) + vtau(ji,jj)
  143. zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
  144. taum(ji,jj) = zmod
  145. wndm(ji,jj) = SQRT( zmod * zcoef )
  146. END DO
  147. END DO
  148. taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1)
  149. CALL lbc_lnk( taum(:,:), 'T', 1. ) ; CALL lbc_lnk( wndm(:,:), 'T', 1. )
  150. IF( nitend-nit000 <= 100 .AND. lwp ) THEN ! control print (if less than 100 time-step asked)
  151. WRITE(numout,*)
  152. WRITE(numout,*) ' read daily momentum, heat and freshwater fluxes OK'
  153. DO jf = 1, jpfld
  154. IF( jf == jp_utau .OR. jf == jp_vtau ) zfact = 1.
  155. IF( jf == jp_qtot .OR. jf == jp_qsr ) zfact = 0.1
  156. IF( jf == jp_emp ) zfact = 86400.
  157. WRITE(numout,*)
  158. WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar), ' * ', zfact
  159. CALL prihre( sf(jf)%fnow, jpi, jpj, 1, jpi, 20, 1, jpj, 10, zfact, numout )
  160. END DO
  161. CALL FLUSH(numout)
  162. ENDIF
  163. !
  164. ENDIF
  165. !
  166. END SUBROUTINE sbc_flx
  167. !!======================================================================
  168. END MODULE sbcflx