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

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

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


Revision 1.9 - (hide annotations) (download)
Sun Jul 23 00:24:18 2017 UTC (6 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.8: +2 -2 lines
allows for negative "jdiag" (interpret |jdiag| instead)

1 jmc 1.9 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_fract_fill.F,v 1.8 2013/08/14 01:00:11 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DIAGNOSTICS_FRACT_FILL
8     C !INTERFACE:
9     SUBROUTINE DIAGNOSTICS_FRACT_FILL(
10 jmc 1.2 I inpFld, fractFld, scaleFact, power, chardiag,
11 jmc 1.5 I kLev, nLevs, bibjFlg, biArg, bjArg, myThid )
12 jmc 1.1
13     C !DESCRIPTION:
14     C***********************************************************************
15 jmc 1.6 C Wrapper routine to increment the diagnostics arrays with a RL field
16 jmc 1.2 C using a scaling factor & square option (power=2)
17 jmc 1.6 C and using a RL fraction-weight (assumed to be the
18     C counter-mate of the current diagnostics)
19 jmc 1.1 C Note: 1) fraction-weight has to correspond to the diagnostics
20     C counter-mate (filled independently with a call to
21     C DIAGNOSTICS_FILL)
22     C 2) assume for now that inpFld & fractFld are both _RL and
23     C have the same horizontal shape (overlap,bi,bj ...)
24     C***********************************************************************
25     C !USES:
26     IMPLICIT NONE
27    
28     C == Global variables ===
29     #include "EEPARAMS.h"
30     #include "SIZE.h"
31     #include "DIAGNOSTICS_SIZE.h"
32     #include "DIAGNOSTICS.h"
33    
34     C !INPUT PARAMETERS:
35     C***********************************************************************
36     C Arguments Description
37     C ----------------------
38     C inpFld :: Field to increment diagnostics array
39     C fractFld :: fraction used for weighted average diagnostics
40     C scaleFact :: scaling factor
41 jmc 1.2 C power :: option to fill-in with the field square (power=2)
42 jmc 1.1 C chardiag :: Character expression for diag to fill
43     C kLev :: Integer flag for vertical levels:
44     C > 0 (any integer): WHICH single level to increment in qdiag.
45     C 0,-1 to increment "nLevs" levels in qdiag,
46     C 0 : fill-in in the same order as the input array
47     C -1: fill-in in reverse order.
48     C nLevs :: indicates Number of levels of the input field array
49     C (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
50     C bibjFlg :: Integer flag to indicate instructions for bi bj loop
51     C 0 indicates that the bi-bj loop must be done here
52     C 1 indicates that the bi-bj loop is done OUTSIDE
53     C 2 indicates that the bi-bj loop is done OUTSIDE
54     C AND that we have been sent a local array (with overlap regions)
55     C 3 indicates that the bi-bj loop is done OUTSIDE
56     C AND that we have been sent a local array
57     C AND that the array has no overlap region (interior only)
58     C NOTE - bibjFlg can be NEGATIVE to indicate not to increment counter
59     C biArg :: X-direction tile number - used for bibjFlg=1-3
60     C bjArg :: Y-direction tile number - used for bibjFlg=1-3
61     C myThid :: my thread Id number
62     C***********************************************************************
63     C NOTE: User beware! If a local (1 tile only) array
64     C is sent here, bibjFlg MUST NOT be set to 0
65     C or there will be out of bounds problems!
66     C***********************************************************************
67     _RL inpFld(*)
68     _RL fractFld(*)
69     _RL scaleFact
70 jmc 1.2 INTEGER power
71 jmc 1.1 CHARACTER*8 chardiag
72     INTEGER kLev, nLevs, bibjFlg, biArg, bjArg
73     INTEGER myThid
74     CEOP
75    
76     C !LOCAL VARIABLES:
77     C ndId :: diagnostic Id number (in available diagnostics list)
78 jmc 1.8 C msgBuf :: Informational/error message buffer
79 jmc 1.1 INTEGER m, n, j, k, l, bi, bj
80     INTEGER ndId, ipt, iSp
81     INTEGER region2fill(0:nRegions)
82     INTEGER mate, nLevFract
83 jmc 1.5 CHARACTER*10 gcode
84 jmc 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
85 jmc 1.6 INTEGER arrType
86     _RS dummyRS(1)
87     C ===============
88 jmc 1.1
89 jmc 1.8 C-- Check if this S/R is called from the right place ;
90     C needs to be after DIAGNOSTICS_SWITCH_ONOFF and before DIAGNOSTICS_WRITE
91     IF ( diag_pkgStatus.NE.ready2fillDiags ) THEN
92     CALL DIAGNOSTICS_STATUS_ERROR( 'DIAGNOSTICS_FRACT_FILL',
93     & ' ', chardiag, ready2fillDiags, myThid )
94     ENDIF
95    
96 jmc 1.6 arrType = 0
97 jmc 1.1 IF ( bibjFlg.EQ.0 ) THEN
98 jmc 1.4 bi = myBxLo(myThid)
99     bj = myByLo(myThid)
100 jmc 1.1 ELSE
101     bi = biArg
102     bj = bjArg
103     ENDIF
104     C-- 2D/3D Diagnostics :
105     C Run through list of active diagnostics to make sure
106     C we are trying to fill a valid diagnostic
107     DO n=1,nlists
108     DO m=1,nActive(n)
109     IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
110     ipt = idiag(m,n)
111     IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
112 jmc 1.9 ndId = ABS(jdiag(m,n))
113 jmc 1.3 ipt = ipt + pdiag(n,bi,bj)*kdiag(ndId)
114 jmc 1.1 C- check for a counter-mate:
115     mate = 0
116 jmc 1.5 gcode = gdiag(ndId)(1:10)
117     IF ( gcode(5:5).EQ.'C' ) mate = hdiag(ndId)
118 jmc 1.1 IF ( mate.LE.0 ) THEN
119     WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_FRACT_FILL: ',
120     & 'did not find a valid counter-mate'
121     CALL PRINT_ERROR( msgBuf , myThid )
122 jmc 1.5 WRITE(msgBuf,'(2A,I6,2A)') 'DIAGNOSTICS_FRACT_FILL: ',
123 jmc 1.1 & 'for diag(#',ndId,' ) :', chardiag
124     CALL PRINT_ERROR( msgBuf , myThid )
125     STOP 'ABNORMAL END: S/R DIAGNOSTICS_FRACT_FILL'
126     ENDIF
127     C- set the nb of levels of fraction-weight field (not > kdiag(mate))
128     nLevFract = MIN(nLevs,kdiag(mate))
129     C- diagnostic is valid & active, has a counter-mate, do the filling:
130     CALL DIAGNOSTICS_FILL_FIELD(
131 jmc 1.6 I inpFld, fractFld, dummyRS, dummyRS,
132     I scaleFact, power, arrType, nLevFract,
133 jmc 1.2 I ndId, ipt, kLev, nLevs,
134     I bibjFlg, biArg, bjArg, myThid )
135 jmc 1.1 ENDIF
136     ENDIF
137     ENDDO
138     ENDDO
139    
140     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
141     C-- Global/Regional Statistics :
142    
143     C Run through list of active statistics-diagnostics to make sure
144     C we are trying to compute & fill a valid diagnostic
145    
146     DO n=1,diagSt_nbLists
147     DO m=1,diagSt_nbActv(n)
148     IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
149     iSp = iSdiag(m,n)
150     IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
151     ndId = jSdiag(m,n)
152     C- check for a counter-mate:
153     mate = 0
154 jmc 1.5 gcode = gdiag(ndId)(1:10)
155     c IF ( gcode(5:5).EQ.'C' ) READ(gcode,'(5X,I3)') mate
156     IF ( gcode(5:5).EQ.'C' ) mate = hdiag(ndId)
157 jmc 1.1 IF ( mate.LE.0 ) THEN
158     WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_FRACT_FILL: ',
159     & 'did not find a valid counter-mate'
160     CALL PRINT_ERROR( msgBuf , myThid )
161 jmc 1.5 WRITE(msgBuf,'(2A,I6,2A)') 'DIAGNOSTICS_FRACT_FILL: ',
162 jmc 1.1 & 'for diag(#',ndId,' ) :', chardiag
163     CALL PRINT_ERROR( msgBuf , myThid )
164     STOP 'ABNORMAL END: S/R DIAGNOSTICS_FRACT_FILL'
165     ENDIF
166     C- set the nb of levels of fraction-weight field (not > kdiag(mate))
167     nLevFract = MIN(nLevs,kdiag(mate))
168     C- Find list of regions to fill:
169     DO j=0,nRegions
170     region2fill(j) = diagSt_region(j,n)
171     ENDDO
172     C- if this diagnostics appears in several lists (with same freq)
173     C then add regions from other lists
174     DO l=1,diagSt_nbLists
175     DO k=1,diagSt_nbActv(l)
176     IF ( iSdiag(k,l).EQ.-iSp ) THEN
177     DO j=0,nRegions
178     region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
179     ENDDO
180     ENDIF
181     ENDDO
182     ENDDO
183     C- diagnostics is valid and Active, has a counter mate: Now do the filling
184     CALL DIAGSTATS_FILL(
185 jmc 1.6 I inpFld, fractFld,
186     #ifndef REAL4_IS_SLOW
187     I dummyRS, dummyRS,
188     #endif
189     I scaleFact, power, arrType, nLevFract,
190 jmc 1.2 I ndId, iSp, region2fill, kLev, nLevs,
191     I bibjFlg, biArg, bjArg, myThid )
192 jmc 1.1 ENDIF
193     ENDIF
194     ENDDO
195     ENDDO
196    
197     RETURN
198     END

  ViewVC Help
Powered by ViewVC 1.1.22