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

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

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

revision 1.1 by adcroft, Mon Mar 4 19:01:29 2002 UTC revision 1.22 by mlosch, Tue Oct 11 08:35:36 2005 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "PTRACERS_OPTIONS.h"  #include "PTRACERS_OPTIONS.h"
5    
6    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7  CBOP  CBOP
8  C !ROUTINE: PTRACERS_READPARMS  C     !ROUTINE: PTRACERS_READPARMS
9          
10  C !INTERFACE: ==========================================================  C     !INTERFACE:
11        SUBROUTINE PTRACERS_READPARMS( myThid )        SUBROUTINE PTRACERS_READPARMS( myThid )
12          
13  C !DESCRIPTION:  C     !DESCRIPTION:
14  C     Initialize PTRACERS parameters, read in data.ptracers  C     Initialize PTRACERS parameters, read in data.ptracers
15    
16  C !USES: ===============================================================  C     !USES:
17        IMPLICIT NONE        IMPLICIT NONE
18  #include "SIZE.h"  #include "SIZE.h"
19  #include "EEPARAMS.h"  #include "EEPARAMS.h"
20    #include "PTRACERS_SIZE.h"
21  #include "PTRACERS.h"  #include "PTRACERS.h"
22    #include "PARAMS.h"
23    #ifdef ALLOW_MNC
24    #include "MNC_PARAMS.h"
25    #endif
26    
27  C !INPUT PARAMETERS: ===================================================  C     !INPUT PARAMETERS:
 C  myThid               :: thread number  
28        INTEGER myThid        INTEGER myThid
29    CEOP
 C !OUTPUT PARAMETERS: ==================================================  
 C  none  
