/[MITgcm]/MITgcm/pkg/mdsio/mdsio_writevec_loc.F
ViewVC logotype

Contents of /MITgcm/pkg/mdsio/mdsio_writevec_loc.F

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


Revision 1.1 - (show annotations) (download)
Sun Oct 30 21:12:20 2005 UTC (18 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint58a_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint58b_post, checkpoint58m_post
write local vector array to binary file (& write a meta file);
 for now, only the _RS version is available.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdswritefield_new.F,v 1.8 2005/02/11 03:06:12 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 SUBROUTINE MDSWRITEVEC_LOC_RS(
7 I fName,
8 I filePrec,
9 I nArr,
10 I arr,
11 I bi, bj,
12 I irecord,
13 I myIter,
14 I myThid )
15 C
16 C Arguments:
17 C
18 C fName string base name for file to written
19 C filePrec integer number of bits per word in file (32 or 64)
20 C nArr number of elements from input array "arr" to be written
21 C arr RS/RL array to WRITE, arr(nArr)
22 C bi,bj tile indices (if tiled array) or 0,0 if not a tiled array
23 C irecord integer record number to WRITE
24 C myIter integer time step number
25 C myThid integer thread identifier
26 C
27 C MDSWRITEVEC_LOC creates either a file of the form "fName.data" and
28 C "fName.meta" IF bi=bj=0. Otherwise it creates MDS tiled files of the
29 C form "fName.xxx.yyy.data" and "fName.xxx.yyy.meta".
30 C A meta-file is always created.
31 C The precision of the file is decsribed by filePrec, set either
32 C to floatPrec32 or floatPrec64.
33 C irecord is the record number to be written and must be >= 1.
34
35 IMPLICIT NONE
36 C Global variables / common blocks
37 #include "SIZE.h"
38 #include "EEPARAMS.h"
39 #include "EESUPPORT.h"
40 #include "PARAMS.h"
41
42 C Routine arguments
43 CHARACTER*(*) fName
44 INTEGER filePrec
45 INTEGER nArr
46 _RS arr(*)
47 INTEGER bi,bj
48 INTEGER irecord
49 INTEGER myIter
50 INTEGER myThid
51 C Functions
52 INTEGER ILNBLNK
53 INTEGER MDS_RECLEN
54 C Local variables
55 CHARACTER*(MAX_LEN_FNAM) dataFName, metaFName, pfName
56 CHARACTER*(MAX_LEN_MBUF) msgBuf
57 LOGICAL fileIsOpen
58 INTEGER iG,jG,irec,k,dUnit,IL,pIL
59 INTEGER dimList(3,3),ndims
60 INTEGER length_of_rec
61 INTEGER loc_size
62 PARAMETER( loc_size = Nx+Ny+Nr )
63 real*4 r4seg(loc_size)
64 real*8 r8seg(loc_size)
65
66 C Only DO I/O IF I am the master thread
67 _BEGIN_MASTER( myThid )
68
69 #ifdef ALLOW_USE_MPI
70 IF ( (mpiMyId.EQ.0 .AND. bi.EQ.0 .AND. bj.EQ.0)
71 & .OR. bi.NE.0 .OR. bj.NE.0 ) THEN
72 C-- we are writing a non-tiled array (bi=bj=0), only 1 time.
73 #endif
74
75 C Record number must be >= 1
76 IF (irecord .LT. 1) THEN
77 WRITE(msgBuf,'(A,I9.8)')
78 & ' MDSWRITEVEC_LOC: argument irecord = ',irecord
79 CALL PRINT_ERROR( msgBuf, myThid )
80 WRITE(msgBuf,'(A)')
81 & ' MDSWRITEVEC_LOC: invalid value for irecord'
82 CALL PRINT_ERROR( msgBuf, myThid )
83 STOP 'ABNORMAL END: S/R MDSWRITEVEC_LOC'
84 ENDIF
85
86 C Assume nothing
87 fileIsOpen=.FALSE.
88 IL = ILNBLNK( fName )
89 irec = irecord
90
91 C Assign special directory
92 IF ( mdsioLocalDir .NE. ' ' ) THEN
93 pIL = ILNBLNK( mdsioLocalDir )
94 WRITE(pFname,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
95 pIL = IL + pIL
96 ELSE
97 WRITE(pFname,'(A)') fName(1:IL)
98 pIL = IL
99 ENDIF
100
101 C Assign a free unit number as the I/O channel for this routine
102 CALL MDSFINDUNIT( dUnit, myThid )
103
104 C-- Set the file Name:
105 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
106 C- we are writing a non-tiled array (bi=bj=0):
107 WRITE(dataFname,'(2A)') fName(1:IL),'.data'
108 ELSE
109 C- we are writing a tiled array (bi>0,bj>0):
110 iG=bi+(myXGlobalLo-1)/sNx
111 jG=bj+(myYGlobalLo-1)/sNy
112 WRITE(dataFname,'(2A,I3.3,A,I3.3,A)')
113 & pfName(1:pIL),'.',iG,'.',jG,'.data'
114 ENDIF
115
116 length_of_rec=MDS_RECLEN( filePrec, nArr, myThid )
117 IF (irecord .EQ. 1) THEN
118 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
119 & access='direct', recl=length_of_rec )
120 fileIsOpen=.TRUE.
121 ELSE
122 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
123 & access='direct', recl=length_of_rec )
124 fileIsOpen=.TRUE.
125 ENDIF
126 IF ( debugLevel.GE.debLevB ) THEN
127 WRITE(msgBuf,'(2A)')
128 & ' MDSWRITEVEC_LOC: open file: ',dataFname(1:pIL+13)
129 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
130 & SQUEEZE_RIGHT , 1)
131 ENDIF
132
133 IF (fileIsOpen) THEN
134 IF (filePrec .EQ. precFloat32) THEN
135 DO k=1,nArr
136 r4seg(k) = arr(k)
137 ENDDO
138 #ifdef _BYTESWAPIO
139 CALL MDS_BYTESWAPR4( nArr, r4seg )
140 #endif
141 WRITE(dUnit,rec=irec) (r4seg(k),k=1,nArr)
142 ELSEIF (filePrec .EQ. precFloat64) THEN
143 DO k=1,nArr
144 r8seg(k) = arr(k)
145 ENDDO
146 #ifdef _BYTESWAPIO
147 CALL MDS_BYTESWAPR8( nArr, r8seg )
148 #endif
149 WRITE(dUnit,rec=irec) (r8seg(k),k=1,nArr)
150 ELSE
151 WRITE(msgBuf,'(A)')
152 & ' MDSWRITEVEC_LOC: illegal value for filePrec'
153 CALL PRINT_ERROR( msgBuf, myThid )
154 STOP 'ABNORMAL END: S/R MDSWRITEVEC_LOC'
155 ENDIF
156 ELSE
157 WRITE(msgBuf,'(A)')
158 & ' MDSWRITEVEC_LOC: should never reach this point'
159 CALL PRINT_ERROR( msgBuf, myThid )
160 STOP 'ABNORMAL END: S/R MDSWRITEVEC_LOC'
161 ENDIF
162
163 C If we were writing to a tiled MDS file then we close it here
164 IF ( fileIsOpen ) THEN
165 CLOSE( dUnit )
166 fileIsOpen = .FALSE.
167 ENDIF
168
169 C Create meta-file for each tile IF we are tiling
170 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
171 C-- we are writing a non-tiled array (bi=bj=0):
172 WRITE(metaFname,'(2A)') fName(1:IL),'.meta'
173 dimList(1,1)=1
174 dimList(2,1)=1
175 dimList(3,1)=1
176 dimList(1,2)=1
177 dimList(2,2)=1
178 dimList(3,2)=1
179 ELSE
180 C-- we are writing a tiled array (bi>0,bj>0):
181 iG=bi+(myXGlobalLo-1)/sNx
182 jG=bj+(myYGlobalLo-1)/sNy
183 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
184 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
185 dimList(1,1)=nSx*nPx
186 dimList(2,1)=iG
187 dimList(3,1)=iG
188 dimList(1,2)=nSy*nPy
189 dimList(2,2)=jG
190 dimList(3,2)=jG
191 ENDIF
192 dimList(1,3)=nArr
193 dimList(2,3)=1
194 dimList(3,3)=nArr
195 ndims=3
196 IF (nArr .EQ. 1) ndims=2
197 CALL MDSWRITEMETA( metaFName, dataFName,
198 & filePrec, ndims, dimList, irec, myIter, myThid )
199
200 #ifdef ALLOW_USE_MPI
201 ENDIF
202 #endif
203
204 _END_MASTER( myThid )
205
206 RETURN
207 END

  ViewVC Help
Powered by ViewVC 1.1.22