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 12377 for NEMO/trunk/src/TOP/trcini.F90 – NEMO

Ignore:
Timestamp:
2020-02-12T15:39:06+01:00 (4 years ago)
Author:
acc
Message:

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

Location:
NEMO/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
  • NEMO/trunk/src/TOP/trcini.F90

    r12136 r12377  
    2121   USE daymod          ! calendar manager 
    2222   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
    23    USE trcsub          ! variables to substep passive tracers 
    2423   USE trcrst 
    2524   USE lib_mpp         ! distribued memory computing library 
    2625   USE trcice          ! tracers in sea ice 
    27    USE trcbc,   only : trc_bc_ini ! generalized Boundary Conditions 
     26   USE trcbc          ! generalized Boundary Conditions 
    2827  
    2928   IMPLICIT NONE 
     
    3938CONTAINS 
    4039    
    41    SUBROUTINE trc_init 
     40   SUBROUTINE trc_init( Kbb, Kmm, Kaa ) 
    4241      !!--------------------------------------------------------------------- 
    4342      !!                     ***  ROUTINE trc_init  *** 
     
    5150      !!                or read data or analytical formulation 
    5251      !!--------------------------------------------------------------------- 
     52      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa   ! time level indices 
    5353      ! 
    5454      IF( ln_timing )   CALL timing_start('trc_init') 
     
    6060      CALL trc_nam       ! read passive tracers namelists 
    6161      CALL top_alloc()   ! allocate TOP arrays 
     62 
    6263      ! 
    6364      IF(.NOT.ln_trcdta )   ln_trc_ini(:) = .FALSE. 
     
    6768      IF(lwp) WRITE(numout,*) 
    6869      ! 
    69       CALL trc_ini_sms   ! SMS 
    70       CALL trc_ini_trp   ! passive tracers transport 
    71       CALL trc_ice_ini   ! Tracers in sea ice 
     70      CALL trc_ini_sms( Kmm )   ! SMS 
     71      CALL trc_ini_trp          ! passive tracers transport 
     72      CALL trc_ice_ini          ! Tracers in sea ice 
    7273      ! 
    7374      IF( lwm .AND. sn_cfctl%l_trcstat ) THEN 
     
    7576      ENDIF 
    7677      ! 
    77       CALL trc_ini_state  !  passive tracers initialisation : from a restart or from clim 
    78       IF( nn_dttrc /= 1 ) & 
    79       CALL trc_sub_ini    ! Initialize variables for substepping passive tracers 
    80       ! 
    81       CALL trc_ini_inv   ! Inventories 
     78      CALL trc_ini_state( Kbb, Kmm, Kaa )  !  passive tracers initialisation : from a restart or from clim 
     79      ! 
     80      CALL trc_ini_inv( Kmm )              ! Inventories 
    8281      ! 
    8382      IF( ln_timing )   CALL timing_stop('trc_init') 
     
    8685 
    8786 
    88    SUBROUTINE trc_ini_inv 
     87   SUBROUTINE trc_ini_inv( Kmm ) 
    8988      !!---------------------------------------------------------------------- 
    9089      !!                     ***  ROUTINE trc_ini_stat  *** 
    9190      !! ** Purpose :      passive tracers inventories at initialsation phase 
    9291      !!---------------------------------------------------------------------- 
    93       INTEGER ::  jk, jn    ! dummy loop indices 
     92      INTEGER, INTENT(in) ::   Kmm    ! time level index 
     93      INTEGER             ::  jk, jn  ! dummy loop indices 
    9494      CHARACTER (len=25) :: charout 
    9595      !!---------------------------------------------------------------------- 
     
    101101      !                          ! masked grid volume 
    102102      DO jk = 1, jpk 
    103          cvol(:,:,jk) = e1e2t(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
     103         cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    104104      END DO 
    105105      !                          ! total volume of the ocean  
     
    108108      trai(:) = 0._wp            ! initial content of all tracers 
    109109      DO jn = 1, jptra 
    110          trai(jn) = trai(jn) + glob_sum( 'trcini', trn(:,:,:,jn) * cvol(:,:,:)   ) 
     110         trai(jn) = trai(jn) + glob_sum( 'trcini', tr(:,:,:,jn,Kmm) * cvol(:,:,:)   ) 
    111111      END DO 
    112112 
     
    123123      ENDIF 
    124124      IF(lwp) WRITE(numout,*) 
    125       IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
     125      IF(sn_cfctl%l_prttrc) THEN            ! print mean trends (used for debugging) 
    126126         CALL prt_ctl_trc_init 
    127127         WRITE(charout, FMT="('ini ')") 
    128128         CALL prt_ctl_trc_info( charout ) 
    129          CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
     129         CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Kmm), mask=tmask, clinfo=ctrcnm ) 
    130130      ENDIF 
    1311319000  FORMAT('      tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
     
    134134 
    135135 
    136    SUBROUTINE trc_ini_sms 
     136   SUBROUTINE trc_ini_sms( Kmm ) 
    137137      !!---------------------------------------------------------------------- 
    138138      !!                     ***  ROUTINE trc_ini_sms  *** 
     
    145145      USE trcini_my_trc  ! MY_TRC   initialisation 
    146146      ! 
     147      INTEGER, INTENT(in) ::   Kmm ! time level indices 
    147148      INTEGER :: jn 
    148149      !!---------------------------------------------------------------------- 
     
    158159         ln_trc_obc(jn) =       sn_tracer(jn)%llobc 
    159160      END DO 
     161      ! 
     162      IF( .NOT.ln_trcbc ) THEN 
     163         DO jn = 1, jp_bgc 
     164            ln_trc_sbc(jn) = .FALSE. 
     165            ln_trc_cbc(jn) = .FALSE. 
     166            ln_trc_obc(jn) = .FALSE. 
     167         END DO 
     168      ENDIF 
     169      
     170      lltrcbc = ( COUNT(ln_trc_sbc) + COUNT(ln_trc_obc) + COUNT(ln_trc_cbc) ) > 0  
    160171      !     
    161       IF( ln_pisces      )   CALL trc_ini_pisces     !  PISCES model 
    162       IF( ln_my_trc      )   CALL trc_ini_my_trc     !  MY_TRC model 
    163       IF( ll_cfc         )   CALL trc_ini_cfc        !  CFC's 
    164       IF( ln_c14         )   CALL trc_ini_c14        !  C14 model 
    165       IF( ln_age         )   CALL trc_ini_age        !  AGE 
     172      IF( ln_pisces      )   CALL trc_ini_pisces( Kmm )     !  PISCES model 
     173      IF( ln_my_trc      )   CALL trc_ini_my_trc( Kmm )     !  MY_TRC model 
     174      IF( ll_cfc         )   CALL trc_ini_cfc   ( Kmm )     !  CFC's 
     175      IF( ln_c14         )   CALL trc_ini_c14   ( Kmm )     !  C14 model 
     176      IF( ln_age         )   CALL trc_ini_age   ( Kmm )     !  AGE 
    166177      ! 
    167178      IF(lwp) THEN                   ! control print 
     
    174185         END DO 
    175186      ENDIF 
     187      IF( lwp .AND. ln_trcbc .AND. lltrcbc ) THEN 
     188         WRITE(numout,*) 
     189         WRITE(numout,*) ' Applying tracer boundary conditions ' 
     190      ENDIF 
     191      
    1761929001  FORMAT(3x,i3,1x,a10,3x,l2,3x,l2,3x,l2,3x,l2) 
    177193      ! 
     
    204220 
    205221 
    206    SUBROUTINE trc_ini_state 
     222   SUBROUTINE trc_ini_state( Kbb, Kmm, Kaa ) 
    207223      !!---------------------------------------------------------------------- 
    208224      !!                     ***  ROUTINE trc_ini_state *** 
     
    213229      USE trcdta          ! initialisation from files 
    214230      ! 
    215       INTEGER :: jn, jl   ! dummy loop indices 
    216       !!---------------------------------------------------------------------- 
    217       ! 
    218       IF( ln_trcdta )   CALL trc_dta_ini( jptra )      ! set initial tracers values 
    219       ! 
    220       IF( ln_my_trc )   CALL trc_bc_ini ( jptra )      ! set tracers Boundary Conditions 
     231      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa   ! time level index 
     232      INTEGER             :: jn, jl          ! dummy loop indices 
     233      !!---------------------------------------------------------------------- 
     234      ! 
     235      IF( ln_trcdta )   CALL trc_dta_ini( jptra )           ! set initial tracers values 
     236      ! 
     237      IF( ln_trcbc .AND. lltrcbc )  THEN  
     238        CALL trc_bc_ini ( jptra, Kmm  )            ! set tracers Boundary Conditions 
     239        CALL trc_bc     ( nit000, Kmm, tr, Kaa )   ! tracers: surface and lateral Boundary Conditions 
     240      ENDIF 
    221241      ! 
    222242      ! 
    223243      IF( ln_rsttr ) THEN              ! restart from a file 
    224244        ! 
    225         CALL trc_rst_read 
     245        CALL trc_rst_read( Kbb, Kmm ) 
    226246        ! 
    227247      ELSE                             ! Initialisation of tracer from a file that may also be used for damping 
     
    232252               IF( ln_trc_ini(jn) ) THEN 
    233253                  jl = n_trc_index(jn)  
    234                   CALL trc_dta( nit000, sf_trcdta(jl), rf_trfac(jl), trn(:,:,:,jn) ) 
     254                  CALL trc_dta( nit000, Kmm, sf_trcdta(jl), rf_trfac(jl), tr(:,:,:,jn,Kmm) ) 
    235255                  ! 
    236256                  ! deallocate data structure if data are not used for damping 
     
    246266        ENDIF 
    247267        ! 
    248         trb(:,:,:,:) = trn(:,:,:,:) 
     268        tr(:,:,:,:,Kbb) = tr(:,:,:,:,Kmm) 
    249269        !  
    250270      ENDIF 
    251271      ! 
    252       tra(:,:,:,:) = 0._wp 
    253       !                                                         ! Partial top/bottom cell: GRADh(trn) 
     272      tr(:,:,:,:,Kaa) = 0._wp 
     273      !                                                         ! Partial top/bottom cell: GRADh(tr(Kmm)) 
    254274   END SUBROUTINE trc_ini_state 
    255275 
Note: See TracChangeset for help on using the changeset viewer.