/[MITgcm]/MITgcm/pkg/cheapaml/cheapaml_write_pickup.F
ViewVC logotype

Contents of /MITgcm/pkg/cheapaml/cheapaml_write_pickup.F

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


Revision 1.10 - (show annotations) (download)
Sun Jan 13 22:46:38 2013 UTC (11 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64c, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.9: +4 -2 lines
- add missing value argument to S/R MDS_WR_METAFILES argument list

1 C $Header: /u/gcmpack/MITgcm/pkg/cheapaml/cheapaml_write_pickup.F,v 1.9 2012/12/23 20:18:01 jmc Exp $
2 C $Name: $
3
4 #include "CHEAPAML_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: CHEAPAML_WRITE_PICKUP
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE CHEAPAML_WRITE_PICKUP( permPickup,
11 & suff, myTime, myIter, myThid )
12
13 C !DESCRIPTION:
14 C Writes current state of cheapaml variables to a pickup file
15
16 C !USES: ===============================================================
17 IMPLICIT NONE
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "FFIELDS.h"
22 #include "CHEAPAML.h"
23
24 C !INPUT PARAMETERS: ===================================================
25 C permPickup :: write a permanent pickup
26 C suff :: suffix for pickup file (eg. ckptA or 0000000010)
27 C myTime :: model time
28 C myIter :: time-step number
29 C myThid :: thread number
30 LOGICAL permPickup
31 CHARACTER*(*) suff
32 _RL myTime
33 INTEGER myIter
34 INTEGER myThid
35
36 C !OUTPUT PARAMETERS: ==================================================
37 C none
38
39 #ifdef ALLOW_CHEAPAML
40
41 C === Functions ====
42 INTEGER ILNBLNK
43 EXTERNAL ILNBLNK
44
45 C !LOCAL VARIABLES: ====================================================
46 C j :: loop index / field number
47 C nj :: record number
48 C fp :: pickup-file precision
49 C glf :: local flag for "globalFiles"
50 C fn :: character buffer for creating filename
51 C nWrFlds :: number of fields being written
52 C listDim :: dimension of "wrFldList" local array
53 C wrFldList :: list of written fields
54 C msgBuf :: Informational/error message buffer
55 INTEGER j, nj, fp, lChar
56 LOGICAL glf
57 _RL timList(1)
58 CHARACTER*(MAX_LEN_FNAM) fn
59 INTEGER listDim, nWrFlds
60 PARAMETER( listDim = 12 )
61 CHARACTER*(8) wrFldList(listDim)
62 CHARACTER*(MAX_LEN_MBUF) msgBuf
63 CEOP
64
65 lChar = ILNBLNK(suff)
66 IF ( lChar.EQ.0 ) THEN
67 WRITE(fn,'(2A)') 'pickup_cheapaml'
68 ELSE
69 WRITE(fn,'(2A)') 'pickup_cheapaml.',suff(1:lChar)
70 ENDIF
71 fp = precFloat64
72 j = 0
73
74 C Firstly, write 3-D fields as consecutive records,
75
76 C record number < 0 : a hack not to write meta files now:
77
78 C- switch to 2-D fields:
79 nj = -j*Nr
80
81 j = j + 1
82 nj = nj-1
83 CALL WRITE_REC_3D_RL( fn, fp, 1,
84 & Tair, nj, myIter, myThid )
85 IF (j.LE.listDim) wrFldList(j) = 'Tair '
86 j = j + 1
87 nj = nj-1
88 CALL WRITE_REC_3D_RL( fn, fp, 1,
89 & gTairm, nj, myIter, myThid )
90 IF (j.LE.listDim) wrFldList(j) = 'gTairNm1'
91
92 IF (useFreshWaterFlux) THEN
93 j = j + 1
94 nj = nj-1
95 CALL WRITE_REC_3D_RL( fn, fp, 1,
96 & qair, nj, myIter, myThid )
97 IF (j.LE.listDim) wrFldList(j) = 'Qair '
98 j = j + 1
99 nj = nj-1
100 CALL WRITE_REC_3D_RL( fn, fp, 1,
101 & gqairm, nj, myIter, myThid )
102 IF (j.LE.listDim) wrFldList(j) = 'gQairNm1'
103 ENDIF
104
105 IF (useCheapTracer) THEN
106 j = j + 1
107 nj = nj-1
108 CALL WRITE_REC_3D_RL( fn, fp, 1,
109 & Cheaptracer, nj, myIter, myThid )
110 IF (j.LE.listDim) wrFldList(j) = 'cTracer '
111 j = j + 1
112 nj = nj-1
113 CALL WRITE_REC_3D_RL( fn, fp, 1,
114 & gCheaptracerm, nj, myIter, myThid )
115 IF (j.LE.listDim) wrFldList(j) = 'gTracNm1'
116 ENDIF
117
118 C--------------------------
119 nWrFlds = j
120 IF ( nWrFlds.GT.listDim ) THEN
121 WRITE(msgBuf,'(2A,I5,A)') 'CHEAPAML_WRITE_PICKUP: ',
122 & 'trying to write ',nWrFlds,' fields'
123 CALL PRINT_ERROR( msgBuf, myThid )
124 WRITE(msgBuf,'(2A,I5,A)') 'CHEAPAML_WRITE_PICKUP: ',
125 & 'field-list dimension (listDim=',listDim,') too small'
126 CALL PRINT_ERROR( msgBuf, myThid )
127 STOP 'ABNORMAL END: S/R CHEAPAML_WRITE_PICKUP (list-size Pb)'
128 ENDIF
129 #ifdef ALLOW_MDSIO
130 C uses this specific S/R to write (with more informations) only meta files
131 j = 1
132 nj = ABS(nj)
133 IF ( nWrFlds*Nr .EQ. nj ) THEN
134 j = Nr
135 nj = nWrFlds
136 ENDIF
137 glf = globalFiles
138 timList(1) = myTime
139 CALL MDS_WR_METAFILES( fn, fp, glf, .FALSE.,
140 & 0, 0, j, ' ',
141 & nWrFlds, wrFldList,
142 & 1, timList, oneRL,
143 & nj, myIter, myThid )
144 #endif /* ALLOW_MDSIO */
145 C--------------------------
146
147 #endif /* ALLOW_CHEAPAML */
148
149 RETURN
150 END

  ViewVC Help
Powered by ViewVC 1.1.22