/[MITgcm]/MITgcm/pkg/diagnostics/diagstats_set_regions.F
ViewVC logotype

Annotation of /MITgcm/pkg/diagnostics/diagstats_set_regions.F

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


Revision 1.3 - (hide annotations) (download)
Mon Jul 31 16:26:32 2006 UTC (17 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58n_post, checkpoint58o_post, checkpoint58p_post
Changes since 1.2: +8 -5 lines
safer in multi-threaded environment

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagstats_set_regions.F,v 1.2 2006/01/24 02:59:47 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DIAGSTATS_SET_REGIONS
8     C !INTERFACE:
9     SUBROUTINE DIAGSTATS_SET_REGIONS( myThid )
10    
11     C !DESCRIPTION: \bv
12     C *==================================================================
13     C | S/R DIAGSTATS_SET_REGIONS
14     C | o set region-mask for regional statistics diagnostics
15     C *==================================================================
16     C \ev
17    
18     C !USES:
19     IMPLICIT NONE
20    
21     C == Global variables ===
22     #include "EEPARAMS.h"
23     #include "SIZE.h"
24     #include "PARAMS.h"
25     #include "DIAGNOSTICS_SIZE.h"
26     #include "DIAGSTATS_REGIONS.h"
27    
28     C !INPUT/OUTPUT PARAMETERS:
29     C == Routine arguments ==
30     C myThid - Thread number for this instance of the routine.
31     INTEGER myThid
32     CEOP
33    
34     C !LOCAL VARIABLES:
35     C == Local variables ==
36     CHARACTER*(MAX_LEN_MBUF) msgBuf
37     INTEGER iLen
38     INTEGER i, j
39     INTEGER bi, bj
40     #ifdef DIAGSTATS_REGION_MASK
41     CHARACTER*(MAX_LEN_MBUF) tmpBuf
42     INTEGER ioUnit
43     INTEGER k, nbReg
44     _RS tmpVar(1-OLx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
45 jmc 1.3 COMMON / SET_REGIONS_LOCAL / tmpVar
46 jmc 1.1 #else
47     LOGICAL flag
48     #endif
49     INTEGER ILNBLNK
50     EXTERNAL ILNBLNK
51    
52     #ifdef DIAGSTATS_REGION_MASK
53    
54     C-- Initialize region-mask array to zero:
55     DO bj = myByLo(myThid), myByHi(myThid)
56     DO bi = myBxLo(myThid), myBxHi(myThid)
57     DO k=1,sizRegMsk
58     DO j=1-Oly,sNy+Oly
59     DO i=1-Olx,sNx+Olx
60     diagSt_regMask(i,j,k,bi,bj) = 0.
61     ENDDO
62     ENDDO
63     ENDDO
64     ENDDO
65     ENDDO
66 jmc 1.3 ioUnit = -1
67 jmc 1.1
68     _BEGIN_MASTER( myThid )
69 jmc 1.3 ioUnit = standardMessageUnit
70 jmc 1.1 C-- Check size & parameter first:
71 jmc 1.2 IF ( (diagSt_regMaskFile.NE.' ' .AND. nSetRegMskFile.EQ.0)
72     & .OR.(diagSt_regMaskFile.EQ.' ' .AND. nSetRegMskFile.GT.0) ) THEN
73 jmc 1.1 WRITE(msgBuf,'(2A)') 'DIAGSTATS_SET_REGIONS:',
74 jmc 1.2 & ' regMaskFile and nSetRegMskFile Not consistent'
75 jmc 1.1 CALL PRINT_ERROR( msgBuf , myThid )
76     STOP 'ABNORMAL END: S/R DIAGSTATS_SET_REGIONS'
77     ENDIF
78 jmc 1.2 IF ( nSetRegMskFile.GT.sizRegMsk ) THEN
79 jmc 1.1 WRITE(msgBuf,'(2A,I4,A,I4)') 'DIAGSTATS_SET_REGIONS:',
80 jmc 1.2 & ' regMaskFile set-index number=', nSetRegMskFile,
81 jmc 1.1 & ' exceeds sizRegMsk=', sizRegMsk
82     CALL PRINT_ERROR( msgBuf , myThid )
83     STOP 'ABNORMAL END: S/R DIAGSTATS_SET_REGIONS'
84     ENDIF
85     _END_MASTER( myThid )
86    
87     C-- Read region-mask from file
88     IF ( diagSt_regMaskFile .NE. ' ' ) THEN
89 jmc 1.3 _BARRIER
90 jmc 1.1 iLen = ILNBLNK(diagSt_regMaskFile)
91 jmc 1.3 IF (ioUnit.GE.0 ) WRITE(ioUnit,'(2A)')
92 jmc 1.1 & ' DIAGSTATS_SET_REGIONS: start reading region-mask file: ',
93     & diagSt_regMaskFile(1:iLen)
94 jmc 1.2 DO k=1,nSetRegMskFile
95 jmc 1.1 C _BEGIN_MASTER( myThid )
96 jmc 1.3 IF (ioUnit.GE.0 ) WRITE(ioUnit,'(A,I3)')
97 jmc 1.2 & ' DIAGSTATS_SET_REGIONS: reading set k=',k
98 jmc 1.1 CALL READ_REC_XY_RS( diagSt_regMaskFile, tmpVar, k,
99     & nIter0, myThid )
100 jmc 1.3 IF (ioUnit.GE.0 ) WRITE(ioUnit,'(A,I3,A)')
101 jmc 1.2 & ' DIAGSTATS_SET_REGIONS: set k=',k,' <= done'
102 jmc 1.1 C _END_MASTER( myThid )
103     _EXCH_XY_RS( tmpVar, myThid )
104     DO bj = myByLo(myThid), myByHi(myThid)
105     DO bi = myBxLo(myThid), myBxHi(myThid)
106     DO j=1-Oly,sNy+Oly
107     DO i=1-Olx,sNx+Olx
108     diagSt_regMask(i,j,k,bi,bj) = tmpVar(i,j,bi,bj)
109     ENDDO
110     ENDDO
111     ENDDO
112     ENDDO
113     C- end of k loop
114     ENDDO
115     ENDIF
116 jmc 1.2 nSetRegMask = nSetRegMskFile
117 jmc 1.1
118     C-- Other way to define regions (e.g., latitude bands):
119 jmc 1.2 C set corresponding set-index of the region-mask array,
120     C starting from nSetRegMskFile+1 up to nSetRegMask
121 jmc 1.1 C note: for now, empty !
122    
123     C-- Region Identificator arrays
124     C for now, directly filled when reading data.diagnostics
125    
126     _BEGIN_MASTER( myThid )
127     C-- Check defined regions
128     nbReg = 0
129     DO j=1,nRegions
130     C- check for valid region-mask index:
131     IF ( diagSt_kRegMsk(j).LT.0 .OR.
132     & diagSt_kRegMsk(j).GT.sizRegMsk ) THEN
133     WRITE(msgBuf,'(2A,I3,A,I4)') 'DIAGSTATS_SET_REGIONS: ',
134     & '(region',j,') invalid region-mask index :',diagSt_kRegMsk(j)
135     CALL PRINT_ERROR( msgBuf , myThid )
136     STOP 'ABNORMAL END: S/R DIAGSTATS_SET_REGIONS'
137     C- check for unset region-mask:
138 jmc 1.2 ELSEIF ( diagSt_kRegMsk(j).GT.nSetRegMask ) THEN
139 jmc 1.1 WRITE(msgBuf,'(2A,I3,A,I3,A)') 'DIAGSTATS_SET_REGIONS: ',
140     & 'region',j,' , kRegMsk=', diagSt_kRegMsk(j),
141     & ' <- has not been set !'
142     CALL PRINT_ERROR( msgBuf , myThid )
143     STOP 'ABNORMAL END: S/R DIAGSTATS_SET_REGIONS'
144     ELSEIF ( diagSt_kRegMsk(j).NE.0 ) THEN
145     nbReg = nbReg + 1
146     C- check for empty region: build temp mask 0 / 1 :
147     c k = diagSt_kRegMsk(j)
148     c IF ( diagSt_regMask(i,j,k,bi,bj).EQ.diagSt_vRegMsk(j) ) THEN
149     c tmpVar(i,j,bi,bj) = 1.
150     c ELSE
151     c tmpVar(i,j,bi,bj) = 0.
152     c ELSE
153     C- print region mask:
154     c IF ( debugLevel.GE.debLevA ) THEN
155     c WRITE(msgBuf,'(A,I3,A)') 'DIAGSTAT Region',j,' mask:'
156     c iLen = ILNBLNK(msgBuf)
157     c CALL PLOT_FIELD_XYRS( tmpVar, msgBuf(1:iLen), -1, myThid )
158     c ENDIF
159     ENDIF
160     ENDDO
161    
162     C- Global statistics (region # 0) <- done in diagnostics_readparams
163     c diagSt_kRegMsk(0) = 1
164     c diagSt_vRegMsk(0) = 0.
165    
166    
167     WRITE(msgBuf,'(A,I4,A)') 'DIAGSTATS_SET_REGIONS: define',
168     & nbReg,' regions:'
169     iLen = ILNBLNK(msgBuf)
170     DO j=1,nRegions
171     IF ( diagSt_kRegMsk(j).NE.0 ) THEN
172     iLen = MIN( iLen, MAX_LEN_MBUF -3 )
173     tmpBuf(1:iLen) = msgBuf(1:iLen)
174     WRITE(msgBuf,'(A,I3)') tmpBuf(1:iLen),j
175     iLen = iLen+3
176     ENDIF
177     ENDDO
178     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
179     & SQUEEZE_RIGHT , myThid)
180     WRITE(msgBuf,'(2A)')
181     & '------------------------------------------------------------'
182     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
183     & SQUEEZE_RIGHT , myThid)
184    
185     _END_MASTER( myThid )
186    
187     #else /* DIAGSTATS_REGION_MASK */
188    
189     C-- Initialize region-mask array to zero:
190     DO bj = myByLo(myThid), myByHi(myThid)
191     DO bi = myBxLo(myThid), myBxHi(myThid)
192     c DO j=1-Oly,sNy+Oly
193     c DO i=1-Olx,sNx+Olx
194     DO j=1-Oly,1-Oly
195     DO i=1-Olx,1-Olx
196     diagSt_regMask(i,j,1,bi,bj) = 0.
197     ENDDO
198     ENDDO
199     ENDDO
200     ENDDO
201    
202     _BEGIN_MASTER( myThid )
203     C-- Check parameter consitency:
204     flag = .FALSE.
205     DO j=1,nRegions
206     flag = flag .OR. diagSt_kRegMsk(j).NE.0
207     & .OR. diagSt_vRegMsk(j).NE.0.
208     ENDDO
209     iLen = ILNBLNK(diagSt_regMaskFile)
210 jmc 1.2 IF ( flag .OR. iLen.GE.1 .OR. nSetRegMskFile.NE.0 ) THEN
211 jmc 1.1 WRITE(msgBuf,'(2A)') 'DIAGSTATS_SET_REGIONS:',
212     & ' #define DIAGSTATS_REGION_MASK missing in DIAG_OPTIONS.h'
213     CALL PRINT_ERROR( msgBuf , myThid )
214     STOP 'ABNORMAL END: S/R DIAGSTATS_SET_REGIONS'
215     ENDIF
216    
217     WRITE(msgBuf,'(A)') 'DIAGSTATS_SET_REGIONS: define no region'
218     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
219     & SQUEEZE_RIGHT , myThid)
220     WRITE(msgBuf,'(2A)')
221     & '------------------------------------------------------------'
222     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
223     & SQUEEZE_RIGHT , myThid)
224    
225     _END_MASTER( myThid )
226    
227     #endif /* DIAGSTATS_REGION_MASK */
228    
229     RETURN
230     END

  ViewVC Help
Powered by ViewVC 1.1.22