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 4245 for branches/2013/dev_LOCEAN_CMCC_INGV_MERC_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

Ignore:
Timestamp:
2013-11-19T12:19:21+01:00 (11 years ago)
Author:
cetlod
Message:

dev_locean_cmcc_ingv_ukmo_merc : merge in the MERC_UKMO dev branch with trunk rev 4119

Location:
branches/2013/dev_LOCEAN_CMCC_INGV_MERC_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/TRA
Files:
2 edited
1 copied

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_LOCEAN_CMCC_INGV_MERC_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/TRA/traadv.F90

    r4147 r4245  
    66   !! History :  2.0  !  2005-11  (G. Madec)  Original code 
    77   !!            3.3  !  2010-09  (C. Ethe, G. Madec)  merge TRC-TRA + switch from velocity to transport 
     8   !!            4.0  !  2011-06  (G. Madec)  Addition of Mixed Layer Eddy parameterisation 
    89   !!---------------------------------------------------------------------- 
    910 
     
    2122   USE traadv_qck      ! QUICKEST scheme           (tra_adv_qck    routine) 
    2223   USE traadv_eiv      ! eddy induced velocity     (tra_adv_eiv    routine) 
     24   USE traadv_mle      ! ML eddy induced velocity  (tra_adv_mle    routine) 
    2325   USE cla             ! cross land advection      (cla_traadv     routine) 
    2426   USE ldftra_oce      ! lateral diffusion coefficient on tracers 
     
    99101         &              CALL tra_adv_eiv( kt, nit000, zun, zvn, zwn, 'TRA' )    ! add the eiv transport (if necessary) 
    100102      ! 
     103      IF( ln_mle    )   CALL tra_adv_mle( kt, nit000, zun, zvn, zwn, 'TRA' )    ! add the mle transport (if necessary) 
    101104      CALL iom_put( "uocetr_eff", zun )                                         ! output effective transport       
    102105      CALL iom_put( "vocetr_eff", zvn ) 
     
    136139         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' ) 
    137140      ! 
    138       IF( nn_timing == 1 )  CALL timing_stop('tra_adv') 
     141      IF( nn_timing == 1 )  CALL timing_stop( 'tra_adv' ) 
    139142      ! 
    140143      CALL wrk_dealloc( jpi, jpj, jpk, zun, zvn, zwn ) 
     
    213216      ENDIF 
    214217      ! 
     218      CALL tra_adv_mle_init          ! initialisation of the Mixed Layer Eddy parametrisation (MLE) 
     219      ! 
    215220   END SUBROUTINE tra_adv_init 
    216221 
  • branches/2013/dev_LOCEAN_CMCC_INGV_MERC_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/TRA/traadv_mle.F90

    r4244 r4245  
    2929 
    3030   !                                               !!* namelist namtra_adv_mle * 
    31    LOGICAL, PUBLIC ::   ln_mle    = .TRUE.          ! flag to activate the Mixed Layer Eddy (MLE) parameterisation 
    32    INTEGER         ::   nn_mle    = 0               ! MLE type: =0 standard Fox-Kemper ; =1 new formulation 
    33    INTEGER         ::   nn_mld_uv = 0               ! space interpolation of MLD at u- & v-pts (0=min,1=averaged,2=max) 
    34    INTEGER         ::   nn_conv   = 0               ! =1 no MLE in case of convection ; =0 always MLE 
    35    REAL(wp)        ::   rn_ce   = 0.06_wp           ! MLE coefficient 
    36    !                                                ! parameters used in nn_mle = 0 case 
    37    REAL(wp)        ::   rn_lf   = 5.e+3_wp               ! typical scale of mixed layer front 
    38    REAL(wp)        ::   rn_time = 2._wp * 86400._wp      ! time scale for mixing momentum across the mixed layer 
    39    !                                                ! parameters used in nn_mle = 1 case 
    40    REAL(wp)        ::   rn_lat  = 20._wp                 ! reference latitude for a 5 km scale of ML front 
    41    REAL(wp)        ::   rn_rho_c_mle  = 0.01        ! Density criterion for definition of MLD used by FK 
     31   LOGICAL, PUBLIC ::   ln_mle              ! flag to activate the Mixed Layer Eddy (MLE) parameterisation 
     32   INTEGER         ::   nn_mle              ! MLE type: =0 standard Fox-Kemper ; =1 new formulation 
     33   INTEGER         ::   nn_mld_uv           ! space interpolation of MLD at u- & v-pts (0=min,1=averaged,2=max) 
     34   INTEGER         ::   nn_conv             ! =1 no MLE in case of convection ; =0 always MLE 
     35   REAL(wp)        ::   rn_ce               ! MLE coefficient 
     36   !                                           ! parameters used in nn_mle = 0 case 
     37   REAL(wp)        ::   rn_lf                  ! typical scale of mixed layer front 
     38   REAL(wp)        ::   rn_time             ! time scale for mixing momentum across the mixed layer 
     39   !                                             ! parameters used in nn_mle = 1 case 
     40   REAL(wp)        ::   rn_lat                   ! reference latitude for a 5 km scale of ML front 
     41   REAL(wp)        ::   rn_rho_c_mle         ! Density criterion for definition of MLD used by FK 
    4242 
    4343   REAL(wp) ::   r5_21 = 5.e0 / 21.e0   ! factor used in mle streamfunction computation 
     
    271271      INTEGER  ::   ji, jj, jk   ! dummy loop indices 
    272272      INTEGER  ::   ierr 
     273      INTEGER ::    ios                 ! Local integer output status for namelist read 
    273274      REAL(wp) ::   z1_t2, zfu, zfv                                !    -         - 
    274275      ! 
     
    276277      !!---------------------------------------------------------------------- 
    277278 
    278       REWIND ( numnam )                ! Read Namelist namtra_adv_mle : mixed layer eddy advection acting on tracers 
    279       READ   ( numnam, namtra_adv_mle ) 
     279 
     280      REWIND( numnam_ref )              ! Namelist namtra_adv_mle in reference namelist : Tracer advection scheme 
     281      READ  ( numnam_ref, namtra_adv_mle, IOSTAT = ios, ERR = 901) 
     282901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_adv_mle in reference namelist', lwp ) 
     283 
     284      REWIND( numnam_cfg )              ! Namelist namtra_adv_mle in configuration namelist : Tracer advection scheme 
     285      READ  ( numnam_cfg, namtra_adv_mle, IOSTAT = ios, ERR = 902 ) 
     286902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtra_adv_mle in configuration namelist', lwp ) 
     287      WRITE ( numond, namtra_adv_mle ) 
    280288 
    281289      IF(lwp) THEN                     ! Namelist print 
  • branches/2013/dev_LOCEAN_CMCC_INGV_MERC_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/TRA/tradmp.F90

    r4147 r4245  
    2727   USE oce            ! ocean: variables 
    2828   USE dom_oce        ! ocean: domain variables 
     29   USE c1d            ! 1D vertical configuration 
    2930   USE trdmod_oce     ! ocean: trend variables 
    3031   USE trdtra         ! active tracers: trends 
     
    4445   PUBLIC   tra_dmp      ! routine called by step.F90 
    4546   PUBLIC   tra_dmp_init ! routine called by opa.F90 
    46    PUBLIC   dtacof       ! routine called by in both tradmp.F90 and trcdmp.F90 
    47    PUBLIC   dtacof_zoom  ! routine called by in both tradmp.F90 and trcdmp.F90 
     47   PUBLIC   dtacof       ! routine called by tradmp.F90, trcdmp.F90 and dyndmp.F90 
     48   PUBLIC   dtacof_zoom  ! routine called by tradmp.F90, trcdmp.F90 and dyndmp.F90 
    4849 
    4950   !                               !!* Namelist namtra_dmp : T & S newtonian damping * 
    50    LOGICAL, PUBLIC ::   ln_tradmp  = .TRUE.  !: internal damping flag 
     51   LOGICAL, PUBLIC ::   ln_tradmp  !: internal damping flag 
    5152   INTEGER         ::   nn_hdmp     ! = 0/-1/'latitude' for damping over T and S 
    5253   INTEGER         ::   nn_zdmp     ! = 0/1/2 flag for damping in the mixed layer 
     
    191192      !! ** Purpose :   Initialization for the newtonian damping  
    192193      !! 
    193       !! ** Method  :   read the nammbf namelist and check the parameters 
     194      !! ** Method  :   read the namtra_dmp namelist and check the parameters 
    194195      !!---------------------------------------------------------------------- 
    195196      NAMELIST/namtra_dmp/ ln_tradmp, nn_hdmp, nn_zdmp, rn_surf, rn_bot, rn_dep, nn_file 
     
    206207      WRITE ( numond, namtra_dmp ) 
    207208       
    208       IF( lzoom )   nn_zdmp = 0          ! restoring to climatology at closed north or south boundaries 
     209      IF( lzoom .AND. .NOT. lk_c1d )   nn_zdmp = 0          ! restoring to climatology at closed north or south boundaries 
    209210 
    210211      IF(lwp) THEN                       ! Namelist print 
     
    213214         WRITE(numout,*) '~~~~~~~' 
    214215         WRITE(numout,*) '   Namelist namtra_dmp : set damping parameter' 
    215          WRITE(numout,*) '      add a damping termn or not      ln_tradmp = ', ln_tradmp 
     216         WRITE(numout,*) '      add a damping term or not       ln_tradmp = ', ln_tradmp 
    216217         WRITE(numout,*) '      T and S damping option          nn_hdmp   = ', nn_hdmp 
    217          WRITE(numout,*) '      mixed layer damping option      nn_zdmp   = ', nn_zdmp, '(zoom: forced to 0)' 
     218         WRITE(numout,*) '      mixed layer damping option      nn_zdmp   = ', nn_zdmp, '(non-C1D zoom: forced to 0)' 
    218219         WRITE(numout,*) '      surface time scale (days)       rn_surf   = ', rn_surf 
    219220         WRITE(numout,*) '      bottom time scale (days)        rn_bot    = ', rn_bot 
     
    227228         IF( tra_dmp_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'tra_dmp_init: unable to allocate arrays' ) 
    228229         ! 
     230#if ! defined key_c1d 
    229231         SELECT CASE ( nn_hdmp ) 
    230232         CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '   tracer damping in the Med & Red seas only' 
     
    235237         END SELECT 
    236238         ! 
     239#endif 
    237240         SELECT CASE ( nn_zdmp ) 
    238241         CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping throughout the water column' 
     
    252255         ttrdmp(:,:,:) = 0._wp 
    253256         !                          ! Damping coefficients initialization 
    254          IF( lzoom ) THEN   ;   CALL dtacof_zoom( resto ) 
     257         IF( lzoom .AND. .NOT. lk_c1d ) THEN   ;   CALL dtacof_zoom( resto ) 
    255258         ELSE               ;   CALL dtacof( nn_hdmp, rn_surf, rn_bot, rn_dep, nn_file, 'TRA', resto ) 
    256259         ENDIF 
     
    360363      REAL(wp)                        , INTENT(in   )  ::  pn_dep     ! depth of transition (meters) 
    361364      INTEGER                         , INTENT(in   )  ::  kn_file    ! save the damping coef on a file or not 
    362       CHARACTER(len=3)                , INTENT(in   )  ::  cdtype     ! =TRA or TRC (tracer indicator) 
     365      CHARACTER(len=3)                , INTENT(in   )  ::  cdtype     ! =TRA, TRC or DYN (tracer/dynamics indicator) 
    363366      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout)  ::  presto     ! restoring coeff. (s-1) 
    364367      ! 
     
    380383      CALL wrk_alloc( jpi, jpj, zmrs      ) 
    381384      CALL wrk_alloc( jpi, jpj, jpk, zdct ) 
     385#if defined key_c1d 
     386      !                                   ! ==================== 
     387      !                                   !  C1D configuration : local domain 
     388      !                                   ! ==================== 
     389      ! 
     390      IF(lwp) WRITE(numout,*) 
     391      IF(lwp) WRITE(numout,*) '              dtacof : C1D 3x3 local domain' 
     392      IF(lwp) WRITE(numout,*) '              -----------------------------' 
     393      ! 
     394      presto(:,:,:) = 0._wp 
     395      ! 
     396      zsdmp = 1._wp / ( pn_surf * rday ) 
     397      zbdmp = 1._wp / ( pn_bot  * rday ) 
     398      DO jk = 2, jpkm1 
     399         DO jj = 1, jpj 
     400            DO ji = 1, jpi 
     401               !   ONLY vertical variation from zsdmp (sea surface) to zbdmp (bottom) 
     402               presto(ji,jj,jk) = zbdmp + (zsdmp-zbdmp) * EXP(-fsdept(ji,jj,jk)/pn_dep) 
     403            END DO 
     404         END DO 
     405      END DO 
     406      ! 
     407      presto(:,:, : ) = presto(:,:,:) * tmask(:,:,:) 
     408#else 
    382409      !                                   ! ==================== 
    383410      !                                   !  ORCA configuration : global domain 
     
    559586         CALL ctl_stop( 'Choose a correct value of nn_hdmp or put ln_tradmp to FALSE' ) 
    560587      ENDIF 
     588#endif 
    561589 
    562590      !                            !--------------------------------! 
     
    566594         IF( cdtype == 'TRA' ) cfile = 'damping.coeff' 
    567595         IF( cdtype == 'TRC' ) cfile = 'damping.coeff.trc' 
     596         IF( cdtype == 'DYN' ) cfile = 'damping.coeff.dyn' 
    568597         cfile = TRIM( cfile ) 
    569598         CALL iom_open  ( cfile, inum0, ldwrt = .TRUE., kiolib = jprstlib ) 
Note: See TracChangeset for help on using the changeset viewer.