/[MITgcm]/MITgcm/model/src/ini_model_io.F
ViewVC logotype

Contents of /MITgcm/model/src/ini_model_io.F

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


Revision 1.43 - (show annotations) (download)
Wed Jun 8 01:21:14 2011 UTC (12 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62z
Changes since 1.42: +4 -2 lines
refine debugLevel criteria when printing messages

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_model_io.F,v 1.42 2011/05/20 22:25:57 gforget Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INI_MODEL_IO
9
10 C !INTERFACE:
11 SUBROUTINE INI_MODEL_IO( myThid )
12
13 C !DESCRIPTION:
14 C Initialisation and setting of I/O:
15 C - Check size and initialise global I/O buffer
16 C - Initialise flags for pickup and for mdsio/rw.
17 C - Do MNC model-IO initialisation
18 C - Do Monitor-IO initialisation
19
20 C !USES:
21 IMPLICIT NONE
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "EESUPPORT.h"
25 #include "PARAMS.h"
26 #include "RESTART.h"
27 #ifdef ALLOW_EXCH2
28 # include "W2_EXCH2_SIZE.h"
29 # include "W2_EXCH2_TOPOLOGY.h"
30 # include "W2_EXCH2_PARAMS.h"
31 #endif /* ALLOW_EXCH2 */
32 #include "EEBUFF_SCPU.h"
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C myThid :: my Thread Id number
36 INTEGER myThid
37
38 C !FUNCTIONS
39 INTEGER ILNBLNK
40 EXTERNAL ILNBLNK
41
42 C !LOCAL VARIABLES:
43 C msgBuf :: Informational/error message buffer
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45 CHARACTER*(MAX_LEN_FNAM) namBuf
46 INTEGER i, iL, pIL
47 LOGICAL useGlobalBuff
48 #ifdef ALLOW_EXCH2
49 INTEGER xySize
50 #endif /* ALLOW_EXCH2 */
51 #ifdef ALLOW_USE_MPI
52 INTEGER iG,jG,np
53 #endif /* ALLOW_USE_MPI */
54 CEOP
55
56 C- Safety check:
57 IF ( nPx*nPy.NE.1 .AND. globalFiles
58 & .AND. .NOT.useSingleCpuIO ) THEN
59 _BEGIN_MASTER( myThid )
60 c WRITE(msgBuf,'(2A)')
61 c & 'INI_MODEL_IO: globalFiles=TRUE is not safe',
62 c & ' in Multi-processors (MPI) run'
63 c CALL PRINT_ERROR( msgBuf , myThid)
64 c WRITE(msgBuf,'(2A)')
65 c & 'INI_MODEL_IO: use instead "useSingleCpuIO=.TRUE."'
66 c CALL PRINT_ERROR( msgBuf , myThid)
67 c STOP 'ABNORMAL END: S/R INI_MODEL_IO'
68 C------
69 C GlobalFiles option with Multi-processors execution (with MPI) is not
70 C safe: dependending on the platform & compiler, it may produce:
71 C - incomplete output files (wrong size)
72 C - wrong isolated values in some output files
73 C - missing tiles (all zeros) in some output files.
74 C A safe alternative is to set "useSingleCpuIO=.TRUE." in file "data",
75 C namelist PARAM01 (and to keep the default value of globalFiles=FALSE)
76 C or if you are really sure that the globalFile works well on our platform
77 C & compiler, comment out the above "stop"
78 C-----
79 WRITE(msgBuf,'(2A)')
80 & '** WARNING ** INI_MODEL_IO: globalFiles=TRUE is not safe',
81 & ' in Multi-processors (MPI) run'
82 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
83 & SQUEEZE_RIGHT, myThid )
84 WRITE(msgBuf,'(2A)') '** WARNING ** INI_MODEL_IO:',
85 & ' use instead "useSingleCpuIO=.TRUE."'
86 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
87 & SQUEEZE_RIGHT, myThid )
88 _END_MASTER( myThid )
89 ENDIF
90
91 C- Check size of IO buffers:
92 useGlobalBuff = useSingleCpuIO
93 #ifdef CG2D_SINGLECPU_SUM
94 useGlobalBuff = .TRUE.
95 #endif /* CG2D_SINGLECPU_SUM */
96 #ifdef ALLOW_EXCH2
97 IF ( useGlobalBuff ) THEN
98 xySize = exch2_global_Nx*exch2_global_Ny
99 #ifndef CG2D_SINGLECPU_SUM
100 IF ( .NOT.W2_useE2ioLayOut ) xySize = Nx*Ny
101 #endif /* ndef CG2D_SINGLECPU_SUM */
102 IF ( xySize.GT.W2_ioBufferSize ) THEN
103 WRITE(msgBuf,'(A,2(I10,A))')
104 & 'W2_ioBufferSize=', W2_ioBufferSize,
105 & ' <', xySize, ' = Size of Global 2-D map'
106 CALL PRINT_ERROR( msgBuf, myThid )
107 WRITE(msgBuf,'(2A)')
108 & 'INI_MODEL_IO: increase W2_ioBufferSize',
109 & ' in "W2_EXCH2_SIZE.h" + recompile'
110 CALL PRINT_ERROR( msgBuf, myThid )
111 STOP 'ABNORMAL END: S/R INI_MODEL_IO (buffer size)'
112 ENDIF
113 ENDIF
114 #endif /* ALLOW_EXCH2 */
115 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
116
117 C- Only Master-thread updates IO-parameter in Common blocks:
118 _BEGIN_MASTER( myThid )
119
120 C- Initialise AB starting level
121 C notes: those could be modified when reading a pickup that does
122 C not correspond to what is actually needed.
123 tempStartAB = nIter0
124 saltStartAB = nIter0
125 mom_StartAB = nIter0
126 nHydStartAB = nIter0
127 IF ( startFromPickupAB2 ) tempStartAB = MIN( nIter0 , 1 )
128 saltStartAB = tempStartAB
129 mom_StartAB = tempStartAB
130 nHydStartAB = tempStartAB
131 dPhiNHstatus= 0
132
133 C- Initialise Alternating pickup-suffix
134 nCheckLev = 1
135 checkPtSuff(1) = 'ckptA'
136 checkPtSuff(2) = 'ckptB'
137
138 C- Flags specific to RW and MDSIO (and PLOT_FIELDS)
139 printDomain = debugLevel.GE.debLevB
140
141 C- now we make local directories with myProcessStr appended
142 IF ( mdsioLocalDir .NE. ' ' ) THEN
143 iL = ILNBLNK( mdsioLocalDir )
144 WRITE(namBuf,'(3A)')
145 & ' mkdir -p ', mdsioLocalDir(1:iL),myProcessStr(1:4)
146 pIL = 1 + ILNBLNK( namBuf )
147 WRITE(standardMessageUnit,'(3A)')
148 & '==> SYSTEM CALL (from INI_MODEL_IO): >',namBuf(1:pIL),'<'
149 CALL SYSTEM( namBuf(1:pIL) )
150 namBuf(1:iL) = mdsioLocalDir(1:iL)
151 WRITE(mdsioLocalDir,'(3A)') namBuf(1:iL),myProcessStr(1:4),'/'
152 ENDIF
153
154 C- Initialise MFLDS variables in common block
155 CALL READ_MFLDS_INIT( myThid )
156
157 C Set globalFiles flag for READ_WRITE_FLD package
158 CALL SET_WRITE_GLOBAL_FLD( globalFiles )
159 C Set globalFiles flag for READ_WRITE_REC package
160 CALL SET_WRITE_GLOBAL_REC( globalFiles )
161 C Set globalFiles flag for READ_WRITE_SEC package
162 IF ( useOBCS .AND. globalFiles ) THEN
163 WRITE(msgBuf,'(2A)') '** WARNING ** INI_MODEL_IO:',
164 & ' use tiled-files to write sections (for OBCS)'
165 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
166 & SQUEEZE_RIGHT, myThid )
167 CALL SET_WRITE_GLOBAL_SEC( .FALSE. )
168 ELSE
169 CALL SET_WRITE_GLOBAL_SEC( globalFiles )
170 ENDIF
171 C Set globalFiles flag for READ_WRITE_PICKUP
172 CALL SET_WRITE_GLOBAL_PICKUP( globalFiles )
173
174 _END_MASTER( myThid )
175 C- Everyone else must wait for the IO-parameters to be set
176 _BARRIER
177
178 C- Global IO-buffers initialisation
179 IF ( useGlobalBuff ) THEN
180 _BEGIN_MASTER( myThid )
181 DO i=1,xyBuffer_size
182 xy_buffer_r8(i) = 0. _d 0
183 xy_buffer_r4(i) = 0.
184 ENDDO
185 _END_MASTER( myThid )
186 ENDIF
187
188 C- MNC model-io initialisation
189
190 #ifdef ALLOW_MNC
191 IF (useMNC) THEN
192
193 C- Initialize look-up tables for MNC
194 CALL MNC_INIT( myThid )
195 CALL MNC_CW_INIT( sNx,sNy,OLx,OLy,nSx,nSy,nPx,nPy,
196 & Nr,myThid )
197 CEH3 IF ( mnc_echo_gvtypes ) THEN
198 CEH3 CALL MNC_CW_DUMP( myThid )
199 CEH3 ENDIF
200
201 C Write units/set precision/etc for I/O of variables/arrays
202 C belonging to the core dynamical model
203 CALL INI_MNC_VARS( myThid )
204
205 ENDIF
206 #endif /* ALLOW_MNC */
207
208 #ifdef ALLOW_AUTODIFF
209 CALL AUTODIFF_INI_MODEL_IO( myThid )
210 #endif
211
212 #ifdef ALLOW_PROFILES
213 c IF ( useProfiles ) THEN
214 CALL PROFILES_INI_IO( myThid )
215 c ENDIF
216 #endif
217
218 #ifdef ALLOW_MONITOR
219 C-- Initialise MONITOR I/O streams so we can report config. info
220 CALL MON_INIT( myThid )
221 #endif
222
223 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
224
225 RETURN
226 END

  ViewVC Help
Powered by ViewVC 1.1.22