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 7351 for branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/TOP_SRC/trcini.F90 – NEMO

Ignore:
Timestamp:
2016-11-28T17:04:10+01:00 (7 years ago)
Author:
emanuelaclementi
Message:

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r5836 r7351  
    2626   USE sbc_oce 
    2727   USE trcice          ! tracers in sea ice 
     28   USE trcbc,   only : trc_bc_init ! generalized Boundary Conditions 
    2829  
    2930   IMPLICIT NONE 
     
    3233   PUBLIC   trc_init   ! called by opa 
    3334 
    34     !! * Substitutions 
    35 #  include "domzgr_substitute.h90" 
    3635   !!---------------------------------------------------------------------- 
    3736   !! NEMO/TOP 4.0 , NEMO Consortium (2011) 
     
    119118      !                                                              ! masked grid volume 
    120119      DO jk = 1, jpk 
    121          cvol(:,:,jk) = e1e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk) 
     120         cvol(:,:,jk) = e1e2t(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
    122121      END DO 
    123       IF( lk_degrad ) cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)      ! degrad option: reduction by facvol 
     122      IF( lk_degrad )   cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)    ! degrad option: reduction by facvol 
    124123      !                                                              ! total volume of the ocean  
    125124      areatot = glob_sum( cvol(:,:,:) ) 
     
    204203      USE trcdta          ! initialisation from files 
    205204      ! 
    206       INTEGER ::   jk, jn, jl    ! dummy loop indices 
    207       REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace 
    208       !!---------------------------------------------------------------------- 
    209       ! 
     205      INTEGER :: jn, jl   ! dummy loop indices 
     206      !!---------------------------------------------------------------------- 
     207      ! 
     208      ! Initialisation of tracers Initial Conditions 
    210209      IF( ln_trcdta )      CALL trc_dta_init(jptra) 
    211210 
     211      ! Initialisation of tracers Boundary Conditions 
     212      IF( lk_my_trc )     CALL trc_bc_init(jptra) 
     213 
    212214      IF( ln_rsttr ) THEN 
    213215        ! 
     
    217219        ! 
    218220        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping 
    219             ! 
    220             CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )    ! Memory allocation 
    221221            ! 
    222222            DO jn = 1, jptra 
    223223               IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
    224224                  jl = n_trc_index(jn)  
    225                   CALL trc_dta( nit000, sf_trcdta(jl),rf_trfac(jl) )   ! read tracer data at nit000 
    226                   ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:) 
    227                   trn(:,:,:,jn) = ztrcdta(:,:,:) * tmask(:,:,:)   
     225                  CALL trc_dta( nit000, sf_trcdta(jl), rf_trfac(jl) )   ! read tracer data at nit000 
     226                  trn(:,:,:,jn) = sf_trcdta(jl)%fnow(:,:,:)  
     227                  ! 
    228228                  IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN      !== deallocate data structure   ==! 
    229229                     !                                                    (data used only for initialisation) 
     
    235235               ENDIF 
    236236            ENDDO 
    237             CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta ) 
     237            ! 
    238238        ENDIF 
    239239        ! 
     
    246246   END SUBROUTINE trc_ini_state 
    247247 
    248  
    249248   SUBROUTINE top_alloc 
    250249      !!---------------------------------------------------------------------- 
     
    253252      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules 
    254253      !!---------------------------------------------------------------------- 
    255       USE trcadv        , ONLY:   trc_adv_alloc          ! TOP-related alloc routines... 
    256254      USE trc           , ONLY:   trc_alloc 
    257       USE trcnxt        , ONLY:   trc_nxt_alloc 
    258       USE trczdf        , ONLY:   trc_zdf_alloc 
    259255      USE trdtrc_oce    , ONLY:   trd_trc_oce_alloc 
    260256#if defined key_trdmxl_trc  
     
    265261      !!---------------------------------------------------------------------- 
    266262      ! 
    267       ierr =        trc_adv_alloc()          ! Start of TOP-related alloc routines... 
    268       ierr = ierr + trc_alloc    () 
    269       ierr = ierr + trc_nxt_alloc() 
    270       ierr = ierr + trc_zdf_alloc() 
     263      ierr =        trc_alloc() 
    271264      ierr = ierr + trd_trc_oce_alloc() 
    272265#if defined key_trdmxl_trc  
Note: See TracChangeset for help on using the changeset viewer.