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 7278 for branches/2016/dev_CNRS_2016/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90 – NEMO

Ignore:
Timestamp:
2016-11-21T10:38:43+01:00 (8 years ago)
Author:
flavoni
Message:

update branch CNRS-2016 to trunk 6720

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_CNRS_2016/NEMOGCM/NEMO/TOP_SRC/TRP/trcdmp.F90

    r7277 r7278  
    3838   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restotr   ! restoring coeff. on tracers (s-1) 
    3939 
    40    INTEGER, PARAMETER           ::   npncts   = 5        ! number of closed sea 
     40   INTEGER, PARAMETER           ::   npncts   = 8        ! number of closed sea 
    4141   INTEGER, DIMENSION(npncts)   ::   nctsi1, nctsj1      ! south-west closed sea limits (i,j) 
    4242   INTEGER, DIMENSION(npncts)   ::   nctsi2, nctsj2      ! north-east closed sea limits (i,j) 
     
    104104               ! 
    105105               jl = n_trc_index(jn)  
    106                CALL trc_dta( kt, sf_trcdta(jl) )   ! read tracer data at nit000 
    107                ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:) * tmask(:,:,:) * rf_trfac(jl) 
     106               CALL trc_dta( kt, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000 
    108107               ! 
    109108               SELECT CASE ( nn_zdmp_tr ) 
     
    181180      !!---------------------------------------------------------------------- 
    182181      ! 
    183       IF( nn_timing == 1 )  CALL timing_start('trc_dmp_init') 
     182      IF( nn_timing == 1 )  CALL timing_start('trc_dmp_ini') 
    184183      ! 
    185184      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping 
     
    200199         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr 
    201200      ENDIF 
     201      !                          ! Allocate arrays 
     202      IF( trc_dmp_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_dmp_ini: unable to allocate arrays' ) 
    202203      ! 
    203204      SELECT CASE ( nn_zdmp_tr ) 
     
    238239      !!                nctsi2(), nctsj2() : north-east Closed sea limits (i,j) 
    239240      !!---------------------------------------------------------------------- 
    240       INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
    241       ! 
    242       INTEGER ::   ji , jj, jk, jn, jl, jc   ! dummy loop indicesa 
    243       INTEGER ::   isrow                     ! local index 
    244       !!---------------------------------------------------------------------- 
    245       ! 
     241      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     242      ! 
     243      INTEGER :: ji , jj, jk, jn, jl, jc                    ! dummy loop indicesa 
     244      INTEGER :: isrow                                      ! local index 
     245      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta       ! 3D  workspace 
     246 
     247      !!---------------------------------------------------------------------- 
     248 
    246249      IF( kt == nit000 ) THEN 
    247250         ! initial values 
     
    261264            ! 
    262265                                                        ! Caspian Sea 
    263             nctsi1(1)   = 332  ; nctsj1(1)   = 243 - isrow 
    264             nctsi2(1)   = 344  ; nctsj2(1)   = 275 - isrow 
     266            nctsi1(1)   = 333  ; nctsj1(1)   = 243 - isrow 
     267            nctsi2(1)   = 342  ; nctsj2(1)   = 274 - isrow 
     268            !                                           ! Lake Superior 
     269            nctsi1(2)   = 198  ; nctsj1(2)   = 258 - isrow 
     270            nctsi2(2)   = 204  ; nctsj2(2)   = 262 - isrow 
     271            !                                           ! Lake Michigan 
     272            nctsi1(3)   = 201  ; nctsj1(3)   = 250 - isrow 
     273            nctsi2(3)   = 203  ; nctsj2(3)   = 256 - isrow 
     274            !                                           ! Lake Huron 
     275            nctsi1(4)   = 204  ; nctsj1(4)   = 252 - isrow 
     276            nctsi2(4)   = 209  ; nctsj2(4)   = 256 - isrow 
     277            !                                           ! Lake Erie 
     278            nctsi1(5)   = 206  ; nctsj1(5)   = 249 - isrow 
     279            nctsi2(5)   = 209  ; nctsj2(5)   = 251 - isrow 
     280            !                                           ! Lake Ontario 
     281            nctsi1(6)   = 210  ; nctsj1(6)   = 252 - isrow 
     282            nctsi2(6)   = 212  ; nctsj2(6)   = 252 - isrow 
     283            !                                           ! Victoria Lake 
     284            nctsi1(7)   = 321  ; nctsj1(7)   = 180 - isrow 
     285            nctsi2(7)   = 322  ; nctsj2(7)   = 189 - isrow 
     286            !                                           ! Baltic Sea 
     287            nctsi1(8)   = 297  ; nctsj1(8)   = 270 - isrow 
     288            nctsi2(8)   = 308  ; nctsj2(8)   = 293 - isrow 
    265289            !                                         
    266290            !                                           ! ======================= 
     
    331355         IF(lwp)  WRITE(numout,*) 
    332356         ! 
     357         CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )   ! Memory allocation 
     358         ! 
    333359         DO jn = 1, jptra 
    334360            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
    335361                jl = n_trc_index(jn) 
    336                 CALL trc_dta( kt, sf_trcdta(jl) )   ! read tracer data at nit000 
     362                CALL trc_dta( kt, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000 
    337363                DO jc = 1, npncts 
    338364                   DO jk = 1, jpkm1 
    339365                      DO jj = nctsj1(jc), nctsj2(jc) 
    340366                         DO ji = nctsi1(jc), nctsi2(jc) 
    341                             trn(ji,jj,jk,jn) = sf_trcdta(jl)%fnow(ji,jj,jk) * tmask(ji,jj,jk) * rf_trfac(jl) 
     367                            trn(ji,jj,jk,jn) = ztrcdta(ji,jj,jk) 
    342368                            trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn) 
    343369                         ENDDO 
     
    347373             ENDIF 
    348374          ENDDO 
    349          ! 
     375          CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta ) 
    350376      ENDIF 
    351377      ! 
    352378   END SUBROUTINE trc_dmp_clo 
    353379 
     380  
    354381#else 
    355382   !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.