/[MITgcm]/MITgcm/pkg/diagnostics/diag_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/diagnostics/diag_readparms.F

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


Revision 1.14 - (show annotations) (download)
Sun Oct 10 06:08:48 2004 UTC (19 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint55g_post, checkpoint55f_post
Changes since 1.13: +1 -4 lines
 o move useMNC and related runtime switches to PARAMS.h

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diag_readparms.F,v 1.13 2004/09/22 02:50:49 edhill Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: DIAG_READPARMS
9
10 C !INTERFACE:
11 SUBROUTINE DIAG_READPARMS(myThid)
12
13 C !DESCRIPTION:
14 C Read Diagnostics Namelists to specify output sequence.
15
16 C !USES:
17 implicit none
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21
22 #include "diagnostics_SIZE.h"
23 #include "diagnostics.h"
24
25 C !INPUT PARAMETERS:
26 integer myThid
27 CEOP
28
29 C !LOCAL VARIABLES:
30 character*(MAX_LEN_MBUF) msgBuf
31 integer ku
32 integer l,n,m,ndim
33 _RL undef, getcon
34 parameter ( ndim = 100 ) ! Max Number of Levels,Fields,Lists
35 integer frequency(ndim) ! Frequency of Output (hhmmss)
36 _RL levels (ndim,ndim) ! List Output Levels
37 character*8 fields(ndim,ndim) ! List Output Fields
38 character*8 filename(ndim) ! List Output Filename
39 character*8 blank
40 LOGICAL diag_mdsio, diag_mnc, diag_ioinc
41 INTEGER mnc_lev_used(ndim)
42
43 namelist / diagnostics_list /
44 & frequency, levels, fields, filename,
45 & diag_mdsio, diag_mnc, diag_ioinc
46
47 C Initialize and Read Diagnostics Namelist
48 _BEGIN_MASTER(myThid)
49
50 undef = getcon('UNDEF')
51 blank = ' '
52
53 do n = 1,ndim
54 frequency(n) = 0
55 do m = 1,ndim
56 levels (n,m) = undef
57 fields (n,m) = blank
58 enddo
59 enddo
60
61 diag_mdsio = .true.
62 diag_mnc = .false.
63 diag_ioinc = .false.
64
65 #ifdef ALLOW_MNC
66 IF (useMNC .and. diag_use_mnc) THEN
67 do n = 1,ndim
68 mnc_lev_used(n) = 0
69 enddo
70 ENDIF
71 #endif /* ALLOW_MNC */
72
73 WRITE(msgBuf,'(A)') ' DIAG_READPARMS: opening data.diagnostics'
74 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,SQUEEZE_RIGHT,1)
75
76 CALL OPEN_COPY_DATA_FILE('data.diagnostics', 'DIAG_READPARMS',
77 . ku,myThid )
78 read (ku,NML=diagnostics_list)
79 close (ku)
80
81
82 C Initialise diag_choices common block
83 nlists = 0
84 do n = 1,numlists
85 freq(n) = 0
86 nlevels(n) = 0
87 nfields(n) = 0
88 fnames(n) = blank
89 do m = 1,numperlist
90 levs(m,n) = 0
91 flds(m,n) = ' '
92 enddo
93 enddo
94
95 C Fill Diagnostics Common Block with Namelist Info
96 diag_use_mdsio = diag_mdsio
97 diag_use_mnc = diag_mnc
98 IF (diag_mnc .AND. (.NOT. diag_ioinc)) THEN
99 diag_use_mdsio = .FALSE.
100 ENDIF
101
102 do n = 1,numlists
103 if (frequency(n) .ne. 0) then
104 nlists = nlists + 1
105 freq(n) = frequency(n)
106 fnames(n) = filename (n)
107 nlevels(n) = 0
108 nfields(n) = 0
109 do m=1,ndim
110 if (levels(m,n) .ne. undef) then
111 nlevels(n) = nlevels(n) + 1
112 endif
113 if (fields(m,n) .ne. blank) nfields(n) = nfields(n) + 1
114 enddo
115 if (levels(1,n) .ne. undef) then
116 do m=1,nlevels(n)
117 levs(m,n) = levels(m,n)
118 enddo
119 else
120 nlevels(n) = Nr
121 do m=1,nlevels(n)
122 levs(m,n) = m
123 enddo
124 endif
125 do m=1,nfields(n)
126 flds(m,n) = fields(m,n)
127 enddo
128 endif
129 enddo
130
131 C Echo History List Data Structure
132 do n = 1,nlists
133 WRITE(msgBuf,'(2a)') 'Creating Output Stream: ',fnames(n)
134 CALL PRINT_MESSAGE(
135 & msgBuf, standardMessageUnit, SQUEEZE_RIGHT, mythid)
136 WRITE(msgBuf,*) 'Frequency: ',freq(n)
137 CALL PRINT_MESSAGE(
138 & msgBuf, standardMessageUnit, SQUEEZE_RIGHT, mythid)
139 WRITE(msgBuf,*) 'Levels: ',(levs(l,n),l=1,nlevels(n))
140 CALL PRINT_MESSAGE(
141 & msgBuf, standardMessageUnit, SQUEEZE_RIGHT, mythid)
142 WRITE(msgBuf,*) 'Fields: ',(' ',flds(l,n),l=1,nfields(n))
143 CALL PRINT_MESSAGE(
144 & msgBuf, standardMessageUnit, SQUEEZE_RIGHT, mythid)
145 enddo
146
147 _END_MASTER(myThid)
148
149 return
150 end

  ViewVC Help
Powered by ViewVC 1.1.22