1 | MODULE trcini |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trcini *** |
---|
4 | !! TOP : Manage the passive tracer initialization |
---|
5 | !!====================================================================== |
---|
6 | !! History : - ! 1991-03 () original code |
---|
7 | !! 1.0 ! 2005-03 (O. Aumont, A. El Moussaoui) F90 |
---|
8 | !! - ! 2005-10 (C. Ethe) print control |
---|
9 | !! 2.0 ! 2005-10 (C. Ethe, G. Madec) revised architecture |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | #if defined key_top |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! 'key_top' TOP models |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | !! trc_init : Initialization for passive tracer |
---|
17 | !!---------------------------------------------------------------------- |
---|
18 | USE oce_trc |
---|
19 | USE trc |
---|
20 | USE trcrst |
---|
21 | USE trcnam ! Namelist read |
---|
22 | USE trcini_cfc ! CFC initialisation |
---|
23 | USE trcini_lobster ! LOBSTER initialisation |
---|
24 | USE trcini_pisces ! PISCES initialisation |
---|
25 | USE trcini_c14b ! C14 bomb initialisation |
---|
26 | USE trcini_my_trc ! MY_TRC initialisation |
---|
27 | USE trcdta |
---|
28 | #if defined key_offline |
---|
29 | USE daymod |
---|
30 | #endif |
---|
31 | USE zpshde ! partial step: hor. derivative (zps_hde routine) |
---|
32 | USE in_out_manager ! I/O manager |
---|
33 | USE prtctl_trc ! Print control passive tracers (prt_ctl_trc_init routine) |
---|
34 | USE lib_mpp ! distributed memory computing library |
---|
35 | |
---|
36 | IMPLICIT NONE |
---|
37 | PRIVATE |
---|
38 | |
---|
39 | PUBLIC trc_init ! called by opa |
---|
40 | |
---|
41 | !! * Substitutions |
---|
42 | # include "domzgr_substitute.h90" |
---|
43 | |
---|
44 | CONTAINS |
---|
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 ! dummy loop indices |
---|
59 | CHARACTER (len=25) :: charout |
---|
60 | |
---|
61 | !!--------------------------------------------------------------------- |
---|
62 | |
---|
63 | IF(lwp) WRITE(numout,*) |
---|
64 | IF(lwp) WRITE(numout,*) 'trc_init : initial set up of the passive tracers' |
---|
65 | IF(lwp) WRITE(numout,*) '~~~~~~~' |
---|
66 | |
---|
67 | ! ! masked grid volume |
---|
68 | DO jk = 1, jpk |
---|
69 | cvol(:,:,jk) = e1t(:,:) * e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk) * tmask_i(:,:) |
---|
70 | END DO |
---|
71 | |
---|
72 | ! total volume of the ocean |
---|
73 | #if ! defined key_degrad |
---|
74 | areatot = SUM( cvol(:,:,:) ) |
---|
75 | #else |
---|
76 | areatot = SUM( cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol |
---|
77 | #endif |
---|
78 | IF( lk_mpp ) CALL mpp_sum( areatot ) ! sum over the global domain |
---|
79 | |
---|
80 | CALL trc_nam ! read passive tracers namelists |
---|
81 | |
---|
82 | ! restart for passive tracer (input) |
---|
83 | IF( ln_rsttr ) THEN |
---|
84 | IF(lwp) WRITE(numout,*) ' read a restart file for passive tracer : ', cn_trcrst_in |
---|
85 | IF(lwp) WRITE(numout,*) ' ' |
---|
86 | ELSE |
---|
87 | IF(lwp) WRITE(numout,*) |
---|
88 | DO jn = 1, jptra |
---|
89 | IF( lwp .AND. lutini(jn) ) & ! open input FILE only IF lutini(jn) is true |
---|
90 | & WRITE(numout,*) ' read an initial file for passive tracer number :', jn, ' traceur : ', ctrcnm(jn) |
---|
91 | END DO |
---|
92 | ENDIF |
---|
93 | |
---|
94 | IF( lk_lobster ) THEN ; CALL trc_ini_lobster ! LOBSTER bio-model |
---|
95 | ELSE ; IF(lwp) WRITE(numout,*) ' LOBSTER not used' |
---|
96 | ENDIF |
---|
97 | |
---|
98 | IF( lk_pisces ) THEN ; CALL trc_ini_pisces ! PISCES bio-model |
---|
99 | ELSE ; IF(lwp) WRITE(numout,*) ' PISCES not used' |
---|
100 | ENDIF |
---|
101 | |
---|
102 | IF( lk_cfc ) THEN ; CALL trc_ini_cfc ! CFC tracers |
---|
103 | ELSE ; IF(lwp) WRITE(numout,*) ' CFC not used' |
---|
104 | ENDIF |
---|
105 | |
---|
106 | IF( lk_c14b ) THEN ; CALL trc_ini_c14b ! C14 bomb tracer |
---|
107 | ELSE ; IF(lwp) WRITE(numout,*) ' C14 not used' |
---|
108 | ENDIF |
---|
109 | |
---|
110 | IF( lk_my_trc ) THEN ; CALL trc_ini_my_trc ! MY_TRC tracers |
---|
111 | ELSE ; IF(lwp) WRITE(numout,*) ' MY_TRC not used' |
---|
112 | ENDIF |
---|
113 | |
---|
114 | IF( .NOT. ln_rsttr ) THEN |
---|
115 | #if defined key_offline |
---|
116 | CALL day_init ! calendar |
---|
117 | #endif |
---|
118 | # if defined key_dtatrc |
---|
119 | ! Initialization of tracer from a file that may also be used for damping |
---|
120 | CALL trc_dta( nit000 ) |
---|
121 | DO jn = 1, jptra |
---|
122 | IF( lutini(jn) ) trn(:,:,:,jn) = trdta(:,:,:,jn) * tmask(:,:,:) ! initialisation from file if required |
---|
123 | END DO |
---|
124 | # endif |
---|
125 | trb(:,:,:,:) = trn(:,:,:,:) |
---|
126 | ELSE |
---|
127 | ! |
---|
128 | CALL trc_rst_read ! restart from a file |
---|
129 | ! |
---|
130 | ENDIF |
---|
131 | |
---|
132 | tra(:,:,:,:) = 0. |
---|
133 | |
---|
134 | IF( ln_zps .AND. .NOT. lk_trc_c1d ) & ! Partial steps: before horizontal gradient of passive |
---|
135 | & CALL zps_hde( nit000, jptra, trn, gtru, gtrv ) ! tracers at the bottom ocean level |
---|
136 | |
---|
137 | |
---|
138 | ! ! Computation content of all tracers |
---|
139 | trai = 0.e0 |
---|
140 | DO jn = 1, jptra |
---|
141 | #if ! defined key_degrad |
---|
142 | trai = trai + SUM( trn(:,:,:,jn) * cvol(:,:,:) ) |
---|
143 | #else |
---|
144 | trai = trai + SUM( trn(:,:,:,jn) * cvol(:,:,:) * facvol(:,:,:) ) ! degrad option: reduction by facvol |
---|
145 | #endif |
---|
146 | END DO |
---|
147 | IF( lk_mpp ) CALL mpp_sum( trai ) ! sum over the global domain |
---|
148 | |
---|
149 | |
---|
150 | ! ! control print |
---|
151 | IF(lwp) WRITE(numout,*) |
---|
152 | IF(lwp) WRITE(numout,*) |
---|
153 | IF(lwp) WRITE(numout,*) ' *** Total number of passive tracer jptra = ', jptra |
---|
154 | IF(lwp) WRITE(numout,*) ' *** Total volume of ocean = ', areatot |
---|
155 | IF(lwp) WRITE(numout,*) ' *** Total inital content of all tracers = ', trai |
---|
156 | IF(lwp) WRITE(numout,*) |
---|
157 | |
---|
158 | IF( ln_ctl ) CALL prt_ctl_trc_init ! control print |
---|
159 | ! |
---|
160 | |
---|
161 | IF(ln_ctl) THEN ! print mean trends (used for debugging) |
---|
162 | WRITE(charout, FMT="('ini ')") |
---|
163 | CALL prt_ctl_trc_info( charout ) |
---|
164 | CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm ) |
---|
165 | ENDIF |
---|
166 | |
---|
167 | END SUBROUTINE trc_init |
---|
168 | |
---|
169 | #else |
---|
170 | !!---------------------------------------------------------------------- |
---|
171 | !! Empty module : No passive tracer |
---|
172 | !!---------------------------------------------------------------------- |
---|
173 | CONTAINS |
---|
174 | SUBROUTINE trc_init ! Dummy routine |
---|
175 | END SUBROUTINE trc_init |
---|
176 | #endif |
---|
177 | |
---|
178 | !!---------------------------------------------------------------------- |
---|
179 | !! NEMO/TOP 3.3 , LOCEAN-IPSL (2010) |
---|
180 | !! $Id$ |
---|
181 | !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) |
---|
182 | !!====================================================================== |
---|
183 | END MODULE trcini |
---|