trabbc.F90 9.5 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202
  1. MODULE trabbc
  2. !!==============================================================================
  3. !! *** MODULE trabbc ***
  4. !! Ocean active tracers: bottom boundary condition (geothermal heat flux)
  5. !!==============================================================================
  6. !! History : OPA ! 1999-10 (G. Madec) original code
  7. !! NEMO 1.0 ! 2002-08 (G. Madec) free form + modules
  8. !! - ! 2002-11 (A. Bozec) tra_bbc_init: original code
  9. !! 3.3 ! 2010-10 (G. Madec) dynamical allocation + suppression of key_trabbc
  10. !! - ! 2010-11 (G. Madec) use mbkt array (deepest ocean t-level)
  11. !!----------------------------------------------------------------------
  12. !!----------------------------------------------------------------------
  13. !! tra_bbc : update the tracer trend at ocean bottom
  14. !! tra_bbc_init : initialization of geothermal heat flux trend
  15. !!----------------------------------------------------------------------
  16. USE oce ! ocean variables
  17. USE dom_oce ! domain: ocean
  18. USE phycst ! physical constants
  19. USE trd_oce ! trends: ocean variables
  20. USE trdtra ! trends manager: tracers
  21. USE in_out_manager ! I/O manager
  22. USE iom ! I/O manager
  23. USE fldread ! read input fields
  24. USE lbclnk ! ocean lateral boundary conditions (or mpp link)
  25. USE lib_mpp ! distributed memory computing library
  26. USE prtctl ! Print control
  27. USE wrk_nemo ! Memory Allocation
  28. USE timing ! Timing
  29. IMPLICIT NONE
  30. PRIVATE
  31. PUBLIC tra_bbc ! routine called by step.F90
  32. PUBLIC tra_bbc_init ! routine called by opa.F90
  33. ! !!* Namelist nambbc: bottom boundary condition *
  34. LOGICAL, PUBLIC :: ln_trabbc !: Geothermal heat flux flag
  35. INTEGER :: nn_geoflx ! Geothermal flux (=1:constant flux, =2:read in file )
  36. REAL(wp) :: rn_geoflx_cst ! Constant value of geothermal heat flux
  37. REAL(wp), PUBLIC, DIMENSION(:,:), ALLOCATABLE :: qgh_trd0 ! geothermal heating trend
  38. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_qgh ! structure of input qgh (file informations, fields read)
  39. !! * Substitutions
  40. # include "domzgr_substitute.h90"
  41. !!----------------------------------------------------------------------
  42. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  43. !! $Id$
  44. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  45. !!----------------------------------------------------------------------
  46. CONTAINS
  47. SUBROUTINE tra_bbc( kt )
  48. !!----------------------------------------------------------------------
  49. !! *** ROUTINE tra_bbc ***
  50. !!
  51. !! ** Purpose : Compute the bottom boundary contition on temperature
  52. !! associated with geothermal heating and add it to the
  53. !! general trend of temperature equations.
  54. !!
  55. !! ** Method : The geothermal heat flux set to its constant value of
  56. !! 86.4 mW/m2 (Stein and Stein 1992, Huang 1999).
  57. !! The temperature trend associated to this heat flux through the
  58. !! ocean bottom can be computed once and is added to the temperature
  59. !! trend juste above the bottom at each time step:
  60. !! ta = ta + Qsf / (rau0 rcp e3T) for k= mbkt
  61. !! Where Qsf is the geothermal heat flux.
  62. !!
  63. !! ** Action : - update the temperature trends (ta) with the trend of
  64. !! the ocean bottom boundary condition
  65. !!
  66. !! References : Stein, C. A., and S. Stein, 1992, Nature, 359, 123-129.
  67. !! Emile-Geay and Madec, 2009, Ocean Science.
  68. !!----------------------------------------------------------------------
  69. INTEGER, INTENT(in) :: kt ! ocean time-step index
  70. !!
  71. INTEGER :: ji, jj, ik ! dummy loop indices
  72. REAL(wp) :: zqgh_trd ! geothermal heat flux trend
  73. REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrdt
  74. !!----------------------------------------------------------------------
  75. !
  76. IF( nn_timing == 1 ) CALL timing_start('tra_bbc')
  77. !
  78. IF( l_trdtra ) THEN ! Save ta and sa trends
  79. CALL wrk_alloc( jpi, jpj, jpk, ztrdt )
  80. ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
  81. ENDIF
  82. !
  83. ! ! Add the geothermal heat flux trend on temperature
  84. DO jj = 2, jpjm1
  85. DO ji = 2, jpim1
  86. ik = mbkt(ji,jj)
  87. zqgh_trd = qgh_trd0(ji,jj) / fse3t(ji,jj,ik)
  88. tsa(ji,jj,ik,jp_tem) = tsa(ji,jj,ik,jp_tem) + zqgh_trd
  89. END DO
  90. END DO
  91. !
  92. CALL lbc_lnk( tsa(:,:,:,jp_tem) , 'T', 1. )
  93. !
  94. IF( l_trdtra ) THEN ! Save the geothermal heat flux trend for diagnostics
  95. ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
  96. CALL trd_tra( kt, 'TRA', jp_tem, jptra_bbc, ztrdt )
  97. CALL wrk_dealloc( jpi, jpj, jpk, ztrdt )
  98. ENDIF
  99. !
  100. IF(ln_ctl) CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' bbc - Ta: ', mask1=tmask, clinfo3='tra-ta' )
  101. !
  102. IF( nn_timing == 1 ) CALL timing_stop('tra_bbc')
  103. !
  104. END SUBROUTINE tra_bbc
  105. SUBROUTINE tra_bbc_init
  106. !!----------------------------------------------------------------------
  107. !! *** ROUTINE tra_bbc_init ***
  108. !!
  109. !! ** Purpose : Compute once for all the trend associated with geothermal
  110. !! heating that will be applied at each time step at the
  111. !! last ocean level
  112. !!
  113. !! ** Method : Read the nambbc namelist and check the parameters.
  114. !!
  115. !! ** Input : - Namlist nambbc
  116. !! - NetCDF file : geothermal_heating.nc ( if necessary )
  117. !!
  118. !! ** Action : - read/fix the geothermal heat qgh_trd0
  119. !!----------------------------------------------------------------------
  120. USE iom
  121. !!
  122. INTEGER :: ji, jj ! dummy loop indices
  123. INTEGER :: inum ! temporary logical unit
  124. INTEGER :: ios ! Local integer output status for namelist read
  125. INTEGER :: ierror ! local integer
  126. !
  127. TYPE(FLD_N) :: sn_qgh ! informations about the geotherm. field to be read
  128. CHARACTER(len=256) :: cn_dir ! Root directory for location of ssr files
  129. !
  130. NAMELIST/nambbc/ln_trabbc, nn_geoflx, rn_geoflx_cst, sn_qgh, cn_dir
  131. !!----------------------------------------------------------------------
  132. REWIND( numnam_ref ) ! Namelist nambbc in reference namelist : Bottom momentum boundary condition
  133. READ ( numnam_ref, nambbc, IOSTAT = ios, ERR = 901)
  134. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbc in reference namelist', lwp )
  135. REWIND( numnam_cfg ) ! Namelist nambbc in configuration namelist : Bottom momentum boundary condition
  136. READ ( numnam_cfg, nambbc, IOSTAT = ios, ERR = 902 )
  137. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambbc in configuration namelist', lwp )
  138. IF(lwm) WRITE ( numond, nambbc )
  139. IF(lwp) THEN ! Control print
  140. WRITE(numout,*)
  141. WRITE(numout,*) 'tra_bbc : Bottom Boundary Condition (bbc), apply a Geothermal heating'
  142. WRITE(numout,*) '~~~~~~~ '
  143. WRITE(numout,*) ' Namelist nambbc : set bbc parameters'
  144. WRITE(numout,*) ' Apply a geothermal heating at ocean bottom ln_trabbc = ', ln_trabbc
  145. WRITE(numout,*) ' type of geothermal flux nn_geoflx = ', nn_geoflx
  146. WRITE(numout,*) ' Constant geothermal flux value rn_geoflx_cst = ', rn_geoflx_cst
  147. WRITE(numout,*)
  148. ENDIF
  149. IF( ln_trabbc ) THEN !== geothermal heating ==!
  150. !
  151. ALLOCATE( qgh_trd0(jpi,jpj) ) ! allocation
  152. !
  153. SELECT CASE ( nn_geoflx ) ! geothermal heat flux / (rauO * Cp)
  154. !
  155. CASE ( 1 ) !* constant flux
  156. IF(lwp) WRITE(numout,*) ' *** constant heat flux = ', rn_geoflx_cst
  157. qgh_trd0(:,:) = r1_rau0_rcp * rn_geoflx_cst
  158. !
  159. CASE ( 2 ) !* variable geothermal heat flux : read the geothermal fluxes in mW/m2
  160. IF(lwp) WRITE(numout,*) ' *** variable geothermal heat flux'
  161. !
  162. ALLOCATE( sf_qgh(1), STAT=ierror )
  163. IF( ierror > 0 ) THEN
  164. CALL ctl_stop( 'tra_bbc_init: unable to allocate sf_qgh structure' ) ;
  165. RETURN
  166. ENDIF
  167. ALLOCATE( sf_qgh(1)%fnow(jpi,jpj,1) )
  168. IF( sn_qgh%ln_tint )ALLOCATE( sf_qgh(1)%fdta(jpi,jpj,1,2) )
  169. ! fill sf_chl with sn_chl and control print
  170. CALL fld_fill( sf_qgh, (/ sn_qgh /), cn_dir, 'tra_bbc_init', &
  171. & 'bottom temperature boundary condition', 'nambbc' )
  172. CALL fld_read( nit000, 1, sf_qgh ) ! Read qgh data
  173. qgh_trd0(:,:) = r1_rau0_rcp * sf_qgh(1)%fnow(:,:,1) * 1.e-3 ! conversion in W/m2
  174. !
  175. CASE DEFAULT
  176. WRITE(ctmp1,*) ' bad flag value for nn_geoflx = ', nn_geoflx
  177. CALL ctl_stop( ctmp1 )
  178. !
  179. END SELECT
  180. !
  181. ELSE
  182. IF(lwp) WRITE(numout,*) ' *** no geothermal heat flux'
  183. ENDIF
  184. !
  185. END SUBROUTINE tra_bbc_init
  186. !!======================================================================
  187. END MODULE trabbc