/[MITgcm]/MITgcm/pkg/atm_phys/atm_phys_read_pickup.F
ViewVC logotype

Contents of /MITgcm/pkg/atm_phys/atm_phys_read_pickup.F

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


Revision 1.1 - (show annotations) (download)
Wed May 8 22:14:14 2013 UTC (11 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64o, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64n, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65d, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint65, checkpoint64j, checkpoint64m, checkpoint64l
add source code for new pkg "atm_phys" (atmospheric physics pkg
  from P. O'Gorman and T. Schneider, JCl, 2008).

1 C $Header: /u/gcmpack/MITgcm/pkg/mypackage/mypackage_read_pickup.F,v 1.5 2012/04/03 00:20:14 jmc Exp $
2 C $Name: $
3
4 #include "ATM_PHYS_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: ATM_PHYS_READ_PICKUP
9
10 C !INTERFACE:
11 SUBROUTINE ATM_PHYS_READ_PICKUP( myIter, myThid )
12
13 C !DESCRIPTION:
14 C Reads current state of Atm_Phys 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 "ATM_PHYS_PARAMS.h"
22 #include "ATM_PHYS_VARS.h"
23
24 C !INPUT PARAMETERS:
25 C myIter :: time-step number
26 C myThid :: thread number
27 INTEGER myIter
28 INTEGER myThid
29
30 #ifdef ALLOW_ATM_PHYS
31
32 C !LOCAL VARIABLES:
33 C fn :: character buffer for creating filename
34 C fp :: precision of pickup files
35 C filePrec :: pickup-file precision (read from meta file)
36 C nbFields :: number of fields in pickup file (read from meta file)
37 C missFldList :: List of missing fields (attempted to read but not found)
38 C missFldDim :: Dimension of missing fields list array: missFldList
39 C nMissing :: Number of missing fields (attempted to read but not found)
40 C j :: loop index
41 C nj :: record number
42 C ioUnit :: temp for writing msg unit
43 C msgBuf :: Informational/error message buffer
44 INTEGER fp
45 INTEGER filePrec, nbFields
46 INTEGER missFldDim, nMissing
47 INTEGER j, nj, ioUnit
48 PARAMETER( missFldDim = 12 )
49 CHARACTER*(MAX_LEN_FNAM) fn
50 CHARACTER*(8) missFldList(missFldDim)
51 CHARACTER*(MAX_LEN_MBUF) msgBuf
52 CEOP
53
54 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
55
56 IF ( pickupSuff.EQ.' ' ) THEN
57 WRITE(fn,'(A,I10.10)') 'pickup_atmPhys.',myIter
58 ELSE
59 WRITE(fn,'(A,A10)') 'pickup_atmPhys.',pickupSuff
60 ENDIF
61 fp = precFloat64
62
63 CALL READ_MFLDS_SET(
64 I fn,
65 O nbFields, filePrec,
66 I Nr, myIter, myThid )
67 _BEGIN_MASTER( myThid )
68 c IF ( filePrec.NE.0 .AND. filePrec.NE.fp ) THEN
69 IF ( nbFields.GE.0 .AND. filePrec.NE.fp ) THEN
70 WRITE(msgBuf,'(2A,I4)') 'ATM_PHYS_READ_PICKUP: ',
71 & 'pickup-file binary precision do not match !'
72 CALL PRINT_ERROR( msgBuf, myThid )
73 WRITE(msgBuf,'(A,2(A,I4))') 'ATM_PHYS_READ_PICKUP: ',
74 & 'file prec.=', filePrec, ' but expecting prec.=', fp
75 CALL PRINT_ERROR( msgBuf, myThid )
76 CALL ALL_PROC_DIE( 0 )
77 STOP 'ABNORMAL END: S/R ATM_PHYS_READ_PICKUP (data-prec Pb)'
78 ENDIF
79 _END_MASTER( myThid )
80
81 IF ( nbFields.LE.0 ) THEN
82 C- No meta-file or old meta-file without List of Fields
83 ioUnit = errorMessageUnit
84 IF ( pickupStrictlyMatch ) THEN
85 WRITE(msgBuf,'(4A)') 'ATM_PHYS_READ_PICKUP: ',
86 & 'no field-list found in meta-file',
87 & ' => cannot check for strick-matching'
88 CALL PRINT_ERROR( msgBuf, myThid )
89 WRITE(msgBuf,'(4A)') 'ATM_PHYS_READ_PICKUP: ',
90 & 'try with " pickupStrictlyMatch=.FALSE.,"',
91 & ' in file: "data", NameList: "PARM03"'
92 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
93 CALL ALL_PROC_DIE( myThid )
94 STOP 'ABNORMAL END: S/R ATM_PHYS_READ_PICKUP'
95 ELSE
96 WRITE(msgBuf,'(4A)') 'WARNING >> ATM_PHYS_READ_PICKUP: ',
97 & ' no field-list found'
98 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
99 IF ( nbFields.EQ.-1 ) THEN
100 C- No meta-file
101 WRITE(msgBuf,'(4A)') 'WARNING >> ',
102 & ' try to read pickup as currently written'
103 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
104 ELSE
105 C- Old meta-file without List of Fields
106 c WRITE(msgBuf,'(4A)') 'WARNING >> ',
107 c & ' try to read pickup as it used to be written'
108 c CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
109 c WRITE(msgBuf,'(4A)') 'WARNING >> ',
110 c & ' until checkpoint59l (2007 Dec 17)'
111 c CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
112 WRITE(msgBuf,'(4A)') 'ATM_PHYS_READ_PICKUP: ',
113 & 'no field-list found in meta-file'
114 CALL PRINT_ERROR( msgBuf, myThid )
115 CALL ALL_PROC_DIE( myThid )
116 STOP 'ABNORMAL END: S/R ATM_PHYS_READ_PICKUP'
117 ENDIF
118 ENDIF
119 ENDIF
120
121 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122
123 IF ( nbFields.EQ.0 ) THEN
124 C--- Old way to read pickup:
125
126 ELSE
127 C--- New way to read ATM_PHYS pickup:
128 nj = 0
129 C--- read ATM_PHYS 3-D fields for restart
130
131 nj = nj*Nr
132 C--- read ATM_PHYS 2-D fields for restart
133 CALL READ_MFLDS_3D_RL( 'AtPh_SST', atmPhys_SST,
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)') 'ATM_PHYS_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 ATM_PHYS_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)') 'ATM_PHYS_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 ATM_PHYS_READ_PICKUP'
161 ENDIF
162
163 C-- Update overlap regions:
164 CALL EXCH_XY_RL( atmPhys_SST, myThid )
165
166 #endif /* ALLOW_ATM_PHYS */
167
168 RETURN
169 END

  ViewVC Help
Powered by ViewVC 1.1.22