/[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.28 - (show annotations) (download)
Mon May 11 02:29:32 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n
Changes since 1.27: +77 -1 lines
initialise and check global buffer size ;

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

  ViewVC Help
Powered by ViewVC 1.1.22