/[MITgcm]/MITgcm/eesupp/src/read_field.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/read_field.F

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


Revision 1.2 - (show annotations) (download)
Sat Aug 22 17:51:06 1998 UTC (25 years, 9 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint15, checkpoint18, checkpoint17, checkpoint16, checkpoint19, checkpoint14, checkpoint20, checkpoint21
Changes since 1.1: +3 -3 lines
Isomorphism consistency changes

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/read_field.F,v 1.1 1998/04/27 18:54:36 cnh Exp $
2
3 #include "CPP_EEOPTIONS.h"
4
5 SUBROUTINE READ_FIELD_XYZR8(
6 O fld,
7 I filNam, filFmt, myThid )
8 C /==========================================================\
9 C | SUBROUTINE READ_FIELD_XYZR8 |
10 C | o Reads a file into three-dimensional model array |
11 C |==========================================================|
12 C | Routine that controls the reading of external datasets |
13 C | into the model. In a multi-threaded and/or MPI world |
14 C | this can be a non-trivial exercise. Here we use the |
15 C | following approach: |
16 C | Thread 1. reads data for the complete domain i.e. all |
17 C | processes and all threads into a buffer. Each individual |
18 C | thread then reads its portion of data into the actual |
19 C | model array. This is clean because there is just one |
20 C | input file with a single format irrespective of the |
21 C | of processes or threads in use. However, it has several |
22 C | potential difficulties. |
23 C | 1. Very large problems may have individual fields of |
24 C | several GB. For example 1/20th degree global and |
25 C | fifty levels is 10GB per field at 8 byte precision. |
26 C | 2. MPI 1.nn is vague about I/O support - not all |
27 C | processes have to support I/O. |
28 C | MPI 2. includes a standard API for distributed data, |
29 C | parallel I/O. If applications funnel all their field |
30 C | I/O through this routine then adopting this or some |
31 C | alternative should be fairly straight-forward. |
32 C | In the light of problem 1. the following strategy |
33 C | is adopted. Files are read one layer at a time. After |
34 C | each layer has been read there is a barrier and then |
35 C | the threads all copy data from the buffer to the arrays.|
36 C | This creates a lower-performance I/O code but reduces |
37 C | the degree to which a single large array is required for|
38 C | the master thread. To be consistent with this binary |
39 C | input files must be written by code of the form |
40 C | WRITE(N) ((array(I,J,K),I=1,Nx),J=1,Ny) |
41 C | rather than of the form |
42 C | WRITE(N) array |
43 C | The approach taken here also avoids one other ugly |
44 C | behaviour. On several systems even Fortran internal |
45 C | reads and writes are not thread-safe. This means that |
46 C | the portion of the code that builds file names has to |
47 C | be a critical section. However, if only the master |
48 C | thread is interested in the value of the file name then |
49 C | only the master need set its value. |
50 C | Finally the IO performed here is for the whole XY |
51 C | domain - even under MPI. The input files can stay the |
52 C | same no matter what processor count is being used. |
53 C | This is not a scalable approach to IO and MPI 2 has much|
54 C | better support for this. Output is handled differently. |
55 C | By default output files are written split and have to be|
56 C | merged in a post-processing stage - YUK! |
57 C \==========================================================/
58
59 C == GLobal variables ==
60 #include "SIZE.h"
61 #include "EEPARAMS.h"
62 #include "EESUPPORT.h"
63 #include "EEIO.h"
64
65 C == Routine arguments ==
66 C fld - Array into which data will be written.
67 C filNam - Name of file to read.
68 C filFmt - Format to use to read the file.
69 C myNz - No. vertical layers for array fld.
70 C myThid - Thread number for this instance of the routine.
71 REAL fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:Nr,nSx, nSy )
72 CHARACTER*(*) filNam
73 CHARACTER*(*) filFmt
74 INTEGER myThid
75
76 C == Local variables ==
77 C msgBuf - Variable for writing error messages
78 C I,J,K, bi,bj - Loop counters
79 C dUnit - Unit number for file I/O
80 C ioStatus - I/O error code
81 CHARACTER*(MAX_LEN_MBUF) msgBuf
82 INTEGER I
83 INTEGER J
84 INTEGER K
85 INTEGER bi
86 INTEGER bj
87 INTEGER iG, jG
88 INTEGER dUnit
89 INTEGER ioStatus
90 C
91 dUnit = 42
92
93 C-- Open the file
94 C Note: The error trapping here is inelegant. There is no
95 C easy way to tell other threads and/or MPI processes that
96 C there was an error. Here we simply STOP if there is an error.
97 C Under a multi-threaded mode this will halt all the threads.
98 C Under MPI the other processes may die or they may just hang!
99 _BEGIN_MASTER(myThid)
100 OPEN(dUnit,FILE=filNam,FORM='unformatted',STATUS='old',
101 & IOSTAT=ioStatus)
102 IF ( ioStatus .GT. 0 ) THEN
103 WRITE(msgBuf,'(A)')
104 & 'S/R READ_FIELD_XYZR8'
105 CALL PRINT_ERROR( msgBuf , myThid)
106 WRITE(msgBuf,'(A)')
107 & 'Open for read failed for'
108 CALL PRINT_ERROR( msgBuf , myThid)
109 WRITE(msgBuf,'(A,A50)')
110 & 'file ',filNam
111 CALL PRINT_ERROR( msgBuf , myThid)
112 STOP 'ABNORMAL END: S/R READ_FIELD_XYZR8'
113 ENDIF
114 _END_MASTER(myThid)
115
116 DO K = 1, Nr
117 C-- Read data from file one XY layer at a time
118 _BEGIN_MASTER(myThid)
119 C READ ...
120 DO J=1,Ny
121 DO I=1,Nx
122 IF ( filNam(1:1) .EQ. 'u' ) THEN
123 IO_tmpXY_R8(I,J) = 0.0 _d 0
124 IF ( J .GT. 15 .AND. J .LT. 24 )
125 & IO_tmpXY_R8(I,J) = 0.1 _d 0
126 ELSEIF ( filNam(1:1) .EQ. 'v' ) THEN
127 IO_tmpXY_R8(I,J) = 0.0 _d 0
128 ELSE
129 IO_tmpXY_R8(I,J) = 0.0 _d 0
130 ENDIF
131 ENDDO
132 ENDDO
133 _END_MASTER(myThid)
134 _BARRIER
135 C-- Copy data into per thread data structures
136 DO bj=myByLo(myThid),myByHi(myThid)
137 DO bi=myBxLo(myThid),myBxHi(myThid)
138 DO j=1,sNy
139 DO i=1,sNx
140 iG = myXGlobalLo+(bi-1)*sNx+I-1
141 jG = myYGlobalLo+(bj-1)*sNy+J-1
142 fld(i,j,k,bi,bj) = IO_tmpXY_R8(iG,jG)
143 ENDDO
144 ENDDO
145 ENDDO
146 ENDDO
147 _BARRIER
148 ENDDO
149 C
150 _EXCH_XYZ_R8(fld, myThid )
151 C
152 RETURN
153 END

  ViewVC Help
Powered by ViewVC 1.1.22