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 8882 for branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90 – NEMO

Ignore:
Timestamp:
2017-12-01T18:44:09+01:00 (6 years ago)
Author:
flavoni
Message:

dev_CNRS_2017 branch: merged dev_r7881_ENHANCE09_RK3 with trunk r8864

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90

    r7753 r8882  
    1717   USE trc            ! ocean passive tracers variables 
    1818   USE oce_trc        ! ocean dynamics and active tracers 
    19    USE ldfslp         ! lateral diffusion: iso-neutral slope 
     19   USE ldftra         ! lateral diffusion: eddy diffusivity & EIV coeff. 
     20   USE ldfslp         ! Lateral diffusion: slopes of neutral surfaces 
    2021   USE traldf_lap_blp ! lateral diffusion: lap/bilaplacian iso-level      operator  (tra_ldf_lap/_blp   routine) 
    2122   USE traldf_iso     ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso        routine) 
     
    3233   PUBLIC   trc_ldf_ini    
    3334   ! 
     35   LOGICAL , PUBLIC ::   ln_trcldf_NONE      !: No operator (no explicit lateral diffusion) 
    3436   LOGICAL , PUBLIC ::   ln_trcldf_lap       !:   laplacian operator 
    3537   LOGICAL , PUBLIC ::   ln_trcldf_blp       !: bilaplacian operator 
     
    4547   REAL(wp) ::  rldf       ! ratio between active and passive tracers diffusive coefficient 
    4648    
    47    INTEGER  ::  nldf = 0   ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals) 
     49   INTEGER  ::  nldf       ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals) 
    4850    
    4951   !! * Substitutions 
     
    98100      CASE ( np_lap   )                               ! iso-level laplacian 
    99101         CALL tra_ldf_lap  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb,      tra, jptra,  1   ) 
    100          ! 
    101102      CASE ( np_lap_i )                               ! laplacian : standard iso-neutral operator (Madec) 
    102103         CALL tra_ldf_iso  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   ) 
    103          ! 
    104104      CASE ( np_lap_it )                              ! laplacian : triad iso-neutral operator (griffies) 
    105105         CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   ) 
    106          ! 
    107106      CASE ( np_blp , np_blp_i , np_blp_it )          ! bilaplacian: all operator (iso-level, -neutral) 
    108107         CALL tra_ldf_blp  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb     , tra, jptra, nldf ) 
    109          ! 
    110108      END SELECT 
    111109      ! 
     
    148146      NAMELIST/namtrc_ldf/ ln_trcldf_lap, ln_trcldf_blp,                                  & 
    149147         &                 ln_trcldf_lev, ln_trcldf_hor, ln_trcldf_iso, ln_trcldf_triad,  & 
    150          &                 rn_ahtrc_0   , rn_bhtrc_0, rn_fact_lap   
     148         &                 rn_ahtrc_0   , rn_bhtrc_0   , rn_fact_lap   
    151149      !!---------------------------------------------------------------------- 
    152150      ! 
     
    166164         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)' 
    167165         WRITE(numout,*) '      operator' 
     166         WRITE(numout,*) '         no explicit diffusion       ln_trcldf_NONE  = ', ln_trcldf_NONE 
    168167         WRITE(numout,*) '           laplacian                 ln_trcldf_lap   = ', ln_trcldf_lap 
    169168         WRITE(numout,*) '         bilaplacian                 ln_trcldf_blp   = ', ln_trcldf_blp 
     
    182181      !                                ! control the namelist parameters 
    183182      ioptio = 0 
    184       IF( ln_trcldf_lap )   ioptio = ioptio + 1 
    185       IF( ln_trcldf_blp )   ioptio = ioptio + 1 
    186       IF( ioptio >  1   )   CALL ctl_stop( 'trc_ldf_ctl: use ONE or NONE of the 2 lap/bilap operator type on tracer' ) 
    187       IF( ioptio == 0   )   nldf = np_no_ldf   ! No lateral diffusion 
     183      IF( ln_trcldf_NONE ) THEN   ;   nldf = np_no_ldf   ;   ioptio = ioptio + 1   ;   ENDIF 
     184      IF( ln_trcldf_lap  ) THEN   ;                          ioptio = ioptio + 1   ;   ENDIF 
     185      IF( ln_trcldf_blp  ) THEN   ;                          ioptio = ioptio + 1   ;   ENDIF 
     186      IF( ioptio /=  1   )   CALL ctl_stop( 'trc_ldf_ini: use ONE of the 3 operator options (NONE/lap/blp)' ) 
    188187       
    189       IF( ln_trcldf_lap .AND. ln_trcldf_blp )   CALL ctl_stop( 'trc_ldf_ctl: bilaplacian should be used on both TRC and TRA' ) 
    190       IF( ln_trcldf_blp .AND. ln_trcldf_lap )   CALL ctl_stop( 'trc_ldf_ctl:   laplacian should be used on both TRC and TRA' ) 
    191       ! 
    192       ioptio = 0 
    193       IF( ln_trcldf_lev )   ioptio = ioptio + 1 
    194       IF( ln_trcldf_hor )   ioptio = ioptio + 1 
    195       IF( ln_trcldf_iso )   ioptio = ioptio + 1 
    196       IF( ioptio /= 1   )   CALL ctl_stop( 'trc_ldf_ctl: use only ONE direction (level/hor/iso)' ) 
    197       ! 
    198       ! defined the type of lateral diffusion from ln_trcldf_... logicals 
    199       ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully 
    200       ierr = 0 
    201       IF( ln_trcldf_lap ) THEN      !==  laplacian operator  ==! 
    202          IF ( ln_zco ) THEN                ! z-coordinate 
    203             IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level = horizontal (no rotation) 
    204             IF ( ln_trcldf_hor   )   nldf = np_lap     ! iso-level = horizontal (no rotation) 
    205             IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard  (   rotation) 
    206             IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad     (   rotation) 
     188      IF( ln_trcldf_lap .AND. .NOT.ln_traldf_lap )   CALL ctl_stop( 'trc_ldf_ini:   laplacian should be used on both TRC and TRA' ) 
     189      IF( ln_trcldf_blp .AND. .NOT.ln_traldf_blp )   CALL ctl_stop( 'trc_ldf_ini: bilaplacian should be used on both TRC and TRA' ) 
     190      ! 
     191      IF( .NOT.ln_trcldf_NONE ) THEN   ! direction ==>> type of operator  
     192         ioptio = 0 
     193         IF( ln_trcldf_lev )   ioptio = ioptio + 1 
     194         IF( ln_trcldf_hor )   ioptio = ioptio + 1 
     195         IF( ln_trcldf_iso )   ioptio = ioptio + 1 
     196         IF( ioptio /= 1   )   CALL ctl_stop( 'trc_ldf_ini: use ONE direction (level/hor/iso)' ) 
     197         ! 
     198         ! defined the type of lateral diffusion from ln_trcldf_... logicals 
     199         ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully 
     200         ierr = 0 
     201         IF( ln_trcldf_lap ) THEN      !==  laplacian operator  ==! 
     202            IF( ln_zco ) THEN                ! z-coordinate 
     203               IF( ln_trcldf_lev   )   nldf = np_lap     ! iso-level = horizontal (no rotation) 
     204               IF( ln_trcldf_hor   )   nldf = np_lap     ! iso-level = horizontal (no rotation) 
     205               IF( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard  (   rotation) 
     206               IF( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad     (   rotation) 
     207            ENDIF 
     208            IF( ln_zps ) THEN             ! z-coordinate with partial step 
     209               IF( ln_trcldf_lev   )   ierr = 1          ! iso-level not allowed  
     210               IF( ln_trcldf_hor   )   nldf = np_lap     ! horizontal (no rotation) 
     211               IF( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation) 
     212               IF( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation) 
     213            ENDIF 
     214            IF( ln_sco ) THEN             ! s-coordinate 
     215               IF( ln_trcldf_lev   )   nldf = np_lap     ! iso-level  (no rotation) 
     216               IF( ln_trcldf_hor   )   nldf = np_lap_it  ! horizontal (   rotation)       !!gm   a checker.... 
     217               IF( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation) 
     218               IF( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation) 
     219            ENDIF 
     220            !                                ! diffusivity ratio: passive / active tracers  
     221            IF( ABS(rn_aht_0) < 2._wp*TINY(1._wp) ) THEN 
     222               IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1._wp) ) THEN 
     223                  rldf = 1.0_wp 
     224               ELSE 
     225                  CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
     226               ENDIF 
     227            ELSE 
     228               rldf = rn_ahtrc_0 / rn_aht_0 
     229            ENDIF 
    207230         ENDIF 
    208          IF ( ln_zps ) THEN             ! z-coordinate with partial step 
    209             IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed  
    210             IF ( ln_trcldf_hor   )   nldf = np_lap     ! horizontal (no rotation) 
    211             IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation) 
    212             IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation) 
     231         ! 
     232         IF( ln_trcldf_blp ) THEN      !==  bilaplacian operator  ==! 
     233            IF ( ln_zco ) THEN                ! z-coordinate 
     234               IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level = horizontal (no rotation) 
     235               IF ( ln_trcldf_hor   )   nldf = np_blp     ! iso-level = horizontal (no rotation) 
     236               IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
     237               IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
     238            ENDIF 
     239            IF ( ln_zps ) THEN             ! z-coordinate with partial step 
     240               IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed  
     241               IF ( ln_trcldf_hor   )   nldf = np_blp     ! horizontal (no rotation) 
     242               IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
     243               IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
     244            ENDIF 
     245            IF ( ln_sco ) THEN             ! s-coordinate 
     246               IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level  (no rotation) 
     247               IF ( ln_trcldf_hor   )   nldf = np_blp_it  ! horizontal (   rotation)       !!gm   a checker.... 
     248               IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
     249               IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
     250            ENDIF 
     251            !                                ! diffusivity ratio: passive / active tracers  
     252            IF( ABS(rn_bht_0) < 2._wp*TINY(1._wp) ) THEN 
     253               IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1._wp) ) THEN 
     254                  rldf = 1.0_wp 
     255               ELSE 
     256                  CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
     257               ENDIF 
     258            ELSE 
     259               rldf = SQRT(  ABS( rn_bhtrc_0 / rn_bht_0 )  ) 
     260            ENDIF 
    213261         ENDIF 
    214          IF ( ln_sco ) THEN             ! s-coordinate 
    215             IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level  (no rotation) 
    216             IF ( ln_trcldf_hor   )   nldf = np_lap_it  ! horizontal (   rotation)       !!gm   a checker.... 
    217             IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation) 
    218             IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation) 
    219          ENDIF 
    220          !                                ! diffusivity ratio: passive / active tracers  
    221          IF( ABS(rn_aht_0) < 2._wp*TINY(1._wp) ) THEN 
    222             IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1._wp) ) THEN 
    223                rldf = 1.0_wp 
    224             ELSE 
    225                CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
    226             ENDIF 
    227          ELSE 
    228             rldf = rn_ahtrc_0 / rn_aht_0 
    229          ENDIF 
    230       ENDIF 
    231       ! 
    232       IF( ln_trcldf_blp ) THEN      !==  bilaplacian operator  ==! 
    233          IF ( ln_zco ) THEN                ! z-coordinate 
    234             IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level = horizontal (no rotation) 
    235             IF ( ln_trcldf_hor   )   nldf = np_blp     ! iso-level = horizontal (no rotation) 
    236             IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
    237             IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
    238          ENDIF 
    239          IF ( ln_zps ) THEN             ! z-coordinate with partial step 
    240             IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed  
    241             IF ( ln_trcldf_hor   )   nldf = np_blp     ! horizontal (no rotation) 
    242             IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
    243             IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
    244          ENDIF 
    245          IF ( ln_sco ) THEN             ! s-coordinate 
    246             IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level  (no rotation) 
    247             IF ( ln_trcldf_hor   )   nldf = np_blp_it  ! horizontal (   rotation)       !!gm   a checker.... 
    248             IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation) 
    249             IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation) 
    250          ENDIF 
    251          !                                ! diffusivity ratio: passive / active tracers  
    252          IF( ABS(rn_bht_0) < 2._wp*TINY(1._wp) ) THEN 
    253             IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1._wp) ) THEN 
    254                rldf = 1.0_wp 
    255             ELSE 
    256                CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' ) 
    257             ENDIF 
    258          ELSE 
    259             rldf = SQRT(  ABS( rn_bhtrc_0 / rn_bht_0 )  ) 
    260          ENDIF 
    261       ENDIF 
    262       ! 
    263       IF( ierr == 1 )   CALL ctl_stop( 'trc_ldf_ctl: iso-level in z-partial step, not allowed' ) 
    264       IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   CALL ctl_stop( 'trc_ldf_ctl: eiv requires isopycnal laplacian diffusion' ) 
     262         ! 
     263         IF( ierr == 1 )   CALL ctl_stop( 'trc_ldf_ini: iso-level in z-partial step, not allowed' ) 
     264      ENDIF 
     265      ! 
     266      IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   CALL ctl_stop( 'trc_ldf_ini: eiv requires isopycnal laplacian diffusion' ) 
    265267      IF( nldf == 1 .OR. nldf == 3 )   l_ldfslp = .TRUE.    ! slope of neutral surfaces required  
    266268      ! 
     
    268270         WRITE(numout,*) 
    269271         SELECT CASE( nldf ) 
    270          CASE( np_no_ldf )   ;   WRITE(numout,*) '          NO lateral diffusion' 
    271          CASE( np_lap    )   ;   WRITE(numout,*) '          laplacian iso-level operator' 
    272          CASE( np_lap_i  )   ;   WRITE(numout,*) '          Rotated laplacian operator (standard)' 
    273          CASE( np_lap_it )   ;   WRITE(numout,*) '          Rotated laplacian operator (triad)' 
    274          CASE( np_blp    )   ;   WRITE(numout,*) '          bilaplacian iso-level operator' 
    275          CASE( np_blp_i  )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (standard)' 
    276          CASE( np_blp_it )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (triad)' 
     272         CASE( np_no_ldf )   ;   WRITE(numout,*) '      ===>>   NO lateral diffusion' 
     273         CASE( np_lap    )   ;   WRITE(numout,*) '      ===>>   laplacian iso-level operator' 
     274         CASE( np_lap_i  )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (standard)' 
     275         CASE( np_lap_it )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (triad)' 
     276         CASE( np_blp    )   ;   WRITE(numout,*) '      ===>>   bilaplacian iso-level operator' 
     277         CASE( np_blp_i  )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (standard)' 
     278         CASE( np_blp_it )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (triad)' 
    277279         END SELECT 
    278280      ENDIF 
    279281      ! 
    280282   END SUBROUTINE trc_ldf_ini 
    281 #else 
    282    !!---------------------------------------------------------------------- 
    283    !!   Default option                                         Empty module 
    284    !!---------------------------------------------------------------------- 
    285 CONTAINS 
    286    SUBROUTINE trc_ldf( kt ) 
    287       INTEGER, INTENT(in) :: kt 
    288       WRITE(*,*) 'trc_ldf: You should not have seen this print! error?', kt 
    289    END SUBROUTINE trc_ldf 
     283 
    290284#endif 
    291285   !!====================================================================== 
Note: See TracChangeset for help on using the changeset viewer.