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 2819 for branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/trcini.F90 – NEMO

Ignore:
Timestamp:
2011-08-09T10:29:53+02:00 (13 years ago)
Author:
cetlod
Message:

Improvment of branch dev_r2787_LOCEAN3_TRA_TRP

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r2715 r2819  
    1616   !!   top_alloc :   allocate the TOP arrays 
    1717   !!---------------------------------------------------------------------- 
    18    USE oce_trc 
    19    USE trc 
    20    USE trcrst 
     18   USE oce_trc         ! shared variables between ocean and passive tracers 
     19   USE trc             ! passive tracers common variables 
     20   USE trcrst          ! passive tracers restart 
    2121   USE trcnam          ! Namelist read 
    2222   USE trcini_cfc      ! CFC      initialisation 
     
    2525   USE trcini_c14b     ! C14 bomb initialisation 
    2626   USE trcini_my_trc   ! MY_TRC   initialisation 
    27    USE trcdta    
    28    USE daymod 
     27   USE trcdta          ! initialisation form files 
     28   USE daymod          ! calendar manager 
    2929   USE zpshde          ! partial step: hor. derivative   (zps_hde routine) 
    3030   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
     
    5656      !!                or read data or analytical formulation 
    5757      !!--------------------------------------------------------------------- 
    58       INTEGER ::   jk, jn    ! dummy loop indices 
     58      INTEGER ::   jk, jn, jl    ! dummy loop indices 
     59      INTEGER ::   ierr          ! local integer 
    5960      CHARACTER (len=25) :: charout 
     61      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) ::  ztrcdta   ! 4D  workspace 
    6062      !!--------------------------------------------------------------------- 
    6163 
     
    6567 
    6668      CALL top_alloc()              ! allocate TOP arrays 
     69 
     70      IF( ln_dm2dc .AND. ( lk_pisces .OR. lk_lobster ) )    & 
     71         &  CALL ctl_stop( ' The diurnal cycle is not compatible with PISCES or LOBSTER  ' ) 
     72 
     73      IF( nn_cla == 1 )   & 
     74         &  CALL ctl_stop( ' Cross Land Advection not yet implemented with passive tracer ; nn_cla must be 0' ) 
    6775 
    6876      !                             ! masked grid volume 
     
    7179      END DO 
    7280 
    73       !                             ! total volume of the ocean 
    74 #if ! defined key_degrad 
    75       areatot = glob_sum( cvol(:,:,:) ) 
    76 #else 
    77       areatot = glob_sum( cvol(:,:,:) * facvol(:,:,:) )  ! degrad option: reduction by facvol 
    78 #endif 
     81      !                           ! total volume of the ocean ( degrad option: reduction by facvol ) 
     82      IF( .NOT.lk_degrad )  THEN  ;  areatot = glob_sum( cvol(:,:,:) ) 
     83      ELSE                        ;  areatot = glob_sum( cvol(:,:,:) * facvol(:,:,:) ) 
     84      ENDIF 
    7985 
    8086      CALL trc_nam                  ! read passive tracers namelists 
    81  
    82       !                             ! restart for passive tracer (input) 
    83       IF( ln_rsttr ) THEN 
    84          IF(lwp) WRITE(numout,*) '       read a restart file for passive tracer : ', cn_trcrst_in 
    85          IF(lwp) WRITE(numout,*) ' ' 
    86       ELSE 
    87          IF( lwp .AND. lk_dtatrc ) THEN 
    88             DO jn = 1, jptra 
    89                IF( lutini(jn) )  &                  ! open input FILE only IF lutini(jn) is true 
    90                   &  WRITE(numout,*) ' read an initial file for passive tracer number :', jn, ' traceur : ', ctrcnm(jn)  
    91              END DO 
    92           ENDIF 
    93           IF( lwp ) WRITE(numout,*) 
    94       ENDIF 
    95  
    96       IF( ln_dm2dc .AND. ( lk_pisces .OR. lk_lobster ) )    & 
    97          &       CALL ctl_stop( ' The diurnal cycle is not compatible with PISCES or LOBSTER  ' ) 
    98  
    99       IF( nn_cla == 1 )   & 
    100          &       CALL ctl_stop( ' Cross Land Advection not yet implemented with passive tracer ; nn_cla must be 0' ) 
    10187 
    10288      IF( lk_lobster ) THEN   ;   CALL trc_ini_lobster      ! LOBSTER bio-model 
     
    119105      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used' 
    120106      ENDIF 
     107 
     108      IF( ln_trcdta )             CALL trc_dta_init 
    121109 
    122110      IF( ln_rsttr ) THEN 
     
    130118           CALL day_init               ! set calendar 
    131119        ENDIF 
    132 #if defined key_dtatrc 
    133         CALL trc_dta( nit000 )      ! Initialization of tracer from a file that may also be used for damping 
    134         DO jn = 1, jptra 
    135            IF( lutini(jn) )   trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:)   ! initialisation from file if required 
    136         END DO 
    137 #endif 
     120        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping 
     121            ALLOCATE( ztrcdta(jpi,jpj,jpk,nb_trcdta), STAT=ierr ) 
     122            IF( ierr > 0 ) THEN 
     123               CALL ctl_stop( 'trc_ini: unable to allocate ztrcdta array' )   ;   RETURN 
     124            ENDIF 
     125            ! 
     126            CALL trc_dta( nit000, ztrcdta )   ! read tracer data at nit000 
     127            ! 
     128            DO jn = 1, jptra 
     129               IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
     130                  jl = n_trc_index(jn)  
     131                  trn(:,:,:,jn) = ztrcdta(:,:,:,jl) * tmask(:,:,:)   
     132               ENDIF 
     133            ENDDO 
     134            DEALLOCATE( ztrcdta )  
     135        ENDIF 
     136        ! 
    138137        trb(:,:,:,:) = trn(:,:,:,:) 
    139138        !  
     
    147146 
    148147      !            
    149       trai = 0._wp         ! Computation content of all tracers 
     148      trai(:) = 0._wp         ! Computation content of all tracers ( degrad option: reduction by facvol ) 
    150149      DO jn = 1, jptra 
    151 #if ! defined key_degrad 
    152          trai = trai + glob_sum( trn(:,:,:,jn) * cvol(:,:,:) ) 
    153 #else 
    154          trai = trai + glob_sum( trn(:,:,:,jn) * cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol 
    155 #endif 
     150         IF( .NOT.lk_degrad )  THEN  ;  trai(jn) =  glob_sum( trn(:,:,:,jn) * cvol(:,:,:) )  
     151         ELSE                        ;  trai(jn) =  glob_sum( trn(:,:,:,jn) * cvol(:,:,:) * facvol(:,:,:) ) 
     152         ENDIF 
    156153      END DO       
    157154 
     
    161158         WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra 
    162159         WRITE(numout,*) '          *** Total volume of ocean                = ', areatot 
    163          WRITE(numout,*) '          *** Total inital content of all tracers  = ', trai 
     160         WRITE(numout,*) '          *** Total inital content of all tracers ' 
     161         DO jn = 1, jptra 
     162            WRITE(numout,*) ' tracer nb : ', jn, '  name : ', ctrcnm(jn), ' initial content :', trai(jn) 
     163         ENDDO 
    164164         WRITE(numout,*) 
    165165      ENDIF 
     
    186186      USE trczdf        , ONLY:   trc_zdf_alloc 
    187187      USE trdmod_trc_oce, ONLY:   trd_mod_trc_oce_alloc 
    188 #if ! defined key_iomput 
    189       USE trcdia        , ONLY:   trc_dia_alloc 
    190 #endif 
    191 #if defined key_trcdmp  
    192       USE trcdmp        , ONLY:   trc_dmp_alloc 
    193 #endif 
    194 #if defined key_dtatrc 
    195       USE trcdta        , ONLY:   trc_dta_alloc 
    196 #endif 
    197 #if defined key_trdmld_trc   ||   defined key_esopa 
     188#if defined key_trdmld_trc  
    198189      USE trdmld_trc    , ONLY:   trd_mld_trc_alloc 
    199190#endif 
     
    207198      ierr = ierr + trc_zdf_alloc() 
    208199      ierr = ierr + trd_mod_trc_oce_alloc() 
    209 #if ! defined key_iomput 
    210       ierr = ierr + trc_dia_alloc() 
    211 #endif 
    212 #if defined key_trcdmp  
    213       ierr = ierr + trc_dmp_alloc() 
    214 #endif 
    215 #if defined key_dtatrc 
    216       ierr = ierr + trc_dta_alloc() 
    217 #endif 
    218 #if defined key_trdmld_trc   ||   defined key_esopa 
     200#if defined key_trdmld_trc  
    219201      ierr = ierr + trd_mld_trc_alloc() 
    220202#endif 
Note: See TracChangeset for help on using the changeset viewer.