/[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.3 by dimitri, Sat Sep 27 07:45:51 2003 UTC revision 1.12 by jmc, Thu Oct 28 00:32:21 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"
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     k,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 k, iTracer
35        INTEGER iUnit        INTEGER iUnit
36          INTEGER ic
37        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
38  CEOP        _RL PTRACERS_diffKr(PTRACERS_num)
39    
40  C This routine has been called by the main model so we set our  C     PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
41  C internal flag to indicate we are in business  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.        PTRACERSisON=.TRUE.
63    
64  C Set defaults values for parameters in PTRACERS.h  C     Set defaults values for parameters in PTRACERS.h
65          PTRACERS_taveFreq=taveFreq
66        PTRACERS_numInUse=-1        PTRACERS_numInUse=-1
67        DO iTracer=1,PTRACERS_num        DO iTracer=1,PTRACERS_num
68         PTRACERS_advScheme(iTracer)=saltAdvScheme          PTRACERS_advScheme(iTracer)=saltAdvScheme
69         PTRACERS_diffKh(iTracer)=diffKhS          PTRACERS_diffKh(iTracer)=diffKhS
70         PTRACERS_diffK4(iTracer)=diffK4S          PTRACERS_diffK4(iTracer)=diffK4S
71         PTRACERS_diffKr(iTracer)=diffKrS          PTRACERS_diffKr(iTracer)=UNSET_RL
72         PTRACERS_useGMRedi(iTracer)=useGMRedi          DO k=1,Nr
73         PTRACERS_useKPP(iTracer)=useKPP            PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
74         PTRACERS_initialFile(iTracer)=' '          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        ENDDO
84        PTRACERS_useRecords=.FALSE.        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  C     Open and read the data.ptracers file
91        _BEGIN_MASTER(myThid)        _BEGIN_MASTER(myThid)
92        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'        WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
93        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
# Line 69  C Open and read the data.ptracers file Line 102  C Open and read the data.ptracers file
102        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
103       &                   SQUEEZE_RIGHT , 1)       &                   SQUEEZE_RIGHT , 1)
104    
105  C Close the open data file  C     Close the open data file
106        CLOSE(iUnit)        CLOSE(iUnit)
107        _END_MASTER(myThid)        _END_MASTER(myThid)
108    
109  C Everyone else must wait for the parameters to be loaded  C     Everyone else must wait for the parameters to be loaded
110        _BARRIER        _BARRIER
111    
112  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
113    C     parameters
114    
115  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
116  C that all PTRACERS fields will be in use  C     assume that all PTRACERS fields will be in use
117        IF (PTRACERS_numInUse.LT.0) THEN        IF (PTRACERS_numInUse.LT.0) THEN
118         PTRACERS_numInUse=PTRACERS_num          PTRACERS_numInUse=PTRACERS_num
119        ENDIF        ENDIF
120  C Check we are not trying to use more tracers than allowed  C     Check we are not trying to use more tracers than allowed
121        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN        IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
122         WRITE(msgBuf,'(A,I2,A,I2,A)')          WRITE(msgBuf,'(A,I2,A,I2,A)')
123       & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,       &       ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
124       & ' tracers at run time when only ',PTRACERS_num,       &       ' tracers at run time when only ',PTRACERS_num,
125       & ' 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  
126          CALL PRINT_ERROR(msgBuf, 1)          CALL PRINT_ERROR(msgBuf, 1)
127          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'          STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
128         ENDIF        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        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    C--   Print a summary of pTracer parameter values:
165          iUnit = standardMessageUnit
166          WRITE(msgBuf,'(A)') '// ==================================='
167          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
168          WRITE(msgBuf,'(A)') '// PTRACERS parameters '
169          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
170          WRITE(msgBuf,'(A)') '// ==================================='
171          CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
172          CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
173         &   'PTRACERS_numInUse =',
174         &   ' /* number of tracers */')
175          CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,
176         &   'PTRACERS_taveFreq =',
177         &   ' /* Frequency^-1 for time-Aver. output (s) */')
178          CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
179         &   'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
180          CALL WRITE_0D_L( PTRACERS_write_mdsio, INDEX_NONE,
181         &   'PTRACERS_write_mdsio =', ' /* write mdsio files */')
182          CALL WRITE_0D_L( PTRACERS_write_mnc, INDEX_NONE,
183         &   'PTRACERS_write_mnc =', ' /* write mnc files */')
184    
185          DO iTracer=1,PTRACERS_numInUse
186            WRITE(msgBuf,'(A)') ' -----------------------------------'
187            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
188            WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
189            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
190            CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
191         &     'PTRACERS_advScheme =', ' /* Advection Scheme */')
192            CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,
193         &     'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
194            CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,
195         &     'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
196            CALL WRITE_1D_R8( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
197         &     'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
198            CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
199         &     'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
200            CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
201         &     'PTRACERS_useKPP =', ' /* apply KPP scheme */')
202    
203          ENDDO
204            WRITE(msgBuf,'(A)') ' -----------------------------------'
205            CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , 1)
206  #endif /* ALLOW_PTRACERS */  #endif /* ALLOW_PTRACERS */
207    
208        RETURN        RETURN
209        END        END
210    

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.12

  ViewVC Help
Powered by ViewVC 1.1.22