/[MITgcm]/MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_read_pickup.F
ViewVC logotype

Annotation of /MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_read_pickup.F

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


Revision 1.2 - (hide annotations) (download)
Fri Jan 22 16:09:34 2016 UTC (9 years, 5 months ago) by dgoldberg
Branch: MAIN
Changes since 1.1: +1 -1 lines
New verification now includes grounding line

1 dgoldberg 1.2 C $Header: /u/gcmpack/MITgcm_contrib/shelfice_remeshing/CLEAN/code/shelfice_read_pickup.F,v 1.4 2016/01/22 10:26:50 dgoldberg Exp $
2 dgoldberg 1.1 C $Name: $
3    
4     #include "SHELFICE_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP
8     C !ROUTINE: SHELFICE_READ_PICKUP
9    
10     C !INTERFACE:
11     SUBROUTINE SHELFICE_READ_PICKUP( myThid )
12    
13     C !DESCRIPTION:
14     C Reads current state of SHELFICE from a pickup file
15    
16     C !USES:
17     IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "SHELFICE.h"
22    
23     C !INPUT PARAMETERS:
24     C myIter :: time-step number
25     C myThid :: thread number
26     INTEGER myIter
27     INTEGER myThid
28    
29     #ifdef ALLOW_SHELFICE
30     C !LOCAL VARIABLES:
31     C fn :: character buffer for creating filename
32     C fp :: precision of pickup files
33     C filePrec :: pickup-file precision (read from meta file)
34     C nbFields :: number of fields in pickup file (read from meta file)
35     C missFldList :: List of missing fields (attempted to read but not found)
36     C missFldDim :: Dimension of missing fields list array: missFldList
37     C nMissing :: Number of missing fields (attempted to read but not found)
38     C j :: loop index
39     C nj :: record number
40     C ioUnit :: temp for writing msg unit
41     C msgBuf :: Informational/error message buffer
42     INTEGER fp
43     INTEGER filePrec, nbFields
44     INTEGER missFldDim, nMissing
45     INTEGER j, nj, ioUnit
46     PARAMETER( missFldDim = 12 )
47     CHARACTER*(MAX_LEN_FNAM) fn
48     CHARACTER*(8) missFldList(missFldDim)
49     CHARACTER*(MAX_LEN_MBUF) msgBuf
50     CEOP
51    
52     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
53    
54     IF ( pickupSuff.EQ.' ' ) THEN
55     WRITE(fn,'(A,I10.10)') 'pickup_shelfice.',nIter0
56     ELSE
57     WRITE(fn,'(A,A10)') 'pickup_shelfice.',pickupSuff
58     ENDIF
59     fp = precFloat64
60    
61     CALL READ_MFLDS_SET(
62     I fn,
63     O nbFields, filePrec,
64     I Nr, nIter0, myThid )
65    
66     _BEGIN_MASTER( myThid )
67     IF ( nbFields.GE.0 .AND. filePrec.NE.fp ) THEN
68     WRITE(msgBuf,'(2A,I4)') 'SHELFICE_READ_PICKUP: ',
69     & 'pickup-file binary precision do not match !'
70     CALL PRINT_ERROR( msgBuf, myThid )
71     WRITE(msgBuf,'(A,2(A,I4))') 'SHELFICE_READ_PICKUP: ',
72     & 'file prec.=', filePrec, ' but expecting prec.=', fp
73     CALL PRINT_ERROR( msgBuf, myThid )
74     CALL ALL_PROC_DIE( 0 )
75     STOP 'ABNORMAL END: S/R SHELFICE_READ_PICKUP (data-prec Pb)'
76     ENDIF
77     _END_MASTER( myThid )
78    
79     IF ( nbFields.LE.0 ) THEN
80     C- No meta-file or old meta-file without List of Fields
81     ioUnit = errorMessageUnit
82     IF ( pickupStrictlyMatch ) THEN
83     WRITE(msgBuf,'(4A)') 'SHELFICE_READ_PICKUP: ',
84     & 'no field-list found in meta-file',
85     & ' => cannot check for strick-matching'
86     CALL PRINT_ERROR( msgBuf, myThid )
87     WRITE(msgBuf,'(4A)') 'SHELFICE_READ_PICKUP: ',
88     & 'try with " pickupStrictlyMatch=.FALSE.,"',
89     & ' in file: "data", NameList: "PARM03"'
90     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
91     CALL ALL_PROC_DIE( myThid )
92     STOP 'ABNORMAL END: S/R SHELFICE_READ_PICKUP'
93     ELSE
94     WRITE(msgBuf,'(4A)') 'WARNING >> SHELFICE_READ_PICKUP: ',
95     & ' no field-list found'
96     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
97     IF ( nbFields.EQ.-1 ) THEN
98     C- No meta-file
99     WRITE(msgBuf,'(4A)') 'WARNING >> ',
100     & ' try to read pickup as currently written'
101     CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
102     ELSE
103     C- Old meta-file without List of Fields
104     c WRITE(msgBuf,'(4A)') 'WARNING >> ',
105     c & ' try to read pickup as it used to be written'
106     c CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
107     c WRITE(msgBuf,'(4A)') 'WARNING >> ',
108     c & ' until checkpoint59l (2007 Dec 17)'
109     c CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
110     WRITE(msgBuf,'(4A)') 'SHELFICE_READ_PICKUP: ',
111     & 'no field-list found in meta-file'
112     CALL PRINT_ERROR( msgBuf, myThid )
113     CALL ALL_PROC_DIE( myThid )
114     STOP 'ABNORMAL END: S/R SHELFICE_READ_PICKUP'
115     ENDIF
116     ENDIF
117     ENDIF
118    
119     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
120    
121     IF ( nbFields.EQ.0 ) THEN
122     C--- Old way to read pickup:
123    
124     ELSE
125     C--- New way to read SHELFICE pickup:
126     nj = 0
127     C--- read SHELFICE 3-D fields for restart
128     nj = nj*Nr
129     C--- read STREAMICE 2-D fields for restart
130    
131     CALL READ_MFLDS_3D_RL( 'SHI_mass', shelfIceMass,
132     & nj, fp, 1 , myIter, myThid )
133     CALL READ_MFLDS_3D_RL( 'SHI_Rshelfice', R_shelfice,
134     & nj, fp, 1 , myIter, myThid )
135    
136     C-- end: new way to read pickup file
137     ENDIF
138    
139     C-- Check for missing fields:
140     nMissing = missFldDim
141     CALL READ_MFLDS_CHECK(
142     O missFldList,
143     U nMissing,
144     I myIter, myThid )
145     IF ( nMissing.GT.missFldDim ) THEN
146     WRITE(msgBuf,'(2A,I4)') 'SHELFICE_READ_PICKUP: ',
147     & 'missing fields list has been truncated to', missFldDim
148     CALL PRINT_ERROR( msgBuf, myThid )
149     CALL ALL_PROC_DIE( myThid )
150     STOP 'ABNORMAL END: S/R SHELFICE_READ_PICKUP (list-size Pb)'
151     ENDIF
152     IF ( nMissing.GE.1 ) THEN
153     ioUnit = errorMessageUnit
154     DO j=1,nMissing
155     WRITE(msgBuf,'(4A)') 'SHELFICE_READ_PICKUP: ',
156     & 'cannot restart without field "',missFldList(nj),'"'
157     CALL PRINT_ERROR( msgBuf, myThid )
158     ENDDO
159     CALL ALL_PROC_DIE( myThid )
160     STOP 'ABNORMAL END: S/R SHELFICE_READ_PICKUP'
161     ENDIF
162    
163     C-- Update overlap regions:
164    
165     CALL EXCH_XY_RL( shelfIceMass, myThid )
166    
167    
168     c CALL EXCH_XY_RL( myPa_Surf2, myThid )
169    
170     #endif /* ALLOW_SHELFICE */
171    
172     RETURN
173     END

  ViewVC Help
Powered by ViewVC 1.1.22