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

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

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


Revision 1.11 - (show annotations) (download)
Fri Oct 22 16:01:20 2004 UTC (19 years, 7 months ago) by jmc
Branch: MAIN
Changes since 1.10: +20 -4 lines
set a vertical profile of vertical diffusivity for each tracer
 (but not yet used !)

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

  ViewVC Help
Powered by ViewVC 1.1.22