/[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.9 - (show annotations) (download)
Sun Oct 17 23:06:52 2004 UTC (19 years, 7 months ago) by jmc
Branch: MAIN
Changes since 1.8: +2 -2 lines
allow to set a vertical profile of vertical diffusivity for T & S

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_readparms.F,v 1.8 2004/10/10 06:08:50 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 iTracer :: loop indices
32 C iUnit :: unit number for I/O
33 C msgBuf :: message buffer
34 INTEGER iTracer
35 INTEGER iUnit
36 INTEGER ic
37 CHARACTER*(MAX_LEN_MBUF) msgBuf
38
39 C PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
40 C are written to post-processing files.
41 NAMELIST /PTRACERS_PARM01/
42 & PTRACERS_taveFreq,
43 & PTRACERS_advScheme,
44 & PTRACERS_diffKh,
45 & PTRACERS_diffK4,
46 & PTRACERS_diffKr,
47 & PTRACERS_useGMRedi,
48 & PTRACERS_useKPP,
49 & PTRACERS_numInUse,
50 & PTRACERS_initialFile,
51 & PTRACERS_useRecords,
52 & PTRACERS_names,
53 & PTRACERS_long_names,
54 & PTRACERS_units,
55 & PTRACERS_write_ioinc,
56 & PTRACERS_read_mnc,
57 & PTRACERS_write_mnc
58
59 C This routine has been called by the main model so we set our
60 C internal flag to indicate we are in business
61 PTRACERSisON=.TRUE.
62
63 C Set defaults values for parameters in PTRACERS.h
64 PTRACERS_taveFreq=taveFreq
65 PTRACERS_numInUse=-1
66 DO iTracer=1,PTRACERS_num
67 PTRACERS_advScheme(iTracer)=saltAdvScheme
68 PTRACERS_diffKh(iTracer)=diffKhS
69 PTRACERS_diffK4(iTracer)=diffK4S
70 PTRACERS_diffKr(iTracer)=diffKrNrS(1)
71 PTRACERS_useGMRedi(iTracer)=useGMRedi
72 PTRACERS_useKPP(iTracer)=useKPP
73 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
80 PTRACERS_useRecords = .FALSE.
81 PTRACERS_read_mdsio = .TRUE.
82 PTRACERS_read_mnc = .FALSE.
83 PTRACERS_write_mdsio = .TRUE.
84 PTRACERS_write_mnc = .FALSE.
85 PTRACERS_write_ioinc = .FALSE.
86
87 C Open and read the data.ptracers file
88 _BEGIN_MASTER(myThid)
89 WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
90 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
91 & SQUEEZE_RIGHT , 1)
92 CALL OPEN_COPY_DATA_FILE(
93 I 'data.ptracers', 'PTRACERS_READPARMS',
94 O iUnit,
95 I myThid )
96 READ(UNIT=iUnit,NML=PTRACERS_PARM01)
97 WRITE(msgBuf,'(A)')
98 & ' PTRACERS_READPARMS: finished reading data.ptracers'
99 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
100 & SQUEEZE_RIGHT , 1)
101
102 C Close the open data file
103 CLOSE(iUnit)
104 _END_MASTER(myThid)
105
106 C Everyone else must wait for the parameters to be loaded
107 _BARRIER
108
109 C Now set-up any remaining parameters that result from the input
110 C parameters
111
112 C If PTRACERS_numInUse was not set in data.ptracers then we can
113 C assume that all PTRACERS fields will be in use
114 IF (PTRACERS_numInUse.LT.0) THEN
115 PTRACERS_numInUse=PTRACERS_num
116 ENDIF
117 C Check we are not trying to use more tracers than allowed
118 IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
119 WRITE(msgBuf,'(A,I2,A,I2,A)')
120 & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
121 & ' tracers at run time when only ',PTRACERS_num,
122 & ' were specified at compile time. Naughty! '
123 CALL PRINT_ERROR(msgBuf, 1)
124 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
125 ENDIF
126 C Check that enough parameters were specified
127 DO iTracer=1,PTRACERS_numInUse
128 IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
129 WRITE(msgBuf,'(A,A,I2)')
130 & ' PTRACERS_READPARMS: ',
131 & 'No advect. scheme specified for tracer #',
132 & iTracer
133 CALL PRINT_ERROR(msgBuf, 1)
134 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
135 ENDIF
136 ENDDO
137
138 #ifdef ALLOW_MNC
139 IF (useMNC) THEN
140 C Set the default I/O Types
141 IF (PTRACERS_read_mnc) PTRACERS_read_mdsio = .FALSE.
142 IF ( (.NOT. PTRACERS_write_ioinc)
143 & .AND. PTRACERS_write_mnc ) pickup_write_mdsio = .FALSE.
144
145 C Initialize the MNC variable types for PTRACERS
146 CALL PTRACERS_MNC_INIT( myThid )
147 ENDIF
148 #endif /* ALLOW_MNC */
149
150 #endif /* ALLOW_PTRACERS */
151
152 RETURN
153 END
154

  ViewVC Help
Powered by ViewVC 1.1.22