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

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

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


Revision 1.4 - (show annotations) (download)
Fri May 20 07:17:07 2005 UTC (19 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint57v_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint58m_post, checkpoint57l_post
Changes since 1.3: +5 -3 lines
 get warnings when I compile this S/R because something is not right
 in the type or one or more arguments. commented out for now

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_read_pickup.F,v 1.3 2005/02/23 16:30:19 edhill Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: DIAGNOSTICS_READ_PICKUP
9 C !INTERFACE:
10 SUBROUTINE DIAGNOSTICS_READ_PICKUP(
11 I myThid )
12
13 C !DESCRIPTION:
14 C Reads previously saved state for the diagnostics package.
15
16 C !USES:
17 IMPLICIT NONE
18
19 C == Global variables ===
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "DIAGNOSTICS_SIZE.h"
24 #include "DIAGNOSTICS.h"
25
26 C !INPUT/OUTPUT PARAMETERS:
27 C myThid :: Number of this instance
28 INTEGER myThid
29
30 #ifdef DIAGNOSTICS_HAS_PICKUP
31
32 C !LOCAL VARIABLES:
33 C fn :: character buffer for creating filename
34 C prec :: precision of pickup files
35 c INTEGER prec, iChar, lChar, k
36 INTEGER prec, lChar, i, sn
37 CHARACTER*(MAX_LEN_FNAM) fn
38
39 INTEGER ILNBLNK
40 EXTERNAL ILNBLNK
41
42 #ifdef ALLOW_MDSIO
43 INTEGER dUnit, n, m
44 #endif /* ALLOW_MDSIO */
45
46 #ifdef ALLOW_MNC
47 INTEGER ii
48 CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
49 INTEGER CW_DIMS, NLEN
50 PARAMETER ( CW_DIMS = 10 )
51 PARAMETER ( NLEN = 80 )
52 INTEGER dim(CW_DIMS), ib(CW_DIMS), ie(CW_DIMS)
53 CHARACTER*(NLEN) dn(CW_DIMS)
54 CHARACTER*(NLEN) d_cw_name
55 CHARACTER*(NLEN) dn_blnk
56 #endif /* ALLOW_MNC */
57
58
59 C Add pickup capability
60 IF (diag_pickup_read) THEN
61
62 #ifdef ALLOW_MNC
63 IF (diag_pickup_read_mnc) THEN
64 DO i = 1,NLEN
65 dn_blnk(i:i) = ' '
66 ENDDO
67 DO i = 1,MAX_LEN_FNAM
68 diag_mnc_bn(i:i) = ' '
69 ENDDO
70 WRITE(diag_mnc_bn,'(A)') 'pickup_diagnostics'
71
72 C Update the record dimension by writing the iteration number
73 CALL MNC_FILE_CLOSE_ALL_MATCHING(diag_mnc_bn, myThid)
74 CALL MNC_CW_SET_UDIM(diag_mnc_bn, 1, myThid)
75
76 C Read the qdiag() array
77 d_cw_name(1:NLEN) = dn_blnk(1:NLEN)
78 DO ii = 1,CW_DIMS
79 dn(ii)(1:NLEN) = dn_blnk(1:NLEN)
80 ENDDO
81 d_cw_name(1:10) = 'diag_state'
82 dn(1)(1:3) = 'Xp1'
83 dim(1) = sNx + 2*OLx
84 ib(1) = OLx + 1
85 ie(1) = OLx + sNx + 1
86 dn(2)(1:3) = 'Yp1'
87 dim(2) = sNy + 2*OLy
88 ib(2) = OLy + 1
89 ie(2) = OLy + sNy + 1
90 dn(3)(1:2) = 'Zd'
91 dim(3) = numdiags
92 ib(3) = 1
93 ie(3) = numdiags
94 dn(4)(1:1) = 'T'
95 dim(4) = -1
96 ib(4) = 1
97 ie(4) = 1
98 CALL MNC_CW_ADD_GNAME(d_cw_name, 4,
99 & dim, dn, ib, ie, myThid)
100 CALL MNC_CW_ADD_VNAME(d_cw_name, d_cw_name,
101 & 4,5, myThid)
102 CALL MNC_CW_RL_R('D',diag_mnc_bn,0,0,
103 & d_cw_name, qdiag, myThid)
104 CALL MNC_CW_DEL_VNAME(d_cw_name, myThid)
105 CALL MNC_CW_DEL_GNAME(d_cw_name, myThid)
106
107 C Read the ndiag() array
108 d_cw_name(1:NLEN) = dn_blnk(1:NLEN)
109 DO ii = 1,CW_DIMS
110 dn(ii)(1:NLEN) = dn_blnk(1:NLEN)
111 ENDDO
112 d_cw_name(1:10) = 'diag_count'
113 dn(1)(1:2) = 'Nd'
114 dim(1) = numdiags
115 ib(1) = 1
116 ie(1) = numdiags
117 dn(2)(1:1) = 'T'
118 dim(2) = -1
119 ib(2) = 1
120 ie(2) = 1
121 CALL MNC_CW_ADD_GNAME(d_cw_name, 2,
122 & dim, dn, ib, ie, myThid)
123 CALL MNC_CW_ADD_VNAME(d_cw_name, d_cw_name,
124 & 4,5, myThid)
125 CALL MNC_CW_ADD_VATTR_TEXT(d_cw_name,'description',
126 & 'diagnostics state',myThid)
127 C- jmc: get warnings when I compile this S/R because something is not right
128 C in the type or one or more arguments. commented out for now
129 c CALL MNC_CW_RL_R('I',diag_mnc_bn,0,0,
130 c & d_cw_name, ndiag, myThid)
131 CALL MNC_CW_DEL_VNAME(d_cw_name, myThid)
132 CALL MNC_CW_DEL_GNAME(d_cw_name, myThid)
133
134 ENDIF
135 #endif /* ALLOW_MNC */
136
137 #ifdef ALLOW_MDSIO
138 IF (diag_pickup_read_mdsio) THEN
139 _BEGIN_MASTER(myThid)
140
141 C Read qdiag()
142 DO i = 1,80
143 fn(i:i) = ' '
144 ENDDO
145 write(fn,'(A,I10.10)') 'pickup_qdiag', nIter0
146 CALL MDSREADFIELD(fn,readBinaryPrec,'RL',
147 & numdiags,qdiag,1,myThid)
148
149 C Read ndiag()
150 DO i = 1,80
151 fn(i:i) = ' '
152 ENDDO
153 WRITE(fn,'(A,I10.10)') 'pickup_ndiag.', nIter0
154 CALL MDSFINDUNIT( dUnit, mythid )
155 OPEN( dUnit, file=fn )
156 DO n = 1,nlists
157 DO m = 1,nfields(n)
158 READ(dUnit,'(I10)') ndiag(jdiag(m,n))
159 ENDDO
160 ENDDO
161 CLOSE( dUnit )
162 _END_MASTER(myThid)
163 ENDIF
164 #endif /* ALLOW_MDSIO */
165
166 ENDIF
167
168 #endif /* DIAGNOSTICS_HAS_PICKUP */
169
170
171 RETURN
172 END

  ViewVC Help
Powered by ViewVC 1.1.22