/[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.6 by edhill, Fri Sep 3 20:10:47 2004 UTC revision 1.24 by jmc, Tue May 23 23:32:41 2006 UTC
# Line 6  C $Name$ Line 6  C $Name$
6  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  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    
# Line 20  C     !USES: Line 20  C     !USES:
20  #include "PTRACERS_SIZE.h"  #include "PTRACERS_SIZE.h"
21  #include "PTRACERS.h"  #include "PTRACERS.h"
22  #include "PARAMS.h"  #include "PARAMS.h"
23          #ifdef ALLOW_MNC
24    #include "MNC_PARAMS.h"
25    #endif
26    
27  C     !INPUT PARAMETERS:  C     !INPUT PARAMETERS:
28        INTEGER myThid        INTEGER myThid
29  CEOP  CEOP
# Line 28  CEOP Line 31  CEOP
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        INTEGER ic
40        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
41          _RL PTRACERS_diffKr(PTRACERS_num)
42    
43  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
44  C                          are written to post-processing files.  C                          are written to post-processing files.
45        NAMELIST /PTRACERS_PARM01/        NAMELIST /PTRACERS_PARM01/
46         &     PTRACERS_dumpFreq,
47       &     PTRACERS_taveFreq,       &     PTRACERS_taveFreq,
48         &     PTRACERS_monitorFreq,
49       &     PTRACERS_advScheme,       &     PTRACERS_advScheme,
50         &     PTRACERS_ImplVertAdv,
51       &     PTRACERS_diffKh,       &     PTRACERS_diffKh,
52       &     PTRACERS_diffK4,       &     PTRACERS_diffK4,
53       &     PTRACERS_diffKr,       &     PTRACERS_diffKr,
54         &     PTRACERS_diffKrNr,
55         &     PTRACERS_ref,
56         &     PTRACERS_EvPrRn,
57       &     PTRACERS_useGMRedi,       &     PTRACERS_useGMRedi,
58       &     PTRACERS_useKPP,       &     PTRACERS_useKPP,
59         &     PTRACERS_Iter0,
60       &     PTRACERS_numInUse,       &     PTRACERS_numInUse,
61       &     PTRACERS_initialFile,       &     PTRACERS_initialFile,
62       &     PTRACERS_useRecords,       &     PTRACERS_useRecords,
63       &     PTRACERS_names,       &     PTRACERS_names,
64       &     PTRACERS_long_names,       &     PTRACERS_long_names,
65       &     PTRACERS_units,       &     PTRACERS_units,
66       &     PTRACERS_mnc_read,       &     PTRACERS_timeave_mnc,
67       &     PTRACERS_mnc_write,       &     PTRACERS_snapshot_mnc,
68       &     PTRACERS_iotypes       &     PTRACERS_monitor_mnc,
69         &     PTRACERS_pickup_write_mnc,
70         &     PTRACERS_pickup_read_mnc
71    
72  C     This routine has been called by the main model so we set our  C     This routine has been called by the main model so we set our
73  C     internal flag to indicate we are in business  C     internal flag to indicate we are in business
74        PTRACERSisON=.TRUE.        PTRACERSisON=.TRUE.
75    
76  C     Set defaults values for parameters in PTRACERS.h  C     Set defaults values for parameters in PTRACERS.h
77        PTRACERS_taveFreq=taveFreq        PTRACERS_dumpFreq    = dumpFreq
78          PTRACERS_taveFreq    = taveFreq
79          PTRACERS_monitorFreq = monitorFreq
80          PTRACERS_Iter0   = 0
81        PTRACERS_numInUse=-1        PTRACERS_numInUse=-1
82        DO iTracer=1,PTRACERS_num        DO iTracer=1,PTRACERS_num
83          PTRACERS_advScheme(iTracer)=saltAdvScheme          PTRACERS_advScheme(iTracer)=saltAdvScheme
84            PTRACERS_ImplVertAdv(iTracer) = .FALSE.
85          PTRACERS_diffKh(iTracer)=diffKhS          PTRACERS_diffKh(iTracer)=diffKhS
86          PTRACERS_diffK4(iTracer)=diffK4S          PTRACERS_diffK4(iTracer)=diffK4S
87          PTRACERS_diffKr(iTracer)=diffKrS          PTRACERS_diffKr(iTracer)=UNSET_RL
88            DO k=1,Nr
89              PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
90              PTRACERS_ref     (k,iTracer)=0. _d 0
91            ENDDO
92            PTRACERS_EvPrRn(iTracer)=UNSET_RL
93          PTRACERS_useGMRedi(iTracer)=useGMRedi          PTRACERS_useGMRedi(iTracer)=useGMRedi
94          PTRACERS_useKPP(iTracer)=useKPP          PTRACERS_useKPP(iTracer)=useKPP
95          PTRACERS_initialFile(iTracer)=' '          PTRACERS_initialFile(iTracer)=' '
# Line 77  C     Set defaults values for parameters Line 99  C     Set defaults values for parameters
99            PTRACERS_units(iTracer)(ic:ic) = ' '            PTRACERS_units(iTracer)(ic:ic) = ' '
100          ENDDO          ENDDO
101        ENDDO        ENDDO
102        PTRACERS_useRecords=.FALSE.        PTRACERS_useRecords       = .FALSE.
103        PTRACERS_iotypes = -1  #ifdef ALLOW_MNC
104        PTRACERS_mnc_read = .true.        PTRACERS_timeave_mnc      = timeave_mnc .AND. useMNC
105        PTRACERS_mnc_write = .true.        PTRACERS_snapshot_mnc     = snapshot_mnc .AND. useMNC
106          PTRACERS_monitor_mnc      = monitor_mnc .AND. useMNC
107          PTRACERS_pickup_write_mnc = pickup_write_mnc .AND. useMNC
108          PTRACERS_pickup_read_mnc  = pickup_read_mnc .AND. useMNC
109    #else
110          PTRACERS_timeave_mnc      = .FALSE.
111          PTRACERS_snapshot_mnc     = .FALSE.
112          PTRACERS_monitor_mnc      = .FALSE.
113          PTRACERS_pickup_write_mnc = .FALSE.
114          PTRACERS_pickup_read_mnc  = .FALSE.
115    #endif
116    
117  C     Open and read the data.ptracers file  C     Open and read the data.ptracers file
118        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
# Line 132  C     Check that enough parameters were Line 164  C     Check that enough parameters were
164            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
165          ENDIF          ENDIF
166        ENDDO        ENDDO
167    #ifndef INCLUDE_IMPLVERTADV_CODE
168  C     Set the default I/O Types        DO iTracer=1,PTRACERS_numInUse
169        IF (PTRACERS_iotypes .EQ. -1) THEN         IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
170          PTRACERS_iotypes = 1          WRITE(msgBuf,'(A)')
171        ENDIF       &   'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
172            CALL PRINT_ERROR( msgBuf , myThid)
173            WRITE(msgBuf,'(2A,I2,A)') 'PTRACERS_READPARMS:',
174         &   ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
175            CALL PRINT_ERROR( msgBuf , myThid)
176            STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
177           ENDIF
178          ENDDO
179    #endif
180          DO iTracer=1,PTRACERS_numInUse
181            PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)
182         &                           .AND.useGMRedi
183            PTRACERS_useKPP(iTracer) = PTRACERS_useKPP(iTracer)
184         &                        .AND.useKPP
185            IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
186             DO k=1,Nr
187              PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
188             ENDDO
189            ENDIF
190          ENDDO
191    
192  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
193  C     Initialize the MNC variable types for PTRACERS        PTRACERS_timeave_mnc      =
194        IF (useMNC) THEN       &     PTRACERS_timeave_mnc      .AND. useMNC
195          CALL PTRACERS_MNC_INIT( myThid )        PTRACERS_snapshot_mnc     =
196        ENDIF       &     PTRACERS_snapshot_mnc     .AND. useMNC
197  #endif /*  ALLOW_MNC  */        PTRACERS_monitor_mnc      =
198         &     PTRACERS_monitor_mnc      .AND. useMNC .AND. monitor_mnc
199          PTRACERS_pickup_write_mnc =
200         &     PTRACERS_pickup_write_mnc .AND. useMNC
201          PTRACERS_pickup_read_mnc  =
202         &     PTRACERS_pickup_read_mnc  .AND. useMNC
203    
204          PTRACERS_timeave_mdsio      = (.NOT. PTRACERS_timeave_mnc)
205         &     .OR. outputTypesInclusive
206          PTRACERS_snapshot_mdsio     = (.NOT. PTRACERS_snapshot_mnc)
207         &     .OR. outputTypesInclusive
208          PTRACERS_monitor_stdio      = (.NOT. PTRACERS_monitor_mnc)
209         &     .OR. outputTypesInclusive
210          PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)
211         &     .OR. outputTypesInclusive
212          PTRACERS_pickup_read_mdsio  = (.NOT. PTRACERS_pickup_read_mnc)
213         &     .OR. outputTypesInclusive
214    
215    #else
216          PTRACERS_timeave_mnc        = .FALSE.
217          PTRACERS_snapshot_mnc       = .FALSE.
218          PTRACERS_monitor_mnc        = .FALSE.
219          PTRACERS_pickup_write_mnc   = .FALSE.
220          PTRACERS_pickup_read_mnc    = .FALSE.
221          PTRACERS_timeave_mdsio      = .TRUE.
222          PTRACERS_snapshot_mdsio     = .TRUE.
223          PTRACERS_monitor_stdio      = .TRUE.
224          PTRACERS_pickup_write_mdsio = .TRUE.
225          PTRACERS_pickup_read_mdsio  = .TRUE.
226    #endif
227    
228    C--   Print a summary of pTracer parameter values:
229          iUnit = standardMessageUnit
230          WRITE(msgBuf,'(A)') '// ==================================='
231          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
232          WRITE(msgBuf,'(A)') '// PTRACERS parameters '
233          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
234          WRITE(msgBuf,'(A)') '// ==================================='
235          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
236          CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
237         &   'PTRACERS_numInUse =',
238         &   ' /* number of tracers */')
239          CALL WRITE_0D_I( PTRACERS_Iter0, INDEX_NONE,
240         &   'PTRACERS_Iter0 =',
241         &   ' /* timestep number when tracers are initialized */')
242          CALL WRITE_0D_R8(PTRACERS_dumpFreq, INDEX_NONE,
243         &   'PTRACERS_dumpFreq =',
244         &   ' /* Frequency^-1 for snapshot output (s) */')
245          CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,
246         &   'PTRACERS_taveFreq =',
247         &   ' /* Frequency^-1 for time-Aver. output (s) */')
248          CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
249         &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
250                
251          CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
252         &     'PTRACERS_timeave_mnc =',
253         &     ' /* use MNC for Tave output */')
254          CALL WRITE_0D_L( PTRACERS_snapshot_mnc, INDEX_NONE,
255         &     'PTRACERS_snapshot_mnc =',
256         &     ' /* use MNC for snapshot output */')
257          CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
258         &     'PTRACERS_pickup_write_mnc =',
259         &     ' /* use MNC for writing pickups */')
260          CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
261         &     'PTRACERS_pickup_read_mnc =',
262         &     ' /* use MNC for reading pickups */')
263    
264          DO iTracer=1,PTRACERS_numInUse
265            WRITE(msgBuf,'(A)') ' -----------------------------------'
266            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
267            WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
268            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
269            CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
270         &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
271            CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
272         &     'PTRACERS_ImplVertAdv =',
273         &     ' /* implicit vert. advection flag */')
274            CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,
275         &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
276            CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,
277         &     'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
278            CALL WRITE_1D_R8( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
279         &     'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
280            CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
281         &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
282            CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
283         &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
284            CALL WRITE_1D_R8( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
285         &     'PTRACERS_ref =', ' /* Reference vertical profile */')
286            CALL WRITE_0D_R8( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
287         &     'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
288    
289          ENDDO
290            WRITE(msgBuf,'(A)') ' -----------------------------------'
291            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
292  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
293    
294        RETURN        RETURN

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.24

  ViewVC Help
Powered by ViewVC 1.1.22