/[MITgcm]/MITgcm/pkg/seaice/seaice_write_pickup.F
ViewVC logotype

Annotation of /MITgcm/pkg/seaice/seaice_write_pickup.F

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


Revision 1.17 - (hide annotations) (download)
Fri May 3 19:29:24 2013 UTC (11 years, 1 month ago) by torge
Branch: MAIN
Changes since 1.16: +11 -12 lines
correcting bug with nj counters in ITD case

1 torge 1.17 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_write_pickup.F,v 1.16 2013/01/13 22:46:38 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SEAICE_WRITE_PICKUP
8     C !INTERFACE:
9     SUBROUTINE SEAICE_WRITE_PICKUP ( permPickup, suff,
10     I myTime, myIter, myThid )
11    
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | SUBROUTINE SEAICE_WRITE_PICKUP
15     C | o Write sea ice pickup file for restarting.
16     C *==========================================================*
17     C \ev
18    
19     C !USES:
20     IMPLICIT NONE
21    
22     C == Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26 heimbach 1.4 #include "SEAICE_SIZE.h"
27 jmc 1.1 #include "SEAICE_PARAMS.h"
28     #include "SEAICE.h"
29 heimbach 1.4 #include "SEAICE_TRACER.h"
30 jmc 1.1
31     C !INPUT/OUTPUT PARAMETERS:
32     C == Routine arguments ==
33     C permPickup :: write a permanent pickup
34     C suff :: suffix for pickup file (eg. ckptA or 0000000010)
35     C myTime :: Current time in simulation
36     C myIter :: Current iteration number in simulation
37     C myThid :: My Thread Id number
38     LOGICAL permPickup
39     CHARACTER*(*) suff
40     _RL myTime
41     INTEGER myIter
42     INTEGER myThid
43    
44     C !LOCAL VARIABLES:
45     C == Local variables ==
46     C fp :: pickup-file precision ( precFloat64 )
47     C glf :: local flag for "globalFiles"
48     C fn :: Temp. for building file name.
49     C nWrFlds :: number of fields being written
50     C listDim :: dimension of "wrFldList" local array
51     C wrFldList :: list of written fields
52     C j :: loop index / field number
53     C nj :: record number
54     C msgBuf :: Informational/error message buffer
55     INTEGER fp
56     LOGICAL glf
57 jmc 1.7 _RL timList(1)
58 jmc 1.1 CHARACTER*(MAX_LEN_FNAM) fn
59     INTEGER listDim, nWrFlds
60     PARAMETER( listDim = 20 )
61 jmc 1.5 CHARACTER*(8) wrFldList(listDim)
62     INTEGER j, nj
63 jmc 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
64 gforget 1.12 #ifdef ALLOW_SITRACER
65 jmc 1.5 CHARACTER*(8) fldName
66 heimbach 1.8 INTEGER iTrac
67 jmc 1.5 #endif
68 jmc 1.1 CEOP
69    
70     C-- Write model fields
71     WRITE(fn,'(A,A)') 'pickup_seaice.',suff
72    
73     c IF ( seaice_pickup_write_mdsio ) THEN
74    
75     fp = precFloat64
76     j = 0
77     nj = 0
78     C record number < 0 : a hack not to write meta files now:
79    
80     C-- write Sea-Ice Thermodynamics State variables, starting with 3-D fields:
81     IF ( .NOT.useThSIce ) THEN
82 torge 1.17 j = j + 1
83     nj = nj-1
84 gforget 1.14 IF (SEAICE_multDim.GT.1) THEN
85     CALL WRITE_REC_3D_RL(fn,fp,MULTDIM,TICES, nj, myIter, myThid )
86     IF (j.LE.listDim) wrFldList(j) = 'siTICES '
87 jmc 1.1 C- switch to 2-D fields:
88 torge 1.17 c nj = nj*MULTDIM
89     nj = nj-MULTDIM+1
90 gforget 1.14 ELSE
91     CALL WRITE_REC_3D_RL( fn, fp, 1, TICE , nj, myIter, myThid )
92     IF (j.LE.listDim) wrFldList(j) = 'siTICE '
93     ENDIF
94 jmc 1.1
95     C--- continue to write 2-D fields:
96     j = j + 1
97 torge 1.17 nj = nj-1
98 heimbach 1.15 #ifdef SEAICE_ITD
99     CALL WRITE_REC_3D_RL(fn, fp, nITD, AREAITD , nj, myIter, myThid)
100     IF (j.LE.listDim) wrFldList(j) = 'siAREAn '
101 torge 1.17 nj = nj-nITD+1
102 heimbach 1.15 #else
103 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, AREA , nj, myIter, myThid )
104 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siAREA '
105 heimbach 1.15 #endif
106 jmc 1.1
107     j = j + 1
108 torge 1.17 nj = nj-1
109 heimbach 1.15 #ifdef SEAICE_ITD
110     CALL WRITE_REC_3D_RL(fn, fp, nITD, HEFFITD , nj, myIter, myThid)
111     IF (j.LE.listDim) wrFldList(j) = 'siHEFFn '
112 torge 1.17 nj = nj-nITD+1
113 heimbach 1.15 #else
114 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, HEFF , nj, myIter, myThid )
115 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siHEFF '
116 heimbach 1.15 #endif
117 jmc 1.1
118     j = j + 1
119 torge 1.17 nj = nj-1
120 heimbach 1.15 #ifdef SEAICE_ITD
121     CALL WRITE_REC_3D_RL(fn, fp, nITD, HSNOWITD, nj, myIter, myThid)
122     IF (j.LE.listDim) wrFldList(j) = 'siHSNOWn'
123 torge 1.17 nj = nj-nITD+1
124 heimbach 1.15 #else
125 jmc 1.1 CALL WRITE_REC_3D_RL( fn, fp, 1, HSNOW , nj, myIter, myThid )
126     IF (j.LE.listDim) wrFldList(j) = 'siHSNOW '
127 heimbach 1.15 #endif
128 ifenty 1.6 #ifdef SEAICE_VARIABLE_SALINITY
129 jmc 1.1 j = j + 1
130     nj = nj-1
131     CALL WRITE_REC_3D_RL( fn, fp, 1, HSALT , nj, myIter, myThid )
132     IF (j.LE.listDim) wrFldList(j) = 'siHSALT '
133     #endif
134 heimbach 1.8 #ifdef ALLOW_SITRACER
135 gforget 1.13 DO iTrac = 1, SItrNumInUse
136 heimbach 1.8 WRITE(fldName,'(A6,I2.2)') 'siTrac', iTrac
137 heimbach 1.11 j = j + 1
138     nj = nj-1
139     CALL WRITE_REC_3D_RL( fn, fp, 1,
140 jmc 1.16 & SItracer(1-OLx,1-OLy,1,1,iTrac),
141 heimbach 1.11 & nj, myIter, myThid )
142     IF (j.LE.listDim) wrFldList(j) = fldName
143 heimbach 1.8 ENDDO
144     #endif
145 jmc 1.1 ENDIF
146    
147     C-- write Sea-Ice Dynamics variables (all 2-D fields):
148     j = j + 1
149     nj = nj-1
150 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, UICE , nj, myIter, myThid )
151 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siUICE '
152    
153     j = j + 1
154     nj = nj-1
155 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, VICE , nj, myIter, myThid )
156 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siVICE '
157    
158     #if (defined(SEAICE_CGRID) && defined(SEAICE_ALLOW_EVP))
159     IF ( SEAICEuseEVP ) THEN
160     j = j + 1
161     nj = nj-1
162     CALL WRITE_REC_3D_RL( fn, fp, 1, seaice_sigma1,
163     & nj, myIter, myThid )
164     IF (j.LE.listDim) wrFldList(j) = 'siSigm1 '
165    
166     j = j + 1
167     nj = nj-1
168     CALL WRITE_REC_3D_RL( fn, fp, 1, seaice_sigma2,
169     & nj, myIter, myThid )
170     IF (j.LE.listDim) wrFldList(j) = 'siSigm2 '
171    
172     j = j + 1
173     nj = nj-1
174     CALL WRITE_REC_3D_RL( fn, fp, 1, seaice_sigma12,
175     & nj, myIter, myThid )
176     IF (j.LE.listDim) wrFldList(j) = 'siSigm12'
177     ENDIF
178     #endif /* SEAICE_ALLOW_EVP */
179    
180     nWrFlds = j
181     IF ( nWrFlds.GT.listDim ) THEN
182     WRITE(msgBuf,'(2A,I5,A)') 'WRITE_SEAICE_PICKUP: ',
183     & 'trying to write ',nWrFlds,' fields'
184     CALL PRINT_ERROR( msgBuf, myThid )
185     WRITE(msgBuf,'(2A,I5,A)') 'WRITE_SEAICE_PICKUP: ',
186     & 'field-list dimension (listDim=',listDim,') too small'
187     CALL PRINT_ERROR( msgBuf, myThid )
188     STOP 'ABNORMAL END: S/R WRITE_SEAICE_PICKUP (list-size Pb)'
189     ENDIF
190 heimbach 1.8
191 jmc 1.1 #ifdef ALLOW_MDSIO
192     C uses this specific S/R to write (with more informations) only meta files
193     nj = ABS(nj)
194     glf = globalFiles
195 jmc 1.7 timList(1) = myTime
196 jmc 1.1 CALL MDS_WR_METAFILES( fn, fp, glf, .FALSE.,
197     & 0, 0, 1, ' ',
198     & nWrFlds, wrFldList,
199 jmc 1.16 & 1, timList, oneRL,
200 jmc 1.1 & nj, myIter, myThid )
201 heimbach 1.8 C
202 jmc 1.1 #endif /* ALLOW_MDSIO */
203     C--------------------------
204     c ENDIF
205    
206     RETURN
207     END

  ViewVC Help
Powered by ViewVC 1.1.22