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

Ignore:
Timestamp:
2020-09-14T17:40:34+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2195:update to trunk 13461

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

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS

    • 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_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@13382        sette 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/TOP/trcini.F90

    r10817 r13463  
    2020   USE trcnam          ! Namelist read 
    2121   USE daymod          ! calendar manager 
    22    USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
    23    USE trcsub          ! variables to substep passive tracers 
     22   USE prtctl          ! Print control passive tracers (prt_ctl_init routine) 
    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 
     
    3231   PUBLIC   trc_init   ! called by opa 
    3332 
     33#  include "domzgr_substitute.h90" 
    3434   !!---------------------------------------------------------------------- 
    3535   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
     
    3939CONTAINS 
    4040    
    41    SUBROUTINE trc_init 
     41   SUBROUTINE trc_init( Kbb, Kmm, Kaa ) 
    4242      !!--------------------------------------------------------------------- 
    4343      !!                     ***  ROUTINE trc_init  *** 
     
    5151      !!                or read data or analytical formulation 
    5252      !!--------------------------------------------------------------------- 
     53      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa   ! time level indices 
    5354      ! 
    5455      IF( ln_timing )   CALL timing_start('trc_init') 
     
    5859      IF(lwp) WRITE(numout,*) '~~~~~~~~' 
    5960      ! 
    60       CALL trc_ini_ctl   ! control  
    6161      CALL trc_nam       ! read passive tracers namelists 
    6262      CALL top_alloc()   ! allocate TOP arrays 
     63 
    6364      ! 
    6465      IF(.NOT.ln_trcdta )   ln_trc_ini(:) = .FALSE. 
     
    6869      IF(lwp) WRITE(numout,*) 
    6970      ! 
    70       CALL trc_ini_sms   ! SMS 
    71       CALL trc_ini_trp   ! passive tracers transport 
    72       CALL trc_ice_ini   ! Tracers in sea ice 
     71      CALL trc_ini_sms( Kmm )   ! SMS 
     72      CALL trc_ini_trp          ! passive tracers transport 
     73      CALL trc_ice_ini          ! Tracers in sea ice 
    7374      ! 
    7475      IF( lwm .AND. sn_cfctl%l_trcstat ) THEN 
     
    7677      ENDIF 
    7778      ! 
    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 
     79      CALL trc_ini_state( Kbb, Kmm, Kaa )  !  passive tracers initialisation : from a restart or from clim 
     80      ! 
     81      CALL trc_ini_inv( Kmm )              ! Inventories 
    8382      ! 
    8483      IF( ln_timing )   CALL timing_stop('trc_init') 
     
    8786 
    8887 
    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 
     88   SUBROUTINE trc_ini_inv( Kmm ) 
    10689      !!---------------------------------------------------------------------- 
    10790      !!                     ***  ROUTINE trc_ini_stat  *** 
    10891      !! ** Purpose :      passive tracers inventories at initialsation phase 
    10992      !!---------------------------------------------------------------------- 
    110       INTEGER ::  jk, jn    ! dummy loop indices 
     93      INTEGER, INTENT(in) ::   Kmm    ! time level index 
     94      INTEGER             ::  jk, jn  ! dummy loop indices 
    11195      CHARACTER (len=25) :: charout 
     96      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) :: zzmsk 
     97      CHARACTER (len=25), DIMENSION(jptra) :: clseb   
    11298      !!---------------------------------------------------------------------- 
    11399      ! 
     
    118104      !                          ! masked grid volume 
    119105      DO jk = 1, jpk 
    120          cvol(:,:,jk) = e1e2t(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
     106         cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    121107      END DO 
    122108      !                          ! total volume of the ocean  
     
    125111      trai(:) = 0._wp            ! initial content of all tracers 
    126112      DO jn = 1, jptra 
    127          trai(jn) = trai(jn) + glob_sum( 'trcini', trn(:,:,:,jn) * cvol(:,:,:)   ) 
     113         trai(jn) = trai(jn) + glob_sum( 'trcini', tr(:,:,:,jn,Kmm) * cvol(:,:,:)   ) 
    128114      END DO 
    129115 
     
    140126      ENDIF 
    141127      IF(lwp) WRITE(numout,*) 
    142       IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
    143          CALL prt_ctl_trc_init 
     128      IF(sn_cfctl%l_prttrc) THEN            ! print mean trends (used for debugging) 
     129         CALL prt_ctl_init( 'top', jptra ) 
    144130         WRITE(charout, FMT="('ini ')") 
    145          CALL prt_ctl_trc_info( charout ) 
    146          CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
     131         CALL prt_ctl_info( charout, cdcomp = 'top' ) 
     132         CALL prt_ctl( tab4d_1=tr(:,:,:,:,Kmm), mask1=tmask, clinfo=ctrcnm ) 
     133         DO jn = 1, jptra 
     134            zzmsk(:,:,:,jn) = tmask(:,:,:) 
     135            WRITE(clseb(jn),'(a,i2.2)') 'seb ', jn 
     136         END DO 
     137         CALL prt_ctl( tab4d_1=zzmsk, mask1=tmask, clinfo=clseb ) 
    147138      ENDIF 
    1481399000  FORMAT('      tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
     
    151142 
    152143 
    153    SUBROUTINE trc_ini_sms 
     144   SUBROUTINE trc_ini_sms( Kmm ) 
    154145      !!---------------------------------------------------------------------- 
    155146      !!                     ***  ROUTINE trc_ini_sms  *** 
     
    162153      USE trcini_my_trc  ! MY_TRC   initialisation 
    163154      ! 
     155      INTEGER, INTENT(in) ::   Kmm ! time level indices 
    164156      INTEGER :: jn 
    165157      !!---------------------------------------------------------------------- 
     
    175167         ln_trc_obc(jn) =       sn_tracer(jn)%llobc 
    176168      END DO 
     169      ! 
     170      IF( .NOT.ln_trcbc ) THEN 
     171         DO jn = 1, jp_bgc 
     172            ln_trc_sbc(jn) = .FALSE. 
     173            ln_trc_cbc(jn) = .FALSE. 
     174            ln_trc_obc(jn) = .FALSE. 
     175         END DO 
     176      ENDIF 
     177      
     178      lltrcbc = ( COUNT(ln_trc_sbc) + COUNT(ln_trc_obc) + COUNT(ln_trc_cbc) ) > 0  
    177179      !     
    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 
     180      IF( ln_pisces      )   CALL trc_ini_pisces( Kmm )     !  PISCES model 
     181      IF( ln_my_trc      )   CALL trc_ini_my_trc( Kmm )     !  MY_TRC model 
     182      IF( ll_cfc         )   CALL trc_ini_cfc   ( Kmm )     !  CFC's 
     183      IF( ln_c14         )   CALL trc_ini_c14   ( Kmm )     !  C14 model 
     184      IF( ln_age         )   CALL trc_ini_age   ( Kmm )     !  AGE 
    183185      ! 
    184186      IF(lwp) THEN                   ! control print 
     
    191193         END DO 
    192194      ENDIF 
     195      IF( lwp .AND. ln_trcbc .AND. lltrcbc ) THEN 
     196         WRITE(numout,*) 
     197         WRITE(numout,*) ' Applying tracer boundary conditions ' 
     198      ENDIF 
     199      
    1932009001  FORMAT(3x,i3,1x,a10,3x,l2,3x,l2,3x,l2,3x,l2) 
    194201      ! 
     
    221228 
    222229 
    223    SUBROUTINE trc_ini_state 
     230   SUBROUTINE trc_ini_state( Kbb, Kmm, Kaa ) 
    224231      !!---------------------------------------------------------------------- 
    225232      !!                     ***  ROUTINE trc_ini_state *** 
     
    230237      USE trcdta          ! initialisation from files 
    231238      ! 
    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 
     239      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa   ! time level index 
     240      INTEGER             :: jn, jl          ! dummy loop indices 
     241      !!---------------------------------------------------------------------- 
     242      ! 
     243      IF( ln_trcdta )   CALL trc_dta_ini( jptra )           ! set initial tracers values 
     244      ! 
     245      IF( ln_trcbc .AND. lltrcbc )  THEN  
     246        CALL trc_bc_ini ( jptra, Kmm  )            ! set tracers Boundary Conditions 
     247        CALL trc_bc     ( nit000, Kmm, tr, Kaa )   ! tracers: surface and lateral Boundary Conditions 
     248      ENDIF 
    238249      ! 
    239250      ! 
    240251      IF( ln_rsttr ) THEN              ! restart from a file 
    241252        ! 
    242         CALL trc_rst_read 
     253        CALL trc_rst_read( Kbb, Kmm ) 
    243254        ! 
    244255      ELSE                             ! Initialisation of tracer from a file that may also be used for damping 
     
    249260               IF( ln_trc_ini(jn) ) THEN 
    250261                  jl = n_trc_index(jn)  
    251                   CALL trc_dta( nit000, sf_trcdta(jl), rf_trfac(jl), trn(:,:,:,jn) ) 
     262                  CALL trc_dta( nit000, Kmm, sf_trcdta(jl), rf_trfac(jl), tr(:,:,:,jn,Kmm) ) 
    252263                  ! 
    253264                  ! deallocate data structure if data are not used for damping 
     
    263274        ENDIF 
    264275        ! 
    265         trb(:,:,:,:) = trn(:,:,:,:) 
     276        tr(:,:,:,:,Kbb) = tr(:,:,:,:,Kmm) 
    266277        !  
    267278      ENDIF 
    268279      ! 
    269       tra(:,:,:,:) = 0._wp 
    270       !                                                         ! Partial top/bottom cell: GRADh(trn) 
     280      tr(:,:,:,:,Kaa) = 0._wp 
     281      !                                                         ! Partial top/bottom cell: GRADh(tr(Kmm)) 
    271282   END SUBROUTINE trc_ini_state 
    272283 
Note: See TracChangeset for help on using the changeset viewer.