/[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.7 - (show annotations) (download)
Fri Aug 17 16:49:10 2001 UTC (22 years, 8 months ago) by adcroft
Branch: MAIN
CVS Tags: HEAD
Changes since 1.6: +2 -2 lines
FILE REMOVED
Old I/O method. Deleting to avoid confusing myself. :)

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

  ViewVC Help
Powered by ViewVC 1.1.22