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.
trcctl.F in trunk/NEMO/TOP_SRC – NEMO

source: trunk/NEMO/TOP_SRC/trcctl.F @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.7 KB
Line 
1      SUBROUTINE trcctl
2!!
3!!
4!!                       ROUTINE trcctl
5!!                     ******************
6!!
7!!  PURPOSE :
8!!  ---------
9!!     only for passive tracer
10!!     control the cpp options for the run and IF files are availables
11!!     control also consistancy between options and namelist values
12!!
13!!   METHOD :
14!!   -------
15!!      we use IF/ENDIF inside #IF defined option-cpp
16!!      c a u t i o n : FILE name must not exceed 21 characters
17!!      -------------
18!!
19!!   INPUT :                      no
20!!   -----
21!!
22!!   OUTPUT :                     no
23!!   ------
24!!
25!!   WORKSPACE :
26!!   ---------
27!!      local
28!!           clold,clnew,clfor,clunf,clseq,cldir,clname,
29!!           ildta,ilglo,ibloc,ilseq
30!!
31!!   EXTERNAL :
32!!   --------
33!!
34!!   MODIFICATIONS:
35!!   --------------
36!!      original :
37!!                 04/00 (O. Aumont, M.A. Foujols) HAMOCC3 and P3ZD
38!!      additions : 00/05 (A. Estublier) TVD Limiter Scheme
39!!      additions : 00/06 (A. Estublier) MUSCL Scheme
40!!      additions : 00/11 (MA Foujols, E Kestenare) Lateral diffusion option
41!!      additions : 00/12  ( E Kestenare): improve controls of defined keys
42!!
43!!----------------------------------------------------------------------
44!! parameters and commons
45!! ======================
46!!
47      USE oce_trc
48      USE trc
49      USE sms
50      USE trctrp_ctl
51      IMPLICIT NONE
52!!
53!!----------------------------------------------------------------------
54!! local declarations
55!! ==================
56
57#if defined key_passivetrc
58      CHARACTER*32 clname,clold,clfor,clseq,clnew,cldir,clunf,clunk
59      INTEGER iused(1,100),ilu
60      INTEGER ildta,ilglo,ibloc,ilseq,istop
61      INTEGER jn
62!!!---------------------------------------------------------------------
63!!  TOP 1.0 , LOCEAN-IPSL (2005)
64!! $Header$
65!! This software is governed by CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
66!!!---------------------------------------------------------------------
67
68! 1. initialization
69! -----------------
70
71! 0. Parameter
72
73      istop = 0
74
75! 1. OPEN specifier
76
77      clold='OLD'
78      clnew='NEW'
79      clunk='UNKNOWN'
80      clfor='FORMATTED'
81      clunf='UNFORMATTED'
82      clseq='SEQUENTIAL'
83      cldir='DIRECT'
84
85! 2. SEQUENTIAL value
86
87      ilseq=1
88
89      ilu=0
90
91! computation of the record length for direct access FILE
92! this length depend of 512 for the t3d machine
93
94      ibloc=512
95      ildta=ibloc*((jpidta*jpjdta)/ibloc+1)*jpbyt
96      ilglo=ibloc*((jpiglo*jpjglo)/ibloc+1)*jpbyt
97
98! 3. LOGICAL UNIT initialization for specifi! files for passive tracer
99
100!     nutwrs : OUTPUT for passive tracer restart UNIT (always used)
101!     nutrst : restart FILE  INPUT  UNIT (lrsttr=.TRUE.)
102!     nutini(jptra) : UNIT for initial FILE for tracer
103
104      nutwrs = 72
105      nutrst = 73
106
107! 4. FILE for restart (output)
108
109#if defined key_mpp || defined key_fdir
110      clname='trc.restart.output'
111      CALL ctlopn(nutwrs,clname,clunk,clunf,cldir,
112     $    ilglo,ilu,iused,numout,lwp,1)
113#endif
114
115! 5. restart for passive tracer (input)
116! -----------------------------
117
118      IF(lwp) THEN
119          WRITE(numout,*) ' '
120          WRITE(numout,*) ' *** PASSIVE TRACER MODEL OPTIONS'
121          WRITE(numout,*) ' *** CONTROL'
122          WRITE(numout,*) ' '
123      ENDIF
124
125      IF(lwp) THEN
126          WRITE(numout,*) ' '
127          WRITE(numout,*) ' *** restart option for passive tracer'
128          WRITE(numout,*) ' '
129      ENDIF
130
131      IF(lrsttr) THEN
132          IF(lwp) THEN
133              WRITE(numout,*) ' READ a restart FILE for passive tracer'
134              WRITE(numout,*) ' '
135          ENDIF
136
137!         NetCDF FORMAT, see in the dtrlec routine
138          trestart='initial.trc.nc'
139
140#if defined key_mpp || defined key_fdir
141          clname='trc.restart'
142          CALL ctlopn(nutrst,clname,clunk,clunf,cldir,
143     $        ilglo,ilu,iused,numout,lwp,1)
144#endif
145
146          IF(lwp) THEN
147              IF(nrsttr.eq.0) THEN
148                  WRITE(numout,*) ' nrsttr = 0 we dont control the date'
149                  WRITE(numout,*) ' '
150              ELSE IF(nrsttr.eq.1) THEN
151                  WRITE(numout,*) ' nrsttr = 1 we control the date'
152                  WRITE(numout,*) ' '
153              ELSE
154                  WRITE(numout,*) '  ===>>>> nrsttr is not egal 0 or 1'
155                  WRITE(numout,*) ' =======                     ======'
156                  WRITE(numout,*) ' we dont control the date'
157                  WRITE(numout,*) ' '
158              ENDIF
159          ENDIF
160      ELSE
161          IF(lwp) THEN
162              WRITE(numout,*) ' no restart FILE'
163              WRITE(numout,*) ' '
164              WRITE(numout,*) ' the PARAMETER nrsttr is not used'
165              WRITE(numout,*) ' '
166              IF(nrsttr.eq.1) THEN
167                  WRITE(numout,*) ' nrsttr = 1 '
168                  WRITE(numout,*) ' '
169                  WRITE(numout,*) ' ===>>>> perhaps it is a mistake'
170                  WRITE(numout,*) ' ======= '
171                  WRITE(numout,*) ' '
172              ENDIF
173          ENDIF
174
175! 6. OPEN FILES for initial tracer value
176
177          DO jn=1,jptra
178
179! OPEN input FILE only IF lutini(jn) is true
180
181            IF (lutini(jn)) THEN 
182
183! prepare input FILE name a
184!                       
185                IF (lwp) THEN
186                    WRITE(numout,*)
187     $                  ' READ an initial FILE :',
188     $                  ' for passive tracer number :',jn
189     $                  ,' traceur : ',ctrcnm(jn) 
190                    WRITE(numout,*) ' '
191                END IF
192            END IF
193          END DO   
194      ENDIF
195
196! 7. Don't USE non penetrative convective mixing option
197!     it's not implemented for passive tracer
198
199#if defined key_convnpc
200      IF (lwp) THEN
201          WRITE (numout,*) ' ===>>>> : w a r n i n g '
202          WRITE (numout,*) ' =======   ============= '
203          WRITE (numout,*) ' STOP, this sheme is not implemented'
204          WRITE (numout,*) ' in passive tracer model:'
205          WRITE (numout,*) ' non penetrative convect. mixing scheme'
206      ENDIF
207      istop = istop + 1
208#endif
209
210
211! 8. transport scheme option
212! --------------------------
213
214      WRITE(numout,*) '  '
215      WRITE(numout,*) '  '
216      CALL trc_trp_ctl
217      WRITE(numout,*) '  '
218      WRITE(numout,*) '  '
219
220! 9. SMS model
221! ---------------------------------------------
222C
223      IF(lwp) THEN
224          WRITE(numout,*) '  '
225          WRITE(numout,*) ' *** Source/Sink model option'
226          WRITE(numout,*) '  '
227      ENDIF
228
229#    if defined key_trc_npzd && defined key_trc_lobster1
230      IF (lwp) THEN
231          WRITE (numout,*) ' ===>>>> : w a r n i n g '
232          WRITE (numout,*) ' =======   ============= '
233          WRITE (numout,*)
234     $         ' STOP, only one model can be specified '
235      END IF
236      istop = istop + 1
237#    endif
238#    if defined key_trc_npzd && defined key_trc_hamocc3
239      IF (lwp) THEN
240          WRITE (numout,*) ' ===>>>> : w a r n i n g '
241          WRITE (numout,*) ' =======   ============= '
242          WRITE (numout,*)
243     $         ' STOP, only one model can be specified '
244      END IF
245      istop = istop + 1
246#    endif
247#    if defined key_trc_pisces && defined key_trc_lobster1
248      IF (lwp) THEN
249          WRITE (numout,*) ' ===>>>> : w a r n i n g '
250          WRITE (numout,*) ' =======   ============= '
251          WRITE (numout,*)
252     $         ' STOP, only one model can be specified '
253      END IF
254      istop = istop + 1
255#    endif
256#    if defined key_trc_pisces && defined key_trc_npzd
257      IF (lwp) THEN
258          WRITE (numout,*) ' ===>>>> : w a r n i n g '
259          WRITE (numout,*) ' =======   ============= '
260          WRITE (numout,*)
261     $         ' STOP, only one model can be specified '
262      END IF
263      istop = istop + 1
264#    endif
265#    if defined key_trc_pisces && defined key_trc_hamocc3
266      IF (lwp) THEN
267          WRITE (numout,*) ' ===>>>> : w a r n i n g '
268          WRITE (numout,*) ' =======   ============= '
269          WRITE (numout,*)
270     $         ' STOP, only one model can be specified '
271      END IF
272      istop = istop + 1
273#    endif
274#    if defined key_trc_npzd
275#     include "trcctl.npzd.h" 
276#    elif defined key_trc_lobster1
277#     include "trcctl.lobster1.h"
278#    elif defined key_trc_pisces
279#     include "trcctl.pisces.h"
280#    elif defined key_trc_hamocc3
281#        if defined key_trc_p3zd
282#     include "trcctl.p3zd.h"
283#        else
284#     include "trcctl.hamocc3.h"
285#        endif
286#    else
287      IF (lwp) THEN
288          WRITE (numout,*) ' No Source/Sink model '
289          WRITE (numout,*) ' '
290      END IF 
291#    endif
292
293! E r r o r  control
294! ------------------
295      IF ( istop .GT. 0  ) THEN
296          IF(lwp)WRITE(numout,*)
297          IF(lwp)WRITE(numout,*) istop,' E R R O R found : we stop'
298          IF(lwp)WRITE(numout,*) '**************************'
299          IF(lwp)WRITE(numout,*)
300          STOP 'trcctl'
301      ENDIF
302
303#else
304
305! no passive tracers
306
307#endif
308
309      RETURN
310      END SUBROUTINE trcctl
Note: See TracBrowser for help on using the repository browser.