30    
31  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
32    
33  C !LOCAL VARIABLES: ====================================================  C     !LOCAL VARIABLES:
34  C  iTracer              :: loop indices  C     k,iTracer  :: loop indices
35  C  iUnit                :: unit number for I/O  C     iUnit      :: unit number for I/O
36  C  msgBuf               :: message buffer  C     msgBuf     :: message buffer
37        INTEGER iTracer        INTEGER k, iTracer
38        INTEGER iUnit        INTEGER iUnit
39          INTEGER ic
40        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
41  CEOP        _RL PTRACERS_diffKr(PTRACERS_num)
42    
43  C This routine has been called by the main model so we set our  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
44  C internal flag to indicate we are in business  C                          are written to post-processing files.
45          NAMELIST /PTRACERS_PARM01/
46         &     PTRACERS_dumpFreq,
47         &     PTRACERS_taveFreq,
48         &     PTRACERS_monitorFreq,
49         &     PTRACERS_advScheme,
50         &     PTRACERS_ImplVertAdv,
51         &     PTRACERS_diffKh,
52         &     PTRACERS_diffK4,
53         &     PTRACERS_diffKr,
54         &     PTRACERS_diffKrNr,
55         &     PTRACERS_useGMRedi,
56         &     PTRACERS_useKPP,
57         &     PTRACERS_Iter0,
58         &     PTRACERS_numInUse,
59         &     PTRACERS_initialFile,
60         &     PTRACERS_useRecords,
61         &     PTRACERS_names,
62         &     PTRACERS_long_names,
63         &     PTRACERS_units,
64         &     PTRACERS_timeave_mnc,
65         &     PTRACERS_snapshot_mnc,
66         &     PTRACERS_monitor_mnc,
67         &     PTRACERS_pickup_write_mnc,
68         &     PTRACERS_pickup_read_mnc
69    
70    C     This routine has been called by the main model so we set our
71    C     internal flag to indicate we are in business
72        PTRACERSisON=.TRUE.        PTRACERSisON=.TRUE.
73    
74  C Set defaults values for parameters in PTRACERS.h  C     Set defaults values for parameters in PTRACERS.h
75          PTRACERS_dumpFreq    = dumpFreq
76          PTRACERS_taveFreq    = taveFreq
77          PTRACERS_monitorFreq = monitorFreq
78          PTRACERS_Iter0   = 0
79        PTRACERS_numInUse=-1        PTRACERS_numInUse=-1
80        DO iTracer=1,PTRACERS_num        DO iTracer=1,PTRACERS_num
81         PTRACERS_advScheme(iTracer)=0          PTRACERS_advScheme(iTracer)=saltAdvScheme
82         PTRACERS_diffKh(iTracer)=0.          PTRACERS_ImplVertAdv(iTracer) = .FALSE.
83         PTRACERS_diffK4(iTracer)=0.          PTRACERS_diffKh(iTracer)=diffKhS
84         PTRACERS_diffKr(iTracer)=0.          PTRACERS_diffK4(iTracer)=diffK4S
85         PTRACERS_useGMRedi(iTracer)=.FALSE.          PTRACERS_diffKr(iTracer)=UNSET_RL
86         PTRACERS_useKPP(iTracer)=.FALSE.          DO k=1,Nr
87         PTRACERS_initialFile(iTracer)=' '            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
88            ENDDO
89            PTRACERS_useGMRedi(iTracer)=useGMRedi
90            PTRACERS_useKPP(iTracer)=useKPP
91            PTRACERS_initialFile(iTracer)=' '
92            DO ic = 1,MAX_LEN_FNAM
93              PTRACERS_names(iTracer)(ic:ic) = ' '
94              PTRACERS_long_names(iTracer)(ic:ic) = ' '
95              PTRACERS_units(iTracer)(ic:ic) = ' '
96            ENDDO
97        ENDDO        ENDDO
98          PTRACERS_useRecords       = .FALSE.
99    #ifdef ALLOW_MNC
100          PTRACERS_timeave_mnc      = timeave_mnc .AND. useMNC
101          PTRACERS_snapshot_mnc     = snapshot_mnc .AND. useMNC
102          PTRACERS_monitor_mnc      = monitor_mnc .AND. useMNC
103          PTRACERS_pickup_write_mnc = pickup_write_mnc .AND. useMNC
104          PTRACERS_pickup_read_mnc  = pickup_read_mnc .AND. useMNC
105    #else
106          PTRACERS_timeave_mnc      = .FALSE.
107          PTRACERS_snapshot_mnc     = .FALSE.
108          PTRACERS_monitor_mnc      = .FALSE.
109          PTRACERS_pickup_write_mnc = .FALSE.
110          PTRACERS_pickup_read_mnc  = .FALSE.
111    #endif
112    
113  C Open and read the data.ptracers file  C     Open and read the data.ptracers file
114        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
115        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
116        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
# Line 67  C Open and read the data.ptracers file Line 125  C Open and read the data.ptracers file
125        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
126       &                   SQUEEZE_RIGHT , 1)       &                   SQUEEZE_RIGHT , 1)
127    
128  C Close the open data file  C     Close the open data file
129        CLOSE(iUnit)        CLOSE(iUnit)
130        _END_MASTER(myThid)        _END_MASTER(myThid)
131    
132  C Everyone else must wait for the parameters to be loaded  C     Everyone else must wait for the parameters to be loaded
133        _BARRIER        _BARRIER
134    
135  C Now set-up any remaining parameters that result from the input parameters  C     Now set-up any remaining parameters that result from the input
136    C     parameters
137    
138  C If PTRACERS_numInUse was not set in data.ptracers then we can assume  C     If PTRACERS_numInUse was not set in data.ptracers then we can
139  C that all PTRACERS fields will be in use  C     assume that all PTRACERS fields will be in use
140        IF (PTRACERS_numInUse.LT.0) THEN        IF (PTRACERS_numInUse.LT.0) THEN
141         PTRACERS_numInUse=PTRACERS_num          PTRACERS_numInUse=PTRACERS_num
142        ENDIF        ENDIF
143  C Check we are not trying to use more tracers than allowed  C     Check we are not trying to use more tracers than allowed
144        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
145         WRITE(msgBuf,'(A,I2,A,I2,A)')          WRITE(msgBuf,'(A,I2,A,I2,A)')
146       & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,       &       ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
147       & ' tracers at run time when only ',PTRACERS_num,       &       ' tracers at run time when only ',PTRACERS_num,
148       & ' were specified at compile time. Naughty! '       &       ' were specified at compile time. Naughty! '
149         CALL PRINT_ERROR(msgBuf, 1)          CALL PRINT_ERROR(msgBuf, 1)
150         STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
151        ENDIF        ENDIF
152  C Check that enough parameters were specified  C     Check that enough parameters were specified
153        DO iTracer=1,PTRACERS_numInUse        DO iTracer=1,PTRACERS_numInUse
154         IF (PTRACERS_advScheme(iTracer).EQ.0) THEN          IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
155          WRITE(msgBuf,'(A,I2)')            WRITE(msgBuf,'(A,A,I2)')
156       &  ' PTRACERS_READPARMS: No advect. scheme specified for tracer #',       &         ' PTRACERS_READPARMS: ',
157       &  iTracer       &         'No advect. scheme specified for tracer #',
158          CALL PRINT_ERROR(msgBuf, 1)       &         iTracer
159              CALL PRINT_ERROR(msgBuf, 1)
160              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
161            ENDIF
162          ENDDO
163    #ifndef INCLUDE_IMPLVERTADV_CODE
164          DO iTracer=1,PTRACERS_numInUse
165           IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
166            WRITE(msgBuf,'(A)')
167         &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
168            CALL PRINT_ERROR( msgBuf , myThid)
169            WRITE(msgBuf,'(2A,I2,A)') 'PTRACERS_READPARMS:',
170         &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
171            CALL PRINT_ERROR( msgBuf , myThid)
172          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
173         ENDIF         ENDIF
174        ENDDO        ENDDO
175    #endif
176          DO iTracer=1,PTRACERS_numInUse
177            PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)
178         &                           .AND.useGMRedi
179            PTRACERS_useKPP(iTracer) = PTRACERS_useKPP(iTracer)
180         &                        .AND.useKPP
181            IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
182             DO k=1,Nr
183              PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
184             ENDDO
185            ENDIF
186          ENDDO
187    
188    #ifdef ALLOW_MNC
189          PTRACERS_timeave_mnc      =
190         &     PTRACERS_timeave_mnc      .AND. useMNC
191          PTRACERS_snapshot_mnc     =
192         &     PTRACERS_snapshot_mnc     .AND. useMNC
193          PTRACERS_monitor_mnc      =
194         &     PTRACERS_monitor_mnc      .AND. useMNC .AND. monitor_mnc
195          PTRACERS_pickup_write_mnc =
196         &     PTRACERS_pickup_write_mnc .AND. useMNC
197          PTRACERS_pickup_read_mnc  =
198         &     PTRACERS_pickup_read_mnc  .AND. useMNC
199    
200          PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)
201         &     .OR. outputTypesInclusive
202          PTRACERS_snapshot_mdsio     = (.NOT. PTRACERS_snapshot_mnc)
203         &     .OR. outputTypesInclusive
204          PTRACERS_monitor_stdio      = (.NOT. PTRACERS_monitor_mnc)
205         &     .OR. outputTypesInclusive
206          PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)
207         &     .OR. outputTypesInclusive
208          PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)
209         &     .OR. outputTypesInclusive
210          
211    #else
212          PTRACERS_timeave_mnc        = .FALSE.
213          PTRACERS_snapshot_mnc       = .FALSE.
214          PTRACERS_monitor_mnc        = .FALSE.
215          PTRACERS_pickup_write_mnc   = .FALSE.
216          PTRACERS_pickup_read_mnc    = .FALSE.
217          PTRACERS_timeave_mdsio      = .TRUE.
218          PTRACERS_snapshot_mdsio     = .TRUE.
219          PTRACERS_monitor_stdio      = .TRUE.
220          PTRACERS_pickup_write_mdsio = .TRUE.
221          PTRACERS_pickup_read_mdsio  = .TRUE.
222    #endif
223          
224    C--   Print a summary of pTracer parameter values:
225          iUnit = standardMessageUnit
226          WRITE(msgBuf,'(A)') '// ==================================='
227          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
228          WRITE(msgBuf,'(A)') '// PTRACERS parameters '
229          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
230          WRITE(msgBuf,'(A)') '// ==================================='
231          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
232          CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
233         &   'PTRACERS_numInUse =',
234         &   ' /* number of tracers */')
235          CALL WRITE_0D_I( PTRACERS_Iter0, INDEX_NONE,
236         &   'PTRACERS_Iter0 =',
237         &   ' /* timestep number when tracers are initialized */')
238          CALL WRITE_0D_R8(PTRACERS_dumpFreq, INDEX_NONE,
239         &   'PTRACERS_dumpFreq =',
240         &   ' /* Frequency^-1 for snapshot output (s) */')
241          CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,
242         &   'PTRACERS_taveFreq =',
243         &   ' /* Frequency^-1 for time-Aver. output (s) */')
244          CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
245         &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
246          
247          CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
248         &     'PTRACERS_timeave_mnc =',
249         &     ' /* use MNC for Tave output */')
250          CALL WRITE_0D_L( PTRACERS_snapshot_mnc, INDEX_NONE,
251         &     'PTRACERS_snapshot_mnc =',
252         &     ' /* use MNC for snapshot output */')
253          CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
254         &     'PTRACERS_pickup_write_mnc =',
255         &     ' /* use MNC for writing pickups */')
256          CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
257         &     'PTRACERS_pickup_read_mnc =',
258         &     ' /* use MNC for reading pickups */')
259    
260          DO iTracer=1,PTRACERS_numInUse
261            WRITE(msgBuf,'(A)') ' -----------------------------------'
262            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
263            WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
264            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
265            CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
266         &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
267            CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
268         &     'PTRACERS_ImplVertAdv =',
269         &     ' /* implicit vert. advection flag */')
270            CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,
271         &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
272            CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,
273         &     'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
274            CALL WRITE_1D_R8( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
275         &     'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
276            CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
277         &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
278            CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
279         &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
280    
281          ENDDO
282            WRITE(msgBuf,'(A)') ' -----------------------------------'
283            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
284  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
285    
286        RETURN        RETURN
287        END        END
288    

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.22

  ViewVC Help
Powered by ViewVC 1.1.22