/[MITgcm]/MITgcm_contrib/torge/itd/code/seaice_read_pickup.F
ViewVC logotype

Annotation of /MITgcm_contrib/torge/itd/code/seaice_read_pickup.F

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


Revision 1.3 - (hide annotations) (download)
Mon Jun 4 16:35:57 2012 UTC (13 years, 2 months ago) by torge
Branch: MAIN
Changes since 1.2: +25 -0 lines
adjusting pickup to work with ITD --- introducing seaice_itd_pickup.F (use pickup from single-category files to initialize multi-category variables assuming a log-normal distribution) --- remove some lines from seaice_init_varia.F and seaice_model.F now that pickup works

1 dimitri 1.1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_read_pickup.F,v 1.16 2012/03/05 15:21:44 gforget Exp $
2     C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SEAICE_READ_PICKUP
8     C !INTERFACE:
9     SUBROUTINE SEAICE_READ_PICKUP ( myThid )
10    
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | SUBROUTINE SEAICE_READ_PICKUP
14     C | o Read in sea ice pickup file for restarting.
15     C *==========================================================*
16     C \ev
17    
18     C !USES:
19     IMPLICIT NONE
20    
21     C == Global variables ===
22     #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "SEAICE_SIZE.h"
26     #include "SEAICE_PARAMS.h"
27     #include "SEAICE.h"
28     #include "SEAICE_TRACER.h"
29    
30     C !INPUT/OUTPUT PARAMETERS:
31     C == Routine arguments ==
32     C myThid :: My Thread Id. number
33     INTEGER myThid
34    
35     C !LOCAL VARIABLES:
36     C == Local variables ==
37     C fp :: pickup-file precision
38     C fn :: Temp. for building file name.
39     C filePrec :: pickup-file precision (read from meta file)
40     C nbFields :: number of fields in pickup file (read from meta file)
41     C missFldList :: List of missing fields (attempted to read but not found)
42     C missFldDim :: Dimension of missing fields list array: missFldList
43     C nMissing :: Number of missing fields (attempted to read but not found)
44     C nj :: record & field number
45     C ioUnit :: temp for writing msg unit
46     C msgBuf :: Informational/error message buffer
47     C i,j,k :: loop indices
48     C bi,bj :: tile indices
49     INTEGER fp
50     CHARACTER*(MAX_LEN_FNAM) fn
51     INTEGER filePrec, nbFields
52     INTEGER missFldDim, nMissing
53     PARAMETER( missFldDim = 20 )
54     CHARACTER*(8) missFldList(missFldDim)
55     INTEGER nj, ioUnit
56     CHARACTER*(MAX_LEN_MBUF) msgBuf
57     INTEGER i,j,k,bi,bj
58     #ifdef ALLOW_SITRACER
59     CHARACTER*(8) fldName
60     INTEGER iTrac
61     #endif
62     CEOP
63    
64     C--
65     IF (pickupSuff .EQ. ' ') THEN
66     WRITE(fn,'(A,I10.10)') 'pickup_seaice.',nIter0
67     ELSE
68     WRITE(fn,'(A,A10)') 'pickup_seaice.',pickupSuff
69     ENDIF
70     fp = precFloat64
71    
72     C Going to really do some IO. Make everyone except master thread wait.
73     _BARRIER
74    
75     c IF ( seaice_pickup_read_mdsio ) THEN
76    
77     C-- Read meta file (if exist) and prepare for reading Multi-Fields file
78     CALL READ_MFLDS_SET(
79     I fn,
80     O nbFields, filePrec,
81     I MULTDIM, nIter0, myThid )
82    
83     _BEGIN_MASTER( myThid )
84     IF ( nbFields.GE.0 .AND. filePrec.NE.fp ) THEN
85     WRITE(msgBuf,'(2A,I4)') 'SEAICE_READ_PICKUP: ',
86     & 'pickup-file binary precision do not match !'
87     CALL PRINT_ERROR( msgBuf, myThid )
88     WRITE(msgBuf,'(A,2(A,I4))') 'SEAICE_READ_PICKUP: ',
89     & 'file prec.=', filePrec, ' but expecting prec.=', fp
90     CALL PRINT_ERROR( msgBuf, myThid )
91     STOP 'ABNORMAL END: S/R SEAICE_READ_PICKUP (data-prec Pb)'
92     ENDIF
93     _END_MASTER( myThid )
94    
95     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
96    
97     IF ( nbFields.LE.0 ) THEN
98     C- No meta-file or old meta-file without List of Fields
99     ioUnit = errorMessageUnit
100     IF ( pickupStrictlyMatch ) THEN
101     WRITE(msgBuf,'(4A)') 'SEAICE_READ_PICKUP: ',
102     & 'no field-list found in meta-file',
103     & ' => cannot check for strict-matching'
104     CALL PRINT_ERROR( msgBuf, myThid )
105     WRITE(msgBuf,'(4A)') 'SEAICE_READ_PICKUP: ',
106     & 'try with " pickupStrictlyMatch=.FALSE.,"',
107     & ' in file: "data", NameList: "PARM03"'
108     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
109     STOP 'ABNORMAL END: S/R SEAICE_READ_PICKUP'
110     ELSE
111     WRITE(msgBuf,'(4A)') 'WARNING >> SEAICE_READ_PICKUP: ',
112     & ' no field-list found'
113     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
114     IF ( nbFields.EQ.-1 ) THEN
115     C- No meta-file
116     WRITE(msgBuf,'(4A)') 'WARNING >> ',
117     & ' try to read pickup as currently written'
118     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
119     ELSE
120     C- Old meta-file without List of Fields
121     WRITE(msgBuf,'(4A)') 'WARNING >> ',
122     & ' try to read pickup as it used to be written'
123     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
124     WRITE(msgBuf,'(4A)') 'WARNING >> ',
125     & ' until checkpoint59j (2007 Nov 25)'
126     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
127     ENDIF
128     ENDIF
129     ENDIF
130    
131     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
132    
133     C--- Old way to read seaice fields:
134     IF ( nbFields.EQ.0 ) THEN
135    
136     C-- Read ice model fields
137     nj = 1
138     IF (SEAICE_multDim.GT.1) THEN
139     CALL READ_REC_3D_RL(fn,fp,MULTDIM,TICES,nj,nIter0,myThid)
140     nj = nj + MULTDIM
141     ELSE
142     CALL READ_REC_3D_RL(fn,fp,1,TICE,nj,nIter0,myThid)
143     nj = nj + 1
144     ENDIF
145     c CALL READ_REC_3D_RL( fn, fp, 1, YNEG , nj, nIter0, myThid )
146     nj = nj + 1
147     CALL READ_REC_3D_RL( fn, fp, 1, HSNOW , nj, nIter0, myThid )
148     nj = nj + 1
149     CALL READ_REC_3D_RL( fn, fp, 1, UICE , nj, nIter0, myThid )
150     nj = nj + 3
151     CALL READ_REC_3D_RL( fn, fp, 1, VICE , nj, nIter0, myThid )
152     nj = nj + 3
153     CALL READ_REC_3D_RL( fn, fp, 1, HEFF , nj, nIter0, myThid )
154     nj = nj + 3
155     CALL READ_REC_3D_RL( fn, fp, 1, AREA , nj, nIter0, myThid )
156     nj = nj + 3
157 torge 1.3 #ifdef SEAICE_ITD
158     C-- no ITD information available with old pickup files
159     C use log-normal distribution based on mean thickness instead
160     CALL SEAICE_ITD_PICKUP( nIter0, myThid )
161     #endif
162 dimitri 1.1 #if (defined(SEAICE_CGRID) && defined(SEAICE_ALLOW_EVP))
163     IF ( SEAICEuseEVP .AND. SEAICEuseEVPpickup ) THEN
164     CALL READ_REC_3D_RL(fn,fp,1,seaice_sigma1,nj, nIter0, myThid )
165     nj = nj + 1
166     CALL READ_REC_3D_RL(fn,fp,1,seaice_sigma2,nj, nIter0, myThid )
167     nj = nj + 1
168     CALL READ_REC_3D_RL(fn,fp,1,seaice_sigma12,nj,nIter0, myThid )
169     nj = nj + 1
170     ENDIF
171     #endif /* SEAICE_ALLOW_EVP */
172     #ifdef SEAICE_VARIABLE_SALINITY
173     CALL READ_REC_3D_RL( fn, fp, 1, HSALT , nj, nIter0, myThid )
174     nj = nj + 1
175     #endif
176    
177     ELSE
178     C--- New way to read model fields:
179     nj = 0
180     C-- read Sea-Ice Thermodynamics State variables, starting with 3-D fields:
181     IF ( .NOT.useThSIce ) THEN
182     IF (SEAICE_multDim.GT.1) THEN
183     CALL READ_MFLDS_3D_RL( 'siTICES ', TICES,
184     & nj, fp, MULTDIM, nIter0, myThid )
185     nj = nj*MULTDIM
186     IF ( nj.EQ.0 ) THEN
187     CALL READ_MFLDS_3D_RL( 'siTICE ', TICE,
188     & nj, fp, 1, nIter0, myThid )
189     ENDIF
190     ELSE
191     CALL READ_MFLDS_3D_RL( 'siTICE ', TICE,
192     & nj, fp, 1, nIter0, myThid )
193     C map to TICES(1)
194     DO bj=myByLo(myThid),myByHi(myThid)
195     DO bi=myBxLo(myThid),myBxHi(myThid)
196     DO k=1,MULTDIM
197     DO j=1-OLy,sNy+OLy
198     DO i=1-OLx,sNx+OLx
199     TICES(i,j,k,bi,bj) = TICE(i,j,bi,bj)
200     ENDDO
201     ENDDO
202     ENDDO
203     ENDDO
204     ENDDO
205    
206     IF ( nj.EQ.0 ) THEN
207     CALL READ_MFLDS_3D_RL( 'siTICES ', TICE,
208     & nj, fp, 1, nIter0, myThid )
209     ENDIF
210     ENDIF
211     C-- continue with 2-D fields:
212 torge 1.3 #ifdef SEAICE_ITD
213     CALL READ_MFLDS_3D_RL( 'siAREAn ', AREAITD,
214     & nj, fp, nITD, nIter0, myThid )
215     IF ( nj.EQ.0 ) THEN
216     C no multi-category fields available
217     C -> read average fields ...
218     #endif
219 dimitri 1.1 CALL READ_MFLDS_3D_RL( 'siAREA ', AREA,
220     & nj, fp, 1, nIter0, myThid )
221     CALL READ_MFLDS_3D_RL( 'siHEFF ', HEFF,
222     & nj, fp, 1, nIter0, myThid )
223     CALL READ_MFLDS_3D_RL( 'siHSNOW ', HSNOW,
224     & nj, fp, 1, nIter0, myThid )
225 torge 1.3 #ifdef SEAICE_ITD
226     C ... and redistribute over categories
227     C assuming a log-normal distribtuion
228     CALL SEAICE_ITD_PICKUP( nIter0, myThid )
229     C
230     ELSE
231     C multi-category fields available, continue reading
232     CALL READ_MFLDS_3D_RL( 'siHEFFn ', HEFFITD,
233     & nj, fp, nITD, nIter0, myThid )
234     CALL READ_MFLDS_3D_RL( 'siHSNOWn ', HSNOWITD,
235     & nj, fp, nITD, nIter0, myThid )
236     ENDIF
237     #endif
238 dimitri 1.1 #ifdef SEAICE_VARIABLE_SALINITY
239     CALL READ_MFLDS_3D_RL( 'siHSALT ', HSALT,
240     & nj, fp, 1, nIter0, myThid )
241     #endif
242     #ifdef ALLOW_SITRACER
243     DO iTrac = 1, SItrNumInUse
244     WRITE(fldName,'(A6,I2.2)') 'siTrac', iTrac
245     CALL READ_MFLDS_3D_RL( fldName,
246     & SItracer(1-OLx,1-OLy,1,1,iTrac),
247     & nj, fp, 1, nIter0, myThid )
248     _EXCH_XY_RL(SItracer(1-OLx,1-OLy,1,1,iTrac),myThid)
249     ENDDO
250     #endif /* ALLOW_SITRACER */
251    
252     ENDIF
253    
254     C-- read Sea-Ice Dynamics variables (all 2-D fields):
255     CALL READ_MFLDS_3D_RL( 'siUICE ', UICE,
256     & nj, fp, 1, nIter0, myThid )
257     CALL READ_MFLDS_3D_RL( 'siVICE ', VICE,
258     & nj, fp, 1, nIter0, myThid )
259     #if (defined(SEAICE_CGRID) && defined(SEAICE_ALLOW_EVP))
260     IF ( SEAICEuseEVP ) THEN
261     CALL READ_MFLDS_3D_RL( 'siSigm1 ', seaice_sigma1,
262     & nj, fp, 1, nIter0, myThid )
263     CALL READ_MFLDS_3D_RL( 'siSigm2 ', seaice_sigma2,
264     & nj, fp, 1, nIter0, myThid )
265     CALL READ_MFLDS_3D_RL( 'siSigm12', seaice_sigma12,
266     & nj, fp, 1, nIter0, myThid )
267     ENDIF
268     #endif /* SEAICE_CGRID & SEAICE_ALLOW_EVP */
269    
270     C--- end: new way to read pickup file
271     ENDIF
272    
273     C-- Check for missing fields:
274     nMissing = missFldDim
275     CALL READ_MFLDS_CHECK(
276     O missFldList,
277     U nMissing,
278     I nIter0, myThid )
279     IF ( nMissing.GT.missFldDim ) THEN
280     WRITE(msgBuf,'(2A,I4)') 'SEAICE_READ_PICKUP: ',
281     & 'missing fields list has been truncated to', missFldDim
282     CALL PRINT_ERROR( msgBuf, myThid )
283     STOP 'ABNORMAL END: S/R SEAICE_READ_PICKUP (list-size Pb)'
284     ENDIF
285     CALL SEAICE_CHECK_PICKUP(
286     I missFldList,
287     I nMissing, nbFields,
288     I nIter0, myThid )
289    
290     C-- end: seaice_pickup_read_mdsio
291     c ENDIF
292    
293     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
294    
295     C-- Update overlap regions
296     CALL EXCH_UV_XY_RL( uIce, vIce,.TRUE.,myThid)
297     _EXCH_XY_RL( HEFF, myThid )
298     _EXCH_XY_RL( AREA, myThid )
299     CALL EXCH_3D_RL ( TICES, MULTDIM, myThid )
300     _EXCH_XY_RL(TICE , myThid )
301     c _EXCH_XY_RL(YNEG , myThid )
302     _EXCH_XY_RL(HSNOW, myThid )
303     #if (defined(SEAICE_CGRID) && defined(SEAICE_ALLOW_EVP))
304     IF ( SEAICEuseEVP ) THEN
305     _EXCH_XY_RL(seaice_sigma1 , myThid )
306     _EXCH_XY_RL(seaice_sigma2 , myThid )
307     _EXCH_XY_RL(seaice_sigma12, myThid )
308     ENDIF
309     #endif /* SEAICE_CGRID SEAICE_ALLOW_EVP */
310     #ifdef SEAICE_VARIABLE_SALINITY
311     _EXCH_XY_RL(HSALT, myThid )
312     #endif
313    
314     RETURN
315     END

  ViewVC Help
Powered by ViewVC 1.1.22