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.
Changeset 3318 for branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRD/trdini.F90 – NEMO

Ignore:
Timestamp:
2012-02-25T16:50:01+01:00 (12 years ago)
Author:
gm
Message:

Ediag branche: #927 split TRA/DYN trd computation

File:
1 copied

Legend:

Unmodified
Added
Removed
  • branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/OPA_SRC/TRD/trdini.F90

    r3317 r3318  
    1 MODULE trdmod 
     1MODULE trdini 
    22   !!====================================================================== 
    3    !!                       ***  MODULE  trdmod  *** 
     3   !!                       ***  MODULE  trdini  *** 
    44   !! Ocean diagnostics:  ocean tracers and dynamic trends 
    55   !!===================================================================== 
    6    !! History :  1.0  !  2004-08  (C. Talandier) Original code 
    7    !!             -   !  2005-04  (C. Deltel)    Add Asselin trend in the ML budget 
    8    !!            3.3  !  2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase 
    9    !!            3.5  !  2012-02  (G. Madec) add 3D trends output for T, S, U, V, PE and KE 
     6   !! History :   3.5  !  2012-02  (G. Madec) add 3D trends output for T, S, U, V, PE and KE 
    107   !!---------------------------------------------------------------------- 
    11 #if  defined key_trdtra || defined key_trddyn || defined key_trdmld || defined key_trdvor || defined key_esopa 
     8 
    129   !!---------------------------------------------------------------------- 
    13    !!   trd_mod       : manage the type of trend diagnostics 
    14    !!   trd_3Diom     : output 3D momentum and/or tracer trends using IOM 
    15    !!   trd_mod_init  : Initialization step 
     10   !!   trd_init      : initialization step 
    1611   !!---------------------------------------------------------------------- 
    17    USE oce            ! ocean dynamics and tracers variables 
    18    USE dom_oce        ! ocean space and time domain variables 
    19    USE zdf_oce        ! ocean vertical physics variables 
    20    USE trdmod_oce     ! ocean variables trends 
    21    USE zdfbfr         ! bottom friction 
    22    USE ldftra_oce     ! ocean active tracers lateral physics 
    23    USE sbc_oce        ! surface boundary condition: ocean 
    24    USE phycst         ! physical constants 
     12   USE trd_oce        ! trends: ocean variables 
     13!   USE ldftra_oce     ! ocean active tracers lateral physics 
     14   USE trdglo         ! ocean bassin integral constraints properties 
     15   USE trdmld         ! ocean active mixed layer tracers trends  
    2516   USE trdvor         ! ocean vorticity trends  
    26    USE trdicp         ! ocean bassin integral constraints properties 
    27    USE trdmld         ! ocean active mixed layer tracers trends  
    2817   USE in_out_manager ! I/O manager 
    29    USE iom            ! I/O manager library 
    3018   USE lib_mpp        ! MPP library 
    31    USE wrk_nemo       ! Memory allocation 
    3219 
    3320   IMPLICIT NONE 
    3421   PRIVATE 
    3522 
    36    REAL(wp) ::   r2dt          ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0 
    37  
    38    PUBLIC trd_mod              ! called by all dynXX or traXX modules 
    39    PUBLIC trd_mod_init         ! called by opa.F90 module 
     23   PUBLIC   trd_init   ! called by nemogcm.F90 module 
    4024 
    4125   !! * Substitutions 
     
    4933CONTAINS 
    5034 
    51    SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt ) 
    52       !!--------------------------------------------------------------------- 
    53       !!                  ***  ROUTINE trd_mod  *** 
     35   SUBROUTINE trd_init 
     36      !!---------------------------------------------------------------------- 
     37      !!                  ***  ROUTINE trd_init  *** 
    5438      !!  
    55       !! ** Purpose :   Dispatch all trends computation, e.g. 3D output, integral 
    56       !!                constraints, barotropic vorticity, kinetic enrgy,  
    57       !!                potential energy, and/or mixed layer budget. 
     39      !! ** Purpose :   Initialization of trend diagnostics 
    5840      !!---------------------------------------------------------------------- 
    59       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend  
    60       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend 
    61       INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index 
    62       CHARACTER(len=3)          , INTENT(in   ) ::   ctype   ! momentum or tracers trends type 'DYN'/'TRA' 
    63       INTEGER                   , INTENT(in   ) ::   kt      ! time step 
    64       !! 
    65       INTEGER ::   ji, jj   ! dummy loop indices 
    66       REAL(wp), POINTER, DIMENSION(:,:) ::   ztswu, ztswv    ! 2D workspace  
    67       !!---------------------------------------------------------------------- 
    68  
    69       CALL wrk_alloc( jpi, jpj, ztswu, ztswv ) 
    70  
    71       IF( neuler == 0 .AND. kt == nit000    ) THEN   ;   r2dt =      rdt      ! = rdtra (restart with Euler time stepping) 
    72       ELSEIF(               kt <= nit000 + 1) THEN   ;   r2dt = 2. * rdt      ! = 2 rdttra (leapfrog) 
    73       ENDIF 
    74  
    75       !                                            !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    76       IF( ln_3D_trd_d .OR. ln_3D_trd_t ) THEN      !   3D output of momentum and/or tracers trends using IOM interface 
    77          !                                         !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    78          CALL trd_3Diom ( ptrdx, ptrdy, ktrd, ctype, kt ) 
    79          ! 
    80       ENDIF 
    81          !                                         !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    82       IF( ln_glo_trd ) THEN                        ! I. Integral Constraints Properties for momentum and/or tracers trends 
    83          !                                         !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    84          CALL trd_budget( ptrdx, ptrdy, ktrd, ctype, kt ) 
    85          ! 
    86       ENDIF 
    87  
    88       !                                            !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    89       IF( lk_trdvor .AND. ctype == 'DYN' ) THEN    ! II. Vorticity trends 
    90          !                                         !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    91          SELECT CASE( ktrd )  
    92          CASE( jpdyn_trd_hpg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_prg )   ! Hydrostatique Pressure Gradient  
    93          CASE( jpdyn_trd_keg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_keg )   ! KE Gradient  
    94          CASE( jpdyn_trd_rvo )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_rvo )   ! Relative Vorticity  
    95          CASE( jpdyn_trd_pvo )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_pvo )   ! Planetary Vorticity Term  
    96          CASE( jpdyn_trd_ldf )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_ldf )   ! Horizontal Diffusion  
    97          CASE( jpdyn_trd_zad )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zad )   ! Vertical Advection  
    98          CASE( jpdyn_trd_spg )   ;   CALL trd_vor_zint( ptrdx, ptrdy, jpvor_spg )   ! Surface Pressure Grad.  
    99          CASE( jpdyn_trd_zdf )                                                      ! Vertical Diffusion  
    100             ztswu(:,:) = 0.e0   ;   ztswv(:,:) = 0.e0 
    101             DO jj = 2, jpjm1                                                             ! wind stress trends 
    102                DO ji = fs_2, fs_jpim1   ! vector opt. 
    103                   ztswu(ji,jj) = 0.5 * ( utau_b(ji,jj) + utau(ji,jj) ) / ( fse3u(ji,jj,1) * rau0 ) 
    104                   ztswv(ji,jj) = 0.5 * ( vtau_b(ji,jj) + vtau(ji,jj) ) / ( fse3v(ji,jj,1) * rau0 ) 
    105                END DO 
    106             END DO 
    107             ! 
    108             CALL trd_vor_zint( ptrdx, ptrdy, jpvor_zdf )                             ! zdf trend including surf./bot. stresses  
    109             CALL trd_vor_zint( ztswu, ztswv, jpvor_swf )                             ! surface wind stress  
    110          CASE ( jpdyn_trd_bfr ) 
    111             CALL trd_vor_zint( ptrdx, ptrdy, jpvor_bfr )                             ! Bottom stress 
    112          END SELECT 
    113          ! 
    114       ENDIF 
    115  
    116       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    117       ! III. Mixed layer trends for active tracers 
    118       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    119  
    120       IF( lk_trdmld .AND. ctype == 'TRA' )   THEN    
    121          !----------------------------------------------------------------------------------------------- 
    122          ! W.A.R.N.I.N.G : 
    123          ! jptra_trd_ldf : called by traldf.F90 
    124          !                 at this stage we store: 
    125          !                  - the lateral geopotential diffusion (here, lateral = horizontal) 
    126          !                  - and the iso-neutral diffusion if activated  
    127          ! jptra_trd_zdf : called by trazdf.F90 
    128          !                 * in case of iso-neutral diffusion we store the vertical diffusion component in the  
    129          !                   lateral trend including the K_z contrib, which will be removed later (see trd_mld) 
    130          !----------------------------------------------------------------------------------------------- 
    131  
    132          SELECT CASE ( ktrd ) 
    133          CASE ( jptra_trd_xad )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_xad, '3D' )   ! zonal    advection 
    134          CASE ( jptra_trd_yad )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_yad, '3D' )   ! merid.   advection 
    135          CASE ( jptra_trd_zad )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_zad, '3D' )   ! vertical advection 
    136          CASE ( jptra_trd_ldf )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' )   ! lateral  diffusion 
    137          CASE ( jptra_trd_bbl )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbl, '3D' )   ! bottom boundary layer 
    138          CASE ( jptra_trd_zdf ) 
    139             IF( ln_traldf_iso ) THEN   ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_ldf, '3D' )   ! lateral  diffusion (K_z) 
    140             ELSE                       ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_zdf, '3D' )   ! vertical diffusion (K_z) 
    141             ENDIF 
    142          CASE ( jptra_trd_dmp )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_dmp, '3D' )   ! internal 3D restoring (tradmp) 
    143          CASE ( jptra_trd_qsr )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '3D' )   ! air-sea : penetrative sol radiat 
    144          CASE ( jptra_trd_nsr ) 
    145             ptrdx(:,:,2:jpk) = 0._wp   ;   ptrdy(:,:,2:jpk) = 0._wp 
    146             CALL trd_mld_zint( ptrdx, ptrdy, jpmld_for, '2D' )                                  ! air-sea : non penetr sol radiat 
    147          CASE ( jptra_trd_bbc )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_bbc, '3D' )   ! bottom bound cond (geoth flux) 
    148          CASE ( jptra_trd_atf )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_atf, '3D' )   ! asselin numerical 
    149          CASE ( jptra_trd_npc )        ;   CALL trd_mld_zint( ptrdx, ptrdy, jpmld_npc, '3D' )   ! non penetr convect adjustment 
    150          END SELECT 
    151          ! 
    152       ENDIF 
    153       ! 
    154       CALL wrk_dealloc( jpi, jpj, ztswu, ztswv ) 
    155       ! 
    156    END SUBROUTINE trd_mod 
    157  
    158  
    159    SUBROUTINE trd_3Diom( ptrdx, ptrdy, ktrd, ctype, kt ) 
    160       !!--------------------------------------------------------------------- 
    161       !!                  ***  ROUTINE trd_3Diom  *** 
    162       !!  
    163       !! ** Purpose :   output 3D trends using IOM 
    164       !!---------------------------------------------------------------------- 
    165       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend  
    166       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend 
    167       INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index 
    168       CHARACTER(len=3)          , INTENT(in   ) ::   ctype   ! momentum or tracers trends type 'DYN'/'TRA' 
    169       INTEGER                   , INTENT(in   ) ::   kt      ! time step 
    170       !! 
    171       INTEGER ::   ji, jj, jk   ! dummy loop indices 
    172       INTEGER ::   ikbu, ikbv   ! local integers 
    173       REAL(wp), POINTER, DIMENSION(:,:)   ::   z2dx, z2dy, ztswu, ztswv   ! 2D workspace  
    174       REAL(wp), POINTER, DIMENSION(:,:,:) ::   z3dx, z3dy                 ! 3D workspace  
    175       !!---------------------------------------------------------------------- 
    176  
    177        IF( lk_trdtra .AND. ctype == 'TRA' ) THEN       ! active tracer trends 
    178          ! 
    179 !!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added 
    180          ! 
    181          SELECT CASE( ktrd ) 
    182          CASE( jptra_trd_xad  )   ;   CALL iom_put( "ttrd_xad" , ptrdx )        ! x- horizontal advection 
    183                                       CALL iom_put( "strd_xad" , ptrdy ) 
    184          CASE( jptra_trd_yad  )   ;   CALL iom_put( "ttrd_yad" , ptrdx )        ! y- horizontal advection 
    185                                       CALL iom_put( "strd_yad" , ptrdy ) 
    186          CASE( jptra_trd_zad  )   ;   CALL iom_put( "ttrd_zad" , ptrdx )        ! z- vertical   advection 
    187                                       CALL iom_put( "strd_zad" , ptrdy ) 
    188                                       IF( .NOT.lk_vvl ) THEN                   ! cst volume : adv flux through z=0 surface 
    189                                          z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / fse3t(:,:,1) 
    190                                          z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / fse3t(:,:,1) 
    191                                          CALL iom_put( "ttrd_sad", z2dx ) 
    192                                          CALL iom_put( "strd_sad", z2dy ) 
    193                                       ENDIF 
    194          CASE( jptra_trd_ldf  )   ;   CALL iom_put( "ttrd_ldf" , ptrdx )        ! lateral diffusion 
    195                                       CALL iom_put( "strd_ldf" , ptrdy ) 
    196          CASE( jptra_trd_zdf  )   ;   CALL iom_put( "ttrd_zdf" , ptrdx )        ! vertical diffusion (including Kz contribution) 
    197                                       CALL iom_put( "strd_zdf" , ptrdy ) 
    198          CASE( jptra_trd_zdfp )   ;   CALL iom_put( "ttrd_zdfp", ptrdx )        ! PURE vertical diffusion (no isoneutral contribution) 
    199                                       CALL iom_put( "strd_zdfp", ptrdy ) 
    200          CASE( jptra_trd_dmp  )   ;   CALL iom_put( "ttrd_dmp" , ptrdx )        ! internal restoring (damping) 
    201                                       CALL iom_put( "strd_dmp" , ptrdy ) 
    202          CASE( jptra_trd_bbl  )   ;   CALL iom_put( "ttrd_bbl" , ptrdx )        ! bottom boundary layer 
    203                                       CALL iom_put( "strd_bbl" , ptrdy ) 
    204          CASE( jptra_trd_npc  )   ;   CALL iom_put( "ttrd_npc" , ptrdx )        ! static instability mixing 
    205                                       CALL iom_put( "strd_npc" , ptrdy ) 
    206          CASE( jptra_trd_nsr  )   ;   CALL iom_put( "ttrd_qns" , ptrdx )        ! surface forcing + runoff (ln_rnf=T) 
    207                                       CALL iom_put( "strd_cdt" , ptrdy ) 
    208          CASE( jptra_trd_qsr  )   ;   CALL iom_put( "ttrd_qsr" , ptrdx )        ! penetrative solar radiat. (only on temperature) 
    209          CASE( jptra_trd_bbc  )   ;   CALL iom_put( "ttrd_bbc" , ptrdx )        ! geothermal heating   (only on temperature) 
    210          CASE( jptra_trd_atf  )   ;   CALL iom_put( "ttrd_atf" , ptrdx )        ! asselin time Filter 
    211                                       CALL iom_put( "strd_atf" , ptrdy ) 
    212  
    213          END SELECT 
    214       ENDIF 
    215  
    216       IF( lk_trddyn .AND. ctype == 'DYN' ) THEN       ! momentum trends  
    217             ! 
    218          ptrdx(:,:,:) = ptrdx(:,:,:) * umask(:,:,:)                       ! mask the trends 
    219          ptrdy(:,:,:) = ptrdy(:,:,:) * vmask(:,:,:) 
    220 !!gm NB : here a lbc_lnk should probably be added 
    221          ! 
    222          SELECT CASE( ktrd ) 
    223          CASE( jpdyn_trd_hpg )   ;   CALL iom_put( "utrd_hpg", ptrdx )    ! hydrostatic pressure gradient 
    224                                      CALL iom_put( "vtrd_hpg", ptrdy ) 
    225          CASE( jpdyn_trd_spg )   ;   CALL iom_put( "utrd_spg", ptrdx )    ! surface pressure gradient 
    226                                      CALL iom_put( "vtrd_spg", ptrdy ) 
    227          CASE( jpdyn_trd_pvo )   ;   CALL iom_put( "utrd_pvo", ptrdx )    ! planetary vorticity 
    228                                      CALL iom_put( "vtrd_pvo", ptrdy ) 
    229          CASE( jpdyn_trd_rvo )   ;   CALL iom_put( "utrd_rvo", ptrdx )    ! relative  vorticity     (or metric term) 
    230                                      CALL iom_put( "vtrd_rvo", ptrdy ) 
    231          CASE( jpdyn_trd_keg )   ;   CALL iom_put( "utrd_keg", ptrdx )    ! Kinetic Energy gradient (or had) 
    232                                      CALL iom_put( "vtrd_keg", ptrdy ) 
    233             z3dx(:,:,:) = 0._wp                                           ! U.dxU & V.dyV (approximation) 
    234             z3dy(:,:,:) = 0._wp 
    235             DO jk = 1, jpkm1                                                  ! no mask as un,vn are masked 
    236                DO jj = 2, jpjm1 
    237                   DO ji = 2, jpim1 
    238                      z3dx(ji,jj,jk) = un(ji,jj,jk) * ( un(ji+1,jj,jk) - un(ji-1,jj,jk) ) / ( 2._wp * e1u(ji,jj) ) 
    239                      z3dy(ji,jj,jk) = vn(ji,jj,jk) * ( vn(ji,jj+1,jk) - vn(ji,jj-1,jk) ) / ( 2._wp * e2v(ji,jj) ) 
    240                   END DO 
    241                END DO 
    242             END DO 
    243             CALL lbc_lnk( z3dx, 'U', -1. )   ;    CALL lbc_lnk( z3dy, 'V', -1. ) 
    244                                      CALL iom_put( "utrd_udx", z3dx  )  
    245                                      CALL iom_put( "vtrd_vdy", z3dy  ) 
    246          CASE( jpdyn_trd_zad )   ;   CALL iom_put( "utrd_zad", ptrdx )    ! vertical   advection 
    247                                      CALL iom_put( "vtrd_zad", ptrdy ) 
    248          CASE( jpdyn_trd_ldf )   ;   CALL iom_put( "utrd_ldf", ptrdx )    ! lateral diffusion 
    249                                      CALL iom_put( "vtrd_ldf", ptrdy ) 
    250          CASE( jpdyn_trd_zdf )   ;   CALL iom_put( "utrd_zdf", ptrdx )    ! vertical diffusion  
    251                                      CALL iom_put( "vtrd_zdf", ptrdy ) 
    252                                      !                                    ! wind stress trends 
    253                                      z2dx(:,:) = ( utau_b(ji,jj) + utau(ji,jj) ) / ( fse3u(:,:,1) * rau0 ) 
    254                                      z2dy(:,:) = ( vtau_b(ji,jj) + vtau(ji,jj) ) / ( fse3v(:,:,1) * rau0 ) 
    255                                      CALL iom_put( "utrd_tau", z2dx ) 
    256                                      CALL iom_put( "vtrd_tau", z2dy ) 
    257          CASE( jpdyn_trd_bfr ) 
    258             IF( .NOT.ln_bfrimp )     CALL iom_put( "utrd_bfr", ptrdx )    ! bottom friction (explicit case) 
    259             IF( .NOT.ln_bfrimp )     CALL iom_put( "vtrd_bfr", ptrdy ) 
    260 !!gm only valid if ln_bfrimp=T otherwise the bottom stress as to be recomputed.... 
    261  
    262          CASE( jpdyn_trd_atf )   ;   CALL iom_put( "utrd_atf", ptrdx )    ! asselin filter trends  
    263                                      CALL iom_put( "vtrd_atf", ptrdy ) 
    264             IF( ln_bfrimp ) THEN                                          ! bottom friction (implicit case) 
    265                z3dx(:,:,:) = 0._wp   ;   z3dy(:,:,:) = 0._wp                 ! after velocity known (now filed at this stage) 
    266                DO jk = 1, jpkm1 
    267                   DO jj = 2, jpjm1 
    268                      DO ji = 2, jpim1 
    269                         ikbu = mbku(ji,jj)          ! deepest ocean u- & v-levels 
    270                         ikbv = mbkv(ji,jj) 
    271                         z3dx(ji,jj,jk) = bfrua(ji,jj) * un(ji,jj,ikbu) / fse3u(ji,jj,ikbu) 
    272                         z3dy(ji,jj,jk) = bfrva(ji,jj) * vn(ji,jj,ikbv) / fse3v(ji,jj,ikbv) 
    273                      END DO 
    274                   END DO 
    275                END DO 
    276                                      CALL iom_put( "utrd_bfr", z3dx )    ! bottom friction (implicit) 
    277                                      CALL iom_put( "vtrd_bfr", z3dy ) 
    278             ENDIF 
    279             ! 
    280          END SELECT 
    281          ! 
    282       ENDIF 
    283       ! 
    284       CALL wrk_dealloc( jpi, jpj     , z2dx, z2dy, ztswu, ztswv ) 
    285       CALL wrk_dealloc( jpi, jpj, jpk, z3dx, z3dy ) 
    286       ! 
    287    END SUBROUTINE trd_3Diom 
    288  
    289 #else 
    290    !!---------------------------------------------------------------------- 
    291    !!   Default case :           Empty module          No trend diagnostics 
    292    !!---------------------------------------------------------------------- 
    293 CONTAINS 
    294    SUBROUTINE trd_mod( ptrdx, ptrdy, ktrd, ctype, kt )   ! Empty routine 
    295       REAL ::   ptrdx(:,:,:), ptrdy(:,:,:) 
    296       INTEGER  ::   ktrd, kt                             
    297       CHARACTER(len=3) ::  ctype                   
    298       WRITE(*,*) 'trd_mod: You should not have seen this print! error ?',   & 
    299          &       ptrdx(1,1,1), ptrdy(1,1,1), ktrd, ctype, kt 
    300    END SUBROUTINE trd_mod 
    301 #endif 
    302  
    303    SUBROUTINE trd_mod_init 
    304       !!---------------------------------------------------------------------- 
    305       !!                  ***  ROUTINE trd_mod_init  *** 
    306       !!  
    307       !! ** Purpose :   Initialization of activated trends 
    308       !!---------------------------------------------------------------------- 
    309       USE in_out_manager          ! I/O manager 
    310  
    311       NAMELIST/namtrd/ ln_3D_trd_d, ln_KE_trd, ln_vor_trd, ln_ML_trd_d,   & 
    312          &             ln_3D_trd_t, ln_PE_trd, ln_glo_trd, ln_ML_trd_t,   & 
    313          &             nn_trd , cn_trdrst_in , ln_trdmld_restart,         & 
     41      NAMELIST/namtrd/ ln_dyn_trd, ln_KE_trd, ln_vor_trd, ln_dyn_mld,   & 
     42         &             ln_tra_trd, ln_PE_trd, ln_glo_trd, ln_tra_mld,   & 
     43         &             nn_trd , cn_trdrst_in , ln_trdmld_restart,       & 
    31444         &             nn_ctls, cn_trdrst_out, ln_trdmld_instant, rn_ucf 
    31545      !!---------------------------------------------------------------------- 
    31646 
    317       IF( l_trdtra .OR. l_trddyn )   THEN 
    318          REWIND( numnam ) 
    319          READ  ( numnam, namtrd )      ! namelist namtrd : trends diagnostic 
     47      REWIND( numnam ) 
     48      READ  ( numnam, namtrd )      ! namelist namtrd : trends diagnostic 
    32049 
    321          IF(lwp) THEN 
    322             WRITE(numout,*) 
    323             WRITE(numout,*) ' trd_mod_init : Momentum/Tracers trends' 
    324             WRITE(numout,*) ' ~~~~~~~~~~~~~' 
    325             WRITE(numout,*) '   Namelist namtrd : set trends parameters' 
    326             WRITE(numout,*) '      U & V trends: 3D output                 ln_3D_trd_d        = ', ln_3D_trd_d 
    327             WRITE(numout,*) '      T & S trends: 3D output                 ln_3D_trd_t        = ', ln_3D_trd_t 
    328             WRITE(numout,*) '      Kinetic   Energy trends                 ln_KE_trd          = ', ln_KE_trd 
    329             WRITE(numout,*) '      Potential Energy trends                 ln_PE_trd          = ', ln_PE_trd 
    330             WRITE(numout,*) '      Barotropic vorticity trends             ln_vor_trd         = ', ln_vor_trd 
    331             WRITE(numout,*) '      check domain averaged dyn & tra trends  ln_glo_trd         = ', ln_glo_trd 
    332             WRITE(numout,*) '      U & V trends: Mixed Layer averaged      ln_ML_trd_d        = ', ln_3D_trd_d 
    333             WRITE(numout,*) '      T & S trends: Mixed Layer averaged      ln_ML_trd_t        = ', ln_3D_trd_t 
    334      ! 
    335             WRITE(numout,*) '      frequency of trends diagnostics (glo)   nn_trd             = ', nn_trd 
    336             WRITE(numout,*) '      control surface type            (mld)   nn_ctls            = ', nn_ctls 
    337             WRITE(numout,*) '      restart for ML diagnostics              ln_trdmld_restart  = ', ln_trdmld_restart 
    338             WRITE(numout,*) '      instantaneous or mean ML T/S            ln_trdmld_instant  = ', ln_trdmld_instant 
    339             WRITE(numout,*) '      unit conversion factor                  rn_ucf             = ', rn_ucf 
    340         ENDIF 
     50      IF(lwp) THEN                  ! control print 
     51         WRITE(numout,*) 
     52         WRITE(numout,*) ' trd_init : Momentum/Tracers trends' 
     53         WRITE(numout,*) ' ~~~~~~~~~~' 
     54         WRITE(numout,*) '   Namelist namtrd : set trends parameters' 
     55         WRITE(numout,*) '      global domain averaged dyn & tra trends        ln_glo_trd  = ', ln_glo_trd 
     56         WRITE(numout,*) '      U & V trends: 3D output                        ln_dyn_trd  = ', ln_dyn_trd 
     57         WRITE(numout,*) '      U & V trends: Mixed Layer averaged             ln_dyn_mld  = ', ln_dyn_mld 
     58         WRITE(numout,*) '      T & S trends: 3D output                        ln_tra_trd  = ', ln_tra_trd 
     59         WRITE(numout,*) '      T & S trends: Mixed Layer averaged             ln_tra_mld  = ', ln_tra_mld 
     60         WRITE(numout,*) '      Kinetic   Energy trends                        ln_KE_trd   = ', ln_KE_trd 
     61         WRITE(numout,*) '      Potential Energy trends                        ln_PE_trd   = ', ln_PE_trd 
     62         WRITE(numout,*) '      Barotropic vorticity trends                    ln_vor_trd  = ', ln_vor_trd 
     63         ! 
     64         WRITE(numout,*) '      frequency of trends diagnostics (glo)   nn_trd             = ', nn_trd 
     65         WRITE(numout,*) '      control surface type            (mld)   nn_ctls            = ', nn_ctls 
     66         WRITE(numout,*) '      restart for ML diagnostics              ln_trdmld_restart  = ', ln_trdmld_restart 
     67         WRITE(numout,*) '      instantaneous or mean ML T/S            ln_trdmld_instant  = ', ln_trdmld_instant 
     68         WRITE(numout,*) '      unit conversion factor                  rn_ucf             = ', rn_ucf 
    34169      ENDIF 
    34270      ! 
    343       IF( ln_KE_trd .OR. ln_PE_trd .OR. ln_ML_trd_d )   & 
     71      !                             ! trend extraction flags   
     72      l_trdtra = .FALSE.                                                       ! tracers   
     73      IF ( ln_tra_trd .OR. ln_PE_trd .OR. ln_tra_mld .OR.   & 
     74         & ln_glo_trd                                       )   l_trdtra = .TRUE.  
     75      ! 
     76      l_trddyn = .FALSE.                                                       ! momentum 
     77      IF ( ln_dyn_trd .OR. ln_KE_trd .OR. ln_dyn_mld .OR.   & 
     78         & ln_vor_trd .OR. ln_glo_trd                       )   l_trddyn = .TRUE. 
     79      ! 
     80       
     81      IF( ln_KE_trd .OR. ln_PE_trd .OR. ln_dyn_mld )   & 
    34482         CALL ctl_stop( 'KE, PE, aur ML on momentum are not yet coded we stop' ) 
     83 
     84      ! 
     85      IF( ln_glo_trd )    CALL trd_glo_init       ! integral constraints trends 
     86      IF( ln_tra_mld )    CALL trd_mld_init       ! mixed-layer trends (active  tracers)   
     87      IF( ln_vor_trd )    CALL trd_vor_init       ! vorticity trends         
     88      ! 
    34589!!gm  : Potential BUG : 3D output only for vector invariant form!  add a ctl_stop or code the flux form case 
    34690!!gm  : bug/pb for vertical advection of tracer in vvl case: add T.dt[eta] in the output...  
    34791      ! 
    348       IF( lk_trddyn .OR. lk_trdtra )    CALL trd_icp_init       ! integral constraints trends 
    349       IF( lk_trdmld                )    CALL trd_mld_init       ! mixed-layer trends (active  tracers)   
    350       IF( lk_trdvor                )    CALL trd_vor_init       ! vorticity trends         
    35192      ! 
    352    END SUBROUTINE trd_mod_init 
     93   END SUBROUTINE trd_init 
    35394 
    35495   !!====================================================================== 
    355 END MODULE trdmod 
     96END MODULE trdini 
Note: See TracChangeset for help on using the changeset viewer.