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 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/trcini.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/trcini.F90

    r10817 r12928  
    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') 
     
    5858      IF(lwp) WRITE(numout,*) '~~~~~~~~' 
    5959      ! 
    60       CALL trc_ini_ctl   ! control  
    6160      CALL trc_nam       ! read passive tracers namelists 
    6261      CALL top_alloc()   ! allocate TOP arrays 
     62 
    6363      ! 
    6464      IF(.NOT.ln_trcdta )   ln_trc_ini(:) = .FALSE. 
     
    6868      IF(lwp) WRITE(numout,*) 
    6969      ! 
    70       CALL trc_ini_sms   ! SMS 
    71       CALL trc_ini_trp   ! passive tracers transport 
    72       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 
    7373      ! 
    7474      IF( lwm .AND. sn_cfctl%l_trcstat ) THEN 
     
    7676      ENDIF 
    7777      ! 
    78       CALL trc_ini_state  !  passive tracers initialisation : from a restart or from clim 
    79       IF( nn_dttrc /= 1 ) & 
    80       CALL trc_sub_ini    ! Initialize variables for substepping passive tracers 
    81       ! 
    82       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 
    8381      ! 
    8482      IF( ln_timing )   CALL timing_stop('trc_init') 
     
    8785 
    8886 
    89    SUBROUTINE trc_ini_ctl 
    90       !!---------------------------------------------------------------------- 
    91       !!                     ***  ROUTINE trc_ini_ctl  *** 
    92       !! ** Purpose :        Control  + ocean volume 
    93       !!---------------------------------------------------------------------- 
    94       INTEGER ::   jk    ! dummy loop indices 
    95       ! 
    96       ! Define logical parameter ton control dirunal cycle in TOP 
    97       l_trcdm2dc = ln_dm2dc .OR. ( ln_cpl .AND. ncpl_qsr_freq /= 1 ) 
    98       l_trcdm2dc = l_trcdm2dc  .AND. .NOT. l_offline 
    99       IF( l_trcdm2dc .AND. lwp )   CALL ctl_warn( 'Coupling with passive tracers and used of diurnal cycle.',   & 
    100          &                           'Computation of a daily mean shortwave for some biogeochemical models ' ) 
    101       ! 
    102    END SUBROUTINE trc_ini_ctl 
    103  
    104  
    105    SUBROUTINE trc_ini_inv 
     87   SUBROUTINE trc_ini_inv( Kmm ) 
    10688      !!---------------------------------------------------------------------- 
    10789      !!                     ***  ROUTINE trc_ini_stat  *** 
    10890      !! ** Purpose :      passive tracers inventories at initialsation phase 
    10991      !!---------------------------------------------------------------------- 
    110       INTEGER ::  jk, jn    ! dummy loop indices 
     92      INTEGER, INTENT(in) ::   Kmm    ! time level index 
     93      INTEGER             ::  jk, jn  ! dummy loop indices 
    11194      CHARACTER (len=25) :: charout 
    11295      !!---------------------------------------------------------------------- 
     
    118101      !                          ! masked grid volume 
    119102      DO jk = 1, jpk 
    120          cvol(:,:,jk) = e1e2t(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
     103         cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    121104      END DO 
    122105      !                          ! total volume of the ocean  
     
    125108      trai(:) = 0._wp            ! initial content of all tracers 
    126109      DO jn = 1, jptra 
    127          trai(jn) = trai(jn) + glob_sum( 'trcini', trn(:,:,:,jn) * cvol(:,:,:)   ) 
     110         trai(jn) = trai(jn) + glob_sum( 'trcini', tr(:,:,:,jn,Kmm) * cvol(:,:,:)   ) 
    128111      END DO 
    129112 
     
    140123      ENDIF 
    141124      IF(lwp) WRITE(numout,*) 
    142       IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
     125      IF(sn_cfctl%l_prttrc) THEN            ! print mean trends (used for debugging) 
    143126         CALL prt_ctl_trc_init 
    144127         WRITE(charout, FMT="('ini ')") 
    145128         CALL prt_ctl_trc_info( charout ) 
    146          CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
     129         CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Kmm), mask=tmask, clinfo=ctrcnm ) 
    147130      ENDIF 
    1481319000  FORMAT('      tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
     
    151134 
    152135 
    153    SUBROUTINE trc_ini_sms 
     136   SUBROUTINE trc_ini_sms( Kmm ) 
    154137      !!---------------------------------------------------------------------- 
    155138      !!                     ***  ROUTINE trc_ini_sms  *** 
     
    162145      USE trcini_my_trc  ! MY_TRC   initialisation 
    163146      ! 
     147      INTEGER, INTENT(in) ::   Kmm ! time level indices 
    164148      INTEGER :: jn 
    165149      !!---------------------------------------------------------------------- 
     
    175159         ln_trc_obc(jn) =       sn_tracer(jn)%llobc 
    176160      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  
    177171      !     
    178       IF( ln_pisces      )   CALL trc_ini_pisces     !  PISCES model 
    179       IF( ln_my_trc      )   CALL trc_ini_my_trc     !  MY_TRC model 
    180       IF( ll_cfc         )   CALL trc_ini_cfc        !  CFC's 
    181       IF( ln_c14         )   CALL trc_ini_c14        !  C14 model 
    182       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 
    183177      ! 
    184178      IF(lwp) THEN                   ! control print 
     
    191185         END DO 
    192186      ENDIF 
     187      IF( lwp .AND. ln_trcbc .AND. lltrcbc ) THEN 
     188         WRITE(numout,*) 
     189         WRITE(numout,*) ' Applying tracer boundary conditions ' 
     190      ENDIF 
     191      
    1931929001  FORMAT(3x,i3,1x,a10,3x,l2,3x,l2,3x,l2,3x,l2) 
    194193      ! 
     
    221220 
    222221 
    223    SUBROUTINE trc_ini_state 
     222   SUBROUTINE trc_ini_state( Kbb, Kmm, Kaa ) 
    224223      !!---------------------------------------------------------------------- 
    225224      !!                     ***  ROUTINE trc_ini_state *** 
     
    230229      USE trcdta          ! initialisation from files 
    231230      ! 
    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_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 
    238241      ! 
    239242      ! 
    240243      IF( ln_rsttr ) THEN              ! restart from a file 
    241244        ! 
    242         CALL trc_rst_read 
     245        CALL trc_rst_read( Kbb, Kmm ) 
    243246        ! 
    244247      ELSE                             ! Initialisation of tracer from a file that may also be used for damping 
     
    249252               IF( ln_trc_ini(jn) ) THEN 
    250253                  jl = n_trc_index(jn)  
    251                   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) ) 
    252255                  ! 
    253256                  ! deallocate data structure if data are not used for damping 
     
    263266        ENDIF 
    264267        ! 
    265         trb(:,:,:,:) = trn(:,:,:,:) 
     268        tr(:,:,:,:,Kbb) = tr(:,:,:,:,Kmm) 
    266269        !  
    267270      ENDIF 
    268271      ! 
    269       tra(:,:,:,:) = 0._wp 
    270       !                                                         ! Partial top/bottom cell: GRADh(trn) 
     272      tr(:,:,:,:,Kaa) = 0._wp 
     273      !                                                         ! Partial top/bottom cell: GRADh(tr(Kmm)) 
    271274   END SUBROUTINE trc_ini_state 
    272275 
Note: See TracChangeset for help on using the changeset viewer.