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 3882 – NEMO

Changeset 3882


Ignore:
Timestamp:
2013-04-22T12:06:32+02:00 (11 years ago)
Author:
cetlod
Message:

trunk: fix on passive tracer damping, see ticket #1083

Location:
trunk/NEMOGCM/NEMO/TOP_SRC
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90

    r3780 r3882  
    7777      ! 
    7878      IF( ln_rsttr .AND. kt == nittrc000 )                         CALL p4z_rst( nittrc000, 'READ' )  !* read or initialize all required fields  
    79       IF( ln_rsttr  .AND. ln_pisclo )                              CALL p4z_clo            ! damping on closed seas 
    8079      IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt )      ! Relaxation of some tracers 
    8180      ! 
     
    164163      NAMELIST/nampiskrp/ xkr_eta, xkr_zeta, xkr_ncontent, xkr_mass_min, xkr_mass_max 
    165164#endif 
    166       NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp, ln_pisclo 
     165      NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp 
    167166      NAMELIST/nampismass/ ln_check_mass 
    168167      !!---------------------------------------------------------------------- 
     
    215214      ln_pisdmp = .true. 
    216215      nn_pisdmp = 1 
    217       ln_pisclo = .false. 
    218216 
    219217      REWIND( numnatp ) 
     
    225223         WRITE(numout,*) '    Relaxation of tracer to glodap mean value             ln_pisdmp      =', ln_pisdmp 
    226224         WRITE(numout,*) '    Frequency of Relaxation                               nn_pisdmp      =', nn_pisdmp 
    227          WRITE(numout,*) '    Restoring of tracer to initial value  on closed seas  ln_pisclo      =', ln_pisclo 
    228225         WRITE(numout,*) ' ' 
    229226      ENDIF 
     
    421418   END SUBROUTINE p4z_chk_mass 
    422419 
    423    SUBROUTINE p4z_clo    
    424       !!--------------------------------------------------------------------- 
    425       !!                  ***  ROUTINE p4z_clo  *** 
    426       !! 
    427       !! ** Purpose :   Closed sea domain initialization 
    428       !! 
    429       !! ** Method  :   if a closed sea is located only in a model grid point 
    430       !!                we restore to initial data 
    431       !! 
    432       !! ** Action  :   ictsi1(), ictsj1() : south-west closed sea limits (i,j) 
    433       !!                ictsi2(), ictsj2() : north-east Closed sea limits (i,j) 
    434       !!---------------------------------------------------------------------- 
    435       INTEGER, PARAMETER           ::   npicts   = 4        ! number of closed sea 
    436       INTEGER, DIMENSION(npicts)   ::   ictsi1, ictsj1      ! south-west closed sea limits (i,j) 
    437       INTEGER, DIMENSION(npicts)   ::   ictsi2, ictsj2      ! north-east closed sea limits (i,j) 
    438       INTEGER :: ji, jj, jk, jn, jl, jc                     ! dummy loop indices 
    439       INTEGER :: ierr                                       ! local integer 
    440       REAL(wp), POINTER, DIMENSION(:,:,:,:) ::  ztrcdta     ! 4D  workspace 
    441       !!---------------------------------------------------------------------- 
    442  
    443       IF(lwp) WRITE(numout,*) 
    444       IF(lwp) WRITE(numout,*)' p4z_clo : closed seas ' 
    445       IF(lwp) WRITE(numout,*)'~~~~~~~' 
    446  
    447       ! initial values 
    448       ictsi1(:) = 1  ;  ictsi2(:) = 1  
    449       ictsj1(:) = 1  ;  ictsj2(:) = 1  
    450  
    451       ! set the closed seas (in data domain indices) 
    452       ! ------------------- 
    453  
    454       IF( cp_cfg == "orca" ) THEN 
    455          ! 
    456          SELECT CASE ( jp_cfg ) 
    457          !                                           ! ======================= 
    458          CASE ( 2 )                                  !  ORCA_R2 configuration 
    459             !                                        ! ======================= 
    460             !                                            ! Caspian Sea 
    461             ictsi1(1)   =  11  ;  ictsj1(1)   = 103 
    462             ictsi2(1)   =  17  ;  ictsj2(1)   = 112 
    463             !                                            ! Great North American Lakes 
    464             ictsi1(2)   =  97  ;  ictsj1(2)   = 107 
    465             ictsi2(2)   = 103  ;  ictsj2(2)   = 111 
    466             !                                            ! Black Sea 1 : west part of the Black Sea 
    467             ictsi1(3)   = 174  ; ictsj1(3)   = 107 
    468             ictsi2(3)   = 181  ; ictsj2(3)   = 112 
    469             !                                            ! Black Sea 2 : est part of the Black Sea 
    470             ictsi1(4)   =   2  ;  ictsj1(4)   = 107 
    471             ictsi2(4)   =   6  ;  ictsj2(4)   = 112 
    472             !                                        ! ======================= 
    473          CASE ( 4 )                                  !  ORCA_R4 configuration 
    474             !                                        ! ======================= 
    475             !                                            ! Caspian Sea 
    476             ictsi1(1)   =  4  ;  ictsj1(1)   = 53 
    477             ictsi2(1)   =  4  ;  ictsj2(1)   = 56 
    478             !                                            ! Great North American Lakes 
    479             ictsi1(2)   = 49  ;  ictsj1(2)   = 55 
    480             ictsi2(2)   = 51  ;  ictsj2(2)   = 56 
    481             !                                            ! Black Sea 
    482             ictsi1(3)   = 88  ;  ictsj1(3)   = 55 
    483             ictsi2(3)   = 91  ;  ictsj2(3)   = 56 
    484             !                                            ! Baltic Sea 
    485             ictsi1(4)   = 75  ;  ictsj1(4)   = 59 
    486             ictsi2(4)   = 76  ;  ictsj2(4)   = 61 
    487             !                                        ! ======================= 
    488             !                                        ! ======================= 
    489          CASE ( 025 )                                ! ORCA_R025 configuration 
    490             !                                        ! ======================= 
    491                                                      ! Caspian + Aral sea 
    492             ictsi1(1)   = 1330 ; ictsj1(1)   = 645 
    493             ictsi2(1)   = 1400 ; ictsj2(1)   = 795 
    494             !                                        ! Azov Sea 
    495             ictsi1(2)   = 1284 ; ictsj1(2)   = 722 
    496             ictsi2(2)   = 1304 ; ictsj2(2)   = 747 
    497             ! 
    498          END SELECT 
    499          ! 
    500       ENDIF 
    501  
    502       ! convert the position in local domain indices 
    503       ! -------------------------------------------- 
    504       DO jc = 1, npicts  
    505          ictsi1(jc)   = mi0( ictsi1(jc) ) 
    506          ictsj1(jc)   = mj0( ictsj1(jc) ) 
    507  
    508          ictsi2(jc)   = mi1( ictsi2(jc) ) 
    509          ictsj2(jc)   = mj1( ictsj2(jc) ) 
    510       END DO 
    511  
    512       ! Restore close seas values to initial data 
    513       IF( ln_trcdta .AND. nb_trcdta > 0 )  THEN   ! Initialisation of tracer from a file that may also be used for damping 
    514          ! 
    515          CALL wrk_alloc( jpi, jpj, jpk, nb_trcdta, ztrcdta )   ! Memory allocation 
    516          ! 
    517          CALL trc_dta( nittrc000, ztrcdta )   ! read tracer data at nittrc000 
    518          ! 
    519          DO jn = 1, jptra 
    520             IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
    521                 jl = n_trc_index(jn) 
    522                 DO jc = 1, npicts 
    523                    DO jk = 1, jpkm1 
    524                       DO jj = ictsj1(jc), ictsj2(jc) 
    525                          DO ji = ictsi1(jc), ictsi2(jc) 
    526                             trn(ji,jj,jk,jn) = ztrcdta(ji,jj,jk,jl) * tmask(ji,jj,jk) 
    527                             trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn) 
    528                          ENDDO 
    529                       ENDDO 
    530                    ENDDO 
    531                 ENDDO 
    532              ENDIF 
    533           ENDDO 
    534           CALL wrk_dealloc( jpi, jpj, jpk, nb_trcdta, ztrcdta ) 
    535       ENDIF 
    536       ! 
    537    END SUBROUTINE p4z_clo 
    538420#else 
    539421   !!====================================================================== 
  • trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/sms_pisces.F90

    r3780 r3882  
    5656   LOGICAL  ::  ln_pisdmp          !: restoring or not of nutrients to a mean value 
    5757   INTEGER  ::  nn_pisdmp          !: frequency of relaxation or not of nutrients to a mean value 
    58    LOGICAL  ::  ln_pisclo          !: Restoring or not of nutrients to initial value on closed seas 
    5958 
    6059   !!* Mass conservation 
  • trunk/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r3294 r3882  
    1111   !!            3.3  !  2010-06  (C. Ethe, G. Madec) merge TRA-TRC  
    1212   !!---------------------------------------------------------------------- 
    13 #if  defined key_top && defined key_trcdmp  
    14    !!---------------------------------------------------------------------- 
    15    !!   key_trcdmp                                         internal damping 
     13#if  defined key_top  
    1614   !!---------------------------------------------------------------------- 
    1715   !!   trc_dmp      : update the tracer trend with the internal damping 
     
    2523   USE prtctl_trc      ! Print control for debbuging 
    2624   USE trdtra 
     25   USE trdmod_oce 
    2726 
    2827   IMPLICIT NONE 
     
    3029 
    3130   PUBLIC trc_dmp            ! routine called by step.F90 
     31   PUBLIC trc_dmp_clo        ! routine called by step.F90 
    3232   PUBLIC trc_dmp_alloc      ! routine called by nemogcm.F90 
    3333 
    34    LOGICAL , PUBLIC, PARAMETER ::   lk_trcdmp = .TRUE.   !: internal damping flag 
    35  
    3634   !                                !!* Namelist namtrc_dmp : passive tracer newtonian damping * 
    37    INTEGER  ::   nn_hdmp_tr =   -1   ! = 0/-1/'latitude' for damping over passive tracer 
    38    INTEGER  ::   nn_zdmp_tr =    0   ! = 0/1/2 flag for damping in the mixed layer 
    39    REAL(wp) ::   rn_surf_tr =   50.  ! surface time scale for internal damping        [days] 
    40    REAL(wp) ::   rn_bot_tr  =  360.  ! bottom time scale for internal damping         [days] 
    41    REAL(wp) ::   rn_dep_tr  =  800.  ! depth of transition between rn_surf and rn_bot [meters] 
    42    INTEGER  ::   nn_file_tr =    2   ! = 1 create a damping.coeff NetCDF file  
    43  
    4435   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1) 
     36 
     37   INTEGER, PARAMETER           ::   npncts   = 5        ! number of closed sea 
     38   INTEGER, DIMENSION(npncts)   ::   nctsi1, nctsj1      ! south-west closed sea limits (i,j) 
     39   INTEGER, DIMENSION(npncts)   ::   nctsi2, nctsj2      ! north-east closed sea limits (i,j) 
    4540 
    4641   !! * Substitutions 
     
    8681      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
    8782      !! 
    88       INTEGER  ::   ji, jj, jk, jn       ! dummy loop indices 
     83      INTEGER  ::   ji, jj, jk, jn, jl       ! dummy loop indices 
    8984      REAL(wp) ::   ztra                 ! temporary scalars 
    9085      CHARACTER (len=22) :: charout 
    9186      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrtrd 
     87      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::  ztrcdta   ! 4D  workspace 
    9288      !!---------------------------------------------------------------------- 
    9389      ! 
     
    9995 
    10096      IF( l_trdtrc )   CALL wrk_alloc( jpi, jpj, jpk, ztrtrd )   ! temporary save of trends 
    101  
    102       ! 1. Newtonian damping trends on tracer fields 
    103       ! -------------------------------------------- 
    104       ! Initialize the input fields for newtonian damping 
    105       CALL trc_dta( kt ) 
    106       !                                                          ! =========== 
    107       DO jn = 1, jptra                                           ! tracer loop 
    108          !                                                       ! =========== 
    109          IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)    ! save trends  
    110  
    111          IF( lutini(jn) ) THEN 
     97      ! 
     98      IF( nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping 
     99         ! 
     100         CALL wrk_alloc( jpi, jpj, jpk, nb_trcdta, ztrcdta )    ! Memory allocation 
     101         CALL trc_dta( kt, ztrcdta )   ! read tracer data at nit000 
     102         !                                                          ! =========== 
     103         DO jn = 1, jptra                                           ! tracer loop 
     104            !                                                       ! =========== 
     105            IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)    ! save trends  
    112106            ! 
    113             SELECT CASE ( nn_zdmp_trc ) 
    114             ! 
    115             CASE( 0 )                !==  newtonian damping throughout the water column  ==! 
    116                DO jk = 1, jpkm1 
    117                   DO jj = 2, jpjm1 
    118                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    119                         ztra = restotr(ji,jj,jk) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) ) 
    120                         tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     107            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     108                
     109               jl = n_trc_index(jn)  
     110 
     111               SELECT CASE ( nn_zdmp_tr ) 
     112               ! 
     113               CASE( 0 )                !==  newtonian damping throughout the water column  ==! 
     114                  DO jk = 1, jpkm1 
     115                     DO jj = 2, jpjm1 
     116                        DO ji = fs_2, fs_jpim1   ! vector opt. 
     117                           ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk,jl) - trb(ji,jj,jk,jn) ) 
     118                           tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     119                        END DO 
    121120                     END DO 
    122121                  END DO 
    123                END DO 
    124             ! 
    125             CASE ( 1 )                !==  no damping in the turbocline (avt > 5 cm2/s)  ==! 
    126                DO jk = 1, jpkm1 
    127                   DO jj = 2, jpjm1 
    128                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    129                         IF( avt(ji,jj,jk) <= 5.e-4 )  THEN  
    130                            ztra = restotr(ji,jj,jk) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) ) 
    131                            tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
    132                         ENDIF 
     122               ! 
     123               CASE ( 1 )                !==  no damping in the turbocline (avt > 5 cm2/s)  ==! 
     124                  DO jk = 1, jpkm1 
     125                     DO jj = 2, jpjm1 
     126                        DO ji = fs_2, fs_jpim1   ! vector opt. 
     127                           IF( avt(ji,jj,jk) <= 5.e-4 )  THEN  
     128                              ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk,jl) - trb(ji,jj,jk,jn) ) 
     129                              tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     130                           ENDIF 
     131                        END DO 
    133132                     END DO 
    134133                  END DO 
    135                END DO 
    136             ! 
    137             CASE ( 2 )               !==  no damping in the mixed layer   ==!  
    138                DO jk = 1, jpkm1 
    139                   DO jj = 2, jpjm1 
    140                      DO ji = fs_2, fs_jpim1   ! vector opt. 
    141                         IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN 
    142                            ztra = restotr(ji,jj,jk,jn) * ( trdta(ji,jj,jk,jn) - trb(ji,jj,jk,jn) ) 
    143                            tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
    144                         END IF 
     134               ! 
     135               CASE ( 2 )               !==  no damping in the mixed layer   ==!  
     136                  DO jk = 1, jpkm1 
     137                     DO jj = 2, jpjm1 
     138                        DO ji = fs_2, fs_jpim1   ! vector opt. 
     139                           IF( fsdept(ji,jj,jk) >= hmlp (ji,jj) ) THEN 
     140                              ztra = restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk,jl) - trb(ji,jj,jk,jn) ) 
     141                              tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + ztra 
     142                           END IF 
     143                        END DO 
    145144                     END DO 
    146145                  END DO 
    147                END DO 
    148             !   
    149             END SELECT 
    150             !  
    151          ENDIF 
    152          ! 
    153          IF( l_trdtrc ) THEN 
    154             ztrtrd(:,:,:) = tra(:,:,:,jn) -  ztrtrd(:,:,:) 
    155             CALL trd_tra( kt, 'TRC', jn, jptra_trd_dmp, ztrtrd ) 
    156          END IF 
    157          !                                                       ! =========== 
    158       END DO                                                     ! tracer loop 
    159       !                                                          ! =========== 
     146               !   
     147               END SELECT 
     148               !  
     149            ENDIF 
     150            ! 
     151            IF( l_trdtrc ) THEN 
     152               ztrtrd(:,:,:) = tra(:,:,:,jn) -  ztrtrd(:,:,:) 
     153               CALL trd_tra( kt, 'TRC', jn, jptra_trd_dmp, ztrtrd ) 
     154            END IF 
     155            !                                                       ! =========== 
     156         END DO                                                     ! tracer loop 
     157         !                                                          ! =========== 
     158         CALL wrk_dealloc( jpi, jpj, jpk, nb_trcdta, ztrcdta ) 
     159      ENDIF 
     160      ! 
    160161      IF( l_trdtrc )  CALL wrk_dealloc( jpi, jpj, jpk, ztrtrd ) 
    161162      !                                          ! print mean trends (used for debugging) 
     
    168169      ! 
    169170   END SUBROUTINE trc_dmp 
     171 
     172   SUBROUTINE trc_dmp_clo( kt ) 
     173      !!--------------------------------------------------------------------- 
     174      !!                  ***  ROUTINE trc_dmp_clo  *** 
     175      !! 
     176      !! ** Purpose :   Closed sea domain initialization 
     177      !! 
     178      !! ** Method  :   if a closed sea is located only in a model grid point 
     179      !!                we restore to initial data 
     180      !! 
     181      !! ** Action  :   nctsi1(), nctsj1() : south-west closed sea limits (i,j) 
     182      !!                nctsi2(), nctsj2() : north-east Closed sea limits (i,j) 
     183      !!---------------------------------------------------------------------- 
     184      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     185      ! 
     186      INTEGER :: ji, jj, jk, jn, jl, jc                     ! dummy loop indicesa 
     187      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::  ztrcdta     ! 4D  workspace 
     188 
     189      !!---------------------------------------------------------------------- 
     190 
     191      IF( kt == nit000 ) THEN 
     192         ! initial values 
     193         nctsi1(:) = 1  ;  nctsi2(:) = 1 
     194         nctsj1(:) = 1  ;  nctsj2(:) = 1 
     195 
     196         ! set the closed seas (in data domain indices) 
     197         ! ------------------- 
     198 
     199         IF( cp_cfg == "orca" ) THEN 
     200            ! 
     201            SELECT CASE ( jp_cfg ) 
     202            !                                           ! ======================= 
     203            CASE ( 2 )                                  !  ORCA_R2 configuration 
     204               !                                        ! ======================= 
     205               !                                            ! Caspian Sea 
     206               nctsi1(1)   =  11  ;  nctsj1(1)   = 103 
     207               nctsi2(1)   =  17  ;  nctsj2(1)   = 112 
     208               !                                            ! Great North American Lakes 
     209               nctsi1(2)   =  97  ;  nctsj1(2)   = 107 
     210               nctsi2(2)   = 103  ;  nctsj2(2)   = 111 
     211               !                                            ! Black Sea 1 : west part of the Black Sea 
     212               nctsi1(3)   = 174  ;  nctsj1(3)   = 107 
     213               nctsi2(3)   = 181  ;  nctsj2(3)   = 112 
     214              !                                            ! Black Sea 2 : est part of the Black Sea 
     215               nctsi1(4)   =   2  ;  nctsj1(4)   = 107 
     216               nctsi2(4)   =   6  ;  nctsj2(4)   = 112 
     217               !                                            ! Baltic Sea 
     218               nctsi1(5)   =  145 ;  nctsj1(5)   = 116 
     219               nctsi2(5)   =  150 ;  nctsj2(5)   = 126 
     220               !                                        ! ======================= 
     221            CASE ( 4 )                                  !  ORCA_R4 configuration 
     222               !                                        ! ======================= 
     223               !                                            ! Caspian Sea 
     224               nctsi1(1)   =  4  ;  nctsj1(1)   = 53 
     225               nctsi2(1)   =  4  ;  nctsj2(1)   = 56 
     226               !                                            ! Great North American Lakes 
     227               nctsi1(2)   = 49  ;  nctsj1(2)   = 55 
     228               nctsi2(2)   = 51  ;  nctsj2(2)   = 56 
     229               !                                            ! Black Sea 
     230               nctsi1(3)   = 88  ;  nctsj1(3)   = 55 
     231               nctsi2(3)   = 91  ;  nctsj2(3)   = 56 
     232               !                                            ! Baltic Sea 
     233               nctsi1(4)   = 75  ;  nctsj1(4)   = 59 
     234               nctsi2(4)   = 76  ;  nctsj2(4)   = 61 
     235               !                                        ! ======================= 
     236            CASE ( 025 )                                ! ORCA_R025 configuration 
     237               !                                        ! ======================= 
     238                                                     ! Caspian + Aral sea 
     239               nctsi1(1)   = 1330 ; nctsj1(1)   = 645 
     240               nctsi2(1)   = 1400 ; nctsj2(1)   = 795 
     241               !                                        ! Azov Sea 
     242               nctsi1(2)   = 1284 ; nctsj1(2)   = 722 
     243               nctsi2(2)   = 1304 ; nctsj2(2)   = 747 
     244               ! 
     245            END SELECT 
     246            ! 
     247         ENDIF 
     248         ! 
     249 
     250         ! convert the position in local domain indices 
     251         ! -------------------------------------------- 
     252         DO jc = 1, npncts 
     253            nctsi1(jc)   = mi0( nctsi1(jc) ) 
     254            nctsj1(jc)   = mj0( nctsj1(jc) ) 
     255 
     256            nctsi2(jc)   = mi1( nctsi2(jc) ) 
     257            nctsj2(jc)   = mj1( nctsj2(jc) ) 
     258         END DO 
     259         ! 
     260      ENDIF 
     261 
     262      ! Restore close seas values to initial data 
     263      IF( ln_trcdta .AND. nb_trcdta > 0 )  THEN   ! Initialisation of tracer from a file that may also be used for damping 
     264         ! 
     265         IF(lwp)  WRITE(numout,*) 
     266         IF(lwp)  WRITE(numout,*) ' trc_dmp_clo : Restoring of nutrients on close seas at time-step kt = ', kt 
     267         IF(lwp)  WRITE(numout,*) 
     268         ! 
     269         CALL wrk_alloc( jpi, jpj, jpk, nb_trcdta, ztrcdta )   ! Memory allocation 
     270         ! 
     271         CALL trc_dta( kt , ztrcdta )   ! read tracer data at nittrc000 
     272         ! 
     273         DO jn = 1, jptra 
     274            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     275                jl = n_trc_index(jn) 
     276                DO jc = 1, npncts 
     277                   DO jk = 1, jpkm1 
     278                      DO jj = nctsj1(jc), nctsj2(jc) 
     279                         DO ji = nctsi1(jc), nctsi2(jc) 
     280                            trn(ji,jj,jk,jn) = ztrcdta(ji,jj,jk,jl) * tmask(ji,jj,jk) 
     281                            trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn) 
     282                         ENDDO 
     283                      ENDDO 
     284                   ENDDO 
     285                ENDDO 
     286             ENDIF 
     287          ENDDO 
     288          CALL wrk_dealloc( jpi, jpj, jpk, nb_trcdta, ztrcdta ) 
     289      ENDIF 
     290      ! 
     291   END SUBROUTINE trc_dmp_clo 
    170292 
    171293 
     
    199321      END SELECT 
    200322 
    201       IF( .NOT. lk_dtatrc )   & 
    202          &   CALL ctl_stop( 'no passive tracer data define key_dtatrc' ) 
    203  
    204       IF( .NOT. lk_tradmp )   & 
     323      IF( .NOT. ln_tradmp )   & 
    205324         &   CALL ctl_stop( 'passive trace damping need key_tradmp to compute damping coef.' ) 
    206325      ! 
     
    214333      ! 
    215334   END SUBROUTINE trc_dmp_init 
     335 
    216336#else 
    217337   !!---------------------------------------------------------------------- 
    218    !!   Default key                                     NO internal damping 
    219    !!---------------------------------------------------------------------- 
    220    LOGICAL , PUBLIC, PARAMETER ::   lk_trcdmp = .FALSE.    !: internal damping flag 
     338   !!  Dummy module :                                     No passive tracer 
     339   !!---------------------------------------------------------------------- 
    221340CONTAINS 
    222341   SUBROUTINE trc_dmp( kt )        ! Empty routine 
     
    225344   END SUBROUTINE trc_dmp 
    226345#endif 
     346 
     347 
    227348   !!====================================================================== 
    228349END MODULE trcdmp 
  • trunk/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90

    r3718 r3882  
    1313   !!   trc_nam_trp  : read the passive tracer namelist for transport 
    1414   !!---------------------------------------------------------------------- 
    15    USE trc                 ! ocean passive tracers variables 
     15   USE oce_trc              ! shared ocean passive tracers variables 
     16   USE trc                 ! passive tracers variables 
    1617   USE in_out_manager      ! ocean dynamics and active tracers variables 
    1718 
     
    4849   INTEGER , PUBLIC ::   nn_trczdf_exp = 3             !: number of sub-time step (explicit time stepping) 
    4950 
    50  
    51 #if defined key_trcdmp 
    5251   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) ** 
    5352   INTEGER , PUBLIC ::   nn_hdmp_tr      =   -1       ! = 0/-1/'latitude' for damping over passive tracer 
     
    5756   REAL(wp), PUBLIC ::   rn_dep_tr       =  800.      ! depth of transition between rn_surf and rn_bot [meters] 
    5857   INTEGER , PUBLIC ::   nn_file_tr      =    2       ! = 1 create a damping.coeff NetCDF file  
    59 #endif 
    6058 
    6159   !!---------------------------------------------------------------------- 
     
    8280      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp 
    8381      NAMELIST/namtrc_rad/ ln_trcrad 
    84 #if defined key_trcdmp 
    85       NAMELIST/namtrc_dmp/ ln_trcdmp, nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, & 
     82      NAMELIST/namtrc_dmp/ nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, & 
    8683        &                  rn_bot_tr , rn_dep_tr , nn_file_tr 
    87 #endif 
    8884      !!---------------------------------------------------------------------- 
    8985 
     
    148144 
    149145 
    150 # if defined key_trcdmp 
    151146      REWIND ( numnat )                  ! Read Namelist namtra_dmp : temperature and salinity damping term 
    152147      READ   ( numnat, namtrc_dmp ) 
    153       IF( lzoom )   nn_zdmp_trc = 0           ! restoring to climatology at closed north or south boundaries 
     148      IF( lzoom )   nn_zdmp_tr = 0           ! restoring to climatology at closed north or south boundaries 
    154149 
    155150      IF(lwp) THEN                       ! Namelist print 
     
    158153         WRITE(numout,*) '~~~~~~~' 
    159154         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter' 
    160          WRITE(numout,*) '      add a damping term or not      ln_trcdmp = ', ln_trcdmp 
    161155         WRITE(numout,*) '      tracer damping option          nn_hdmp_tr = ', nn_hdmp_tr 
    162156         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)' 
     
    166160         WRITE(numout,*) '      create a damping.coeff file    nn_file_tr = ', nn_file_tr 
    167161      ENDIF 
    168 #endif 
    169162      ! 
    170163   END SUBROUTINE trc_nam_trp 
  • trunk/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp.F90

    r3680 r3882  
    6666                                CALL trc_sbc( kstp )            ! surface boundary condition 
    6767         IF( lk_trabbl )        CALL trc_bbl( kstp )            ! advective (and/or diffusive) bottom boundary layer scheme 
    68          IF( lk_trcdmp )        CALL trc_dmp( kstp )            ! internal damping trends 
     68         IF( ln_trcdmp )        CALL trc_dmp( kstp )            ! internal damping trends 
     69         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kstp )        ! internal damping trends on closed seas only 
    6970                                CALL trc_adv( kstp )            ! horizontal & vertical advection  
    7071                                CALL trc_ldf( kstp )            ! lateral mixing 
  • trunk/NEMOGCM/NEMO/TOP_SRC/trc.F90

    r3770 r3882  
    2626   INTEGER, PUBLIC                                                 ::   numrtr        !: logical unit for trc restart (read ) 
    2727   INTEGER, PUBLIC                                                 ::   numrtw        !: logical unit for trc restart ( write ) 
    28    LOGICAL, PUBLIC                                                 ::   ln_top_euler  !: boolean term for euler integration in the first timestep 
    2928 
    3029   !! passive tracers fields (before,now,after) 
     
    5352   CHARACTER(len = 80) , PUBLIC                                    ::  cn_trcrst_out  !: suffix of pass. tracer restart name (output) 
    5453   REAL(wp)            , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::  rdttrc         !: vertical profile of passive tracer time step 
     54   LOGICAL             , PUBLIC                                    ::  ln_top_euler  !: boolean term for euler integration  
    5555   LOGICAL             , PUBLIC                                    ::  ln_trcdta      !: Read inputs data from files 
    5656   LOGICAL             , PUBLIC                                    ::  ln_trcdmp      !: internal damping flag 
     57   LOGICAL             , PUBLIC                                    ::  ln_trcdmp_clo  !: internal damping flag on closed seas 
    5758   INTEGER             , PUBLIC                                    ::  nittrc000       !: first time step of passive tracers model 
    5859 
  • trunk/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    r3827 r3882  
    254254            ENDDO 
    255255         ENDIF 
    256          ! 
    257          IF( .NOT.ln_trcdmp ) THEN                   !==   deallocate data structure   ==!  
     256          
     257         IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN      !==   deallocate data structure   ==!  
    258258            !                                              (data used only for initialisation) 
    259259            IF(lwp) WRITE(numout,*) 'trc_dta: deallocate data arrays as they are only use to initialize the run' 
  • trunk/NEMOGCM/NEMO/TOP_SRC/trcnam.F90

    r3749 r3882  
    5959      !! 
    6060      NAMELIST/namtrc/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, & 
    61          &             cn_trcrst_in, cn_trcrst_out, sn_tracer, ln_trcdta, ln_trcdmp, & 
    62          &             ln_top_euler 
     61         &             cn_trcrst_in, cn_trcrst_out, sn_tracer, ln_trcdta, & 
     62         &             ln_trcdmp, ln_trcdmp_clo, ln_top_euler 
    6363#if defined key_trdmld_trc  || defined key_trdtrc 
    6464      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, & 
     
    9292         sn_tracer(jn)%llsave  = .TRUE. 
    9393      END DO 
    94       ln_trcdta = .FALSE. 
    95       ln_trcdmp = .FALSE. 
     94      ln_trcdta     = .FALSE. 
     95      ln_trcdmp     = .FALSE. 
     96      ln_trcdmp_clo = .FALSE. 
    9697 
    9798 
     
    121122         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta 
    122123         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp 
     124         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo 
    123125         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler 
    124126         WRITE(numout,*) ' ' 
     
    181183 
    182184 
    183       IF( ln_trcdmp .AND. .NOT.ln_trcdta ) THEN 
    184          CALL ctl_warn( 'trc_nam: passive tracer damping requires data from files we set ln_trcdta to TRUE' ) 
    185          ln_trcdta = .TRUE. 
    186       ENDIF 
    187       ! 
    188       IF( ln_rsttr .AND. .NOT.ln_trcdmp .AND. ln_trcdta ) THEN 
    189           CALL ctl_warn( 'trc_nam: passive tracer restart and  data intialisation, ',   & 
    190              &           'we keep the restart values and set ln_trcdta to FALSE' ) 
    191          ln_trcdta = .FALSE. 
    192       ENDIF 
     185      IF( ln_rsttr )                      ln_trcdta = .FALSE.   ! restart : no need of clim data 
     186      ! 
     187      IF( ln_trcdmp .OR. ln_trcdmp_clo )  ln_trcdta = .TRUE.   ! damping : need to have clim data 
    193188      ! 
    194189      IF( .NOT.ln_trcdta ) THEN 
     
    199194         IF( ln_rsttr ) THEN 
    200195            WRITE(numout,*) 
    201             WRITE(numout,*) '    read a restart file for passive tracer : ', TRIM( cn_trcrst_in ) 
    202             WRITE(numout,*) 
    203          ELSE 
    204             IF( .NOT.ln_trcdta ) THEN 
    205                 WRITE(numout,*) 
    206                 WRITE(numout,*) '  All the passive tracers are initialised with constant values ' 
    207                 WRITE(numout,*) 
    208             ENDIF 
     196            WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in ) 
     197            WRITE(numout,*) 
     198         ENDIF 
     199         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN 
     200            WRITE(numout,*) 
     201            WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies ' 
     202            WRITE(numout,*) 
     203         ENDIF 
     204         IF( .NOT.ln_trcdta ) THEN 
     205            WRITE(numout,*) 
     206            WRITE(numout,*) '  All the passive tracers are initialised with constant values ' 
     207            WRITE(numout,*) 
    209208         ENDIF 
    210209      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.