New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
trdini.F90 in NEMO/trunk/src/OCE/TRD – NEMO

source: NEMO/trunk/src/OCE/TRD/trdini.F90

Last change on this file was 14834, checked in by hadcv, 3 years ago

#2600: Merge in dev_r14273_HPC-02_Daley_Tiling

  • Property svn:keywords set to Id
File size: 5.5 KB
RevLine 
[4619]1MODULE trdini
2   !!======================================================================
3   !!                       ***  MODULE  trdini  ***
4   !! Ocean diagnostics:  ocean tracers and dynamic trends
5   !!=====================================================================
6   !! History :   3.5  !  2012-02  (G. Madec) add 3D trends output for T, S, U, V, PE and KE
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   trd_init      : initialization step
11   !!----------------------------------------------------------------------
12   USE dom_oce        ! ocean domain
[14090]13   USE domtile
[4619]14   USE trd_oce        ! trends: ocean variables
15   USE trdken         ! trends: 3D kinetic   energy
16   USE trdpen         ! trends: 3D potential energy
17   USE trdglo         ! trends: global domain averaged tracers and dynamics
18   USE trdmxl         ! trends: mixed layer averaged trends (tracer only)
[14072]19   USE trdvor         ! trends: vertical averaged vorticity
[4619]20   USE in_out_manager ! I/O manager
21   USE lib_mpp        ! MPP library
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   trd_init   ! called by nemogcm.F90 module
27
28   !!----------------------------------------------------------------------
[9598]29   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[5215]30   !! $Id$
[10068]31   !! Software governed by the CeCILL license (see ./LICENSE)
[4619]32   !!----------------------------------------------------------------------
33CONTAINS
34
[12377]35   SUBROUTINE trd_init( Kmm )
[4619]36      !!----------------------------------------------------------------------
37      !!                  ***  ROUTINE trd_init  ***
[14072]38      !!
[4619]39      !! ** Purpose :   Initialization of trend diagnostics
40      !!----------------------------------------------------------------------
[12377]41      INTEGER, INTENT(in) ::   Kmm  ! time level index
[4619]42      INTEGER ::   ios   ! local integer
43      !!
44      NAMELIST/namtrd/ ln_dyn_trd, ln_KE_trd, ln_vor_trd, ln_dyn_mxl,   &
[14072]45         &             ln_tra_trd, ln_PE_trd, ln_glo_trd, ln_tra_mxl, nn_trd
[4619]46      !!----------------------------------------------------------------------
47      !
48      READ  ( numnam_ref, namtrd, IOSTAT = ios, ERR = 901 )
[11536]49901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrd in reference namelist' )
[4619]50      !
51      READ  ( numnam_cfg, namtrd, IOSTAT = ios, ERR = 902 )
[11536]52902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrd in configuration namelist' )
[4957]53      IF(lwm) WRITE( numond, namtrd )
[4619]54      !
55      IF(lwp) THEN                  ! control print
56         WRITE(numout,*)
[7646]57         WRITE(numout,*) 'trd_init : Momentum/Tracers trends'
58         WRITE(numout,*) '~~~~~~~~'
[4619]59         WRITE(numout,*) '   Namelist namtrd : set trends parameters'
60         WRITE(numout,*) '      global domain averaged dyn & tra trends   ln_glo_trd  = ', ln_glo_trd
61         WRITE(numout,*) '      U & V trends: 3D output                   ln_dyn_trd  = ', ln_dyn_trd
62         WRITE(numout,*) '      U & V trends: Mixed Layer averaged        ln_dyn_mxl  = ', ln_dyn_mxl
63         WRITE(numout,*) '      T & S trends: 3D output                   ln_tra_trd  = ', ln_tra_trd
64         WRITE(numout,*) '      T & S trends: Mixed Layer averaged        ln_tra_mxl  = ', ln_tra_mxl
65         WRITE(numout,*) '      Kinetic   Energy trends                   ln_KE_trd   = ', ln_KE_trd
66         WRITE(numout,*) '      Potential Energy trends                   ln_PE_trd   = ', ln_PE_trd
67         WRITE(numout,*) '      Barotropic vorticity trends               ln_vor_trd  = ', ln_vor_trd
68         !
69         WRITE(numout,*) '      frequency of trends diagnostics (glo)     nn_trd      = ', nn_trd
70      ENDIF
71      !
[14072]72      !                             ! trend extraction flags
73      l_trdtra = .FALSE.                                                       ! tracers
[4619]74      IF ( ln_tra_trd .OR. ln_PE_trd .OR. ln_tra_mxl .OR.   &
[14072]75         & ln_glo_trd                                       )   l_trdtra = .TRUE.
[4619]76      !
77      l_trddyn = .FALSE.                                                       ! momentum
78      IF ( ln_dyn_trd .OR. ln_KE_trd .OR. ln_dyn_mxl .OR.   &
79         & ln_vor_trd .OR. ln_glo_trd                       )   l_trddyn = .TRUE.
80      !
81
[14072]82!!gm check the stop below
[4619]83      IF( ln_dyn_mxl )   CALL ctl_stop( 'ML diag on momentum are not yet coded we stop' )
84      !
85
86!!gm end
87      IF( ln_tra_mxl .OR. ln_vor_trd )   CALL ctl_stop( 'ML tracer and Barotropic vorticity diags are still using old IOIPSL' )
88!!gm end
89      !
[7646]90!      IF( .NOT.ln_linssh .AND. ( l_trdtra .OR. l_trddyn ) )  CALL ctl_stop( 'trend diagnostics with variable volume not validated' )
[13982]91
92      IF( ln_tile .AND. ( l_trdtra .OR. l_trddyn ) ) THEN
93         CALL ctl_warn('Tiling is not yet implemented for the trends diagnostics; ln_tile is forced to FALSE')
94         ln_tile = .FALSE.
[14834]95         CALL dom_tile_init
[13982]96      ENDIF
97
[4619]98!!gm  : Potential BUG : 3D output only for vector invariant form!  add a ctl_stop or code the flux form case
[14072]99!!gm  : bug/pb for vertical advection of tracer in vvl case: add T.dt[eta] in the output...
[4619]100
[14072]101      !                             ! diagnostic initialization
[12377]102      IF( ln_glo_trd )   CALL trd_glo_init( Kmm )      ! global domain averaged trends
[14072]103      IF( ln_tra_mxl )   CALL trd_mxl_init      ! mixed-layer          trends
[4619]104      IF( ln_vor_trd )   CALL trd_vor_init      ! barotropic vorticity trends
105      IF( ln_KE_trd  )   CALL trd_ken_init      ! 3D Kinetic    energy trends
106      IF( ln_PE_trd  )   CALL trd_pen_init      ! 3D Potential  energy trends
107      !
108   END SUBROUTINE trd_init
109
110   !!======================================================================
111END MODULE trdini
Note: See TracBrowser for help on using the repository browser.