trdtrc_oce.F90 10 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180
  1. MODULE trdtrc_oce
  2. !!======================================================================
  3. !! *** MODULE trdtrc_oce ***
  4. !! Ocean trends : set tracer and momentum trend variables
  5. !!======================================================================
  6. #if defined key_top || defined key_esopa
  7. !!----------------------------------------------------------------------
  8. !! 'key_top' TOP models
  9. !!----------------------------------------------------------------------
  10. USE par_oce ! ocean parameters
  11. USE par_trc ! passive tracers parameters
  12. IMPLICIT NONE
  13. PUBLIC
  14. ! !!* Namelist namtoptrd: diagnostics on passive tracers trends
  15. INTEGER :: nn_trd_trc !: time step frequency dynamics and tracers trends
  16. INTEGER :: nn_ctls_trc !: control surface type for trends vertical integration
  17. REAL(wp) :: rn_ucf_trc !: unit conversion factor (for netCDF trends outputs)
  18. LOGICAL :: ln_trdmxl_trc_instant !: flag to diagnose inst./mean ML trc trends
  19. LOGICAL :: ln_trdmxl_trc_restart !: flag to restart mixed-layer trc diagnostics
  20. CHARACTER(len=50) :: cn_trdrst_trc_in !: suffix of pass. tracer restart name (input)
  21. CHARACTER(len=50) :: cn_trdrst_trc_out !: suffix of pass. tracer restart name (output)
  22. LOGICAL, DIMENSION(jptra) :: ln_trdtrc !: large trends diagnostic to write or not (namelist)
  23. # if defined key_trdtrc && defined key_iomput
  24. LOGICAL, PARAMETER :: lk_trdtrc = .TRUE.
  25. # else
  26. LOGICAL, PARAMETER :: lk_trdtrc = .FALSE. !: ML trend flag
  27. # endif
  28. # if defined key_trdmxl_trc || defined key_esopa
  29. !!----------------------------------------------------------------------
  30. !! 'key_trdmxl_trc' mixed layer trends diagnostics
  31. !!----------------------------------------------------------------------
  32. LOGICAL, PARAMETER :: lk_trdmxl_trc = .TRUE. !: ML trend flag
  33. INTEGER, PARAMETER :: & !: mixed layer trends indices
  34. jpmxl_trc_xad = 1, & !: zonal advection
  35. jpmxl_trc_yad = 2, & !: meridonal =========
  36. jpmxl_trc_zad = 3, & !: vertical =========
  37. jpmxl_trc_ldf = 4, & !: lateral diffusion (geopot. or iso-neutral)
  38. jpmxl_trc_zdf = 5, & !: vertical diffusion (TKE)
  39. jpmxl_trc_bbl = 6, & !: bottom boundary layer (advective/diffusive)
  40. jpmxl_trc_dmp = 7, & !: internal restoring trend
  41. jpmxl_trc_sbc = 8, & !: forcing
  42. jpmxl_trc_sms = 9, & !: sources minus sinks trend
  43. ! jpmxl_trc_xxx = xx, & !: add here any additional trend (** AND UPDATE JPLTRD_TRC BELOW **)
  44. jpmxl_trc_radn = 10, & !: corr. trn<0 in trcrad
  45. jpmxl_trc_radb = 11, & !: corr. trb<0 in trcrad (like atf) (** MUST BE BEFORE THE LAST ONE **)
  46. jpmxl_trc_atf = 12 !: asselin trend (** MUST BE THE LAST ONE**)
  47. !! Trends diagnostics parameters
  48. !!---------------------------------------------------------------------
  49. INTEGER, PARAMETER :: jpltrd_trc = 12 !: number of mixed-layer trends arrays
  50. INTEGER :: jpktrd_trc !: max level for mixed-layer trends diag.
  51. !! Arrays used for diagnosing mixed-layer trends
  52. !!---------------------------------------------------------------------
  53. CHARACTER(LEN=80) :: clname_trc, ctrd_trc(jpltrd_trc+1,2)
  54. INTEGER, ALLOCATABLE, SAVE, DIMENSION(:,:) :: &
  55. nmld_trc , & !: mixed layer depth indexes
  56. nbol_trc !: mixed-layer depth indexes when read from file
  57. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: wkx_trc !:
  58. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: rmld_trc !: ML depth (m) corresponding to nmld_trc
  59. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: rmld_sum_trc !: needed to compute the leap-frog time mean of ML depth
  60. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: rmldbn_trc !: idem
  61. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: &
  62. tml_trc , & !: \ "now" mixed layer temperature/salinity
  63. tmlb_trc , & !: / and associated "before" fields
  64. tmlbb_trc , & !: \ idem, but valid at the 1rst time step of the
  65. tmlbn_trc , & !: / current analysis window
  66. tml_sum_trc, & !: mixed layer T, summed over the current analysis period
  67. tml_sumb_trc, & !: idem, but from the previous analysis period
  68. tmltrd_atf_sumb_trc, & !: Asselin trends, summed over the previous analysis period
  69. tmltrd_rad_sumb_trc !: trends due to trb correction in trcrad.F90, summed over the
  70. !: previous analysis period
  71. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: &
  72. tmlatfb_trc, tmlatfn_trc , & !: "before" Asselin contrib. at beginning of the averaging
  73. !: period (i.e. last contrib. from previous such period)
  74. !: and "now" Asselin contrib. to the ML trc. trends
  75. tmlatfm_trc, & !: accumulator for Asselin trends (needed for storage only)
  76. tmlradb_trc, tmlradn_trc , & !: similar to Asselin above, but for the trend due to trb
  77. !: correction in trcrad.F90
  78. tmlradm_trc !: accumulator for the previous trcrad trend
  79. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: &
  80. tmltrd_trc, & !: \ physical contributions to the total trend (for T/S),
  81. !: / cumulated over the current analysis window
  82. tmltrd_sum_trc, & !: sum of these trends over the analysis period
  83. tmltrd_csum_ln_trc, & !: now cumulated sum of trends over the "lower triangle"
  84. tmltrd_csum_ub_trc !: before (prev. analysis period) cumulated sum over the
  85. !: upper triangle
  86. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: &
  87. tmltrdm_trc !: total cumulative trends over the analysis window
  88. # else
  89. LOGICAL, PARAMETER :: lk_trdmxl_trc = .FALSE. !: ML trend flag
  90. # endif
  91. # if defined key_pisces_reduced
  92. CHARACTER(LEN=80) :: clname_bio, ctrd_bio(jpdiabio,2)
  93. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: &
  94. tmltrd_bio, & !: \ biological contributions to the total trend ,
  95. !: / cumulated over the current analysis window
  96. tmltrd_sum_bio, & !: sum of these trends over the analysis period
  97. tmltrd_csum_ln_bio, & !: now cumulated sum of trends over the "lower triangle"
  98. tmltrd_csum_ub_bio !: before (prev. analysis period) cumulated sum over the
  99. !: upper triangle
  100. #endif
  101. !!----------------------------------------------------------------------
  102. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  103. !! $Id: trdtrc_oce.F90 2355 2015-05-20 07:11:50Z ufla $
  104. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  105. !!----------------------------------------------------------------------
  106. CONTAINS
  107. INTEGER FUNCTION trd_trc_oce_alloc()
  108. !!----------------------------------------------------------------------
  109. !! *** ROUTINE trd_trc_oce_alloc ***
  110. !!----------------------------------------------------------------------
  111. USE lib_mpp, ONLY: ctl_warn
  112. INTEGER :: ierr(2)
  113. !!----------------------------------------------------------------------
  114. ierr(:) = 0
  115. !
  116. # if defined key_trdmxl_trc
  117. ALLOCATE(nmld_trc(jpi,jpj), nbol_trc(jpi,jpj), &
  118. wkx_trc(jpi,jpj,jpk), rmld_trc(jpi,jpj), &
  119. rmld_sum_trc(jpi,jpj), rmldbn_trc(jpi,jpj), &
  120. tml_trc(jpi,jpj,jptra), tmlb_trc(jpi,jpj,jptra), &
  121. tmlbb_trc(jpi,jpj,jptra), tmlbn_trc(jpi,jpj,jptra), &
  122. tml_sum_trc(jpi,jpj,jptra), tml_sumb_trc(jpi,jpj,jptra), &
  123. tmltrd_atf_sumb_trc(jpi,jpj,jptra), &
  124. tmltrd_rad_sumb_trc(jpi,jpj,jptra), &
  125. !
  126. tmlatfb_trc(jpi,jpj,jptra), tmlatfn_trc(jpi,jpj,jptra), &
  127. tmlatfm_trc(jpi,jpj,jptra), tmlradb_trc(jpi,jpj,jptra), &
  128. tmlradn_trc(jpi,jpj,jptra), tmlradm_trc(jpi,jpj,jptra), &
  129. !
  130. tmltrd_trc(jpi,jpj,jpltrd_trc,jptra) , &
  131. tmltrd_sum_trc(jpi,jpj,jpltrd_trc,jptra) , &
  132. tmltrd_csum_ln_trc(jpi,jpj,jpltrd_trc,jptra) , &
  133. tmltrd_csum_ub_trc(jpi,jpj,jpltrd_trc,jptra) , &
  134. !
  135. tmltrdm_trc(jpi,jpj,jptra) , STAT=ierr(1) )
  136. #endif
  137. !
  138. # if defined key_pisces_reduced
  139. ALLOCATE( tmltrd_bio (jpi,jpj,jpdiabio) , &
  140. & tmltrd_sum_bio (jpi,jpj,jpdiabio) , &
  141. & tmltrd_csum_ln_bio(jpi,jpj,jpdiabio) , &
  142. & tmltrd_csum_ub_bio(jpi,jpj,jpdiabio) , STAT=ierr(2) )
  143. # endif
  144. !
  145. trd_trc_oce_alloc = MAXVAL(ierr)
  146. !
  147. IF( trd_trc_oce_alloc /= 0 ) CALL ctl_warn('trd_trc_oce_alloc: failed to allocate arrays')
  148. !
  149. # if defined key_trdmxl_trc
  150. jpktrd_trc = jpk ! Initialise what used to be a parameter - max level for mixed-layer trends diag.
  151. # endif
  152. !
  153. END FUNCTION trd_trc_oce_alloc
  154. #else
  155. !!----------------------------------------------------------------------
  156. !! Empty module : No passive tracer
  157. !!----------------------------------------------------------------------
  158. #endif
  159. !!======================================================================
  160. END MODULE trdtrc_oce