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.
trdpen.F90 in NEMO/trunk/src/OCE/TRD – NEMO

source: NEMO/trunk/src/OCE/TRD/trdpen.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 7.3 KB
Line 
1MODULE trdpen
2   !!======================================================================
3   !!                       ***  MODULE  trdpen  ***
4   !! Ocean diagnostics:  Potential Energy trends
5   !!=====================================================================
6   !! History :  3.5  !  2012-02  (G. Madec) original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   trd_pen       : compute and output Potential Energy trends from T & S trends
11   !!   trd_pen_init  : initialisation of PE trends
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean dynamics and tracers variables
14   USE dom_oce        ! ocean domain
15   USE sbc_oce        ! surface boundary condition: ocean
16   USE zdf_oce        ! ocean vertical physics
17   USE trd_oce        ! trends: ocean variables
18   USE eosbn2         ! equation of state and related derivatives
19   USE ldftra         ! lateral diffusion: eddy diffusivity & EIV coeff.
20   USE zdfddm         ! vertical physics: double diffusion
21   USE phycst         ! physical constants
22   !
23   USE in_out_manager ! I/O manager
24   USE iom            ! I/O manager library
25   USE lib_mpp        ! MPP library
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   trd_pen        ! called by all trdtra module
31   PUBLIC   trd_pen_init   ! called by all nemogcm module
32
33   INTEGER ::   nkstp   ! current time step
34
35   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   rab_pe   ! partial derivatives of PE anomaly with respect to T and S
36
37   !!----------------------------------------------------------------------
38   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
39   !! $Id$
40   !! Software governed by the CeCILL license (see ./LICENSE)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   INTEGER FUNCTION trd_pen_alloc()
45      !!---------------------------------------------------------------------
46      !!                  ***  FUNCTION trd_tra_alloc  ***
47      !!---------------------------------------------------------------------
48      ALLOCATE( rab_pe(jpi,jpj,jpk,jpts) , STAT= trd_pen_alloc )
49      !
50      CALL mpp_sum ( 'trdpen', trd_pen_alloc )
51      IF( trd_pen_alloc /= 0 )   CALL ctl_stop( 'STOP',  'trd_pen_alloc: failed to allocate arrays'  )
52   END FUNCTION trd_pen_alloc
53
54
55   SUBROUTINE trd_pen( ptrdx, ptrdy, ktrd, kt, pdt, Kmm )
56      !!---------------------------------------------------------------------
57      !!                  ***  ROUTINE trd_tra_mng  ***
58      !!
59      !! ** Purpose :   Dispatch all trends computation, e.g. 3D output, integral
60      !!                constraints, barotropic vorticity, kinetic enrgy,
61      !!                potential energy, and/or mixed layer budget.
62      !!----------------------------------------------------------------------
63      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   ptrdx, ptrdy   ! Temperature & Salinity trends
64      INTEGER                   , INTENT(in) ::   ktrd           ! tracer trend index
65      INTEGER                   , INTENT(in) ::   kt             ! time step index
66      INTEGER                   , INTENT(in) ::   Kmm            ! time level index
67      REAL(wp)                  , INTENT(in) ::   pdt            ! time step [s]
68      !
69      INTEGER ::   jk                                            ! dummy loop indices
70      REAL(wp), ALLOCATABLE, DIMENSION(:,:)      ::   z2d            ! 2D workspace
71      REAL(wp), DIMENSION(jpi,jpj,jpk)           ::   zpe            ! 3D workspace
72      !!----------------------------------------------------------------------
73      !
74      zpe(:,:,:) = 0._wp
75      !
76      IF( kt /= nkstp ) THEN     ! full eos: set partial derivatives at the 1st call of kt time step
77         nkstp = kt
78         CALL eos_pen( ts(:,:,:,:,Kmm), rab_PE, zpe, Kmm )
79         CALL iom_put( "alphaPE", rab_pe(:,:,:,jp_tem) )
80         CALL iom_put( "betaPE" , rab_pe(:,:,:,jp_sal) )
81         CALL iom_put( "PEanom" , zpe )
82      ENDIF
83      !
84      zpe(:,:,jpk) = 0._wp
85      DO jk = 1, jpkm1
86         zpe(:,:,jk) = ( - ( rab_n(:,:,jk,jp_tem) + rab_pe(:,:,jk,jp_tem) ) * ptrdx(:,:,jk)   &
87            &            + ( rab_n(:,:,jk,jp_sal) + rab_pe(:,:,jk,jp_sal) ) * ptrdy(:,:,jk)  )
88      END DO
89
90      SELECT CASE ( ktrd )
91      CASE ( jptra_xad  )   ;   CALL iom_put( "petrd_xad", zpe )   ! zonal    advection
92      CASE ( jptra_yad  )   ;   CALL iom_put( "petrd_yad", zpe )   ! merid.   advection
93      CASE ( jptra_zad  )   ;   CALL iom_put( "petrd_zad", zpe )   ! vertical advection
94                                IF( ln_linssh ) THEN                   ! cst volume : adv flux through z=0 surface
95                                   ALLOCATE( z2d(jpi,jpj) )
96                                   z2d(:,:) = ww(:,:,1) * ( &
97                                     &   - ( rab_n(:,:,1,jp_tem) + rab_pe(:,:,1,jp_tem) ) * ts(:,:,1,jp_tem,Kmm)    &
98                                     &   + ( rab_n(:,:,1,jp_sal) + rab_pe(:,:,1,jp_sal) ) * ts(:,:,1,jp_sal,Kmm)    &
99                                     & ) / e3t(:,:,1,Kmm)
100                                   CALL iom_put( "petrd_sad" , z2d )
101                                   DEALLOCATE( z2d )
102                                ENDIF
103      CASE ( jptra_ldf  )   ;   CALL iom_put( "petrd_ldf" , zpe )   ! lateral  diffusion
104      CASE ( jptra_zdf  )   ;   CALL iom_put( "petrd_zdf" , zpe )   ! lateral  diffusion (K_z)
105      CASE ( jptra_zdfp )   ;   CALL iom_put( "petrd_zdfp", zpe )   ! vertical diffusion (K_z)
106      CASE ( jptra_dmp  )   ;   CALL iom_put( "petrd_dmp" , zpe )   ! internal 3D restoring (tradmp)
107      CASE ( jptra_bbl  )   ;   CALL iom_put( "petrd_bbl" , zpe )   ! bottom boundary layer
108      CASE ( jptra_npc  )   ;   CALL iom_put( "petrd_npc" , zpe )   ! non penetr convect adjustment
109      CASE ( jptra_nsr  )   ;   CALL iom_put( "petrd_nsr" , zpe )   ! surface forcing + runoff (ln_rnf=T)
110      CASE ( jptra_qsr  )   ;   CALL iom_put( "petrd_qsr" , zpe )   ! air-sea : penetrative sol radiat
111      CASE ( jptra_bbc  )   ;   CALL iom_put( "petrd_bbc" , zpe )   ! bottom bound cond (geoth flux)
112      CASE ( jptra_atf  )   ;   CALL iom_put( "petrd_atf" , zpe )   ! asselin time filter (last trend)
113         !
114      END SELECT
115      !
116      !
117   END SUBROUTINE trd_pen
118
119
120   SUBROUTINE trd_pen_init
121      !!---------------------------------------------------------------------
122      !!                  ***  ROUTINE trd_pen_init  ***
123      !!
124      !! ** Purpose :   initialisation of 3D Kinetic Energy trend diagnostic
125      !!----------------------------------------------------------------------
126      INTEGER  ::   ji, jj, jk   ! dummy loop indices
127      !!----------------------------------------------------------------------
128      !
129      IF(lwp) THEN
130         WRITE(numout,*)
131         WRITE(numout,*) 'trd_pen_init : 3D Potential ENergy trends'
132         WRITE(numout,*) '~~~~~~~~~~~~~'
133      ENDIF
134      !                           ! allocate box volume arrays
135      IF ( trd_pen_alloc() /= 0 )   CALL ctl_stop('trd_pen_alloc: failed to allocate arrays')
136      !
137      rab_pe(:,:,:,:) = 0._wp
138      !
139      IF( .NOT.ln_linssh )   CALL ctl_stop('trd_pen_init : PE trends not coded for variable volume')
140      !
141      nkstp     = nit000 - 1
142      !
143   END SUBROUTINE trd_pen_init
144
145   !!======================================================================
146END MODULE trdpen
Note: See TracBrowser for help on using the repository browser.