1 | MODULE trc |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trc *** |
---|
4 | !! Passive tracers : module for tracers defined |
---|
5 | !!====================================================================== |
---|
6 | !! History : OPA ! 1996-01 (M. Levy) Original code |
---|
7 | !! - ! 2000-04 (O. Aumont, M.A. Foujols) HAMOCC3 and P3ZD |
---|
8 | !! NEMO 1.0 ! 2004-03 (C. Ethe) Free form and module |
---|
9 | !!---------------------------------------------------------------------- |
---|
10 | USE par_oce |
---|
11 | USE par_trc |
---|
12 | USE bdy_oce, only: jp_bdy, ln_bdy, nb_bdy, OBC_DATA |
---|
13 | |
---|
14 | IMPLICIT NONE |
---|
15 | PUBLIC |
---|
16 | |
---|
17 | PUBLIC trc_alloc ! called by nemogcm.F90 |
---|
18 | |
---|
19 | ! !!- logical units of passive tracers |
---|
20 | INTEGER, PUBLIC :: numont = -1 !: reference passive tracer namelist output output.namelist.top |
---|
21 | INTEGER, PUBLIC :: numonr = -1 !: reference passive tracer namelist output output.namelist.top |
---|
22 | INTEGER, PUBLIC :: numstr !: tracer statistics |
---|
23 | CHARACTER(:), ALLOCATABLE, PUBLIC :: numnat_ref !: character buffer for reference passive tracer namelist_top_ref |
---|
24 | CHARACTER(:), ALLOCATABLE, PUBLIC :: numnat_cfg !: character buffer for configuration specific passive tracer namelist_top_cfg |
---|
25 | CHARACTER(:), ALLOCATABLE, PUBLIC :: numtrc_ref !: character buffer for reference passive tracer namelist_trc_ref |
---|
26 | CHARACTER(:), ALLOCATABLE, PUBLIC :: numtrc_cfg !: character buffer for configuration specific passive tracer namelist_trc_cfg |
---|
27 | |
---|
28 | !! passive tracers fields (before,now,after) |
---|
29 | !! -------------------------------------------------- |
---|
30 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: trai !: initial total tracer |
---|
31 | REAL(wp), PUBLIC :: areatot !: total volume |
---|
32 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,: ) :: cvol !: volume correction -degrad option- |
---|
33 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:,:) :: tr !: tracer concentration |
---|
34 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,: ) :: sbc_trc_b !: Before sbc fluxes for tracers |
---|
35 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,: ) :: sbc_trc !: Now sbc fluxes for tracers |
---|
36 | |
---|
37 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,: ) :: trc_i !: prescribed tracer concentration in sea ice for SBC |
---|
38 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,: ) :: trc_o !: prescribed tracer concentration in ocean for SBC |
---|
39 | INTEGER , PUBLIC :: nn_ice_tr !: handling of sea ice tracers |
---|
40 | INTEGER , PUBLIC :: nn_ais_tr !: handling of Antarctic Ice Sheet tracers |
---|
41 | |
---|
42 | !! interpolated gradient |
---|
43 | !!-------------------------------------------------- |
---|
44 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: gtru !: hor. gradient at u-points at bottom ocean level |
---|
45 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: gtrv !: hor. gradient at v-points at bottom ocean level |
---|
46 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: gtrui !: hor. gradient at u-points at top ocean level |
---|
47 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: gtrvi !: hor. gradient at v-points at top ocean level |
---|
48 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: qsr_mean !: daily mean qsr |
---|
49 | |
---|
50 | !! passive tracers (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_writetrc !: time step frequency for concentration outputs (namelist) |
---|
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 = 80) , PUBLIC :: cn_trcrst_in !: suffix of pass. tracer restart name (input) |
---|
59 | CHARACTER(len = 256), PUBLIC :: cn_trcrst_indir !: restart input directory |
---|
60 | CHARACTER(len = 80) , PUBLIC :: cn_trcrst_out !: suffix of pass. tracer restart name (output) |
---|
61 | CHARACTER(len = 256), PUBLIC :: cn_trcrst_outdir !: restart output directory |
---|
62 | REAL(wp) , PUBLIC :: rDt_trc !: = 2*rn_Dt except at nit000 (=rn_Dt) if l_1st_euler=.true. |
---|
63 | LOGICAL , PUBLIC :: ln_top_euler !: boolean term for euler integration |
---|
64 | LOGICAL , PUBLIC :: ln_trcdta !: Read inputs data from files |
---|
65 | LOGICAL , PUBLIC :: ln_trcbc !: Enable surface, lateral or open boundaries conditions |
---|
66 | LOGICAL , PUBLIC :: ln_trcais !: Enable Antarctic Ice Sheet nutrient supply |
---|
67 | LOGICAL , PUBLIC :: ln_trcdmp !: internal damping flag |
---|
68 | LOGICAL , PUBLIC :: ln_trcdmp_clo !: internal damping flag on closed seas |
---|
69 | INTEGER , PUBLIC :: nittrc000 !: first time step of passive tracers model |
---|
70 | LOGICAL , PUBLIC :: l_trcdm2dc !: Diurnal cycle for TOP |
---|
71 | |
---|
72 | !! Information for the ice module for tracers |
---|
73 | !! ------------------------------------------ |
---|
74 | TYPE, PUBLIC :: TRC_I_NML !: Ice tracer namelist structure |
---|
75 | REAL(wp) :: trc_ratio ! ice-ocean trc ratio |
---|
76 | REAL(wp) :: trc_prescr ! prescribed ice trc cc |
---|
77 | CHARACTER(len=2) :: ctrc_o ! choice of ocean trc cc |
---|
78 | END TYPE |
---|
79 | ! |
---|
80 | REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: trc_ice_ratio !: ice-ocean tracer ratio |
---|
81 | REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: trc_ice_prescr !: prescribed ice trc cc |
---|
82 | CHARACTER(len=2), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: cn_trc_o !: choice of ocean tracer cc |
---|
83 | |
---|
84 | |
---|
85 | !! information for outputs |
---|
86 | !! -------------------------------------------------- |
---|
87 | TYPE, PUBLIC :: PTRACER !: Passive tracer type |
---|
88 | CHARACTER(len=20) :: clsname ! short name |
---|
89 | CHARACTER(len=80) :: cllname ! long name |
---|
90 | CHARACTER(len=20) :: clunit ! unit |
---|
91 | LOGICAL :: llinit ! read in a file or not |
---|
92 | LOGICAL :: llsbc ! read in a file or not |
---|
93 | LOGICAL :: llcbc ! read in a file or not |
---|
94 | LOGICAL :: llobc ! read in a file or not |
---|
95 | LOGICAL :: llais ! read in a file or not |
---|
96 | END TYPE PTRACER |
---|
97 | ! |
---|
98 | CHARACTER(len=20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ctrcnm !: tracer name |
---|
99 | CHARACTER(len=80), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ctrcln !: trccer field long name |
---|
100 | CHARACTER(len=20), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ctrcun !: tracer unit |
---|
101 | ! |
---|
102 | TYPE, PUBLIC :: DIAG !: Passive trcacer ddditional diagnostic type |
---|
103 | CHARACTER(len=20) :: sname ! short name |
---|
104 | CHARACTER(len=80) :: lname ! long name |
---|
105 | CHARACTER(len=20) :: units ! unit |
---|
106 | END TYPE DIAG |
---|
107 | ! |
---|
108 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: trc3d !: 3D diagnostics for tracers |
---|
109 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) :: trc2d !: 2D diagnostics for tracers |
---|
110 | |
---|
111 | !! information for inputs |
---|
112 | !! -------------------------------------------------- |
---|
113 | LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ln_trc_ini !: Initialisation from data input file |
---|
114 | LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ln_trc_obc !: Use open boundary condition data |
---|
115 | LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ln_trc_sbc !: Use surface boundary condition data |
---|
116 | LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ln_trc_cbc !: Use coastal boundary condition data |
---|
117 | LOGICAL , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: ln_trc_ais !: Use Antarctic Ice Sheet boundary condition data |
---|
118 | LOGICAL , PUBLIC :: ln_rnf_ctl !: remove runoff dilution on tracers |
---|
119 | REAL(wp), PUBLIC :: rn_sbc_time !: Time scaling factor for SBC data (seconds in a day) |
---|
120 | REAL(wp), PUBLIC :: rn_cbc_time !: Time scaling factor for CBC data (seconds in a day) |
---|
121 | LOGICAL , PUBLIC :: lltrcbc !: Applying one of the boundary conditions |
---|
122 | ! |
---|
123 | CHARACTER(len=20), PUBLIC, DIMENSION(jp_bdy) :: cn_trc_dflt ! Default OBC condition for all tracers |
---|
124 | CHARACTER(len=20), PUBLIC, DIMENSION(jp_bdy) :: cn_trc ! Choice of boundary condition for tracers |
---|
125 | INTEGER, PUBLIC, DIMENSION(jp_bdy) :: nn_trcdmp_bdy !: =T Tracer damping |
---|
126 | ! |
---|
127 | ! Vertical axis used in the sediment module |
---|
128 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: profsed |
---|
129 | !$AGRIF_DO_NOT_TREAT |
---|
130 | ! External data structure of BDY for TOP. Available elements: cn_obc, ll_trc, trcnow, dmp |
---|
131 | TYPE(OBC_DATA), PUBLIC, ALLOCATABLE, DIMENSION(:,:), TARGET :: trcdta_bdy !: bdy external data (local process) |
---|
132 | !$AGRIF_END_DO_NOT_TREAT |
---|
133 | ! |
---|
134 | !! Substitutions |
---|
135 | #include "do_loop_substitute.h90" |
---|
136 | !!---------------------------------------------------------------------- |
---|
137 | !! NEMO/TOP 4.0 , NEMO Consortium (2018) |
---|
138 | !! $Id$ |
---|
139 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
140 | !!---------------------------------------------------------------------- |
---|
141 | CONTAINS |
---|
142 | |
---|
143 | INTEGER FUNCTION trc_alloc() |
---|
144 | !!------------------------------------------------------------------- |
---|
145 | !! *** ROUTINE trc_alloc *** |
---|
146 | !!------------------------------------------------------------------- |
---|
147 | USE lib_mpp, ONLY: ctl_stop |
---|
148 | !!------------------------------------------------------------------- |
---|
149 | INTEGER :: ierr(4) |
---|
150 | !!------------------------------------------------------------------- |
---|
151 | ierr(:) = 0 |
---|
152 | ! |
---|
153 | ALLOCATE( tr(jpi,jpj,jpk,jptra,jpt) , & |
---|
154 | & trc_i(jpi,jpj,jptra) , trc_o(jpi,jpj,jptra) , & |
---|
155 | & gtru (jpi,jpj,jptra) , gtrv (jpi,jpj,jptra) , & |
---|
156 | & gtrui(jpi,jpj,jptra) , gtrvi(jpi,jpj,jptra) , & |
---|
157 | & trc_ice_ratio(jptra) , trc_ice_prescr(jptra) , cn_trc_o(jptra) , & |
---|
158 | & sbc_trc_b(jpi,jpj,jptra), sbc_trc(jpi,jpj,jptra) , & |
---|
159 | & cvol(jpi,jpj,jpk) , trai(jptra) , qsr_mean(jpi,jpj) , & |
---|
160 | & ctrcnm(jptra) , ctrcln(jptra) , ctrcun(jptra) , & |
---|
161 | & ln_trc_ini(jptra) , & |
---|
162 | & ln_trc_sbc(jptra) , ln_trc_cbc(jptra) , ln_trc_obc(jptra) , & |
---|
163 | & ln_trc_ais(jptra) , & |
---|
164 | & STAT = ierr(1) ) |
---|
165 | ! |
---|
166 | IF( ln_bdy ) ALLOCATE( trcdta_bdy(jptra, jp_bdy) , STAT = ierr(2) ) |
---|
167 | ! |
---|
168 | IF (jp_dia3d > 0 ) ALLOCATE( trc3d(jpi,jpj,jpk,jp_dia3d), STAT = ierr(3) ) |
---|
169 | ! |
---|
170 | IF (jp_dia2d > 0 ) ALLOCATE( trc2d(jpi,jpj,jpk,jp_dia2d), STAT = ierr(4) ) |
---|
171 | ! |
---|
172 | trc_alloc = MAXVAL( ierr ) |
---|
173 | IF( trc_alloc /= 0 ) CALL ctl_stop( 'STOP', 'trc_alloc: failed to allocate arrays' ) |
---|
174 | ! |
---|
175 | END FUNCTION trc_alloc |
---|
176 | |
---|
177 | !!====================================================================== |
---|
178 | END MODULE trc |
---|