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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90

    r3294 r6225  
    44   !! Ocean Passive tracers : lateral diffusive trends 
    55   !!===================================================================== 
    6    !! History :  9.0  ! 2005-11 (G. Madec)  Original code 
    7    !!       NEMO 3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA 
     6   !! History :  1.0  ! 2005-11  (G. Madec)  Original code 
     7   !!            3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA 
     8   !!            3.7  ! 2014-03  (G. Madec)  LDF simplification 
    89   !!---------------------------------------------------------------------- 
    910#if defined key_top 
     
    1112   !!   'key_top'                                                TOP models 
    1213   !!---------------------------------------------------------------------- 
    13    !!---------------------------------------------------------------------- 
    14    !!   trc_ldf     : update the tracer trend with the lateral diffusion 
    15    !!       ldf_ctl : initialization, namelist read, and parameters control 
    16    !!---------------------------------------------------------------------- 
    17    USE oce_trc         ! ocean dynamics and active tracers 
    18    USE trc             ! ocean passive tracers variables 
    19    USE trcnam_trp      ! passive tracers transport namelist variables 
    20    USE ldftra_oce      ! lateral diffusion coefficient on tracers 
    21    USE ldfslp          ! ??? 
    22    USE traldf_bilapg   ! lateral mixing            (tra_ldf_bilapg routine) 
    23    USE traldf_bilap    ! lateral mixing            (tra_ldf_bilap routine) 
    24    USE traldf_iso      ! lateral mixing            (tra_ldf_iso routine) 
    25    USE traldf_iso_grif ! lateral mixing          (tra_ldf_iso_grif routine) 
    26    USE traldf_lap      ! lateral mixing            (tra_ldf_lap routine) 
    27    USE trdmod_oce 
    28    USE trdtra 
    29    USE prtctl_trc      ! Print control 
     14   !!   trc_ldf       : update the tracer trend with the lateral diffusion 
     15   !!   trc_ldf_ini   : initialization, namelist read, and parameters control 
     16   !!---------------------------------------------------------------------- 
     17   USE trc            ! ocean passive tracers variables 
     18   USE oce_trc        ! ocean dynamics and active tracers 
     19   USE ldfslp         ! lateral diffusion: iso-neutral slope 
     20   USE traldf_lap_blp ! lateral diffusion: lap/bilaplacian iso-level      operator  (tra_ldf_lap/_blp   routine) 
     21   USE traldf_iso     ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso        routine) 
     22   USE traldf_triad   ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_     triad routine) 
     23   USE trd_oce        ! trends: ocean variables 
     24   USE trdtra         ! trends manager: tracers 
     25   ! 
     26   USE prtctl_trc     ! Print control 
    3027 
    3128   IMPLICIT NONE 
    3229   PRIVATE 
    3330 
    34    PUBLIC   trc_ldf    ! called by step.F90 
    35    !                                                 !!: ** lateral mixing namelist (nam_trcldf) ** 
    36    REAL(wp) ::  rldf_rat    ! ratio between active and passive tracers diffusive coefficient 
     31   PUBLIC   trc_ldf     
     32   PUBLIC   trc_ldf_ini    
     33   ! 
     34   LOGICAL , PUBLIC ::   ln_trcldf_lap       !:   laplacian operator 
     35   LOGICAL , PUBLIC ::   ln_trcldf_blp       !: bilaplacian operator 
     36   LOGICAL , PUBLIC ::   ln_trcldf_lev       !: iso-level   direction 
     37   LOGICAL , PUBLIC ::   ln_trcldf_hor       !: horizontal  direction (rotation to geopotential) 
     38   LOGICAL , PUBLIC ::   ln_trcldf_iso       !: iso-neutral direction (standard) 
     39   LOGICAL , PUBLIC ::   ln_trcldf_triad     !: iso-neutral direction (triad) 
     40   REAL(wp), PUBLIC ::   rn_ahtrc_0          !:   laplacian diffusivity coefficient for passive tracer [m2/s] 
     41   REAL(wp), PUBLIC ::   rn_bhtrc_0          !: bilaplacian      -          --     -       -   [m4/s] 
     42   ! 
     43   !                      !!: ** lateral mixing namelist (nam_trcldf) ** 
     44   REAL(wp) ::  rldf       ! ratio between active and passive tracers diffusive coefficient 
     45    
    3746   INTEGER  ::  nldf = 0   ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals) 
     47    
    3848   !! * Substitutions 
    39 #  include "domzgr_substitute.h90" 
    4049#  include "vectopt_loop_substitute.h90" 
    4150   !!---------------------------------------------------------------------- 
    42    !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     51   !! NEMO/TOP 3.7 , NEMO Consortium (2014) 
    4352   !! $Id$ 
    4453   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4554   !!---------------------------------------------------------------------- 
    46  
    4755CONTAINS 
    4856 
     
    5563      !!---------------------------------------------------------------------- 
    5664      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    57       !! 
     65      ! 
    5866      INTEGER            :: jn 
    5967      CHARACTER (len=22) :: charout 
     68      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zahu, zahv 
    6069      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd 
    6170      !!---------------------------------------------------------------------- 
     
    6372      IF( nn_timing == 1 )   CALL timing_start('trc_ldf') 
    6473      ! 
    65       IF( kt == nittrc000 )   CALL ldf_ctl          ! initialisation & control of options 
    66  
    67       rldf = rldf_rat 
    68  
    6974      IF( l_trdtrc )  THEN 
    70          CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrtrd ) 
     75         CALL wrk_alloc( jpi,jpj,jpk,jptra,  ztrtrd ) 
    7176         ztrtrd(:,:,:,:)  = tra(:,:,:,:) 
    7277      ENDIF 
    73  
    74       SELECT CASE ( nldf )                       ! compute lateral mixing trend and add it to the general trend 
    75       CASE ( 0 )   ;   CALL tra_ldf_lap   ( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra            )  ! iso-level laplacian 
    76       CASE ( 1 )                                                                                            ! rotated laplacian 
    77                        IF( ln_traldf_grif ) THEN 
    78                           CALL tra_ldf_iso_grif( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra, rn_ahtb_0 ) 
    79                        ELSE 
    80                           CALL tra_ldf_iso     ( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra, rn_ahtb_0 ) 
    81                        ENDIF 
    82       CASE ( 2 )   ;   CALL tra_ldf_bilap ( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra            )  ! iso-level bilaplacian 
    83       CASE ( 3 )   ;   CALL tra_ldf_bilapg( kt, nittrc000, 'TRC',             trb, tra, jptra            )  ! s-coord. horizontal bilaplacian 
    84          ! 
    85       CASE ( -1 )                                     ! esopa: test all possibility with control print 
    86          CALL tra_ldf_lap   ( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra            ) 
    87          WRITE(charout, FMT="('ldf0 ')") ;  CALL prt_ctl_trc_info(charout) 
    88                                             CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    89          IF( ln_traldf_grif ) THEN 
    90             CALL tra_ldf_iso_grif( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra, rn_ahtb_0 ) 
    91          ELSE 
    92             CALL tra_ldf_iso     ( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra, rn_ahtb_0 ) 
    93          ENDIF 
    94          WRITE(charout, FMT="('ldf1 ')") ;  CALL prt_ctl_trc_info(charout) 
    95                                             CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    96          CALL tra_ldf_bilap ( kt, nittrc000, 'TRC', gtru, gtrv, trb, tra, jptra            ) 
    97          WRITE(charout, FMT="('ldf2 ')") ;  CALL prt_ctl_trc_info(charout) 
    98                                             CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    99          CALL tra_ldf_bilapg( kt, nittrc000, 'TRC',             trb, tra, jptra            ) 
    100          WRITE(charout, FMT="('ldf3 ')") ;  CALL prt_ctl_trc_info(charout) 
    101                                             CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     78      ! 
     79      !                                        !* set the lateral diffusivity coef. for passive tracer       
     80      CALL wrk_alloc( jpi,jpj,jpk,   zahu, zahv ) 
     81      zahu(:,:,:) = rldf * ahtu(:,:,:) 
     82      zahv(:,:,:) = rldf * ahtv(:,:,:) 
     83 
     84      SELECT CASE ( nldf )                     !* compute lateral mixing trend and add it to the general trend 
     85      ! 
     86      CASE ( np_lap   )                               ! iso-level laplacian 
     87         CALL tra_ldf_lap  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb,      tra, jptra,  1   ) 
     88         ! 
     89      CASE ( np_lap_i )                               ! laplacian : standard iso-neutral operator (Madec) 
     90         CALL tra_ldf_iso  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   ) 
     91         ! 
     92      CASE ( np_lap_it )                              ! laplacian : triad iso-neutral operator (griffies) 
     93         CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   ) 
     94         ! 
     95      CASE ( np_blp , np_blp_i , np_blp_it )          ! bilaplacian: all operator (iso-level, -neutral) 
     96         CALL tra_ldf_blp  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb     , tra, jptra, nldf ) 
     97         ! 
    10298      END SELECT 
    10399      ! 
    104       IF( l_trdtrc )   THEN                      ! save the horizontal diffusive trends for further diagnostics 
     100      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics 
    105101        DO jn = 1, jptra 
    106102           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn) 
    107            CALL trd_tra( kt, 'TRC', jn, jptra_trd_ldf, ztrtrd(:,:,:,jn) ) 
     103           CALL trd_tra( kt, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) ) 
    108104        END DO 
    109105        CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd ) 
    110106      ENDIF 
    111       !                                          ! print mean trends (used for debugging) 
    112       IF( ln_ctl )   THEN 
    113          WRITE(charout, FMT="('ldf ')") ;  CALL prt_ctl_trc_info(charout) 
    114                                            CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    115       ENDIF 
     107      !                 
     108      IF( ln_ctl ) THEN                        ! print mean trends (used for debugging) 
     109         WRITE(charout, FMT="('ldf ')") 
     110         CALL prt_ctl_trc_info(charout) 
     111         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     112      ENDIF 
     113      ! 
     114      CALL wrk_dealloc( jpi,jpj,jpk,   zahu, zahv ) 
    116115      ! 
    117116      IF( nn_timing == 1 )   CALL timing_stop('trc_ldf') 
     
    120119 
    121120 
    122    SUBROUTINE ldf_ctl 
     121   SUBROUTINE trc_ldf_ini 
    123122      !!---------------------------------------------------------------------- 
    124123      !!                  ***  ROUTINE ldf_ctl  *** 
    125124      !! 
    126       !! ** Purpose :   Choice of the operator for the lateral tracer diffusion 
     125      !! ** Purpose :   Define the operator for the lateral diffusion 
    127126      !! 
    128127      !! ** Method  :   set nldf from the namtra_ldf logicals 
    129       !!      nldf == -2   No lateral diffusion 
    130       !!      nldf == -1   ESOPA test: ALL operators are used 
    131128      !!      nldf ==  0   laplacian operator 
    132129      !!      nldf ==  1   Rotated laplacian operator 
     
    134131      !!      nldf ==  3   Rotated bilaplacian 
    135132      !!---------------------------------------------------------------------- 
    136       INTEGER ::   ioptio, ierr         ! temporary integers 
    137       !!---------------------------------------------------------------------- 
    138  
    139       IF (ABS(rn_aht_0) < 2._wp*TINY(1.e0)) THEN 
    140          IF (ABS(rn_ahtrc_0) < 2._wp*TINY(1.e0)) THEN 
    141             rldf_rat = 1.0_wp 
    142          ELSE 
    143             CALL ctl_stop( 'STOP', 'ldf_ctl : cannot define rldf_rat, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
    144          END IF 
    145       ELSE 
    146          rldf_rat = rn_ahtrc_0 / rn_aht_0 
    147       END IF 
    148       !  Define the lateral mixing oparator for tracers 
    149       ! =============================================== 
    150  
    151       !                               ! control the input 
     133      INTEGER ::   ioptio, ierr   ! temporary integers 
     134      INTEGER ::   ios            ! Local integer output status for namelist read 
     135      !! 
     136      NAMELIST/namtrc_ldf/ ln_trcldf_lap, ln_trcldf_blp,                                  & 
     137         &                 ln_trcldf_lev, ln_trcldf_hor, ln_trcldf_iso, ln_trcldf_triad,  & 
     138         &                 rn_ahtrc_0   , rn_bhtrc_0 
     139      !!---------------------------------------------------------------------- 
     140      ! 
     141      REWIND( numnat_ref )             !  namtrc_ldf in reference namelist  
     142      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903) 
     143903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp ) 
     144      ! 
     145      REWIND( numnat_cfg )             !  namtrc_ldf in configuration namelist  
     146      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 ) 
     147904   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp ) 
     148      IF(lwm) WRITE ( numont, namtrc_ldf ) 
     149      ! 
     150      IF(lwp) THEN                     ! Namelist print 
     151         WRITE(numout,*) 
     152         WRITE(numout,*) 'trc_ldf_ini : lateral tracer diffusive operator' 
     153         WRITE(numout,*) '~~~~~~~~~~~' 
     154         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)' 
     155         WRITE(numout,*) '      operator' 
     156         WRITE(numout,*) '           laplacian                 ln_trcldf_lap   = ', ln_trcldf_lap 
     157         WRITE(numout,*) '         bilaplacian                 ln_trcldf_blp   = ', ln_trcldf_blp 
     158         WRITE(numout,*) '      direction of action' 
     159         WRITE(numout,*) '         iso-level                   ln_trcldf_lev   = ', ln_trcldf_lev 
     160         WRITE(numout,*) '         horizontal (geopotential)   ln_trcldf_hor   = ', ln_trcldf_hor 
     161         WRITE(numout,*) '         iso-neutral (standard)      ln_trcldf_iso   = ', ln_trcldf_iso 
     162         WRITE(numout,*) '         iso-neutral (triad)         ln_trcldf_triad = ', ln_trcldf_triad 
     163         WRITE(numout,*) '      diffusivity coefficient' 
     164         WRITE(numout,*) '           laplacian                 rn_ahtrc_0      = ', rn_ahtrc_0 
     165         WRITE(numout,*) '         bilaplacian                 rn_bhtrc_0      = ', rn_bhtrc_0 
     166      ENDIF 
     167      !       
     168      !                                ! control the namelist parameters 
    152169      ioptio = 0 
    153       IF( ln_trcldf_lap   )   ioptio = ioptio + 1 
    154       IF( ln_trcldf_bilap )   ioptio = ioptio + 1 
    155       IF( ioptio >  1 )   CALL ctl_stop( '          use ONE or NONE of the 2 lap/bilap operator type on tracer' ) 
    156       IF( ioptio == 0 )   nldf = -2   ! No lateral diffusion 
     170      IF( ln_trcldf_lap )   ioptio = ioptio + 1 
     171      IF( ln_trcldf_blp )   ioptio = ioptio + 1 
     172      IF( ioptio >  1   )   CALL ctl_stop( 'trc_ldf_ctl: use ONE or NONE of the 2 lap/bilap operator type on tracer' ) 
     173      IF( ioptio == 0   )   nldf = np_no_ldf   ! No lateral diffusion 
     174       
     175      IF( ln_trcldf_lap .AND. ln_trcldf_blp )   CALL ctl_stop( 'trc_ldf_ctl: bilaplacian should be used on both TRC and TRA' ) 
     176      IF( ln_trcldf_blp .AND. ln_trcldf_lap )   CALL ctl_stop( 'trc_ldf_ctl:   laplacian should be used on both TRC and TRA' ) 
     177      ! 
    157178      ioptio = 0 
    158       IF( ln_trcldf_level )   ioptio = ioptio + 1 
    159       IF( ln_trcldf_hor   )   ioptio = ioptio + 1 
    160       IF( ln_trcldf_iso   )   ioptio = ioptio + 1 
    161       IF( ioptio /= 1 )   CALL ctl_stop( '          use only ONE direction (level/hor/iso)' ) 
    162  
     179      IF( ln_trcldf_lev )   ioptio = ioptio + 1 
     180      IF( ln_trcldf_hor )   ioptio = ioptio + 1 
     181      IF( ln_trcldf_iso )   ioptio = ioptio + 1 
     182      IF( ioptio /= 1   )   CALL ctl_stop( 'trc_ldf_ctl: use only ONE direction (level/hor/iso)' ) 
     183      ! 
    163184      ! defined the type of lateral diffusion from ln_trcldf_... logicals 
    164185      ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully 
    165186      ierr = 0 
    166       IF( ln_trcldf_lap ) THEN       ! laplacian operator 
     187      IF( ln_trcldf_lap ) THEN      !==  laplacian operator  ==! 
    167188         IF ( ln_zco ) THEN                ! z-coordinate 
    168             IF ( ln_trcldf_level )   nldf = 0      ! iso-level  (no rotation) 
    169             IF ( ln_trcldf_hor   )   nldf = 0      ! horizontal (no rotation) 
    170             IF ( ln_trcldf_iso   )   nldf = 1      ! isoneutral (   rotation) 
    171          ENDIF 
    172          IF ( ln_zps ) THEN             ! z-coordinate 
    173             IF ( ln_trcldf_level )   ierr = 1      ! iso-level not allowed 
    174             IF ( ln_trcldf_hor   )   nldf = 0      ! horizontal (no rotation) 
    175             IF ( ln_trcldf_iso   )   nldf = 1      ! isoneutral (   rotation) 
    176          ENDIF 
    177          IF ( ln_sco ) THEN             ! z-coordinate 
    178             IF ( ln_trcldf_level )   nldf = 0      ! iso-level  (no rotation) 
    179             IF ( ln_trcldf_hor   )   nldf = 1      ! horizontal (   rotation) 
    180             IF ( ln_trcldf_iso   )   nldf = 1      ! isoneutral (   rotation) 
    181          ENDIF 
    182       ENDIF 
    183  
    184       IF( ln_trcldf_bilap ) THEN      ! bilaplacian operator 
     189            IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level = horizontal (no rotation) 
     190            IF ( ln_trcldf_hor   )   nldf = np_lap     ! iso-level = horizontal (no rotation) 
     191            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard  (   rotation) 
     192            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad     (   rotation) 
     193         ENDIF 
     194         IF ( ln_zps ) THEN             ! z-coordinate with partial step 
     195            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed  
     196            IF ( ln_trcldf_hor   )   nldf = np_lap     ! horizontal (no rotation) 
     197            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation) 
     198            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation) 
     199         ENDIF 
     200         IF ( ln_sco ) THEN             ! s-coordinate 
     201            IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level  (no rotation) 
     202            IF ( ln_trcldf_hor   )   nldf = np_lap_it  ! horizontal (   rotation)       !!gm   a checker.... 
     203            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation) 
     204            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation) 
     205         ENDIF 
     206         !                                ! diffusivity ratio: passive / active tracers  
     207         IF( ABS(rn_aht_0) < 2._wp*TINY(1._wp) ) THEN 
     208            IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1._wp) ) THEN 
     209               rldf = 1.0_wp 
     210            ELSE 
     211               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
     212            ENDIF 
     213         ELSE 
     214            rldf = rn_ahtrc_0 / rn_aht_0 
     215         ENDIF 
     216      ENDIF 
     217      ! 
     218      IF( ln_trcldf_blp ) THEN      !==  bilaplacian operator  ==! 
    185219         IF ( ln_zco ) THEN                ! z-coordinate 
    186             IF ( ln_trcldf_level )   nldf = 2      ! iso-level  (no rotation) 
    187             IF ( ln_trcldf_hor   )   nldf = 2      ! horizontal (no rotation) 
    188             IF ( ln_trcldf_iso   )   ierr = 2      ! isoneutral (   rotation) 
    189          ENDIF 
    190          IF ( ln_zps ) THEN             ! z-coordinate 
    191             IF ( ln_trcldf_level )   ierr = 1      ! iso-level not allowed 
    192             IF ( ln_trcldf_hor   )   nldf = 2      ! horizontal (no rotation) 
    193             IF ( ln_trcldf_iso   )   ierr = 2      ! isoneutral (   rotation) 
    194          ENDIF 
    195          IF ( ln_sco ) THEN             ! z-coordinate 
    196             IF ( ln_trcldf_level )   nldf = 2      ! iso-level  (no rotation) 
    197             IF ( ln_trcldf_hor   )   nldf = 3      ! horizontal (   rotation) 
    198             IF ( ln_trcldf_iso   )   ierr = 2      ! isoneutral (   rotation) 
    199          ENDIF 
    200       ENDIF 
    201  
    202       IF( ierr == 1 )   CALL ctl_stop( ' iso-level in z-coordinate - partial step, not allowed' ) 
    203       IF( ierr == 2 )   CALL ctl_stop( ' isoneutral bilaplacian operator does not exist' ) 
    204       IF( lk_traldf_eiv .AND. .NOT.ln_trcldf_iso )   & 
    205            CALL ctl_stop( '          eddy induced velocity on tracers',   & 
    206            &              ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion' ) 
    207       IF( nldf == 1 .OR. nldf == 3 ) THEN      ! rotation 
    208          IF( .NOT.lk_ldfslp )   CALL ctl_stop( '          the rotation of the diffusive tensor require key_ldfslp' ) 
    209 #if defined key_offline 
    210          l_traldf_rot = .TRUE.                 ! needed for trazdf_imp 
    211 #endif 
    212       ENDIF 
    213  
    214       IF( lk_esopa ) THEN 
    215          IF(lwp) WRITE(numout,*) '          esopa control: use all lateral physics options' 
    216          nldf = -1 
    217       ENDIF 
    218  
    219       IF( .NOT. ln_trcldf_diff ) THEN 
    220          IF(lwp) WRITE(numout,*) '          No lateral diffusion on passive tracers' 
    221          nldf = -2 
    222       ENDIF 
    223  
     220            IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level = horizontal (no rotation) 
     221            IF ( ln_trcldf_hor   )   nldf = np_blp     ! iso-level = horizontal (no rotation) 
     222            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
     223            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
     224         ENDIF 
     225         IF ( ln_zps ) THEN             ! z-coordinate with partial step 
     226            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed  
     227            IF ( ln_trcldf_hor   )   nldf = np_blp     ! horizontal (no rotation) 
     228            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
     229            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
     230         ENDIF 
     231         IF ( ln_sco ) THEN             ! s-coordinate 
     232            IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level  (no rotation) 
     233            IF ( ln_trcldf_hor   )   nldf = np_blp_it  ! horizontal (   rotation)       !!gm   a checker.... 
     234            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
     235            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
     236         ENDIF 
     237         !                                ! diffusivity ratio: passive / active tracers  
     238         IF( ABS(rn_bht_0) < 2._wp*TINY(1._wp) ) THEN 
     239            IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1._wp) ) THEN 
     240               rldf = 1.0_wp 
     241            ELSE 
     242               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
     243            ENDIF 
     244         ELSE 
     245            rldf = SQRT(  ABS( rn_bhtrc_0 / rn_bht_0 )  ) 
     246         ENDIF 
     247      ENDIF 
     248      ! 
     249      IF( ierr == 1 )   CALL ctl_stop( 'trc_ldf_ctl: iso-level in z-partial step, not allowed' ) 
     250      IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   CALL ctl_stop( 'trc_ldf_ctl: eiv requires isopycnal laplacian diffusion' ) 
     251      IF( nldf == 1 .OR. nldf == 3 )   l_ldfslp = .TRUE.    ! slope of neutral surfaces required  
     252      ! 
    224253      IF(lwp) THEN 
    225254         WRITE(numout,*) 
    226          IF( nldf == -2 )   WRITE(numout,*) '          NO lateral diffusion' 
    227          IF( nldf == -1 )   WRITE(numout,*) '          ESOPA test All scheme used' 
    228          IF( nldf ==  0 )   WRITE(numout,*) '          laplacian operator' 
    229          IF( nldf ==  1 )   WRITE(numout,*) '          Rotated laplacian operator' 
    230          IF( nldf ==  2 )   WRITE(numout,*) '          bilaplacian operator' 
    231          IF( nldf ==  3 )   WRITE(numout,*) '          Rotated bilaplacian' 
    232       ENDIF 
    233  
    234       IF( ln_trcldf_bilap ) THEN 
    235          IF(lwp) WRITE(numout,*) '          biharmonic tracer diffusion' 
    236          IF( rn_ahtrc_0 > 0 .AND. .NOT. lk_esopa )   CALL ctl_stop( 'The horizontal diffusivity coef. rn_ahtrc_0 must be negative' ) 
    237       ELSE 
    238          IF(lwp) WRITE(numout,*) '          harmonic tracer diffusion (default)' 
    239          IF( rn_ahtrc_0 < 0 .AND. .NOT. lk_esopa )   CALL ctl_stop('The horizontal diffusivity coef. rn_ahtrc_0 must be positive' ) 
    240       ENDIF 
    241  
    242       ! ratio between active and passive tracers diffusive coef. 
    243       IF (ABS(rn_aht_0) < 2._wp*TINY(1.e0)) THEN 
    244          IF (ABS(rn_ahtrc_0) < 2._wp*TINY(1.e0)) THEN 
    245             rldf_rat = 1.0_wp 
    246          ELSE 
    247             CALL ctl_stop( 'STOP', 'ldf_ctl : cannot define rldf_rat, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
    248          END IF 
    249       ELSE 
    250          rldf_rat = rn_ahtrc_0 / rn_aht_0 
    251       END IF 
    252       IF( rldf_rat < 0 ) THEN 
    253          IF( .NOT.lk_offline ) THEN  
    254             CALL ctl_stop( 'Choose the same type of diffusive scheme both for active & passive tracers' ) 
    255          ELSE 
    256             CALL ctl_stop( 'Change the sign of rn_aht_0 in namelist to -/+1' ) 
    257          ENDIF  
    258       ENDIF 
    259       ! 
    260    END SUBROUTINE ldf_ctl 
     255         SELECT CASE( nldf ) 
     256         CASE( np_no_ldf )   ;   WRITE(numout,*) '          NO lateral diffusion' 
     257         CASE( np_lap    )   ;   WRITE(numout,*) '          laplacian iso-level operator' 
     258         CASE( np_lap_i  )   ;   WRITE(numout,*) '          Rotated laplacian operator (standard)' 
     259         CASE( np_lap_it )   ;   WRITE(numout,*) '          Rotated laplacian operator (triad)' 
     260         CASE( np_blp    )   ;   WRITE(numout,*) '          bilaplacian iso-level operator' 
     261         CASE( np_blp_i  )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (standard)' 
     262         CASE( np_blp_it )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (triad)' 
     263         END SELECT 
     264      ENDIF 
     265      ! 
     266   END SUBROUTINE trc_ldf_ini 
    261267#else 
    262268   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.