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 2528 for trunk/NEMOGCM/NEMO/TOP_SRC/trcini.F90 – NEMO

Ignore:
Timestamp:
2010-12-27T18:33:53+01:00 (13 years ago)
Author:
rblod
Message:

Update NEMOGCM from branch nemo_v3_3_beta

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    • Property svn:eol-style deleted
    r1836 r2528  
    1414   !!---------------------------------------------------------------------- 
    1515   !!---------------------------------------------------------------------- 
    16    !!   trc_ini :   Initialization for passive tracer 
     16   !!   trc_init :   Initialization for passive tracer 
    1717   !!---------------------------------------------------------------------- 
    1818   USE oce_trc 
    1919   USE trc 
    20    USE trp_trc 
    2120   USE trcrst 
    22    USE trcctl 
    23    USE trclec 
     21   USE trcnam          ! Namelist read 
    2422   USE trcini_cfc      ! CFC      initialisation 
    2523   USE trcini_lobster  ! LOBSTER  initialisation 
     
    2826   USE trcini_my_trc   ! MY_TRC   initialisation 
    2927   USE trcdta    
    30 #if defined key_off_tra  
     28#if defined key_offline 
    3129   USE daymod 
    3230#endif 
    33    USE zpshde_trc      ! partial step: hor. derivative  
     31   USE zpshde          ! partial step: hor. derivative   (zps_hde routine) 
    3432   USE in_out_manager  ! I/O manager 
    3533   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
    3634   USE lib_mpp         ! distributed memory computing library 
     35   USE lib_fortran     !  
    3736    
    3837   IMPLICIT NONE 
    3938   PRIVATE 
    4039    
    41    PUBLIC   trc_ini   ! called by opa 
     40   PUBLIC   trc_init   ! called by opa 
    4241 
    4342    !! * Substitutions 
    4443#  include "domzgr_substitute.h90" 
    45    !!---------------------------------------------------------------------- 
    46    !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
    47    !! $Id$  
    48    !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    49    !!---------------------------------------------------------------------- 
    5044   
    5145CONTAINS 
    5246    
    53    SUBROUTINE trc_ini 
     47   SUBROUTINE trc_init 
    5448      !!--------------------------------------------------------------------- 
    55       !!                     ***  ROUTINE trc_ini  *** 
     49      !!                     ***  ROUTINE trc_init  *** 
    5650      !! 
    5751      !! ** Purpose :   Initialization of the passive tracer fields  
     
    6963 
    7064      IF(lwp) WRITE(numout,*) 
    71       IF(lwp) WRITE(numout,*) 'trc_ini : initial set up of the passive tracers' 
     65      IF(lwp) WRITE(numout,*) 'trc_init : initial set up of the passive tracers' 
    7266      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    7367 
    7468      !                 ! masked grid volume 
    7569      DO jk = 1, jpk 
    76          cvol(:,:,jk) = e1t(:,:) * e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk) * tmask_i(:,:) 
     70         cvol(:,:,jk) = e1t(:,:) * e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk)  
    7771      END DO 
    7872 
    7973      ! total volume of the ocean 
    80 #if ! defined key_off_degrad 
    81       areatot = SUM( cvol(:,:,:) ) 
     74#if ! defined key_degrad 
     75      areatot = glob_sum( cvol(:,:,:) ) 
    8276#else 
    83       areatot = SUM( cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol 
     77      areatot = glob_sum( cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol 
    8478#endif 
    85       IF( lk_mpp )   CALL mpp_sum( areatot )     ! sum over the global domain   
    8679 
    87                                   CALL trc_lec      ! READ passive tracers namelists 
     80                                  CALL trc_nam      ! read passive tracers namelists 
    8881 
    89                                   CALL trc_ctl      ! control consistency between parameters, cpp key 
     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) WRITE(numout,*) 
     88         DO jn = 1, jptra 
     89            IF( lwp .AND. 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 
     94      IF( ln_dm2dc .AND. ( lk_pisces .OR. lk_lobster ) )    & 
     95         &       CALL ctl_stop( ' The diurnal cycle is not compatible with PISCES or LOBSTER  ' ) 
     96 
     97      IF( nn_cla == 1 )   & 
     98         &       CALL ctl_stop( ' Cross Land Advection not yet implemented with passive tracer ; nn_cla must be 0' ) 
    9099 
    91100      IF( lk_lobster ) THEN   ;   CALL trc_ini_lobster      ! LOBSTER bio-model 
     
    109118      ENDIF 
    110119 
    111       IF( .NOT. ln_rsttr ) THEN  
    112 #if defined key_off_tra 
    113          CALL day_init      ! calendar 
    114 #endif 
    115 # if defined key_dtatrc 
    116          ! Initialization of tracer from a file that may also be used for damping 
    117          CALL trc_dta( nittrc000 ) 
    118          DO jn = 1, jptra 
    119             IF( lutini(jn) )   trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:)   ! initialisation from file if required 
    120          END DO 
    121 # endif 
    122          trb(:,:,:,:) = trn(:,:,:,:) 
     120      IF( ln_rsttr ) THEN 
     121        ! 
     122        IF( lk_offline )  neuler = 1   ! Set time-step indicator at nit000 (leap-frog) 
     123        CALL trc_rst_read              ! restart from a file 
     124        ! 
    123125      ELSE 
    124          ! 
    125          CALL trc_rst_read      ! restart from a file 
    126          ! 
     126        IF( lk_offline )  THEN 
     127           neuler = 0                  ! Set time-step indicator at nit000 (euler) 
     128           CALL day_init               ! set calendar 
     129        ENDIF 
     130        IF( lk_dtatrc )  THEN 
     131           CALL trc_dta( nit000 )      ! Initialization of tracer from a file that may also be used for damping 
     132           DO jn = 1, jptra 
     133              IF( lutini(jn) )   trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:)   ! initialisation from file if required 
     134           END DO 
     135        ENDIF  
     136        trb(:,:,:,:) = trn(:,:,:,:) 
     137        !  
    127138      ENDIF 
    128  
     139  
    129140      tra(:,:,:,:) = 0. 
    130141       
    131       IF( ln_zps .AND. .NOT. lk_trc_c1d )   &              ! Partial steps: before horizontal gradient of passive 
    132       &                     CALL zps_hde_trc( nittrc000, trb, gtru, gtrv )       ! tracers at the bottom ocean level 
     142      IF( ln_zps .AND. .NOT. lk_c1d )   &              ! Partial steps: before horizontal gradient of passive 
     143      &                     CALL zps_hde( nit000, jptra, trn, gtru, gtrv )       ! tracers at the bottom ocean level 
    133144 
    134145 
     
    136147      trai = 0.e0 
    137148      DO jn = 1, jptra 
    138 #if ! defined key_off_degrad 
    139          trai = trai + SUM( trn(:,:,:,jn) * cvol(:,:,:) ) 
     149#if ! defined key_degrad 
     150         trai = trai + glob_sum( trn(:,:,:,jn) * cvol(:,:,:) ) 
    140151#else 
    141          trai = trai + SUM( trn(:,:,:,jn) * cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol 
     152         trai = trai + glob_sum( trn(:,:,:,jn) * cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol 
    142153#endif 
    143154      END DO       
    144       IF( lk_mpp )   CALL mpp_sum( trai )     ! sum over the global domain   
    145  
    146155 
    147156      !                 ! control print 
     
    162171      ENDIF 
    163172 
    164    END SUBROUTINE trc_ini 
     173   END SUBROUTINE trc_init 
    165174 
    166175#else 
     
    169178   !!---------------------------------------------------------------------- 
    170179CONTAINS 
    171    SUBROUTINE trc_ini                      ! Dummy routine    
    172    END SUBROUTINE trc_ini 
     180   SUBROUTINE trc_init                      ! Dummy routine    
     181   END SUBROUTINE trc_init 
    173182#endif 
    174183 
     184   !!---------------------------------------------------------------------- 
     185   !! NEMO/TOP 3.3 , NEMO Consortium (2010) 
     186   !! $Id$  
     187   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    175188   !!====================================================================== 
    176189END MODULE trcini 
Note: See TracChangeset for help on using the changeset viewer.