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/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/trcini.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 9 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 12.5 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 trcnam          ! Namelist read
21   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
24   USE trcrst
25   USE lib_mpp         ! distribued memory computing library
26   USE sbc_oce
27   USE trcice          ! tracers in sea ice
28 
29   IMPLICIT NONE
30   PRIVATE
31   
32   PUBLIC   trc_init   ! called by opa
33
34    !! * Substitutions
35#  include "domzgr_substitute.h90"
36   !!----------------------------------------------------------------------
37   !! NEMO/TOP 4.0 , NEMO Consortium (2011)
38   !! $Id$
39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41CONTAINS
42   
43   SUBROUTINE trc_init
44      !!---------------------------------------------------------------------
45      !!                     ***  ROUTINE trc_init  ***
46      !!
47      !! ** Purpose :   Initialization of the passive tracer fields
48      !!
49      !! ** Method  : - read namelist
50      !!              - control the consistancy
51      !!              - compute specific initialisations
52      !!              - set initial tracer fields (either read restart
53      !!                or read data or analytical formulation
54      !!---------------------------------------------------------------------
55      !
56      IF( nn_timing == 1 )   CALL timing_start('trc_init')
57      !
58      IF(lwp) WRITE(numout,*)
59      IF(lwp) WRITE(numout,*) 'trc_init : initial set up of the passive tracers'
60      IF(lwp) WRITE(numout,*) '~~~~~~~'
61
62      !
63      CALL top_alloc()   ! allocate TOP arrays
64      !
65      CALL trc_ini_ctl   ! control
66      !
67      CALL trc_nam       ! read passive tracers namelists
68      !
69      IF(lwp) WRITE(numout,*)
70      !
71      IF( ln_rsttr .AND. .NOT. lk_offline ) CALL trc_rst_cal( nit000, 'READ' )   ! calendar
72      !
73      IF(lwp) WRITE(numout,*)
74      !
75      CALL trc_ini_sms   ! SMS
76      !
77      CALL trc_ini_trp   ! passive tracers transport
78      !
79      CALL trc_ice_ini   ! Tracers in sea ice
80      !
81      IF( lwp )  &
82         &  CALL ctl_opn( numstr, 'tracer.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp , narea )
83      !
84      CALL trc_ini_state  !  passive tracers initialisation : from a restart or from clim
85      !
86      IF( nn_dttrc /= 1 )        CALL trc_sub_ini      ! Initialize variables for substepping passive tracers
87      !
88      CALL trc_ini_inv   ! Inventories
89      !
90      IF( nn_timing == 1 )   CALL timing_stop('trc_init')
91      !
92   END SUBROUTINE trc_init
93
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
103      l_trcdm2dc = ln_dm2dc .OR. ( ln_cpl .AND. ncpl_qsr_freq /= 1 )
104      l_trcdm2dc = l_trcdm2dc  .AND. .NOT. lk_offline
105      IF( l_trcdm2dc .AND. lwp )   CALL ctl_warn( 'Coupling with passive tracers and used of diurnal cycle.',   &
106         &                           'Computation of a daily mean shortwave for some biogeochemical models ' )
107      !
108   END SUBROUTINE trc_ini_ctl
109
110
111   SUBROUTINE trc_ini_inv
112      !!----------------------------------------------------------------------
113      !!                     ***  ROUTINE trc_ini_stat  ***
114      !! ** Purpose :      passive tracers inventories at initialsation phase
115      !!----------------------------------------------------------------------
116      INTEGER ::  jk, jn    ! dummy loop indices
117      CHARACTER (len=25) :: charout
118      !!----------------------------------------------------------------------
119      !                                                              ! masked grid volume
120      DO jk = 1, jpk
121         cvol(:,:,jk) = e1e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk)
122      END DO
123      IF( lk_degrad ) cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)      ! degrad option: reduction by facvol
124      !                                                              ! total volume of the ocean
125      areatot = glob_sum( cvol(:,:,:) )
126      !
127      trai(:) = 0._wp                                                   ! initial content of all tracers
128      DO jn = 1, jptra
129         trai(jn) = trai(jn) + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   )
130      END DO
131
132      IF(lwp) THEN               ! control print
133         WRITE(numout,*)
134         WRITE(numout,*)
135         WRITE(numout,*) '          *** Total number of passive tracer jptra = ', jptra
136         WRITE(numout,*) '          *** Total volume of ocean                = ', areatot
137         WRITE(numout,*) '          *** Total inital content of all tracers '
138         WRITE(numout,*)
139         DO jn = 1, jptra
140            WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), trai(jn)
141         ENDDO
142         WRITE(numout,*)
143      ENDIF
144      IF(lwp) WRITE(numout,*)
145      IF(ln_ctl) THEN            ! print mean trends (used for debugging)
146         CALL prt_ctl_trc_init
147         WRITE(charout, FMT="('ini ')")
148         CALL prt_ctl_trc_info( charout )
149         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
150      ENDIF
1519000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10)
152      !
153   END SUBROUTINE trc_ini_inv
154
155
156   SUBROUTINE trc_ini_sms
157      !!----------------------------------------------------------------------
158      !!                     ***  ROUTINE trc_ini_sms  ***
159      !! ** Purpose :   SMS initialisation
160      !!----------------------------------------------------------------------
161      USE trcini_cfc      ! CFC      initialisation
162      USE trcini_pisces   ! PISCES   initialisation
163      USE trcini_c14b     ! C14 bomb initialisation
164      USE trcini_my_trc   ! MY_TRC   initialisation
165      !!----------------------------------------------------------------------
166      IF( lk_pisces  )       CALL trc_ini_pisces       ! PISCES  bio-model
167      IF( lk_cfc     )       CALL trc_ini_cfc          ! CFC     tracers
168      IF( lk_c14b    )       CALL trc_ini_c14b         ! C14 bomb  tracer
169      IF( lk_my_trc  )       CALL trc_ini_my_trc       ! MY_TRC  tracers
170      !
171   END SUBROUTINE trc_ini_sms
172
173   SUBROUTINE trc_ini_trp
174      !!----------------------------------------------------------------------
175      !!                     ***  ROUTINE trc_ini_trp  ***
176      !!
177      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules
178      !!----------------------------------------------------------------------
179      USE trcdmp , ONLY:  trc_dmp_ini
180      USE trcadv , ONLY:  trc_adv_ini
181      USE trcldf , ONLY:  trc_ldf_ini
182      USE trczdf , ONLY:  trc_zdf_ini
183      USE trcrad , ONLY:  trc_rad_ini
184      !
185      INTEGER :: ierr
186      !!----------------------------------------------------------------------
187      !
188      IF( ln_trcdmp )  CALL  trc_dmp_ini          ! damping
189                       CALL  trc_adv_ini          ! advection
190                       CALL  trc_ldf_ini          ! lateral diffusion
191                       CALL  trc_zdf_ini          ! vertical diffusion
192                       CALL  trc_rad_ini          ! positivity of passive tracers
193      !
194   END SUBROUTINE trc_ini_trp
195
196
197   SUBROUTINE trc_ini_state
198      !!----------------------------------------------------------------------
199      !!                     ***  ROUTINE trc_ini_state ***
200      !! ** Purpose :          Initialisation of passive tracer concentration
201      !!----------------------------------------------------------------------
202      USE zpshde          ! partial step: hor. derivative   (zps_hde routine)
203      USE trcrst          ! passive tracers restart
204      USE trcdta          ! initialisation from files
205      !
206      INTEGER ::   jk, jn, jl    ! dummy loop indices
207      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrcdta   ! 4D  workspace
208      !!----------------------------------------------------------------------
209      !
210      IF( ln_trcdta )      CALL trc_dta_init(jptra)
211
212      IF( ln_rsttr ) THEN
213        !
214        CALL trc_rst_read              ! restart from a file
215        !
216      ELSE
217        !
218        IF( ln_trcdta .AND. nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping
219            !
220            CALL wrk_alloc( jpi, jpj, jpk, ztrcdta )    ! Memory allocation
221            !
222            DO jn = 1, jptra
223               IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
224                  jl = n_trc_index(jn) 
225                  CALL trc_dta( nit000, sf_trcdta(jl),rf_trfac(jl) )   ! read tracer data at nit000
226                  ztrcdta(:,:,:) = sf_trcdta(jl)%fnow(:,:,:)
227                  trn(:,:,:,jn) = ztrcdta(:,:,:) * tmask(:,:,:) 
228                  IF( .NOT.ln_trcdmp .AND. .NOT.ln_trcdmp_clo ) THEN      !== deallocate data structure   ==!
229                     !                                                    (data used only for initialisation)
230                     IF(lwp) WRITE(numout,*) 'trc_dta: deallocate data arrays as they are only used to initialize the run'
231                                                  DEALLOCATE( sf_trcdta(jl)%fnow )     !  arrays in the structure
232                     IF( sf_trcdta(jl)%ln_tint )  DEALLOCATE( sf_trcdta(jl)%fdta )
233                     !
234                  ENDIF
235               ENDIF
236            ENDDO
237            CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta )
238        ENDIF
239        !
240        trb(:,:,:,:) = trn(:,:,:,:)
241        !
242      ENDIF
243 
244      tra(:,:,:,:) = 0._wp
245      !                                                         ! Partial top/bottom cell: GRADh(trn)
246   END SUBROUTINE trc_ini_state
247
248
249   SUBROUTINE top_alloc
250      !!----------------------------------------------------------------------
251      !!                     ***  ROUTINE top_alloc  ***
252      !!
253      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules
254      !!----------------------------------------------------------------------
255      USE trcadv        , ONLY:   trc_adv_alloc          ! TOP-related alloc routines...
256      USE trc           , ONLY:   trc_alloc
257      USE trcnxt        , ONLY:   trc_nxt_alloc
258      USE trczdf        , ONLY:   trc_zdf_alloc
259      USE trdtrc_oce    , ONLY:   trd_trc_oce_alloc
260#if defined key_trdmxl_trc 
261      USE trdmxl_trc    , ONLY:   trd_mxl_trc_alloc
262#endif
263      !
264      INTEGER :: ierr
265      !!----------------------------------------------------------------------
266      !
267      ierr =        trc_adv_alloc()          ! Start of TOP-related alloc routines...
268      ierr = ierr + trc_alloc    ()
269      ierr = ierr + trc_nxt_alloc()
270      ierr = ierr + trc_zdf_alloc()
271      ierr = ierr + trd_trc_oce_alloc()
272#if defined key_trdmxl_trc 
273      ierr = ierr + trd_mxl_trc_alloc()
274#endif
275      !
276      IF( lk_mpp    )   CALL mpp_sum( ierr )
277      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'top_alloc : unable to allocate standard ocean arrays' )
278      !
279   END SUBROUTINE top_alloc
280
281#else
282   !!----------------------------------------------------------------------
283   !!  Empty module :                                     No passive tracer
284   !!----------------------------------------------------------------------
285CONTAINS
286   SUBROUTINE trc_init                      ! Dummy routine   
287   END SUBROUTINE trc_init
288#endif
289
290   !!======================================================================
291END MODULE trcini
Note: See TracBrowser for help on using the repository browser.