trczdf.F90 8.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178
  1. MODULE trczdf
  2. !!==============================================================================
  3. !! *** MODULE trczdf ***
  4. !! Ocean Passive tracers : vertical diffusive trends
  5. !!=====================================================================
  6. !! History : 9.0 ! 2005-11 (G. Madec) Original code
  7. !! NEMO 3.0 ! 2008-01 (C. Ethe, G. Madec) merge TRC-TRA
  8. !!----------------------------------------------------------------------
  9. #if defined key_top
  10. !!----------------------------------------------------------------------
  11. !! 'key_top' TOP models
  12. !!----------------------------------------------------------------------
  13. !! trc_ldf : update the tracer trend with the lateral diffusion
  14. !! ldf_ctl : initialization, namelist read, and parameters control
  15. !!----------------------------------------------------------------------
  16. USE oce_trc ! ocean dynamics and active tracers
  17. USE trc ! ocean passive tracers variables
  18. USE trcnam_trp ! passive tracers transport namelist variables
  19. USE trazdf_exp ! vertical diffusion: explicit (tra_zdf_exp routine)
  20. USE trazdf_imp ! vertical diffusion: implicit (tra_zdf_imp routine)
  21. USE trd_oce
  22. USE trdtra
  23. USE prtctl_trc ! Print control
  24. IMPLICIT NONE
  25. PRIVATE
  26. PUBLIC trc_zdf ! called by step.F90
  27. PUBLIC trc_zdf_alloc ! called by nemogcm.F90
  28. INTEGER :: nzdf = 0 ! type vertical diffusion algorithm used
  29. ! ! defined from ln_zdf... namlist logicals)
  30. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) :: r2dt ! vertical profile time-step, = 2 rdttra
  31. ! ! except at nittrc000 (=rdttra) if neuler=0
  32. !! * Substitutions
  33. # include "domzgr_substitute.h90"
  34. # include "zdfddm_substitute.h90"
  35. # include "vectopt_loop_substitute.h90"
  36. !!----------------------------------------------------------------------
  37. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  38. !! $Id: trczdf.F90 4990 2014-12-15 16:42:49Z timgraham $
  39. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  40. !!----------------------------------------------------------------------
  41. CONTAINS
  42. INTEGER FUNCTION trc_zdf_alloc()
  43. !!----------------------------------------------------------------------
  44. !! *** ROUTINE trc_zdf_alloc ***
  45. !!----------------------------------------------------------------------
  46. ALLOCATE( r2dt(jpk) , STAT=trc_zdf_alloc )
  47. !
  48. IF( trc_zdf_alloc /= 0 ) CALL ctl_warn('trc_zdf_alloc : failed to allocate array.')
  49. !
  50. END FUNCTION trc_zdf_alloc
  51. SUBROUTINE trc_zdf( kt )
  52. !!----------------------------------------------------------------------
  53. !! *** ROUTINE trc_zdf ***
  54. !!
  55. !! ** Purpose : compute the vertical ocean tracer physics.
  56. !!---------------------------------------------------------------------
  57. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  58. !
  59. INTEGER :: jk, jn
  60. CHARACTER (len=22) :: charout
  61. REAL(wp), POINTER, DIMENSION(:,:,:,:) :: ztrtrd ! 4D workspace
  62. !!---------------------------------------------------------------------
  63. !
  64. IF( nn_timing == 1 ) CALL timing_start('trc_zdf')
  65. !
  66. IF( kt == nittrc000 ) CALL zdf_ctl ! initialisation & control of options
  67. IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN ! at nittrc000
  68. r2dt(:) = rdttrc(:) ! = rdttrc (use or restarting with Euler time stepping)
  69. ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN ! at nittrc000 or nittrc000+1
  70. r2dt(:) = 2. * rdttrc(:) ! = 2 rdttrc (leapfrog)
  71. ENDIF
  72. IF( l_trdtrc ) THEN
  73. CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrtrd )
  74. ztrtrd(:,:,:,:) = tra(:,:,:,:)
  75. ENDIF
  76. SELECT CASE ( nzdf ) ! compute lateral mixing trend and add it to the general trend
  77. CASE ( -1 ) ! esopa: test all possibility with control print
  78. CALL tra_zdf_exp( kt, nittrc000, 'TRC', r2dt, nn_trczdf_exp, trb, tra, jptra )
  79. WRITE(charout, FMT="('zdf1 ')") ; CALL prt_ctl_trc_info(charout)
  80. CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
  81. CALL tra_zdf_imp( kt, nittrc000, 'TRC', r2dt, trb, tra, jptra )
  82. WRITE(charout, FMT="('zdf2 ')") ; CALL prt_ctl_trc_info(charout)
  83. CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
  84. CASE ( 0 ) ; CALL tra_zdf_exp( kt, nittrc000, 'TRC', r2dt, nn_trczdf_exp, trb, tra, jptra ) ! explicit scheme
  85. CASE ( 1 ) ; CALL tra_zdf_imp( kt, nittrc000, 'TRC', r2dt, trb, tra, jptra ) ! implicit scheme
  86. END SELECT
  87. IF( l_trdtrc ) THEN ! save the vertical diffusive trends for further diagnostics
  88. DO jn = 1, jptra
  89. DO jk = 1, jpkm1
  90. ztrtrd(:,:,jk,jn) = ( ( tra(:,:,jk,jn) - trb(:,:,jk,jn) ) / r2dt(jk) ) - ztrtrd(:,:,jk,jn)
  91. END DO
  92. CALL trd_tra( kt, 'TRC', jn, jptra_zdf, ztrtrd(:,:,:,jn) )
  93. END DO
  94. CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd )
  95. ENDIF
  96. ! ! print mean trends (used for debugging)
  97. IF( ln_ctl ) THEN
  98. WRITE(charout, FMT="('zdf ')") ; CALL prt_ctl_trc_info(charout)
  99. CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
  100. END IF
  101. !
  102. IF( nn_timing == 1 ) CALL timing_stop('trc_zdf')
  103. !
  104. END SUBROUTINE trc_zdf
  105. SUBROUTINE zdf_ctl
  106. !!----------------------------------------------------------------------
  107. !! *** ROUTINE zdf_ctl ***
  108. !!
  109. !! ** Purpose : Choose the vertical mixing scheme
  110. !!
  111. !! ** Method : Set nzdf from ln_zdfexp
  112. !! nzdf = 0 explicit (time-splitting) scheme (ln_trczdf_exp=T)
  113. !! = 1 implicit (euler backward) scheme (ln_trczdf_exp=F)
  114. !! NB: The implicit scheme is required when using :
  115. !! - rotated lateral mixing operator
  116. !! - TKE, GLS or KPP vertical mixing scheme
  117. !!----------------------------------------------------------------------
  118. ! Define the vertical tracer physics scheme
  119. ! ==========================================
  120. ! Choice from ln_zdfexp already read in namelist in zdfini module
  121. IF( ln_trczdf_exp ) THEN ! use explicit scheme
  122. nzdf = 0
  123. ELSE ! use implicit scheme
  124. nzdf = 1
  125. ENDIF
  126. ! Force implicit schemes
  127. IF( ln_trcldf_iso ) nzdf = 1 ! iso-neutral lateral physics
  128. IF( ln_trcldf_hor .AND. ln_sco ) nzdf = 1 ! horizontal lateral physics in s-coordinate
  129. #if defined key_zdftke || defined key_zdfgls || defined key_zdfkpp
  130. nzdf = 1 ! TKE, GLS or KPP physics
  131. #endif
  132. IF( ln_trczdf_exp .AND. nzdf == 1 ) THEN
  133. CALL ctl_stop( 'trc_zdf : If using the rotated lateral mixing operator or TKE, GLS or KPP vertical scheme ', &
  134. & ' the implicit scheme is required, set ln_trczdf_exp = .false.' )
  135. ENDIF
  136. ! Test: esopa
  137. IF( lk_esopa ) nzdf = -1 ! All schemes used
  138. IF(lwp) THEN
  139. WRITE(numout,*)
  140. WRITE(numout,*) 'trc:zdf_ctl : vertical passive tracer physics scheme'
  141. WRITE(numout,*) '~~~~~~~~~~~'
  142. IF( nzdf == -1 ) WRITE(numout,*) ' ESOPA test All scheme used'
  143. IF( nzdf == 0 ) WRITE(numout,*) ' Explicit time-splitting scheme'
  144. IF( nzdf == 1 ) WRITE(numout,*) ' Implicit (euler backward) scheme'
  145. ENDIF
  146. END SUBROUTINE zdf_ctl
  147. #else
  148. !!----------------------------------------------------------------------
  149. !! Default option Empty module
  150. !!----------------------------------------------------------------------
  151. CONTAINS
  152. SUBROUTINE trc_zdf( kt )
  153. INTEGER, INTENT(in) :: kt
  154. WRITE(*,*) 'trc_zdf: You should not have seen this print! error?', kt
  155. END SUBROUTINE trc_zdf
  156. #endif
  157. !!==============================================================================
  158. END MODULE trczdf