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.
trc.F90 in branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2011/dev_r2802_TOP_substepping/NEMOGCM/NEMO/TOP_SRC/trc.F90 @ 2892

Last change on this file since 2892 was 2892, checked in by kpedwards, 13 years ago

Updates for substepping: include nittrc000 in call to advection routines and added physics variables for averaging.

  • Property svn:keywords set to Id
File size: 14.6 KB
Line 
1MODULE trc
2   !!======================================================================
3   !!                      ***  MODULE  trc  ***
4   !! Passive tracers   :  module for tracers defined
5   !!======================================================================
6   !! History :   OPA  !  1996-01  (M. Levy)  Original code
7   !!              -   !  1999-07  (M. Levy)  for LOBSTER1 or NPZD model
8   !!              -   !  2000-04  (O. Aumont, M.A. Foujols)  HAMOCC3 and P3ZD
9   !!   NEMO      1.0  !  2004-03  (C. Ethe)  Free form and module
10   !!----------------------------------------------------------------------
11#if defined key_top
12   !!----------------------------------------------------------------------
13   !!   'key_top'                                                TOP models
14   !!----------------------------------------------------------------------
15   USE par_oce
16   USE par_trc
17   
18   IMPLICIT NONE
19   PUBLIC
20
21   PUBLIC   trc_alloc   ! called by nemogcm.F90
22
23   !! passive tracers names and units (read in namelist)
24   !! --------------------------------------------------
25   CHARACTER(len=12), PUBLIC, DIMENSION(jptra) ::   ctrcnm     !: tracer name
26   CHARACTER(len=12), PUBLIC, DIMENSION(jptra) ::   ctrcun     !: tracer unit
27   CHARACTER(len=80), PUBLIC, DIMENSION(jptra) ::   ctrcnl     !: tracer long name
28   
29   
30   !! parameters for the control of passive tracers
31   !! --------------------------------------------------
32   INTEGER, PUBLIC                   ::   numnat   !: the number of the passive tracer NAMELIST
33   LOGICAL, PUBLIC, DIMENSION(jptra) ::   lutini   !:  initialisation from FILE or not (NAMELIST)
34   LOGICAL, PUBLIC, DIMENSION(jptra) ::   lutsav   !:  save the tracer or not
35
36   !! passive tracers fields (before,now,after)
37   !! --------------------------------------------------
38   REAL(wp), PUBLIC ::   trai                          !: initial total tracer
39   REAL(wp), PUBLIC ::   areatot                       !: total volume
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:)   ::   cvol   !: volume correction -degrad option-
41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) ::   trn    !: traceur concentration for now time step
42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) ::   tra    !: traceur concentration for next time step
43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) ::   trb    !: traceur concentration for before time step
44
45   !! interpolated gradient
46   !!-------------------------------------------------- 
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   gtru   !: hor. gradient at u-points at bottom ocean level
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   gtrv   !: hor. gradient at v-points at bottom ocean level
49   
50   !! passive tracers restart (input and output)
51   !! ------------------------------------------ 
52   LOGICAL          , PUBLIC ::  ln_rsttr        !: boolean term for restart i/o for passive tracers (namelist)
53   LOGICAL          , PUBLIC ::  lrst_trc        !: logical to control the trc restart write
54   INTEGER          , PUBLIC ::  nn_dttrc        !: frequency of step on passive tracers
55   INTEGER          , PUBLIC ::  nutwrs          !: output FILE for passive tracers restart
56   INTEGER          , PUBLIC ::  nutrst          !: logical unit for restart FILE for passive tracers
57   INTEGER          , PUBLIC ::  nn_rsttr        !: control of the time step ( 0 or 1 ) for pass. tr.
58   CHARACTER(len=50), PUBLIC ::  cn_trcrst_in    !: suffix of pass. tracer restart name (input)
59   CHARACTER(len=50), PUBLIC ::  cn_trcrst_out   !: suffix of pass. tracer restart name (output)
60
61   INTEGER          , PUBLIC ::  nittrc000       !: first time step of passive tracers model
62   
63   !! information for outputs
64   !! --------------------------------------------------
65   INTEGER , PUBLIC ::   nn_writetrc   !: time step frequency for concentration outputs (namelist)
66   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   rdttrc        !: vertical profile of passive tracer time step
67   
68# if defined key_diatrc && ! defined key_iomput
69   !! additional 2D/3D outputs namelist
70   !! --------------------------------------------------
71   INTEGER         , PUBLIC                      ::   nn_writedia   !: frequency of additional arrays outputs(namelist)
72   CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia2d) ::   ctrc2d      !: 2d output field name
73   CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia2d) ::   ctrc2u      !: 2d output field unit   
74   CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia3d) ::   ctrc3d      !: 3d output field name
75   CHARACTER(len= 8), PUBLIC, DIMENSION(jpdia3d) ::   ctrc3u      !: 3d output field unit
76   CHARACTER(len=80), PUBLIC, DIMENSION(jpdia2d) ::   ctrc2l      !: 2d output field long name
77   CHARACTER(len=80), PUBLIC, DIMENSION(jpdia3d) ::   ctrc3l      !: 3d output field long name
78
79   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,  :) ::   trc2d    !:  additional 2d outputs 
80   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trc3d    !:  additional 3d outputs 
81# endif
82
83# if defined key_diabio || defined key_trdmld_trc
84   !                                                              !!*  namtop_XXX namelist *
85   INTEGER , PUBLIC                               ::   nn_writebio   !: time step frequency for biological outputs
86   CHARACTER(len=8 ), PUBLIC, DIMENSION(jpdiabio) ::   ctrbio      !: biological trends name     
87   CHARACTER(len=20), PUBLIC, DIMENSION(jpdiabio) ::   ctrbiu      !: biological trends unit   
88   CHARACTER(len=80), PUBLIC, DIMENSION(jpdiabio) ::   ctrbil      !: biological trends long name
89# endif
90# if defined key_diabio
91   !! Biological trends
92   !! -----------------
93   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   trbio   !: biological trends
94# endif
95
96   
97   !! passive tracers data read and at given time_step
98   !! --------------------------------------------------
99# if defined key_dtatrc
100   INTEGER , PUBLIC, DIMENSION(jptra) ::   numtr   !: logical unit for passive tracers data
101# endif
102
103   !! variables to average over physics over passive tracer sub-steps.
104   !! ----------------------------------------------------------------
105  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  un_tm      !: i-horizontal velocity average     [m/s]
106  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  vn_tm      !: j-horizontal velocity average     [m/s]
107  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  wn_tm      !: k-vertical velocity average       [m/s]
108  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  avt_tm     !: vertical viscosity & diffusivity coeff. at  w-point   [m2/s]
109  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshn_tm !: average ssh for the now step [m]
110  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshb_hold !:hold sshb from the beginning of each sub-stepping[m] 
111  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshu_n_tm !: average ssh for the now step [m]
112  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshu_b_hold !:hold sshb from the beginning of each sub-stepping[m] 
113  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshv_n_tm !: average ssh for the now step [m]
114  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    sshv_b_hold !:hold sshb from the beginning of each sub-stepping[m] 
115#if defined key_ldfslp
116  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   wslpi_tm !: i-direction slope at u-, w-points
117  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   wslpj_tm !: j-direction slope at u-, w-points
118  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   uslp_tm !: j-direction slope at u-, w-points
119  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::   vslp_tm !: j-direction slope at u-, w-points
120#endif
121
122  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:,:) :: tsn_tm      !: t/s average     [m/s]
123  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::     fr_i_tm    !: average ice fraction     [m/s]
124  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::     hmld_tm    !: mixed layer depth average [m]
125  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::     qsr_tm     !: solar radiation average [m]
126  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::     wndm_tm    !: 10m wind average [m]
127  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::     emp_tm     !: freshwater budget: volume flux [Kg/m2/s]
128  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::     emp_b_hold !:hold emp from the beginning of each sub-stepping[m] 
129  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:) ::    emps_tm    !: freshwater budget:concentration/dilution [Kg/m2/s]
130# if defined key_zdfddm
131  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  avs_tm      !: salinity vertical diffusivity coeff. at w-point   [m/s]
132# endif
133#if defined key_traldf_c3d
134   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm   !: ** 3D coefficients ** at T-,U-,V-,W-points
135#elif defined key_traldf_c2d
136   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm   !: ** 2D coefficients ** at T-,U-,V-,W-points
137#elif defined key_traldf_c1d
138   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm   !: ** 1D coefficients ** at T-,U-,V-,W-points
139#else
140   REAL(wp), PUBLIC                                      ::   ahtt_tm, ahtu_tm, ahtv_tm, ahtw_tm   !: ** 0D coefficients ** at T-,U-,V-,W-points
141#endif
142#if defined key_traldf_eiv
143# if defined key_traldf_c3d
144   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aeiu_tm , aeiv_tm , aeiw_tm   !: ** 3D coefficients **
145# elif defined key_traldf_c2d
146   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   aeiu_tm , aeiv_tm , aeiw_tm   !: ** 2D coefficients **
147# elif defined key_traldf_c1d
148   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::   aeiu_tm , aeiv_tm, aeiw_tm   !: ** 1D coefficients **
149# else
150   REAL(wp), PUBLIC                                      ::   aeiu_tm , aeiv_tm , aeiw_tm   !: ** 0D coefficients **
151# endif
152# endif
153
154  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:)  ::   rnf_tm !: river runoff
155  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:)  ::   h_rnf_tm !: depth in metres to the bottom of the relevant grid box
156  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::    avt_temp,un_temp,vn_temp,wn_temp     !: hold current values of avt, un, vn, wn
157#if defined key_ldfslp
158  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::    wslpi_temp,wslpj_temp, uslp_temp, vslp_temp    !: hold current values
159#endif
160  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::    e3t_temp,e3u_temp,e3v_temp,e3w_temp     !: hold current values
161  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshn_temp, sshb_temp, ssha_temp, rnf_temp,h_rnf_temp
162  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshu_n_temp, sshu_b_temp, sshu_a_temp
163  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshf_n_temp, sshf_b_temp, sshf_a_temp
164  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       sshv_n_temp, sshv_b_temp, sshv_a_temp
165  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       hu_temp, hv_temp, hur_temp, hvr_temp
166  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:)::     hdivn_temp, rotn_temp
167  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:)::     hdivb_temp, rotb_temp
168  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::  tsn_temp
169  REAL(wp), PUBLIC,ALLOCATABLE, SAVE, DIMENSION(:,:)::       hmld_temp, qsr_temp, emp_temp, emps_temp,fr_i_temp,wndm_temp,emp_b_temp
170# if defined key_zdfddm
171  REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION (:,:,:) ::  avs_temp      !: salinity vertical diffusivity coeff. at w-point   [m/s]
172# endif
173#if defined key_traldf_c3d
174   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp   !: ** 3D coefficients ** at T-,U-,V-,W-points
175#elif defined key_traldf_c2d
176   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp   !: ** 2D coefficients ** at T-,U-,V-,W-points
177#elif defined key_traldf_c1d
178   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::  ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp   !: ** 1D coefficients ** at T-,U-,V-,W-points
179#else
180   REAL(wp), PUBLIC                                      ::  ahtt_temp, ahtu_temp, ahtv_temp, ahtw_temp   !: ** 0D coefficients ** at T-,U-,V-,W-points
181#endif
182#if defined key_traldf_eiv
183# if defined key_traldf_c3d
184   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  aeiu_temp , aeiv_temp , aeiw_temp   !: ** 3D coefficients **
185# elif defined key_traldf_c2d
186   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::  aeiu_temp , aeiv_temp , aeiw_temp   !: ** 2D coefficients **
187# elif defined key_traldf_c1d
188   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     ::  aeiu_temp , aeiv_temp, aeiw_temp   !: ** 1D coefficients **
189# else
190   REAL(wp), PUBLIC                                      ::  aeiu_temp , aeiv_temp , aeiw_temp   !: ** 0D coefficients **
191# endif
192# endif
193
194   !!----------------------------------------------------------------------
195   !! NEMO/TOP 3.3.1 , NEMO Consortium (2010)
196   !! $Id$
197   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
198   !!----------------------------------------------------------------------
199CONTAINS
200
201   INTEGER FUNCTION trc_alloc()
202      !!-------------------------------------------------------------------
203      !!                    *** ROUTINE trc_alloc ***
204      !!-------------------------------------------------------------------
205      USE lib_mpp, ONLY: ctl_warn
206      !!-------------------------------------------------------------------
207      !
208      ALLOCATE( cvol(jpi,jpj,jpk      ) ,                           &
209         &      trn (jpi,jpj,jpk,jptra) ,                           &
210         &      tra (jpi,jpj,jpk,jptra) ,                           &
211         &      trb (jpi,jpj,jpk,jptra) ,                           &
212         &      gtru(jpi,jpj    ,jptra) , gtrv(jpi,jpj,jptra) ,     &
213# if defined key_diatrc && ! defined key_iomput
214         &      trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d), &
215# endif
216# if defined key_diabio
217         &      trbio(jpi,jpj,jpk,jpdiabio),                        &
218#endif
219               rdttrc(jpk) ,  STAT=trc_alloc )     
220
221      IF( trc_alloc /= 0 )   CALL ctl_warn('trc_alloc: failed to allocate arrays')
222      !
223   END FUNCTION trc_alloc
224
225#else
226   !!----------------------------------------------------------------------
227   !!  Empty module :                                     No passive tracer
228   !!----------------------------------------------------------------------
229#endif
230
231   !!======================================================================
232END MODULE trc
Note: See TracBrowser for help on using the repository browser.