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 7256 for branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcini.F90 – NEMO

Ignore:
Timestamp:
2016-11-18T08:18:45+01:00 (7 years ago)
Author:
cbricaud
Message:

phaze NEMO routines in CRS branch with nemo_v3_6_STABLE branch at rev 7213 (09-09-2016) (merge -r 5519:7213 )

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r7217 r7256  
    2525   USE trcini_my_trc   ! MY_TRC   initialisation 
    2626   USE trcdta          ! initialisation from files 
    27    USE zpshde,ONLY: zps_hde, zps_hde_isf    ! partial step: hor. derivative   (zps_hde routine) 
    28    USE zpshde_crs      ! partial step: hor. derivative   (zps_hde routine) 
     27   USE daymod          ! calendar manager 
    2928   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
    3029   USE trcsub          ! variables to substep passive tracers 
     
    6362      INTEGER ::   jk, jn, jl    ! dummy loop indices 
    6463      CHARACTER (len=25) :: charout 
    65       REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace 
    6664      !!--------------------------------------------------------------------- 
    6765      ! 
     
    123121        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping 
    124122            ! 
    125             CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )    ! Memory allocation 
    126             ! 
    127123            DO jn = 1, jptra 
    128124               IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
    129125                  jl = n_trc_index(jn)  
    130                   CALL trc_dta( nit000, sf_trcdta(jl),rf_trfac(jl) )   ! read tracer data at nit000 
    131                   ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:) 
    132                   trn(:,:,:,jn) = ztrcdta(:,:,:) * tmask(:,:,:)   
     126                  CALL trc_dta( nit000, sf_trcdta(jl), rf_trfac(jl) )   ! read tracer data at nit000 
     127                  trn(:,:,:,jn) = sf_trcdta(jl)%fnow(:,:,:)  
    133128                  IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN      !== deallocate data structure   ==! 
    134129                     !                                                    (data used only for initialisation) 
     
    140135               ENDIF 
    141136            ENDDO 
    142             CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta ) 
     137            ! 
    143138        ENDIF 
    144139        ! 
     
    148143  
    149144      tra(:,:,:,:) = 0._wp 
    150       IF( ln_crs_top)  THEN 
    151          CALL zps_hde_crs( nit000, jptra, trn, gtru, gtrv ) 
    152       ELSE 
    153          IF( ln_zps .AND. .NOT. lk_c1d .AND. .NOT. ln_isfcav )   &              ! Partial steps: before horizontal gradient of passive 
    154          &    CALL zps_hde    ( nit000, jptra, trn, gtru, gtrv  )  ! Partial steps: before horizontal gradient 
    155          IF( ln_zps .AND. .NOT. lk_c1d .AND.       ln_isfcav )   & 
    156          &    CALL zps_hde_isf( nit000, jptra, trn, pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi )       ! tracers at the bottom ocean level 
    157       ENDIF 
    158  
    159145      ! 
    160146      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers 
Note: See TracChangeset for help on using the changeset viewer.