/[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.5 by jmc, Tue Jul 13 16:47:49 2004 UTC revision 1.6 by edhill, Fri Sep 3 20:10:47 2004 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"  #include "PTRACERS_SIZE.h"
21  #include "PTRACERS.h"  #include "PTRACERS.h"
22  #include "PARAMS.h"  #include "PARAMS.h"
23          
24  C !INPUT PARAMETERS: ===================================================  C     !INPUT PARAMETERS:
 C  myThid               :: thread number  
25        INTEGER myThid        INTEGER myThid
26    CEOP
 C !OUTPUT PARAMETERS: ==================================================  
 C  none  
27    
28  #ifdef ALLOW_PTRACERS  #ifdef ALLOW_PTRACERS
29    
30  C !LOCAL VARIABLES: ====================================================  C     !LOCAL VARIABLES:
31  C  iTracer              :: loop indices  C     iTracer    :: loop indices
32  C  iUnit                :: unit number for I/O  C     iUnit      :: unit number for I/O
33  C  msgBuf               :: message buffer  C     msgBuf     :: message buffer
34        INTEGER iTracer        INTEGER iTracer
35        INTEGER iUnit        INTEGER iUnit
36          INTEGER ic
37        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
 CEOP  
38    
39  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
40  C                          are written to post-processing files.  C                          are written to post-processing files.
41        NAMELIST /PTRACERS_PARM01/        NAMELIST /PTRACERS_PARM01/
42       &                   PTRACERS_taveFreq,       &     PTRACERS_taveFreq,
43       &                   PTRACERS_advScheme,       &     PTRACERS_advScheme,
44       &                   PTRACERS_diffKh,       &     PTRACERS_diffKh,
45       &                   PTRACERS_diffK4,       &     PTRACERS_diffK4,
46       &                   PTRACERS_diffKr,       &     PTRACERS_diffKr,
47       &                   PTRACERS_useGMRedi,       &     PTRACERS_useGMRedi,
48       &                   PTRACERS_useKPP,       &     PTRACERS_useKPP,
49       &                   PTRACERS_numInUse,       &     PTRACERS_numInUse,
50       &                   PTRACERS_initialFile,       &     PTRACERS_initialFile,
51       &                   PTRACERS_useRecords       &     PTRACERS_useRecords,
52         &     PTRACERS_names,
53         &     PTRACERS_long_names,
54         &     PTRACERS_units,
55         &     PTRACERS_mnc_read,
56         &     PTRACERS_mnc_write,
57         &     PTRACERS_iotypes
58    
59  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
60  C internal flag to indicate we are in business  C     internal flag to indicate we are in business
61        PTRACERSisON=.TRUE.        PTRACERSisON=.TRUE.
62    
63  C Set defaults values for parameters in PTRACERS.h  C     Set defaults values for parameters in PTRACERS.h
64        PTRACERS_taveFreq=taveFreq        PTRACERS_taveFreq=taveFreq
65        PTRACERS_numInUse=-1        PTRACERS_numInUse=-1
66        DO iTracer=1,PTRACERS_num        DO iTracer=1,PTRACERS_num
67         PTRACERS_advScheme(iTracer)=saltAdvScheme          PTRACERS_advScheme(iTracer)=saltAdvScheme
68         PTRACERS_diffKh(iTracer)=diffKhS          PTRACERS_diffKh(iTracer)=diffKhS
69         PTRACERS_diffK4(iTracer)=diffK4S          PTRACERS_diffK4(iTracer)=diffK4S
70         PTRACERS_diffKr(iTracer)=diffKrS          PTRACERS_diffKr(iTracer)=diffKrS
71         PTRACERS_useGMRedi(iTracer)=useGMRedi          PTRACERS_useGMRedi(iTracer)=useGMRedi
72         PTRACERS_useKPP(iTracer)=useKPP          PTRACERS_useKPP(iTracer)=useKPP
73         PTRACERS_initialFile(iTracer)=' '          PTRACERS_initialFile(iTracer)=' '
74            DO ic = 1,MAX_LEN_FNAM
75              PTRACERS_names(iTracer)(ic:ic) = ' '
76              PTRACERS_long_names(iTracer)(ic:ic) = ' '
77              PTRACERS_units(iTracer)(ic:ic) = ' '
78            ENDDO
79        ENDDO        ENDDO
80        PTRACERS_useRecords=.FALSE.        PTRACERS_useRecords=.FALSE.
81          PTRACERS_iotypes = -1
82          PTRACERS_mnc_read = .true.
83          PTRACERS_mnc_write = .true.
84    
85  C Open and read the data.ptracers file  C     Open and read the data.ptracers file
86        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
87        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
88        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
# Line 85  C Open and read the data.ptracers file Line 97  C Open and read the data.ptracers file
97        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
98       &                   SQUEEZE_RIGHT , 1)       &                   SQUEEZE_RIGHT , 1)
99    
100  C Close the open data file  C     Close the open data file
101        CLOSE(iUnit)        CLOSE(iUnit)
102        _END_MASTER(myThid)        _END_MASTER(myThid)
103    
104  C Everyone else must wait for the parameters to be loaded  C     Everyone else must wait for the parameters to be loaded
105        _BARRIER        _BARRIER
106    
107  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
108    C     parameters
109    
110  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
111  C that all PTRACERS fields will be in use  C     assume that all PTRACERS fields will be in use
112        IF (PTRACERS_numInUse.LT.0) THEN        IF (PTRACERS_numInUse.LT.0) THEN
113         PTRACERS_numInUse=PTRACERS_num          PTRACERS_numInUse=PTRACERS_num
114        ENDIF        ENDIF
115  C Check we are not trying to use more tracers than allowed  C     Check we are not trying to use more tracers than allowed
116        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
117         WRITE(msgBuf,'(A,I2,A,I2,A)')          WRITE(msgBuf,'(A,I2,A,I2,A)')
118       & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,       &       ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
119       & ' tracers at run time when only ',PTRACERS_num,       &       ' tracers at run time when only ',PTRACERS_num,
120       & ' were specified at compile time. Naughty! '       &       ' were specified at compile time. Naughty! '
        CALL PRINT_ERROR(msgBuf, 1)  
        STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'  
       ENDIF  
 C Check that enough parameters were specified  
       DO iTracer=1,PTRACERS_numInUse  
        IF (PTRACERS_advScheme(iTracer).EQ.0) THEN  
         WRITE(msgBuf,'(A,I2)')  
      &  ' PTRACERS_READPARMS: No advect. scheme specified for tracer #',  
      &  iTracer  
121          CALL PRINT_ERROR(msgBuf, 1)          CALL PRINT_ERROR(msgBuf, 1)
122          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
123         ENDIF        ENDIF
124    C     Check that enough parameters were specified
125          DO iTracer=1,PTRACERS_numInUse
126            IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
127              WRITE(msgBuf,'(A,A,I2)')
128         &         ' PTRACERS_READPARMS: ',
129         &         'No advect. scheme specified for tracer #',
130         &         iTracer
131              CALL PRINT_ERROR(msgBuf, 1)
132              STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
133            ENDIF
134        ENDDO        ENDDO
135    
136    C     Set the default I/O Types
137          IF (PTRACERS_iotypes .EQ. -1) THEN
138            PTRACERS_iotypes = 1
139          ENDIF
140    
141    #ifdef ALLOW_MNC
142    C     Initialize the MNC variable types for PTRACERS
143          IF (useMNC) THEN
144            CALL PTRACERS_MNC_INIT( myThid )
145          ENDIF
146    #endif /*  ALLOW_MNC  */
147          
148  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
149    
150        RETURN        RETURN
151        END        END
152    

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

  ViewVC Help
Powered by ViewVC 1.1.22