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 5766 for branches/2015/dev_r5721_CNRS9_NOC3_LDF/NEMOGCM/NEMO/TOP_SRC/trcini.F90 – NEMO

Ignore:
Timestamp:
2015-09-28T16:42:34+02:00 (9 years ago)
Author:
cetlod
Message:

LDF: phasing the improvements/simplifications of TOP component

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5721_CNRS9_NOC3_LDF/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r5758 r5766  
    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 
     
    5953      !!                or read data or analytical formulation 
    6054      !!--------------------------------------------------------------------- 
    61       INTEGER ::   jk, jn, jl    ! dummy loop indices 
    62       CHARACTER (len=25) :: charout 
    63       REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace 
    6455      !!--------------------------------------------------------------------- 
    6556      ! 
     
    7061      IF(lwp) WRITE(numout,*) '~~~~~~~' 
    7162 
    72       CALL top_alloc()              ! allocate TOP arrays 
    73  
     63      ! 
     64      CALL top_alloc()   ! allocate TOP arrays 
     65      ! 
     66      CALL trc_ini_ctl   ! control  
     67      ! 
     68      CALL trc_nam       ! read passive tracers namelists 
     69      ! 
     70      IF(lwp) WRITE(numout,*) 
     71      ! 
     72      IF( ln_rsttr .AND. .NOT. lk_offline ) CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
     73      ! 
     74      IF(lwp) WRITE(numout,*) 
     75      ! 
     76      CALL trc_ini_sms   ! SMS 
     77      ! 
     78      CALL trc_ini_trp   ! passive tracers transport 
     79      ! 
     80      CALL trc_ice_ini   ! Tracers in sea ice 
     81      ! 
     82      IF( lwp )  & 
     83         &  CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea ) 
     84      ! 
     85      CALL trc_ini_state  !  passive tracers initialisation : from a restart or from clim 
     86      ! 
     87      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers 
     88      ! 
     89      CALL trc_ini_inv   ! Inventories 
     90      ! 
     91      IF( nn_timing == 1 )   CALL timing_stop('trc_init') 
     92      ! 
     93   END SUBROUTINE trc_init 
     94 
     95   SUBROUTINE trc_ini_ctl 
     96      !!---------------------------------------------------------------------- 
     97      !!                     ***  ROUTINE trc_ini_ctl  *** 
     98      !! ** Purpose :        Control  + ocean volume 
     99      !!---------------------------------------------------------------------- 
     100      INTEGER ::   jk    ! dummy loop indices 
     101      ! 
     102      ! Define logical parameter ton control dirunal cycle in TOP 
    74103      l_trcdm2dc = ln_dm2dc .OR. ( ln_cpl .AND. ncpl_qsr_freq /= 1 ) 
    75104      l_trcdm2dc = l_trcdm2dc  .AND. .NOT. lk_offline 
     
    78107         & Computation of a daily mean shortwave for some biogeochemical models) ') 
    79108 
     109      ! 
    80110      IF( nn_cla == 1 )   & 
    81111         &  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 
     112      ! 
     113   END SUBROUTINE trc_ini_ctl 
     114 
     115   SUBROUTINE trc_ini_inv 
     116      !!---------------------------------------------------------------------- 
     117      !!                     ***  ROUTINE trc_ini_stat  *** 
     118      !! ** Purpose :      passive tracers inventories at initialsation phase 
     119      !!---------------------------------------------------------------------- 
     120      INTEGER ::  jk, jn    ! dummy loop indices 
     121      CHARACTER (len=25) :: charout 
     122      !!---------------------------------------------------------------------- 
    91123      !                                                              ! masked grid volume 
    92124      DO jk = 1, jpk 
     
    96128      !                                                              ! total volume of the ocean  
    97129      areatot = glob_sum( cvol(:,:,:) ) 
    98  
     130      ! 
     131      trai(:) = 0._wp                                                   ! initial content of all tracers 
     132      DO jn = 1, jptra 
     133         trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   ) 
     134      END DO 
     135 
     136      IF(lwp) THEN               ! control print 
     137         WRITE(numout,*) 
     138         WRITE(numout,*) 
     139         WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra 
     140         WRITE(numout,*) '          *** Total volume of ocean                = ', areatot 
     141         WRITE(numout,*) '          *** Total inital content of all tracers ' 
     142         WRITE(numout,*) 
     143         DO jn = 1, jptra 
     144            WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn) 
     145         ENDDO 
     146         WRITE(numout,*) 
     147      ENDIF 
     148      IF(lwp) WRITE(numout,*) 
     149      IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
     150         CALL prt_ctl_trc_init 
     151         WRITE(charout, FMT="('ini ')") 
     152         CALL prt_ctl_trc_info( charout ) 
     153         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
     154      ENDIF 
     1559000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
     156      ! 
     157   END SUBROUTINE trc_ini_inv 
     158 
     159   SUBROUTINE trc_ini_sms 
     160      !!---------------------------------------------------------------------- 
     161      !!                     ***  ROUTINE trc_ini_sms  *** 
     162      !! ** Purpose :   SMS initialisation 
     163      !!---------------------------------------------------------------------- 
     164      USE trcini_cfc      ! CFC      initialisation 
     165      USE trcini_pisces   ! PISCES   initialisation 
     166      USE trcini_c14b     ! C14 bomb initialisation 
     167      USE trcini_my_trc   ! MY_TRC   initialisation 
     168      !!---------------------------------------------------------------------- 
    99169      IF( lk_pisces  )       CALL trc_ini_pisces       ! PISCES  bio-model 
    100170      IF( lk_cfc     )       CALL trc_ini_cfc          ! CFC     tracers 
    101171      IF( lk_c14b    )       CALL trc_ini_c14b         ! C14 bomb  tracer 
    102172      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  
     173      ! 
     174   END SUBROUTINE trc_ini_sms 
     175 
     176   SUBROUTINE trc_ini_trp 
     177      !!---------------------------------------------------------------------- 
     178      !!                     ***  ROUTINE trc_ini_trp  *** 
     179      !! 
     180      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules 
     181      !!---------------------------------------------------------------------- 
     182      USE trcdmp , ONLY:  trc_dmp_ini 
     183      USE trcadv , ONLY:  trc_adv_ini 
     184      USE trcldf , ONLY:  trc_ldf_ini 
     185      USE trczdf , ONLY:  trc_zdf_ini 
     186      USE trcrad , ONLY:  trc_rad_ini 
     187      ! 
     188      INTEGER :: ierr 
     189      !!---------------------------------------------------------------------- 
     190      ! 
     191      IF( ln_trcdmp )  CALL  trc_dmp_ini          ! damping 
     192                       CALL  trc_adv_ini          ! advection 
     193                       CALL  trc_ldf_ini          ! lateral diffusion 
     194                       CALL  trc_zdf_ini          ! vertical diffusion 
     195                       CALL  trc_rad_ini          ! positivity of passive tracers  
     196      ! 
     197   END SUBROUTINE trc_ini_trp 
     198 
     199   SUBROUTINE trc_ini_state 
     200      !!---------------------------------------------------------------------- 
     201      !!                     ***  ROUTINE trc_ini_state *** 
     202      !! ** Purpose :          Initialisation of passive tracer concentration  
     203      !!---------------------------------------------------------------------- 
     204      USE zpshde          ! partial step: hor. derivative   (zps_hde routine) 
     205      USE trcrst          ! passive tracers restart 
     206      USE trcdta          ! initialisation from files 
     207      ! 
     208      INTEGER ::   jk, jn, jl    ! dummy loop indices 
     209      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace 
     210      !!---------------------------------------------------------------------- 
     211      ! 
    112212      IF( ln_trcdta )      CALL trc_dta_init(jptra) 
    113  
    114213 
    115214      IF( ln_rsttr ) THEN 
     
    146245  
    147246      tra(:,:,:,:) = 0._wp 
    148  
    149 !!gm  case not.lk_c1d   is useless since in 1D, 9 identical column all resulting arrays are zero 
    150 !!                       it is at the initialization so not a issue      
    151 !      IF(.NOT. lk_c1d ) THEN 
    152 !!gm 
    153       IF( ln_isfcav .AND. ln_zps ) THEN   ;   CALL zps_hde_isf( nit000, jptra, trn, gtru, gtrv, gtrui, gtrvi )  ! both top & bottom 
    154       ELSEIF(             ln_zps ) THEN   ;   CALL zps_hde    ( nit000, jptra, trn, gtru, gtrv )                ! only bottom  
    155       ENDIF 
    156 !!gm       
    157 !      ENDIF 
    158 !!gm 
    159  
    160 !!gm  ===>>>>>>  Anyyway, I don't understand why a call to zps_hde is needed here ! 
    161  
    162       ! 
    163       IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers 
    164       ! 
    165  
    166       trai(:) = 0._wp                                                   ! initial content of all tracers 
    167       DO jn = 1, jptra 
    168          trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   ) 
    169       END DO 
    170  
    171       IF(lwp) THEN               ! control print 
    172          WRITE(numout,*) 
    173          WRITE(numout,*) 
    174          WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra 
    175          WRITE(numout,*) '          *** Total volume of ocean                = ', areatot 
    176          WRITE(numout,*) '          *** Total inital content of all tracers ' 
    177          WRITE(numout,*) 
    178          DO jn = 1, jptra 
    179             WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn) 
    180          ENDDO 
    181          WRITE(numout,*) 
    182       ENDIF 
    183       IF(lwp) WRITE(numout,*) 
    184       IF(ln_ctl) THEN            ! print mean trends (used for debugging) 
    185          CALL prt_ctl_trc_init 
    186          WRITE(charout, FMT="('ini ')") 
    187          CALL prt_ctl_trc_info( charout ) 
    188          CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) 
    189       ENDIF 
    190 9000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
    191       ! 
    192       IF( nn_timing == 1 )   CALL timing_stop('trc_init') 
    193       ! 
    194    END SUBROUTINE trc_init 
    195  
     247      !                                                         ! Partial top/bottom cell: GRADh(trn) 
     248   END SUBROUTINE trc_ini_state 
    196249 
    197250   SUBROUTINE top_alloc 
Note: See TracChangeset for help on using the changeset viewer.