/[MITgcm]/MITgcm/pkg/ptracers/ptracers_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/ptracers/ptracers_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.13 - (hide annotations) (download)
Sun Nov 28 23:50:59 2004 UTC (19 years, 6 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint56a_post
Changes since 1.12: +6 -2 lines
o PTRACERS:
  - rename GCHEM_MONITOR to PTRACERS_MONITOR and call it from MONITOR, so
    that ALL experiments with ptracers enable can be checked. This makes
    GCHEM_MONITOR obsolete.
  - include a runtime parameter PTRACERS_monitorFreq that defaults to
    monitorFreq
  - set default PTRACERS_write_mdsio to false if PTRACERS_write_mnc is true

1 mlosch 1.13 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_readparms.F,v 1.12 2004/10/28 00:32:21 jmc Exp $
2 dimitri 1.2 C $Name: $
3 adcroft 1.1
4     #include "PTRACERS_OPTIONS.h"
5    
6 edhill 1.6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 adcroft 1.1 CBOP
8 edhill 1.6 C !ROUTINE: PTRACERS_READPARMS
9    
10     C !INTERFACE:
11 adcroft 1.1 SUBROUTINE PTRACERS_READPARMS( myThid )
12 edhill 1.6
13     C !DESCRIPTION:
14 adcroft 1.1 C Initialize PTRACERS parameters, read in data.ptracers
15    
16 edhill 1.6 C !USES:
17 adcroft 1.1 IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20 jmc 1.5 #include "PTRACERS_SIZE.h"
21 adcroft 1.1 #include "PTRACERS.h"
22 dimitri 1.2 #include "PARAMS.h"
23 edhill 1.7
24 edhill 1.6 C !INPUT PARAMETERS:
25 adcroft 1.1 INTEGER myThid
26 edhill 1.6 CEOP
27 adcroft 1.1
28     #ifdef ALLOW_PTRACERS
29    
30 edhill 1.6 C !LOCAL VARIABLES:
31 jmc 1.11 C k,iTracer :: loop indices
32 edhill 1.6 C iUnit :: unit number for I/O
33     C msgBuf :: message buffer
34 jmc 1.11 INTEGER k, iTracer
35 adcroft 1.1 INTEGER iUnit
36 edhill 1.6 INTEGER ic
37 adcroft 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
38 jmc 1.11 _RL PTRACERS_diffKr(PTRACERS_num)
39 adcroft 1.1
40 jmc 1.5 C PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
41     C are written to post-processing files.
42     NAMELIST /PTRACERS_PARM01/
43 edhill 1.6 & PTRACERS_taveFreq,
44 mlosch 1.13 & PTRACERS_monitorFreq,
45 edhill 1.6 & PTRACERS_advScheme,
46     & PTRACERS_diffKh,
47     & PTRACERS_diffK4,
48     & PTRACERS_diffKr,
49 jmc 1.11 & PTRACERS_diffKrNr,
50 edhill 1.6 & PTRACERS_useGMRedi,
51     & PTRACERS_useKPP,
52     & PTRACERS_numInUse,
53     & PTRACERS_initialFile,
54     & PTRACERS_useRecords,
55     & PTRACERS_names,
56     & PTRACERS_long_names,
57     & PTRACERS_units,
58 edhill 1.7 & PTRACERS_read_mnc,
59     & PTRACERS_write_mnc
60 jmc 1.5
61 edhill 1.6 C This routine has been called by the main model so we set our
62     C internal flag to indicate we are in business
63 adcroft 1.1 PTRACERSisON=.TRUE.
64    
65 edhill 1.6 C Set defaults values for parameters in PTRACERS.h
66 mlosch 1.13 PTRACERS_taveFreq = taveFreq
67     PTRACERS_monitorFreq = monitorFreq
68 adcroft 1.1 PTRACERS_numInUse=-1
69     DO iTracer=1,PTRACERS_num
70 edhill 1.6 PTRACERS_advScheme(iTracer)=saltAdvScheme
71     PTRACERS_diffKh(iTracer)=diffKhS
72     PTRACERS_diffK4(iTracer)=diffK4S
73 jmc 1.11 PTRACERS_diffKr(iTracer)=UNSET_RL
74     DO k=1,Nr
75     PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
76     ENDDO
77 edhill 1.6 PTRACERS_useGMRedi(iTracer)=useGMRedi
78     PTRACERS_useKPP(iTracer)=useKPP
79     PTRACERS_initialFile(iTracer)=' '
80     DO ic = 1,MAX_LEN_FNAM
81     PTRACERS_names(iTracer)(ic:ic) = ' '
82     PTRACERS_long_names(iTracer)(ic:ic) = ' '
83     PTRACERS_units(iTracer)(ic:ic) = ' '
84     ENDDO
85 adcroft 1.1 ENDDO
86 edhill 1.7 PTRACERS_useRecords = .FALSE.
87     PTRACERS_read_mdsio = .TRUE.
88     PTRACERS_read_mnc = .FALSE.
89     PTRACERS_write_mdsio = .TRUE.
90     PTRACERS_write_mnc = .FALSE.
91 adcroft 1.1
92 edhill 1.6 C Open and read the data.ptracers file
93 adcroft 1.1 _BEGIN_MASTER(myThid)
94     WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
95     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
96     & SQUEEZE_RIGHT , 1)
97     CALL OPEN_COPY_DATA_FILE(
98     I 'data.ptracers', 'PTRACERS_READPARMS',
99     O iUnit,
100     I myThid )
101     READ(UNIT=iUnit,NML=PTRACERS_PARM01)
102     WRITE(msgBuf,'(A)')
103     & ' PTRACERS_READPARMS: finished reading data.ptracers'
104     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
105     & SQUEEZE_RIGHT , 1)
106    
107 edhill 1.6 C Close the open data file
108 adcroft 1.1 CLOSE(iUnit)
109     _END_MASTER(myThid)
110    
111 edhill 1.6 C Everyone else must wait for the parameters to be loaded
112 adcroft 1.1 _BARRIER
113    
114 edhill 1.6 C Now set-up any remaining parameters that result from the input
115     C parameters
116 adcroft 1.1
117 edhill 1.6 C If PTRACERS_numInUse was not set in data.ptracers then we can
118     C assume that all PTRACERS fields will be in use
119 adcroft 1.1 IF (PTRACERS_numInUse.LT.0) THEN
120 edhill 1.6 PTRACERS_numInUse=PTRACERS_num
121 adcroft 1.1 ENDIF
122 edhill 1.6 C Check we are not trying to use more tracers than allowed
123 adcroft 1.1 IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
124 edhill 1.6 WRITE(msgBuf,'(A,I2,A,I2,A)')
125     & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
126     & ' tracers at run time when only ',PTRACERS_num,
127     & ' were specified at compile time. Naughty! '
128     CALL PRINT_ERROR(msgBuf, 1)
129     STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
130 adcroft 1.1 ENDIF
131 edhill 1.6 C Check that enough parameters were specified
132 adcroft 1.1 DO iTracer=1,PTRACERS_numInUse
133 edhill 1.6 IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
134     WRITE(msgBuf,'(A,A,I2)')
135     & ' PTRACERS_READPARMS: ',
136     & 'No advect. scheme specified for tracer #',
137     & iTracer
138     CALL PRINT_ERROR(msgBuf, 1)
139     STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
140     ENDIF
141 adcroft 1.1 ENDDO
142 jmc 1.11 DO iTracer=1,PTRACERS_numInUse
143     PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)
144     & .AND.useGMRedi
145     PTRACERS_useKPP(iTracer) = PTRACERS_useKPP(iTracer)
146     & .AND.useKPP
147     IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
148     DO k=1,Nr
149     PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
150     ENDDO
151     ENDIF
152     ENDDO
153 adcroft 1.1
154 edhill 1.6 #ifdef ALLOW_MNC
155     IF (useMNC) THEN
156 edhill 1.7 C Set the default I/O Types
157     IF (PTRACERS_read_mnc) PTRACERS_read_mdsio = .FALSE.
158 edhill 1.10 IF ( (.NOT. outputTypesInclusive)
159 edhill 1.7 & .AND. PTRACERS_write_mnc ) pickup_write_mdsio = .FALSE.
160 mlosch 1.13 IF ( (.NOT. outputTypesInclusive)
161     & .AND. PTRACERS_write_mnc ) PTRACERS_write_mdsio = .FALSE.
162 edhill 1.7
163     C Initialize the MNC variable types for PTRACERS
164 edhill 1.6 CALL PTRACERS_MNC_INIT( myThid )
165     ENDIF
166     #endif /* ALLOW_MNC */
167    
168 jmc 1.12 C-- Print a summary of pTracer parameter values:
169     iUnit = standardMessageUnit
170     WRITE(msgBuf,'(A)') '// ==================================='
171     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
172     WRITE(msgBuf,'(A)') '// PTRACERS parameters '
173     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
174     WRITE(msgBuf,'(A)') '// ==================================='
175     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
176     CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
177     & 'PTRACERS_numInUse =',
178     & ' /* number of tracers */')
179     CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,
180     & 'PTRACERS_taveFreq =',
181     & ' /* Frequency^-1 for time-Aver. output (s) */')
182     CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
183     & 'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
184     CALL WRITE_0D_L( PTRACERS_write_mdsio, INDEX_NONE,
185     & 'PTRACERS_write_mdsio =', ' /* write mdsio files */')
186     CALL WRITE_0D_L( PTRACERS_write_mnc, INDEX_NONE,
187     & 'PTRACERS_write_mnc =', ' /* write mnc files */')
188    
189     DO iTracer=1,PTRACERS_numInUse
190     WRITE(msgBuf,'(A)') ' -----------------------------------'
191     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
192     WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
193     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
194     CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
195     & 'PTRACERS_advScheme =', ' /* Advection Scheme */')
196     CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,
197     & 'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
198     CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,
199     & 'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
200     CALL WRITE_1D_R8( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
201     & 'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
202     CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
203     & 'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
204     CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
205     & 'PTRACERS_useKPP =', ' /* apply KPP scheme */')
206    
207     ENDDO
208     WRITE(msgBuf,'(A)') ' -----------------------------------'
209     CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
210 adcroft 1.1 #endif /* ALLOW_PTRACERS */
211    
212     RETURN
213     END
214 edhill 1.6

  ViewVC Help
Powered by ViewVC 1.1.22