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/2013/dev_r3996_CMCC6_topbc/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2013/dev_r3996_CMCC6_topbc/NEMOGCM/NEMO/TOP_SRC/trcini.F90 @ 4011

Last change on this file since 4011 was 4011, checked in by vichi, 11 years ago

Make a generic interface for trcdta when using other BGCM

This change introduces a more general trcdta structure that
is not strictly dependent on the number of tracers defined
in PISCES. The loop on the number of tracers is moved outside
trcdta and the tracer info and array is passed as an argument.
This allows to use trcdta as a library subroutine by the BFM and
other models.
NOTE: it must be tested throughly with all the PISCES configurations

This commit also updates the GYRE_BFM configuration and corrects
some minor missing cpp keys and real type definitions

  • Property svn:keywords set to Id
File size: 9.2 KB
Line 
1MODULE trcini
2   !!======================================================================
3   !!                         ***  MODULE trcini  ***
4   !! TOP :   Manage the passive tracer initialization
5   !!======================================================================
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
10   !!----------------------------------------------------------------------
11#if defined key_top
12   !!----------------------------------------------------------------------
13   !!   'key_top'                                                TOP models
14   !!----------------------------------------------------------------------
15   !!   trc_init  :   Initialization for passive tracer
16   !!   top_alloc :   allocate the TOP arrays
17   !!----------------------------------------------------------------------
18   USE oce_trc         ! shared variables between ocean and passive tracers
19   USE trc             ! passive tracers common variables
20   USE trcrst          ! passive tracers restart
21   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
27   USE daymod          ! calendar manager
28   USE zpshde          ! partial step: hor. derivative   (zps_hde routine)
29   USE prtctl_trc      ! Print control passive tracers (prt_ctl_trc_init routine)
30   USE trcsub       ! variables to substep passive tracers
31   
32   IMPLICIT NONE
33   PRIVATE
34   
35   PUBLIC   trc_init   ! called by opa
36
37    !! * Substitutions
38#  include "domzgr_substitute.h90"
39   !!----------------------------------------------------------------------
40   !! NEMO/TOP 4.0 , NEMO Consortium (2011)
41   !! $Id$
42   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
43   !!----------------------------------------------------------------------
44CONTAINS
45   
46   SUBROUTINE trc_init
47      !!---------------------------------------------------------------------
48      !!                     ***  ROUTINE trc_init  ***
49      !!
50      !! ** Purpose :   Initialization of the passive tracer fields
51      !!
52      !! ** Method  : - read namelist
53      !!              - control the consistancy
54      !!              - compute specific initialisations
55      !!              - set initial tracer fields (either read restart
56      !!                or read data or analytical formulation
57      !!---------------------------------------------------------------------
58      INTEGER ::   jk, jn, jl    ! dummy loop indices
59      CHARACTER (len=25) :: charout
60      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace
61      !!---------------------------------------------------------------------
62      !
63      IF( nn_timing == 1 )   CALL timing_start('trc_init')
64      !
65      IF(lwp) WRITE(numout,*)
66      IF(lwp) WRITE(numout,*) 'trc_init : initial set up of the passive tracers'
67      IF(lwp) WRITE(numout,*) '~~~~~~~'
68
69      CALL top_alloc()              ! allocate TOP arrays
70
71      IF( ln_dm2dc .AND. lk_pisces )    &
72         &  CALL ctl_stop( ' The diurnal cycle is not compatible with PISCES ' )
73
74      IF( nn_cla == 1 )   &
75         &  CALL ctl_stop( ' Cross Land Advection not yet implemented with passive tracer ; nn_cla must be 0' )
76
77      CALL trc_nam                  ! read passive tracers namelists
78      !
79      IF(lwp) WRITE(numout,*)
80      IF( ln_rsttr ) THEN
81        !
82        IF( lk_offline )  neuler = 1   ! Set time-step indicator at nit000 (leap-frog)
83        CALL trc_rst_cal( nittrc000, 'READ' )   ! calendar
84        !
85      ELSE
86        IF( lk_offline )  THEN
87           neuler = 0                  ! Set time-step indicator at nit000 (euler)
88           CALL day_init               ! set calendar
89        ENDIF
90        !
91      ENDIF
92      IF(lwp) WRITE(numout,*)
93                                                              ! masked grid volume
94      !                                                              ! masked grid volume
95      DO jk = 1, jpk
96         cvol(:,:,jk) = e1e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk)
97      END DO
98      IF( lk_degrad ) cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)      ! degrad option: reduction by facvol
99      !                                                              ! total volume of the ocean
100      areatot = glob_sum( cvol(:,:,:) )
101
102      IF( lk_pisces  )       CALL trc_ini_pisces       ! PISCES  bio-model
103      IF( lk_cfc     )       CALL trc_ini_cfc          ! CFC     tracers
104      IF( lk_c14b    )       CALL trc_ini_c14b         ! C14 bomb  tracer
105      IF( lk_my_trc  )       CALL trc_ini_my_trc       ! MY_TRC  tracers
106
107      IF( lwp ) THEN
108         !
109         CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
110         !
111      ENDIF
112
113      IF( ln_trcdta )      CALL trc_dta_init(jptra)
114
115
116      IF( ln_rsttr ) THEN
117        !
118        CALL trc_rst_read              ! restart from a file
119        !
120      ELSE
121        !
122        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping
123            !
124            CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )    ! Memory allocation
125            !
126            DO jn = 1, jptra
127               IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
128                  jl = n_trc_index(jn) 
129                  CALL trc_dta( kt, sf_trcdta(jl),rf_trfac(jl) )   ! read tracer data at nit000
130                  ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:)
131                  trn(:,:,:,jn) = ztrcdta(:,:,:) * tmask(:,:,:) 
132               ENDIF
133            ENDDO
134            CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta )
135        ENDIF
136        !
137        trb(:,:,:,:) = trn(:,:,:,:)
138        !
139      ENDIF
140 
141      tra(:,:,:,:) = 0._wp
142     
143      IF( ln_zps .AND. .NOT. lk_c1d )   &              ! Partial steps: before horizontal gradient of passive
144        &    CALL zps_hde( nit000, jptra, trn, gtru, gtrv )       ! tracers at the bottom ocean level
145
146      !
147      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers
148      !
149
150      trai(:) = 0._wp                                                   ! initial content of all tracers
151      DO jn = 1, jptra
152         trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   )
153      END DO
154
155      IF(lwp) THEN               ! control print
156         WRITE(numout,*)
157         WRITE(numout,*)
158         WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra
159         WRITE(numout,*) '          *** Total volume of ocean                = ', areatot
160         WRITE(numout,*) '          *** Total inital content of all tracers '
161         WRITE(numout,*)
162         DO jn = 1, jptra
163            WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn)
164         ENDDO
165         WRITE(numout,*)
166      ENDIF
167      IF(lwp) WRITE(numout,*)
168      IF(ln_ctl) THEN            ! print mean trends (used for debugging)
169         CALL prt_ctl_trc_init
170         WRITE(charout, FMT="('ini ')")
171         CALL prt_ctl_trc_info( charout )
172         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
173      ENDIF
1749000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10)
175      !
176      IF( nn_timing == 1 )   CALL timing_stop('trc_init')
177      !
178   END SUBROUTINE trc_init
179
180
181   SUBROUTINE top_alloc
182      !!----------------------------------------------------------------------
183      !!                     ***  ROUTINE top_alloc  ***
184      !!
185      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules
186      !!----------------------------------------------------------------------
187      USE trcadv        , ONLY:   trc_adv_alloc          ! TOP-related alloc routines...
188      USE trc           , ONLY:   trc_alloc
189      USE trcnxt        , ONLY:   trc_nxt_alloc
190      USE trczdf        , ONLY:   trc_zdf_alloc
191      USE trdmod_trc_oce, ONLY:   trd_mod_trc_oce_alloc
192#if defined key_trdmld_trc 
193      USE trdmld_trc    , ONLY:   trd_mld_trc_alloc
194#endif
195      !
196      INTEGER :: ierr
197      !!----------------------------------------------------------------------
198      !
199      ierr =        trc_adv_alloc()          ! Start of TOP-related alloc routines...
200      ierr = ierr + trc_alloc    ()
201      ierr = ierr + trc_nxt_alloc()
202      ierr = ierr + trc_zdf_alloc()
203      ierr = ierr + trd_mod_trc_oce_alloc()
204#if defined key_trdmld_trc 
205      ierr = ierr + trd_mld_trc_alloc()
206#endif
207      !
208      IF( lk_mpp    )   CALL mpp_sum( ierr )
209      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'top_alloc : unable to allocate standard ocean arrays' )
210      !
211   END SUBROUTINE top_alloc
212
213#else
214   !!----------------------------------------------------------------------
215   !!  Empty module :                                     No passive tracer
216   !!----------------------------------------------------------------------
217CONTAINS
218   SUBROUTINE trc_init                      ! Dummy routine   
219   END SUBROUTINE trc_init
220#endif
221
222   !!======================================================================
223END MODULE trcini
Note: See TracBrowser for help on using the repository browser.