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.
trcini.F90 in branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/TOP_SRC/trcini.F90 @ 8442

Last change on this file since 8442 was 8442, checked in by frrh, 7 years ago

Commit changes relating to Met Office GMED ticket 340 for the
tidying of MEDUSA related code and debugging statements in the TOP code.

Only code introduced at revision 8434 of branch
http://fcm3/projects/NEMO.xm/log/branches/NERC/dev_r5518_GO6_split_trcbiomedusa
is included here, all previous revisions of that branch having been dealt with
under GMED ticket 339.

File size: 10.7 KB
RevLine 
[268]1MODULE trcini
[945]2   !!======================================================================
3   !!                         ***  MODULE trcini  ***
4   !! TOP :   Manage the passive tracer initialization
5   !!======================================================================
[2715]6   !! History :   -   ! 1991-03 (O. Marti)  original code
7   !!            1.0  ! 2005-03 (O. Aumont, A. El Moussaoui) F90
8   !!            2.0  ! 2005-10 (C. Ethe, G. Madec) revised architecture
9   !!            4.0  ! 2011-01 (A. R. Porter, STFC Daresbury) dynamical allocation
[8280]10   !!             -   ! 2014-06 (A. Yool, J. Palmieri) adding MEDUSA-2
[274]11   !!----------------------------------------------------------------------
[1011]12#if defined key_top
13   !!----------------------------------------------------------------------
14   !!   'key_top'                                                TOP models
15   !!----------------------------------------------------------------------
[2715]16   !!   trc_init  :   Initialization for passive tracer
17   !!   top_alloc :   allocate the TOP arrays
[1011]18   !!----------------------------------------------------------------------
[3294]19   USE oce_trc         ! shared variables between ocean and passive tracers
20   USE trc             ! passive tracers common variables
21   USE trcrst          ! passive tracers restart
[2528]22   USE trcnam          ! Namelist read
[1254]23   USE trcini_cfc      ! CFC      initialisation
24   USE trcini_pisces   ! PISCES   initialisation
25   USE trcini_c14b     ! C14 bomb initialisation
[8442]26   USE trcini_age      ! AGE      initialisation
[1254]27   USE trcini_my_trc   ! MY_TRC   initialisation
[8442]28   USE trcini_idtra    ! idealize tracer initialisation
[8280]29   USE trcini_medusa   ! MEDUSA   initialisation
[4230]30   USE trcdta          ! initialisation from files
[3294]31   USE daymod          ! calendar manager
[1011]32   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine)
[4306]33   USE trcsub          ! variables to substep passive tracers
34   USE lib_mpp         ! distribued memory computing library
35   USE sbc_oce
[5385]36   USE trcice          ! tracers in sea ice
[4306]37 
[335]38   IMPLICIT NONE
39   PRIVATE
[1011]40   
[2528]41   PUBLIC   trc_init   ! called by opa
[268]42
[1011]43    !! * Substitutions
44#  include "domzgr_substitute.h90"
[2715]45   !!----------------------------------------------------------------------
46   !! NEMO/TOP 4.0 , NEMO Consortium (2011)
[6486]47   !! $Id$
[2715]48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
[335]50CONTAINS
[1011]51   
[2528]52   SUBROUTINE trc_init
[1011]53      !!---------------------------------------------------------------------
[2528]54      !!                     ***  ROUTINE trc_init  ***
[335]55      !!
[1011]56      !! ** Purpose :   Initialization of the passive tracer fields
57      !!
58      !! ** Method  : - read namelist
59      !!              - control the consistancy
60      !!              - compute specific initialisations
61      !!              - set initial tracer fields (either read restart
62      !!                or read data or analytical formulation
63      !!---------------------------------------------------------------------
[3294]64      INTEGER ::   jk, jn, jl    ! dummy loop indices
[1011]65      CHARACTER (len=25) :: charout
66      !!---------------------------------------------------------------------
[3294]67      !
68      IF( nn_timing == 1 )   CALL timing_start('trc_init')
69      !
[945]70      IF(lwp) WRITE(numout,*)
[2528]71      IF(lwp) WRITE(numout,*) 'trc_init : initial set up of the passive tracers'
[945]72      IF(lwp) WRITE(numout,*) '~~~~~~~'
[1011]73
[2715]74      CALL top_alloc()              ! allocate TOP arrays
75
[5407]76      l_trcdm2dc = ln_dm2dc .OR. ( ln_cpl .AND. ncpl_qsr_freq /= 1 )
[5385]77      l_trcdm2dc = l_trcdm2dc  .AND. .NOT. lk_offline
78      IF( l_trcdm2dc .AND. lwp ) &
79         &   CALL ctl_warn(' Coupling with passive tracers and used of diurnal cycle. &
80         & Computation of a daily mean shortwave for some biogeochemical models) ')
[8442]81
[3294]82      IF( nn_cla == 1 )   &
83         &  CALL ctl_stop( ' Cross Land Advection not yet implemented with passive tracer ; nn_cla must be 0' )
[1011]84
[4152]85      CALL trc_nam      ! read passive tracers namelists
[3294]86      !
87      IF(lwp) WRITE(numout,*)
[4152]88      !
89      IF( ln_rsttr .AND. .NOT. lk_offline ) CALL trc_rst_cal( nit000, 'READ' )   ! calendar
90      !
[3294]91      IF(lwp) WRITE(numout,*)
92                                                              ! masked grid volume
93      !                                                              ! masked grid volume
94      DO jk = 1, jpk
95         cvol(:,:,jk) = e1e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk)
96      END DO
97      IF( lk_degrad ) cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)      ! degrad option: reduction by facvol
98      !                                                              ! total volume of the ocean
99      areatot = glob_sum( cvol(:,:,:) )
[1011]100
[3294]101      IF( lk_pisces  )       CALL trc_ini_pisces       ! PISCES  bio-model
102      IF( lk_cfc     )       CALL trc_ini_cfc          ! CFC     tracers
103      IF( lk_c14b    )       CALL trc_ini_c14b         ! C14 bomb  tracer
[8280]104      IF( lk_age     )       CALL trc_ini_age          ! AGE       tracer
[7203]105      IF( lk_my_trc  )       CALL trc_ini_my_trc       ! MY_TRC  tracers
[8442]106      IF( lk_idtra   )       CALL trc_ini_idtra        ! Idealize tracers
107      IF( lk_medusa  )       CALL trc_ini_medusa       ! MEDUSA  tracers
[2528]108
[5385]109      CALL trc_ice_ini                                 ! Tracers in sea ice
110
[8280]111      IF( ln_ctl ) THEN
[3294]112         !
[8280]113         IF (narea == 1) THEN 
114            ! The tracer.stat file only contains global tracer sum values, if
115            ! it contains anything at all. Hence it only needs to be opened
116            ! and written to on the master PE, not on all PEs. 
117            CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE','FORMATTED',  & 
118                          'SEQUENTIAL', -1, numout, lwp , narea ) 
119         ENDIF 
[3294]120         !
[945]121      ENDIF
[1254]122
[8280]123      IF( ln_trcdta ) THEN
124         CALL trc_dta_init(jptra)
125      ENDIF
126
[2528]127      IF( ln_rsttr ) THEN
128        !
129        CALL trc_rst_read              ! restart from a file
130        !
[1011]131      ELSE
[3294]132        !
133        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping
134            !
135            DO jn = 1, jptra
136               IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
137                  jl = n_trc_index(jn) 
[6793]138                  CALL trc_dta( nit000, sf_trcdta(jl), rf_trfac(jl) )   ! read tracer data at nit000
139                  trn(:,:,:,jn) = sf_trcdta(jl)%fnow(:,:,:) 
[4230]140                  IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN      !== deallocate data structure   ==!
141                     !                                                    (data used only for initialisation)
142                     IF(lwp) WRITE(numout,*) 'trc_dta: deallocate data arrays as they are only used to initialize the run'
143                                                  DEALLOCATE( sf_trcdta(jl)%fnow )     !  arrays in the structure
144                     IF( sf_trcdta(jl)%ln_tint )  DEALLOCATE( sf_trcdta(jl)%fdta )
145                     !
146                  ENDIF
[3294]147               ENDIF
148            ENDDO
[6498]149            !
[2528]150        ENDIF
[3294]151        !
[2528]152        trb(:,:,:,:) = trn(:,:,:,:)
153        !
[1011]154      ENDIF
[2528]155 
[2715]156      tra(:,:,:,:) = 0._wp
[3294]157      !
158      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers
159      !
[8442]160
[3294]161      trai(:) = 0._wp                                                   ! initial content of all tracers
[1011]162      DO jn = 1, jptra
[3294]163         trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   )
164      END DO
[1011]165
[2715]166      IF(lwp) THEN               ! control print
167         WRITE(numout,*)
168         WRITE(numout,*)
169         WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra
170         WRITE(numout,*) '          *** Total volume of ocean                = ', areatot
[3294]171         WRITE(numout,*) '          *** Total inital content of all tracers '
[2715]172         WRITE(numout,*)
[8280]173# if defined key_debug_medusa
174         CALL flush(numout)
175# endif
176         !
177# if defined key_debug_medusa
178         WRITE(numout,*) ' litle check :  ', ctrcnm(1)
179         CALL flush(numout)
180# endif
[3294]181         DO jn = 1, jptra
182            WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn)
183         ENDDO
184         WRITE(numout,*)
[2715]185      ENDIF
[3294]186      IF(lwp) WRITE(numout,*)
[2715]187      IF(ln_ctl) THEN            ! print mean trends (used for debugging)
188         CALL prt_ctl_trc_init
[1011]189         WRITE(charout, FMT="('ini ')")
190         CALL prt_ctl_trc_info( charout )
191         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
192      ENDIF
[8280]193
194      IF(lwp) WRITE(numout,*)
195      IF(lwp) WRITE(numout,*) 'trc_init : passive tracer set up completed'
196      IF(lwp) WRITE(numout,*) '~~~~~~~'
197      IF(lwp) CALL flush(numout)
198# if defined key_debug_medusa
199         CALL trc_rst_stat
200         CALL flush(numout)
201# endif
202
[3294]2039000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10)
[2715]204      !
[3294]205      IF( nn_timing == 1 )   CALL timing_stop('trc_init')
206      !
[2528]207   END SUBROUTINE trc_init
[268]208
[2715]209
210   SUBROUTINE top_alloc
211      !!----------------------------------------------------------------------
212      !!                     ***  ROUTINE top_alloc  ***
213      !!
214      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules
215      !!----------------------------------------------------------------------
216      USE trcadv        , ONLY:   trc_adv_alloc          ! TOP-related alloc routines...
217      USE trc           , ONLY:   trc_alloc
218      USE trcnxt        , ONLY:   trc_nxt_alloc
219      USE trczdf        , ONLY:   trc_zdf_alloc
[4990]220      USE trdtrc_oce    , ONLY:   trd_trc_oce_alloc
221#if defined key_trdmxl_trc 
222      USE trdmxl_trc    , ONLY:   trd_mxl_trc_alloc
[2715]223#endif
[8441]224# if defined key_medusa
225      USE bio_medusa_mod, ONLY:   bio_medusa_alloc
226# endif
227
[2715]228      !
229      INTEGER :: ierr
230      !!----------------------------------------------------------------------
231      !
232      ierr =        trc_adv_alloc()          ! Start of TOP-related alloc routines...
233      ierr = ierr + trc_alloc    ()
234      ierr = ierr + trc_nxt_alloc()
235      ierr = ierr + trc_zdf_alloc()
[4990]236      ierr = ierr + trd_trc_oce_alloc()
237#if defined key_trdmxl_trc 
238      ierr = ierr + trd_mxl_trc_alloc()
[2715]239#endif
[8441]240#if defined key_medusa
241      ierr = ierr + bio_medusa_alloc()
242#endif
[2715]243      !
244      IF( lk_mpp    )   CALL mpp_sum( ierr )
245      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'top_alloc : unable to allocate standard ocean arrays' )
246      !
247   END SUBROUTINE top_alloc
248
[1011]249#else
250   !!----------------------------------------------------------------------
251   !!  Empty module :                                     No passive tracer
252   !!----------------------------------------------------------------------
253CONTAINS
[2528]254   SUBROUTINE trc_init                      ! Dummy routine   
255   END SUBROUTINE trc_init
[1011]256#endif
257
[335]258   !!======================================================================
[268]259END MODULE trcini
Note: See TracBrowser for help on using the repository browser.