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 branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/OPA_SRC/TRD/trdpen.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 8 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 8.2 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   USE wrk_nemo       ! Memory allocation
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   trd_pen        ! called by all trdtra module
32   PUBLIC   trd_pen_init   ! called by all nemogcm module
33
34   INTEGER ::   nkstp   ! current time step
35
36   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   rab_pe   ! partial derivatives of PE anomaly with respect to T and S
37
38   !! * Substitutions
39#  include "domzgr_substitute.h90"
40#  include "zdfddm_substitute.h90"
41#  include "vectopt_loop_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
44   !! $Id$
45   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   INTEGER FUNCTION trd_pen_alloc()
50      !!---------------------------------------------------------------------
51      !!                  ***  FUNCTION trd_tra_alloc  ***
52      !!---------------------------------------------------------------------
53      ALLOCATE( rab_pe(jpi,jpj,jpk,jpts) , STAT= trd_pen_alloc )
54      !
55      IF( lk_mpp             )   CALL mpp_sum ( trd_pen_alloc )
56      IF( trd_pen_alloc /= 0 )   CALL ctl_warn( 'trd_pen_alloc: failed to allocate arrays' )
57   END FUNCTION trd_pen_alloc
58
59
60   SUBROUTINE trd_pen( ptrdx, ptrdy, ktrd, kt, pdt )
61      !!---------------------------------------------------------------------
62      !!                  ***  ROUTINE trd_tra_mng  ***
63      !!
64      !! ** Purpose :   Dispatch all trends computation, e.g. 3D output, integral
65      !!                constraints, barotropic vorticity, kinetic enrgy,
66      !!                potential energy, and/or mixed layer budget.
67      !!----------------------------------------------------------------------
68      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   ptrdx, ptrdy   ! Temperature & Salinity trends
69      INTEGER                   , INTENT(in) ::   ktrd           ! tracer trend index
70      INTEGER                   , INTENT(in) ::   kt             ! time step index
71      REAL(wp)                  , INTENT(in) ::   pdt            ! time step [s]
72      !
73      INTEGER ::   jk                                            ! dummy loop indices
74      REAL(wp), POINTER, DIMENSION(:,:)      ::   z2d            ! 2D workspace
75      REAL(wp), POINTER, DIMENSION(:,:,:)    ::   zpe            ! 3D workspace
76      !!----------------------------------------------------------------------
77      !
78      CALL wrk_alloc( jpi, jpj, jpk, zpe )
79      zpe(:,:,:) = 0._wp
80      !
81      IF ( kt /= nkstp ) THEN   ! full eos: set partial derivatives at the 1st call of kt time step
82         nkstp = kt
83         CALL eos_pen( tsn, rab_PE, zpe )
84         CALL iom_put( "alphaPE", rab_pe(:,:,:,jp_tem) )
85         CALL iom_put( "betaPE" , rab_pe(:,:,:,jp_sal) )
86         CALL iom_put( "PEanom" , zpe )
87      ENDIF
88      !
89      zpe(:,:,jpk) = 0._wp
90      DO jk = 1, jpkm1
91         zpe(:,:,jk) = ( - ( rab_n(:,:,jk,jp_tem) + rab_pe(:,:,jk,jp_tem) ) * ptrdx(:,:,jk)   &
92            &            + ( rab_n(:,:,jk,jp_sal) + rab_pe(:,:,jk,jp_sal) ) * ptrdy(:,:,jk)  )
93      END DO
94
95      SELECT CASE ( ktrd )
96      CASE ( jptra_xad  )   ;   CALL iom_put( "petrd_xad", zpe )   ! zonal    advection
97      CASE ( jptra_yad  )   ;   CALL iom_put( "petrd_yad", zpe )   ! merid.   advection
98      CASE ( jptra_zad  )   ;   CALL iom_put( "petrd_zad", zpe )   ! vertical advection
99                                IF( .NOT.lk_vvl ) THEN                   ! cst volume : adv flux through z=0 surface
100                                   CALL wrk_alloc( jpi, jpj, z2d )
101                                   z2d(:,:) = wn(:,:,1) * ( &
102                                     &   - ( rab_n(:,:,1,jp_tem) + rab_pe(:,:,1,jp_tem) ) * tsn(:,:,1,jp_tem)    &
103                                     &   + ( rab_n(:,:,1,jp_sal) + rab_pe(:,:,1,jp_sal) ) * tsn(:,:,1,jp_sal)    &
104                                     & ) / fse3t(:,:,1)
105                                   CALL iom_put( "petrd_sad" , z2d )
106                                   CALL wrk_dealloc( jpi, jpj, z2d )
107                                ENDIF
108      CASE ( jptra_ldf  )   ;   CALL iom_put( "petrd_ldf" , zpe )   ! lateral  diffusion
109      CASE ( jptra_zdf  )   ;   CALL iom_put( "petrd_zdf" , zpe )   ! lateral  diffusion (K_z)
110      CASE ( jptra_zdfp )   ;   CALL iom_put( "petrd_zdfp", zpe )   ! vertical diffusion (K_z)
111      CASE ( jptra_dmp  )   ;   CALL iom_put( "petrd_dmp" , zpe )   ! internal 3D restoring (tradmp)
112      CASE ( jptra_bbl  )   ;   CALL iom_put( "petrd_bbl" , zpe )   ! bottom boundary layer
113      CASE ( jptra_npc  )   ;   CALL iom_put( "petrd_npc" , zpe )   ! non penetr convect adjustment
114      CASE ( jptra_nsr  )   ;   CALL iom_put( "petrd_nsr" , zpe )   ! surface forcing + runoff (ln_rnf=T)
115      CASE ( jptra_qsr  )   ;   CALL iom_put( "petrd_qsr" , zpe )   ! air-sea : penetrative sol radiat
116      CASE ( jptra_bbc  )   ;   CALL iom_put( "petrd_bbc" , zpe )   ! bottom bound cond (geoth flux)
117      CASE ( jptra_atf  )   ;   CALL iom_put( "petrd_atf" , zpe )   ! asselin time filter (last trend)
118                                !IF( .NOT.lk_vvl ) THEN                   ! cst volume : ssh term (otherwise include in e3t variation)
119                                !   CALL wrk_alloc( jpi, jpj, z2d )
120                                !   z2d(:,:) = ( ssha(:,:) - sshb(:,:) )                 &
121                                !      &     * (   dPE_dt(:,:,1) * tsn(:,:,1,jp_tem)    &
122                                !      &         + dPE_ds(:,:,1) * tsn(:,:,1,jp_sal)  ) / ( fse3t(:,:,1) * pdt )
123                                !   CALL iom_put( "petrd_sad" , z2d )
124                                !   CALL wrk_dealloc( jpi, jpj, z2d )
125                                !ENDIF
126         !
127      END SELECT
128      !
129      CALL wrk_dealloc( jpi, jpj, jpk, zpe )
130      !
131   END SUBROUTINE trd_pen
132
133
134   SUBROUTINE trd_pen_init
135      !!---------------------------------------------------------------------
136      !!                  ***  ROUTINE trd_pen_init  ***
137      !!
138      !! ** Purpose :   initialisation of 3D Kinetic Energy trend diagnostic
139      !!----------------------------------------------------------------------
140      INTEGER  ::   ji, jj, jk   ! dummy loop indices
141      !!----------------------------------------------------------------------
142      !
143      IF(lwp) THEN
144         WRITE(numout,*)
145         WRITE(numout,*) 'trd_pen_init : 3D Potential ENergy trends'
146         WRITE(numout,*) '~~~~~~~~~~~~~'
147      ENDIF
148      !                           ! allocate box volume arrays
149      IF ( trd_pen_alloc() /= 0 )   CALL ctl_stop('trd_pen_alloc: failed to allocate arrays')
150      !
151      rab_pe(:,:,:,:) = 0._wp
152      !
153      IF ( lk_vvl               )   CALL ctl_stop('trd_pen_init : PE trends not coded for variable volume')
154      !
155      nkstp     = nit000 - 1
156      !
157   END SUBROUTINE trd_pen_init
158
159   !!======================================================================
160END MODULE trdpen
Note: See TracBrowser for help on using the repository browser.