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 6808 for branches/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/TOP_SRC/trcini.F90 – NEMO

Ignore:
Timestamp:
2016-07-19T10:38:35+02:00 (8 years ago)
Author:
jamesharle
Message:

merge with trunk@6232 for consistency with SSB code

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5549_BDY_ZEROGRAD/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r5407 r6808  
    1818   USE oce_trc         ! shared variables between ocean and passive tracers 
    1919   USE trc             ! passive tracers common variables 
    20    USE trcrst          ! passive tracers restart 
    2120   USE trcnam          ! Namelist read 
    22    USE trcini_cfc      ! CFC      initialisation 
    23    USE trcini_pisces   ! PISCES   initialisation 
    24    USE trcini_c14b     ! C14 bomb initialisation 
    25    USE trcini_my_trc   ! MY_TRC   initialisation 
    26    USE trcdta          ! initialisation from files 
    2721   USE daymod          ! calendar manager 
    28    USE zpshde          ! partial step: hor. derivative   (zps_hde routine) 
    2922   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine) 
    3023   USE trcsub          ! variables to substep passive tracers 
     24   USE trcrst 
    3125   USE lib_mpp         ! distribued memory computing library 
    3226   USE sbc_oce 
    3327   USE trcice          ! tracers in sea ice 
     28   USE trcbc,   only : trc_bc_init ! generalized Boundary Conditions 
    3429  
    3530   IMPLICIT NONE 
     
    3833   PUBLIC   trc_init   ! called by opa 
    3934 
    40     !! * Substitutions 
    41 #  include "domzgr_substitute.h90" 
    4235   !!---------------------------------------------------------------------- 
    4336   !! NEMO/TOP 4.0 , NEMO Consortium (2011) 
     
    5952      !!                or read data or analytical formulation 
    6053      !!--------------------------------------------------------------------- 
    61       INTEGER ::   jk, jn, jl    ! dummy loop indices 
    62       CHARACTER (len=25) :: charout 
    63       REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace 
    64       !!--------------------------------------------------------------------- 
    6554      ! 
    6655      IF( nn_timing == 1 )   CALL timing_start('trc_init') 
     
    7059      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    7160 
    72       CALL top_alloc()              ! allocate TOP arrays 
    73  
     61      ! 
     62      CALL top_alloc()   ! allocate TOP arrays 
     63      ! 
     64      CALL trc_ini_ctl   ! control  
     65      ! 
     66      CALL trc_nam       ! read passive tracers namelists 
     67      ! 
     68      IF(lwp) WRITE(numout,*) 
     69      ! 
     70      IF( ln_rsttr .AND. .NOT. lk_offline ) CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
     71      ! 
     72      IF(lwp) WRITE(numout,*) 
     73      ! 
     74      CALL trc_ini_sms   ! SMS 
     75      ! 
     76      CALL trc_ini_trp   ! passive tracers transport 
     77      ! 
     78      CALL trc_ice_ini   ! Tracers in sea ice 
     79      ! 
     80      IF( lwp )  & 
     81         &  CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea ) 
     82      ! 
     83      CALL trc_ini_state  !  passive tracers initialisation : from a restart or from clim 
     84      ! 
     85      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers 
     86      ! 
     87      CALL trc_ini_inv   ! Inventories 
     88      ! 
     89      IF( nn_timing == 1 )   CALL timing_stop('trc_init') 
     90      ! 
     91   END SUBROUTINE trc_init 
     92 
     93 
     94   SUBROUTINE trc_ini_ctl 
     95      !!---------------------------------------------------------------------- 
     96      !!                     ***  ROUTINE trc_ini_ctl  *** 
     97      !! ** Purpose :        Control  + ocean volume 
     98      !!---------------------------------------------------------------------- 
     99      INTEGER ::   jk    ! dummy loop indices 
     100      ! 
     101      ! Define logical parameter ton control dirunal cycle in TOP 
    74102      l_trcdm2dc = ln_dm2dc .OR. ( ln_cpl .AND. ncpl_qsr_freq /= 1 ) 
    75103      l_trcdm2dc = l_trcdm2dc  .AND. .NOT. lk_offline 
    76       IF( l_trcdm2dc .AND. lwp ) & 
    77          &   CALL ctl_warn(' Coupling with passive tracers and used of diurnal cycle. & 
    78          & Computation of a daily mean shortwave for some biogeochemical models) ') 
    79  
    80       IF( nn_cla == 1 )   & 
    81          &  CALL ctl_stop( ' Cross Land Advection not yet implemented with passive tracer ; nn_cla must be 0' ) 
    82  
    83       CALL trc_nam      ! read passive tracers namelists 
    84       ! 
    85       IF(lwp) WRITE(numout,*) 
    86       ! 
    87       IF( ln_rsttr .AND. .NOT. lk_offline ) CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
    88       ! 
    89       IF(lwp) WRITE(numout,*) 
    90                                                               ! masked grid volume 
     104      IF( l_trcdm2dc .AND. lwp )   CALL ctl_warn( 'Coupling with passive tracers and used of diurnal cycle.',   & 
     105         &                           'Computation of a daily mean shortwave for some biogeochemical models ' ) 
     106      ! 
     107   END SUBROUTINE trc_ini_ctl 
     108 
     109 
     110   SUBROUTINE trc_ini_inv 
     111      !!---------------------------------------------------------------------- 
     112      !!                     ***  ROUTINE trc_ini_stat  *** 
     113      !! ** Purpose :      passive tracers inventories at initialsation phase 
     114      !!---------------------------------------------------------------------- 
     115      INTEGER ::  jk, jn    ! dummy loop indices 
     116      CHARACTER (len=25) :: charout 
     117      !!---------------------------------------------------------------------- 
    91118      !                                                              ! masked grid volume 
    92119      DO jk = 1, jpk 
    93          cvol(:,:,jk) = e1e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk) 
     120         cvol(:,:,jk) = e1e2t(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
    94121      END DO 
    95       IF( lk_degrad ) cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)      ! degrad option: reduction by facvol 
     122      IF( lk_degrad )   cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)    ! degrad option: reduction by facvol 
    96123      !                                                              ! total volume of the ocean  
    97124      areatot = glob_sum( cvol(:,:,:) ) 
    98  
     125      ! 
     126      trai(:) = 0._wp                                                   ! initial content of all tracers 
     127      DO jn = 1, jptra 
     128         trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   ) 
     129      END DO 
     130 
     131      IF(lwp) THEN               ! control print 
     132         WRITE(numout,*) 
     133         WRITE(numout,*) 
     134         WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra 
     135         WRITE(numout,*) '          *** Total volume of ocean                = ', areatot 
     136         WRITE(numout,*) '          *** Total inital content of all tracers ' 
     137         WRITE(numout,*) 
     138         DO jn = 1, jptra 
     139            WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn) 
     140         ENDDO 
     141         WRITE(numout,*) 
     142      ENDIF 
     143      IF(lwp) WRITE(numout,*) 
     144      IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
     145         CALL prt_ctl_trc_init 
     146         WRITE(charout, FMT="('ini ')") 
     147         CALL prt_ctl_trc_info( charout ) 
     148         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
     149      ENDIF 
     1509000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
     151      ! 
     152   END SUBROUTINE trc_ini_inv 
     153 
     154 
     155   SUBROUTINE trc_ini_sms 
     156      !!---------------------------------------------------------------------- 
     157      !!                     ***  ROUTINE trc_ini_sms  *** 
     158      !! ** Purpose :   SMS initialisation 
     159      !!---------------------------------------------------------------------- 
     160      USE trcini_cfc      ! CFC      initialisation 
     161      USE trcini_pisces   ! PISCES   initialisation 
     162      USE trcini_c14b     ! C14 bomb initialisation 
     163      USE trcini_my_trc   ! MY_TRC   initialisation 
     164      !!---------------------------------------------------------------------- 
    99165      IF( lk_pisces  )       CALL trc_ini_pisces       ! PISCES  bio-model 
    100166      IF( lk_cfc     )       CALL trc_ini_cfc          ! CFC     tracers 
    101167      IF( lk_c14b    )       CALL trc_ini_c14b         ! C14 bomb  tracer 
    102168      IF( lk_my_trc  )       CALL trc_ini_my_trc       ! MY_TRC  tracers 
    103  
    104       CALL trc_ice_ini                                 ! Tracers in sea ice 
    105  
    106       IF( lwp ) THEN 
    107          ! 
    108          CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea ) 
    109          ! 
    110       ENDIF 
    111  
     169      ! 
     170   END SUBROUTINE trc_ini_sms 
     171 
     172   SUBROUTINE trc_ini_trp 
     173      !!---------------------------------------------------------------------- 
     174      !!                     ***  ROUTINE trc_ini_trp  *** 
     175      !! 
     176      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules 
     177      !!---------------------------------------------------------------------- 
     178      USE trcdmp , ONLY:  trc_dmp_ini 
     179      USE trcadv , ONLY:  trc_adv_ini 
     180      USE trcldf , ONLY:  trc_ldf_ini 
     181      USE trczdf , ONLY:  trc_zdf_ini 
     182      USE trcrad , ONLY:  trc_rad_ini 
     183      ! 
     184      INTEGER :: ierr 
     185      !!---------------------------------------------------------------------- 
     186      ! 
     187      IF( ln_trcdmp )  CALL  trc_dmp_ini          ! damping 
     188                       CALL  trc_adv_ini          ! advection 
     189                       CALL  trc_ldf_ini          ! lateral diffusion 
     190                       CALL  trc_zdf_ini          ! vertical diffusion 
     191                       CALL  trc_rad_ini          ! positivity of passive tracers  
     192      ! 
     193   END SUBROUTINE trc_ini_trp 
     194 
     195 
     196   SUBROUTINE trc_ini_state 
     197      !!---------------------------------------------------------------------- 
     198      !!                     ***  ROUTINE trc_ini_state *** 
     199      !! ** Purpose :          Initialisation of passive tracer concentration  
     200      !!---------------------------------------------------------------------- 
     201      USE zpshde          ! partial step: hor. derivative   (zps_hde routine) 
     202      USE trcrst          ! passive tracers restart 
     203      USE trcdta          ! initialisation from files 
     204      ! 
     205      INTEGER ::   jk, jn, jl    ! dummy loop indices 
     206      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace 
     207      !!---------------------------------------------------------------------- 
     208      ! 
     209      ! Initialisation of tracers Initial Conditions 
    112210      IF( ln_trcdta )      CALL trc_dta_init(jptra) 
    113211 
     212      ! Initialisation of tracers Boundary Conditions 
     213      IF( lk_my_trc )     CALL trc_bc_init(jptra) 
    114214 
    115215      IF( ln_rsttr ) THEN 
     
    146246  
    147247      tra(:,:,:,:) = 0._wp 
    148       IF( ln_zps .AND. .NOT. lk_c1d .AND. .NOT. ln_isfcav )   &              ! Partial steps: before horizontal gradient of passive 
    149         &    CALL zps_hde    ( nit000, jptra, trn, gtru, gtrv  )  ! Partial steps: before horizontal gradient 
    150       IF( ln_zps .AND. .NOT. lk_c1d .AND.       ln_isfcav )   & 
    151         &    CALL zps_hde_isf( nit000, jptra, trn, pgtu=gtru, pgtv=gtrv, pgtui=gtrui, pgtvi=gtrvi )       ! tracers at the bottom ocean level 
    152  
    153  
    154       ! 
    155       IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers 
    156       ! 
    157  
    158       trai(:) = 0._wp                                                   ! initial content of all tracers 
    159       DO jn = 1, jptra 
    160          trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   ) 
    161       END DO 
    162  
    163       IF(lwp) THEN               ! control print 
    164          WRITE(numout,*) 
    165          WRITE(numout,*) 
    166          WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra 
    167          WRITE(numout,*) '          *** Total volume of ocean                = ', areatot 
    168          WRITE(numout,*) '          *** Total inital content of all tracers ' 
    169          WRITE(numout,*) 
    170          DO jn = 1, jptra 
    171             WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn) 
    172          ENDDO 
    173          WRITE(numout,*) 
    174       ENDIF 
    175       IF(lwp) WRITE(numout,*) 
    176       IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
    177          CALL prt_ctl_trc_init 
    178          WRITE(charout, FMT="('ini ')") 
    179          CALL prt_ctl_trc_info( charout ) 
    180          CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
    181       ENDIF 
    182 9000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
    183       ! 
    184       IF( nn_timing == 1 )   CALL timing_stop('trc_init') 
    185       ! 
    186    END SUBROUTINE trc_init 
    187  
     248      !                                                         ! Partial top/bottom cell: GRADh(trn) 
     249   END SUBROUTINE trc_ini_state 
    188250 
    189251   SUBROUTINE top_alloc 
     
    193255      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules 
    194256      !!---------------------------------------------------------------------- 
    195       USE trcadv        , ONLY:   trc_adv_alloc          ! TOP-related alloc routines... 
    196257      USE trc           , ONLY:   trc_alloc 
    197       USE trcnxt        , ONLY:   trc_nxt_alloc 
    198       USE trczdf        , ONLY:   trc_zdf_alloc 
    199258      USE trdtrc_oce    , ONLY:   trd_trc_oce_alloc 
    200259#if defined key_trdmxl_trc  
     
    205264      !!---------------------------------------------------------------------- 
    206265      ! 
    207       ierr =        trc_adv_alloc()          ! Start of TOP-related alloc routines... 
    208       ierr = ierr + trc_alloc    () 
    209       ierr = ierr + trc_nxt_alloc() 
    210       ierr = ierr + trc_zdf_alloc() 
     266      ierr =        trc_alloc() 
    211267      ierr = ierr + trd_trc_oce_alloc() 
    212268#if defined key_trdmxl_trc  
Note: See TracChangeset for help on using the changeset viewer.