/[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.13 - (hide annotations) (download)
Thu Feb 16 01:23:27 2012 UTC (12 years, 3 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint63j
Changes since 1.12: +2 -2 lines
- simple propagation of SItrNumInUse.

1 gforget 1.13 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_write_pickup.F,v 1.12 2012/02/03 13:34:32 gforget 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     #ifdef SEAICE_MULTICATEGORY
83     j = j + 1
84     nj = nj-1
85     CALL WRITE_REC_3D_RL(fn,fp,MULTDIM,TICES, nj, myIter, myThid )
86     IF (j.LE.listDim) wrFldList(j) = 'siTICES '
87     C- switch to 2-D fields:
88     nj = nj*MULTDIM
89     #else
90     j = j + 1
91     nj = nj-1
92     CALL WRITE_REC_3D_RL( fn, fp, 1, TICE , nj, myIter, myThid )
93     IF (j.LE.listDim) wrFldList(j) = 'siTICE '
94     #endif /* SEAICE_MULTICATEGORY */
95    
96     C--- continue to write 2-D fields:
97     j = j + 1
98     nj = nj-1
99 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, AREA , nj, myIter, myThid )
100 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siAREA '
101    
102     j = j + 1
103     nj = nj-1
104 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, HEFF , nj, myIter, myThid )
105 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siHEFF '
106    
107     j = j + 1
108     nj = nj-1
109     CALL WRITE_REC_3D_RL( fn, fp, 1, HSNOW , nj, myIter, myThid )
110     IF (j.LE.listDim) wrFldList(j) = 'siHSNOW '
111 ifenty 1.6 #ifdef SEAICE_VARIABLE_SALINITY
112 jmc 1.1 j = j + 1
113     nj = nj-1
114     CALL WRITE_REC_3D_RL( fn, fp, 1, HSALT , nj, myIter, myThid )
115     IF (j.LE.listDim) wrFldList(j) = 'siHSALT '
116     #endif
117 heimbach 1.8 #ifdef ALLOW_SITRACER
118 gforget 1.13 DO iTrac = 1, SItrNumInUse
119 heimbach 1.8 WRITE(fldName,'(A6,I2.2)') 'siTrac', iTrac
120 heimbach 1.11 j = j + 1
121     nj = nj-1
122     CALL WRITE_REC_3D_RL( fn, fp, 1,
123 heimbach 1.8 & SItracer(1-Olx,1-Oly,1,1,iTrac),
124 heimbach 1.11 & nj, myIter, myThid )
125     IF (j.LE.listDim) wrFldList(j) = fldName
126 heimbach 1.8 ENDDO
127     #endif
128 jmc 1.1 ENDIF
129    
130     C-- write Sea-Ice Dynamics variables (all 2-D fields):
131     j = j + 1
132     nj = nj-1
133 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, UICE , nj, myIter, myThid )
134 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siUICE '
135    
136     j = j + 1
137     nj = nj-1
138 mlosch 1.3 CALL WRITE_REC_3D_RL( fn, fp, 1, VICE , nj, myIter, myThid )
139 jmc 1.1 IF (j.LE.listDim) wrFldList(j) = 'siVICE '
140    
141     #if (defined(SEAICE_CGRID) && defined(SEAICE_ALLOW_EVP))
142     IF ( SEAICEuseEVP ) THEN
143     j = j + 1
144     nj = nj-1
145     CALL WRITE_REC_3D_RL( fn, fp, 1, seaice_sigma1,
146     & nj, myIter, myThid )
147     IF (j.LE.listDim) wrFldList(j) = 'siSigm1 '
148    
149     j = j + 1
150     nj = nj-1
151     CALL WRITE_REC_3D_RL( fn, fp, 1, seaice_sigma2,
152     & nj, myIter, myThid )
153     IF (j.LE.listDim) wrFldList(j) = 'siSigm2 '
154    
155     j = j + 1
156     nj = nj-1
157     CALL WRITE_REC_3D_RL( fn, fp, 1, seaice_sigma12,
158     & nj, myIter, myThid )
159     IF (j.LE.listDim) wrFldList(j) = 'siSigm12'
160     ENDIF
161     #endif /* SEAICE_ALLOW_EVP */
162    
163     nWrFlds = j
164     IF ( nWrFlds.GT.listDim ) THEN
165     WRITE(msgBuf,'(2A,I5,A)') 'WRITE_SEAICE_PICKUP: ',
166     & 'trying to write ',nWrFlds,' fields'
167     CALL PRINT_ERROR( msgBuf, myThid )
168     WRITE(msgBuf,'(2A,I5,A)') 'WRITE_SEAICE_PICKUP: ',
169     & 'field-list dimension (listDim=',listDim,') too small'
170     CALL PRINT_ERROR( msgBuf, myThid )
171     STOP 'ABNORMAL END: S/R WRITE_SEAICE_PICKUP (list-size Pb)'
172     ENDIF
173 heimbach 1.8
174 jmc 1.1 #ifdef ALLOW_MDSIO
175     C uses this specific S/R to write (with more informations) only meta files
176     nj = ABS(nj)
177     glf = globalFiles
178 jmc 1.7 timList(1) = myTime
179 jmc 1.1 CALL MDS_WR_METAFILES( fn, fp, glf, .FALSE.,
180     & 0, 0, 1, ' ',
181     & nWrFlds, wrFldList,
182 jmc 1.7 & 1, timList,
183 jmc 1.1 & nj, myIter, myThid )
184 heimbach 1.8 C
185 jmc 1.1 #endif /* ALLOW_MDSIO */
186     C--------------------------
187     c ENDIF
188    
189     RETURN
190     END

  ViewVC Help
Powered by ViewVC 1.1.22