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 5901 for branches/2014/dev_r4621_NOC4_BDY_VERT_INTERP/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90 – NEMO

Ignore:
Timestamp:
2015-11-20T09:39:06+01:00 (8 years ago)
Author:
jamesharle
Message:

merging branch with head of the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4621_NOC4_BDY_VERT_INTERP/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r5038 r5901  
    1818   USE oce_trc         ! ocean dynamics and tracers variables 
    1919   USE trc             ! ocean passive tracers variables 
    20    USE trcnam_trp      ! passive tracers transport namelist variables 
    2120   USE trcdta 
    2221   USE tradmp 
     
    2423   USE trdtra 
    2524   USE trd_oce 
     25   USE iom 
    2626 
    2727   IMPLICIT NONE 
    2828   PRIVATE 
    2929 
    30    PUBLIC trc_dmp            ! routine called by step.F90 
    31    PUBLIC trc_dmp_clo        ! routine called by step.F90 
    32    PUBLIC trc_dmp_alloc      ! routine called by nemogcm.F90 
     30   PUBLIC trc_dmp       
     31   PUBLIC trc_dmp_clo    
     32   PUBLIC trc_dmp_alloc   
     33   PUBLIC trc_dmp_ini     
     34 
     35   INTEGER , PUBLIC ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer 
     36   CHARACTER(LEN=200) , PUBLIC :: cn_resto_tr    !File containing restoration coefficient 
    3337 
    3438   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1) 
     
    3943 
    4044   !! * Substitutions 
    41 #  include "top_substitute.h90" 
     45#  include "domzgr_substitute.h90" 
     46#  include "vectopt_loop_substitute.h90" 
    4247   !!---------------------------------------------------------------------- 
    4348   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
    44    !! $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/TRP/trcdmp.F90,v 1.11 2006/09/01 14:03:49 opalod Exp $  
     49   !! $Id$  
    4550   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4651   !!---------------------------------------------------------------------- 
     
    8994      IF( nn_timing == 1 )  CALL timing_start('trc_dmp') 
    9095      ! 
    91       ! 0. Initialization (first time-step only) 
    92       !    -------------- 
    93       IF( kt == nittrc000 ) CALL trc_dmp_init 
    94  
    9596      IF( l_trdtrc )   CALL wrk_alloc( jpi, jpj, jpk, ztrtrd )   ! temporary save of trends 
    9697      ! 
     
    125126                     DO jj = 2, jpjm1 
    126127                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    127                            IF( avt(ji,jj,jk) <= 5.e-4 )  THEN  
     128                           IF( avt(ji,jj,jk) <= 5.e-4_wp )  THEN  
    128129                              ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) 
    129130                              tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     
    170171   END SUBROUTINE trc_dmp 
    171172 
     173   SUBROUTINE trc_dmp_ini 
     174      !!---------------------------------------------------------------------- 
     175      !!                  ***  ROUTINE trc_dmp_ini  *** 
     176      !!  
     177      !! ** Purpose :   Initialization for the newtonian damping  
     178      !! 
     179      !! ** Method  :   read the nammbf namelist and check the parameters 
     180      !!              called by trc_dmp at the first timestep (nittrc000) 
     181      !!---------------------------------------------------------------------- 
     182      ! 
     183      INTEGER ::  ios                 ! Local integer output status for namelist read 
     184      INTEGER :: imask  !local file handle 
     185      ! 
     186      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr 
     187      !!---------------------------------------------------------------------- 
     188 
     189      IF( nn_timing == 1 )  CALL timing_start('trc_dmp_init') 
     190      ! 
     191 
     192      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping 
     193      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909) 
     194909   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in reference namelist', lwp ) 
     195 
     196      REWIND( numnat_cfg )              ! Namelist namtrc_dmp in configuration namelist : Passive tracers newtonian damping 
     197      READ  ( numnat_cfg, namtrc_dmp, IOSTAT = ios, ERR = 910) 
     198910   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in configuration namelist', lwp ) 
     199      IF(lwm) WRITE ( numont, namtrc_dmp ) 
     200 
     201      IF(lwp) THEN                       ! Namelist print 
     202         WRITE(numout,*) 
     203         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping' 
     204         WRITE(numout,*) '~~~~~~~' 
     205         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter' 
     206         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)' 
     207         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr 
     208      ENDIF 
     209      ! 
     210      IF( lzoom .AND. .NOT.lk_c1d )   nn_zdmp_tr = 0           ! restoring to climatology at closed north or south boundaries 
     211      SELECT CASE ( nn_zdmp_tr ) 
     212      CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping throughout the water column' 
     213      CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the turbocline (avt > 5 cm2/s)' 
     214      CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the mixed layer' 
     215      CASE DEFAULT 
     216         WRITE(ctmp1,*) 'bad flag value for nn_zdmp_tr = ', nn_zdmp_tr 
     217         CALL ctl_stop(ctmp1) 
     218      END SELECT 
     219 
     220      IF( .NOT.lk_c1d ) THEN 
     221         IF( .NOT. ln_tradmp )   & 
     222            &   CALL ctl_stop( 'passive trace damping need ln_tradmp to compute damping coef.' ) 
     223         ! 
     224         !                          ! Read damping coefficients from file 
     225         !Read in mask from file 
     226         CALL iom_open ( cn_resto_tr, imask) 
     227         CALL iom_get  ( imask, jpdom_autoglo, 'resto', restotr) 
     228         CALL iom_close( imask ) 
     229         ! 
     230      ENDIF 
     231      IF( nn_timing == 1 )  CALL timing_stop('trc_dmp_init') 
     232      ! 
     233   END SUBROUTINE trc_dmp_ini 
     234 
    172235   SUBROUTINE trc_dmp_clo( kt ) 
    173236      !!--------------------------------------------------------------------- 
     
    184247      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    185248      ! 
    186       INTEGER :: ji, jj, jk, jn, jl, jc                     ! dummy loop indicesa 
     249      INTEGER :: ji , jj, jk, jn, jl, jc                     ! dummy loop indicesa 
     250      INTEGER :: isrow                                      ! local index 
    187251      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta       ! 3D  workspace 
    188252 
     
    200264            ! 
    201265            SELECT CASE ( jp_cfg ) 
     266            !                                           ! ======================= 
     267            CASE ( 1 )                                  ! eORCA_R1 configuration 
     268            !                                           ! ======================= 
     269            isrow = 332 - jpjglo 
     270            ! 
     271                                                        ! Caspian Sea 
     272            nctsi1(1)   = 332  ; nctsj1(1)   = 243 - isrow 
     273            nctsi2(1)   = 344  ; nctsj2(1)   = 275 - isrow 
     274            !                                         
    202275            !                                           ! ======================= 
    203276            CASE ( 2 )                                  !  ORCA_R2 configuration 
     
    292365 
    293366 
    294    SUBROUTINE trc_dmp_init 
    295       !!---------------------------------------------------------------------- 
    296       !!                  ***  ROUTINE trc_dmp_init  *** 
    297       !!  
    298       !! ** Purpose :   Initialization for the newtonian damping  
    299       !! 
    300       !! ** Method  :   read the nammbf namelist and check the parameters 
    301       !!              called by trc_dmp at the first timestep (nittrc000) 
    302       !!---------------------------------------------------------------------- 
    303       ! 
    304       IF( nn_timing == 1 )  CALL timing_start('trc_dmp_init') 
    305       ! 
    306       SELECT CASE ( nn_hdmp_tr ) 
    307       CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '   tracer damping in the Med & Red seas only' 
    308       CASE ( 1:90 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping poleward of', nn_hdmp_tr, ' degrees' 
    309       CASE DEFAULT 
    310          WRITE(ctmp1,*) '          bad flag value for nn_hdmp_tr = ', nn_hdmp_tr 
    311          CALL ctl_stop(ctmp1) 
    312       END SELECT 
    313  
    314       IF( lzoom )   nn_zdmp_tr = 0           ! restoring to climatology at closed north or south boundaries 
    315       SELECT CASE ( nn_zdmp_tr ) 
    316       CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping throughout the water column' 
    317       CASE ( 1 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the turbocline (avt > 5 cm2/s)' 
    318       CASE ( 2 )   ;   IF(lwp) WRITE(numout,*) '   no tracer damping in the mixed layer' 
    319       CASE DEFAULT 
    320          WRITE(ctmp1,*) 'bad flag value for nn_zdmp_tr = ', nn_zdmp_tr 
    321          CALL ctl_stop(ctmp1) 
    322       END SELECT 
    323  
    324       IF( .NOT. ln_tradmp )   & 
    325          &   CALL ctl_stop( 'passive trace damping need key_tradmp to compute damping coef.' ) 
    326       ! 
    327       !                          ! Damping coefficients initialization 
    328       IF( lzoom ) THEN   ;   CALL dtacof_zoom( restotr ) 
    329       ELSE               ;   CALL dtacof( nn_hdmp_tr, rn_surf_tr, rn_bot_tr, rn_dep_tr,  & 
    330                              &            nn_file_tr, 'TRC'     , restotr                ) 
    331       ENDIF 
    332       ! 
    333       IF( nn_timing == 1 )  CALL timing_stop('trc_dmp_init') 
    334       ! 
    335    END SUBROUTINE trc_dmp_init 
    336  
    337367#else 
    338368   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.