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 @ 186

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

CL + CE : NEMO TRC_SRC start

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.6 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!!!  OPA8, LODY! (15/11/96)
64!!!---------------------------------------------------------------------
65
66! 1. initialization
67! -----------------
68
69! 0. Parameter
70
71      istop = 0
72
73! 1. OPEN specifier
74
75      clold='OLD'
76      clnew='NEW'
77      clunk='UNKNOWN'
78      clfor='FORMATTED'
79      clunf='UNFORMATTED'
80      clseq='SEQUENTIAL'
81      cldir='DIRECT'
82
83! 2. SEQUENTIAL value
84
85      ilseq=1
86
87      ilu=0
88
89! computation of the record length for direct access FILE
90! this length depend of 512 for the t3d machine
91
92      ibloc=512
93      ildta=ibloc*((jpidta*jpjdta)/ibloc+1)*jpbyt
94      ilglo=ibloc*((jpiglo*jpjglo)/ibloc+1)*jpbyt
95
96! 3. LOGICAL UNIT initialization for specifi! files for passive tracer
97
98!     nutwrs : OUTPUT for passive tracer restart UNIT (always used)
99!     nutrst : restart FILE  INPUT  UNIT (lrsttr=.TRUE.)
100!     nutini(jptra) : UNIT for initial FILE for tracer
101
102      nutwrs = 72
103      nutrst = 73
104
105! 4. FILE for restart (output)
106
107#if defined key_mpp || defined key_fdir
108      clname='trc.restart.output'
109      CALL ctlopn(nutwrs,clname,clunk,clunf,cldir,
110     $    ilglo,ilu,iused,numout,lwp,1)
111#endif
112
113! 5. restart for passive tracer (input)
114! -----------------------------
115
116      IF(lwp) THEN
117          WRITE(numout,*) ' '
118          WRITE(numout,*) ' *** PASSIVE TRACER MODEL OPTIONS'
119          WRITE(numout,*) ' *** CONTROL'
120          WRITE(numout,*) ' '
121      ENDIF
122
123      IF(lwp) THEN
124          WRITE(numout,*) ' '
125          WRITE(numout,*) ' *** restart option for passive tracer'
126          WRITE(numout,*) ' '
127      ENDIF
128
129      IF(lrsttr) THEN
130          IF(lwp) THEN
131              WRITE(numout,*) ' READ a restart FILE for passive tracer'
132              WRITE(numout,*) ' '
133          ENDIF
134
135!         NetCDF FORMAT, see in the dtrlec routine
136          trestart='initial.trc.nc'
137
138#if defined key_mpp || defined key_fdir
139          clname='trc.restart'
140          CALL ctlopn(nutrst,clname,clunk,clunf,cldir,
141     $        ilglo,ilu,iused,numout,lwp,1)
142#endif
143
144          IF(lwp) THEN
145              IF(nrsttr.eq.0) THEN
146                  WRITE(numout,*) ' nrsttr = 0 we dont control the date'
147                  WRITE(numout,*) ' '
148              ELSE IF(nrsttr.eq.1) THEN
149                  WRITE(numout,*) ' nrsttr = 1 we control the date'
150                  WRITE(numout,*) ' '
151              ELSE
152                  WRITE(numout,*) '  ===>>>> nrsttr is not egal 0 or 1'
153                  WRITE(numout,*) ' =======                     ======'
154                  WRITE(numout,*) ' we dont control the date'
155                  WRITE(numout,*) ' '
156              ENDIF
157          ENDIF
158      ELSE
159          IF(lwp) THEN
160              WRITE(numout,*) ' no restart FILE'
161              WRITE(numout,*) ' '
162              WRITE(numout,*) ' the PARAMETER nrsttr is not used'
163              WRITE(numout,*) ' '
164              IF(nrsttr.eq.1) THEN
165                  WRITE(numout,*) ' nrsttr = 1 '
166                  WRITE(numout,*) ' '
167                  WRITE(numout,*) ' ===>>>> perhaps it is a mistake'
168                  WRITE(numout,*) ' ======= '
169                  WRITE(numout,*) ' '
170              ENDIF
171          ENDIF
172
173! 6. OPEN FILES for initial tracer value
174
175          DO jn=1,jptra
176
177! OPEN input FILE only IF lutini(jn) is true
178
179            IF (lutini(jn)) THEN 
180
181! prepare input FILE name a
182!                       
183                IF (lwp) THEN
184                    WRITE(numout,*)
185     $                  ' READ an initial FILE :',
186     $                  ' for passive tracer number :',jn
187     $                  ,' traceur : ',ctrcnm(jn) 
188                    WRITE(numout,*) ' '
189                END IF
190            END IF
191          END DO   
192      ENDIF
193
194! 7. Don't USE non penetrative convective mixing option
195!     it's not implemented for passive tracer
196
197#if defined key_convnpc
198      IF (lwp) THEN
199          WRITE (numout,*) ' ===>>>> : w a r n i n g '
200          WRITE (numout,*) ' =======   ============= '
201          WRITE (numout,*) ' STOP, this sheme is not implemented'
202          WRITE (numout,*) ' in passive tracer model:'
203          WRITE (numout,*) ' non penetrative convect. mixing scheme'
204      ENDIF
205      istop = istop + 1
206#endif
207
208
209! 8. transport scheme option
210! --------------------------
211
212      WRITE(numout,*) '  '
213      WRITE(numout,*) '  '
214      CALL trc_trp_ctl
215      WRITE(numout,*) '  '
216      WRITE(numout,*) '  '
217
218! 9. SMS model
219! ---------------------------------------------
220C
221      IF(lwp) THEN
222          WRITE(numout,*) '  '
223          WRITE(numout,*) ' *** Source/Sink model option'
224          WRITE(numout,*) '  '
225      ENDIF
226
227#    if defined key_trc_npzd && defined key_trc_lobster1
228      IF (lwp) THEN
229          WRITE (numout,*) ' ===>>>> : w a r n i n g '
230          WRITE (numout,*) ' =======   ============= '
231          WRITE (numout,*)
232     $         ' STOP, only one model can be specified '
233      END IF
234      istop = istop + 1
235#    endif
236#    if defined key_trc_npzd && defined key_trc_hamocc3
237      IF (lwp) THEN
238          WRITE (numout,*) ' ===>>>> : w a r n i n g '
239          WRITE (numout,*) ' =======   ============= '
240          WRITE (numout,*)
241     $         ' STOP, only one model can be specified '
242      END IF
243      istop = istop + 1
244#    endif
245#    if defined key_trc_pisces && defined key_trc_lobster1
246      IF (lwp) THEN
247          WRITE (numout,*) ' ===>>>> : w a r n i n g '
248          WRITE (numout,*) ' =======   ============= '
249          WRITE (numout,*)
250     $         ' STOP, only one model can be specified '
251      END IF
252      istop = istop + 1
253#    endif
254#    if defined key_trc_pisces && defined key_trc_npzd
255      IF (lwp) THEN
256          WRITE (numout,*) ' ===>>>> : w a r n i n g '
257          WRITE (numout,*) ' =======   ============= '
258          WRITE (numout,*)
259     $         ' STOP, only one model can be specified '
260      END IF
261      istop = istop + 1
262#    endif
263#    if defined key_trc_pisces && defined key_trc_hamocc3
264      IF (lwp) THEN
265          WRITE (numout,*) ' ===>>>> : w a r n i n g '
266          WRITE (numout,*) ' =======   ============= '
267          WRITE (numout,*)
268     $         ' STOP, only one model can be specified '
269      END IF
270      istop = istop + 1
271#    endif
272#    if defined key_trc_npzd
273#     include "trcctl.npzd.h" 
274#    elif defined key_trc_lobster1
275#     include "trcctl.lobster1.h"
276#    elif defined key_trc_pisces
277#     include "trcctl.pisces.h"
278#    elif defined key_trc_hamocc3
279#        if defined key_trc_p3zd
280#     include "trcctl.p3zd.h"
281#        else
282#     include "trcctl.hamocc3.h"
283#        endif
284#    else
285      IF (lwp) THEN
286          WRITE (numout,*) ' No Source/Sink model '
287          WRITE (numout,*) ' '
288      END IF 
289#    endif
290
291! E r r o r  control
292! ------------------
293      IF ( istop .GT. 0  ) THEN
294          IF(lwp)WRITE(numout,*)
295          IF(lwp)WRITE(numout,*) istop,' E R R O R found : we stop'
296          IF(lwp)WRITE(numout,*) '**************************'
297          IF(lwp)WRITE(numout,*)
298          STOP 'trcctl'
299      ENDIF
300
301#else
302
303! no passive tracers
304
305#endif
306
307      RETURN
308      END SUBROUTINE trcctl
Note: See TracBrowser for help on using the repository browser.