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/branches/UKMO/NEMO_4.0.4_momentum_trends_iceoc_drag/src/OCE/TRD – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.4_momentum_trends_iceoc_drag/src/OCE/TRD/trdini.F90 @ 15197

Last change on this file since 15197 was 15197, checked in by davestorkey, 3 years ago

UKMO/NEMO_4.0.4_momentum_trends_iceoc_drag: Science changes.

File size: 6.0 KB
Line 
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
13   USE sbc_oce        ! for sea ice flag and ice-ocean stresses
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)
19   USE trdvor         ! trends: vertical averaged vorticity
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   !! * Substitutions
29#  include "vectopt_loop_substitute.h90"
30   !!----------------------------------------------------------------------
31   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
32   !! $Id$
33   !! Software governed by the CeCILL license (see ./LICENSE)
34   !!----------------------------------------------------------------------
35CONTAINS
36
37   SUBROUTINE trd_init
38      !!----------------------------------------------------------------------
39      !!                  ***  ROUTINE trd_init  ***
40      !!
41      !! ** Purpose :   Initialization of trend diagnostics
42      !!----------------------------------------------------------------------
43      INTEGER ::   ios   ! local integer
44      !!
45      NAMELIST/namtrd/ ln_dyn_trd, ln_KE_trd, ln_vor_trd, ln_dyn_mxl,   &
46         &             ln_tra_trd, ln_PE_trd, ln_glo_trd, ln_tra_mxl, nn_trd 
47      !!----------------------------------------------------------------------
48      !
49      REWIND( numnam_ref )              ! Namelist namtrd in reference namelist : trends diagnostic
50      READ  ( numnam_ref, namtrd, IOSTAT = ios, ERR = 901 )
51901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrd in reference namelist' )
52      !
53      REWIND( numnam_cfg )              ! Namelist namtrd in configuration namelist : trends diagnostic
54      READ  ( numnam_cfg, namtrd, IOSTAT = ios, ERR = 902 )
55902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrd in configuration namelist' )
56      IF(lwm) WRITE( numond, namtrd )
57      !
58      IF(lwp) THEN                  ! control print
59         WRITE(numout,*)
60         WRITE(numout,*) 'trd_init : Momentum/Tracers trends'
61         WRITE(numout,*) '~~~~~~~~'
62         WRITE(numout,*) '   Namelist namtrd : set trends parameters'
63         WRITE(numout,*) '      global domain averaged dyn & tra trends   ln_glo_trd  = ', ln_glo_trd
64         WRITE(numout,*) '      U & V trends: 3D output                   ln_dyn_trd  = ', ln_dyn_trd
65         WRITE(numout,*) '      U & V trends: Mixed Layer averaged        ln_dyn_mxl  = ', ln_dyn_mxl
66         WRITE(numout,*) '      T & S trends: 3D output                   ln_tra_trd  = ', ln_tra_trd
67         WRITE(numout,*) '      T & S trends: Mixed Layer averaged        ln_tra_mxl  = ', ln_tra_mxl
68         WRITE(numout,*) '      Kinetic   Energy trends                   ln_KE_trd   = ', ln_KE_trd
69         WRITE(numout,*) '      Potential Energy trends                   ln_PE_trd   = ', ln_PE_trd
70         WRITE(numout,*) '      Barotropic vorticity trends               ln_vor_trd  = ', ln_vor_trd
71         !
72         WRITE(numout,*) '      frequency of trends diagnostics (glo)     nn_trd      = ', nn_trd
73      ENDIF
74      !
75      !                             ! trend extraction flags 
76      l_trdtra = .FALSE.                                                       ! tracers 
77      IF ( ln_tra_trd .OR. ln_PE_trd .OR. ln_tra_mxl .OR.   &
78         & ln_glo_trd                                       )   l_trdtra = .TRUE. 
79      !
80      l_trddyn = .FALSE.                                                       ! momentum
81      IF ( ln_dyn_trd .OR. ln_KE_trd .OR. ln_dyn_mxl .OR.   &
82         & ln_vor_trd .OR. ln_glo_trd                       )   l_trddyn = .TRUE.
83      !
84
85      ! Allocate (partial) ice-ocean stresses (only used for dynamics trends diagnostics).
86      IF( l_trddyn .and. nn_ice == 2 ) ALLOCATE( uiceoc(jpi,jpj), uiceoc_b(jpi,jpj), &
87                                                 viceoc(jpi,jpj), viceoc_b(jpi,jpj), &
88                                                 uiceoc_iceimp(jpi,jpj), uiceoc_iceimp_b(jpi,jpj), &
89                                                 viceoc_iceimp(jpi,jpj), viceoc_iceimp_b(jpi,jpj) )
90
91!!gm check the stop below     
92      IF( ln_dyn_mxl )   CALL ctl_stop( 'ML diag on momentum are not yet coded we stop' )
93      !
94
95!!gm end
96      IF( ln_tra_mxl .OR. ln_vor_trd )   CALL ctl_stop( 'ML tracer and Barotropic vorticity diags are still using old IOIPSL' )
97!!gm end
98      !
99!      IF( .NOT.ln_linssh .AND. ( l_trdtra .OR. l_trddyn ) )  CALL ctl_stop( 'trend diagnostics with variable volume not validated' )
100     
101!!gm  : Potential BUG : 3D output only for vector invariant form!  add a ctl_stop or code the flux form case
102!!gm  : bug/pb for vertical advection of tracer in vvl case: add T.dt[eta] in the output...
103
104      !                             ! diagnostic initialization 
105      IF( ln_glo_trd )   CALL trd_glo_init      ! global domain averaged trends
106      IF( ln_tra_mxl )   CALL trd_mxl_init      ! mixed-layer          trends 
107      IF( ln_vor_trd )   CALL trd_vor_init      ! barotropic vorticity trends
108      IF( ln_KE_trd  )   CALL trd_ken_init      ! 3D Kinetic    energy trends
109      IF( ln_PE_trd  )   CALL trd_pen_init      ! 3D Potential  energy trends
110      !
111   END SUBROUTINE trd_init
112
113   !!======================================================================
114END MODULE trdini
Note: See TracBrowser for help on using the repository browser.