/[MITgcm]/MITgcm_contrib/quarter_degree_global/code_srdiags_call/diagnostics_fill.F
ViewVC logotype

Contents of /MITgcm_contrib/quarter_degree_global/code_srdiags_call/diagnostics_fill.F

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


Revision 1.2 - (show annotations) (download)
Fri Jul 28 22:12:12 2006 UTC (19 years ago) by cnh
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +36 -1 lines
Mods to call sub-region diags

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_fill.F,v 1.12 2006/06/05 18:17:22 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIAGNOSTICS_FILL
8 C !INTERFACE:
9 SUBROUTINE DIAGNOSTICS_FILL(
10 I inpFld, chardiag,
11 I kLev, nLevs, bibjFlg, biArg, bjArg, myThid )
12
13 C !DESCRIPTION:
14 C***********************************************************************
15 C Wrapper routine to increment the diagnostics arrays with a field
16 C***********************************************************************
17 C !USES:
18 IMPLICIT NONE
19
20 C == Global variables ===
21 #include "EEPARAMS.h"
22 #include "SIZE.h"
23 #include "DIAGNOSTICS_SIZE.h"
24 #include "DIAGNOSTICS.h"
25
26 C !INPUT PARAMETERS:
27 C***********************************************************************
28 C Arguments Description
29 C ----------------------
30 C inpFld :: Field to increment diagnostics array
31 C chardiag :: Character expression for diag to fill
32 C kLev :: Integer flag for vertical levels:
33 C > 0 (any integer): WHICH single level to increment in qdiag.
34 C 0,-1 to increment "nLevs" levels in qdiag,
35 C 0 : fill-in in the same order as the input array
36 C -1: fill-in in reverse order.
37 C nLevs :: indicates Number of levels of the input field array
38 C (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
39 C bibjFlg :: Integer flag to indicate instructions for bi bj loop
40 C 0 indicates that the bi-bj loop must be done here
41 C 1 indicates that the bi-bj loop is done OUTSIDE
42 C 2 indicates that the bi-bj loop is done OUTSIDE
43 C AND that we have been sent a local array (with overlap regions)
44 C 3 indicates that the bi-bj loop is done OUTSIDE
45 C AND that we have been sent a local array
46 C AND that the array has no overlap region (interior only)
47 C NOTE - bibjFlg can be NEGATIVE to indicate not to increment counter
48 C biArg :: X-direction tile number - used for bibjFlg=1-3
49 C bjArg :: Y-direction tile number - used for bibjFlg=1-3
50 C myThid :: my thread Id number
51 C***********************************************************************
52 C NOTE: User beware! If a local (1 tile only) array
53 C is sent here, bibjFlg MUST NOT be set to 0
54 C or there will be out of bounds problems!
55 C***********************************************************************
56 _RL inpFld(*)
57 CHARACTER*8 chardiag
58 INTEGER kLev, nLevs, bibjFlg, biArg, bjArg
59 INTEGER myThid
60 CEOP
61
62 C !LOCAL VARIABLES:
63 C ndId :: diagnostic Id number (in available diagnostics list)
64 C ===============
65 INTEGER m, n, j, k, l, bi, bj
66 INTEGER ndId, ipt, iSp
67 INTEGER region2fill(0:nRegions)
68 _RL scaleFact
69 CcnhBegin
70 _RL tempFld(1:sNx,1:sNy,Nr)
71 INTEGER i1, i2, j1, j2, k1, k2, iB
72 C iLo,iHi,jLo,jHi,nr,ntx,nty,klev
73 INTEGER iFldParms(8)
74 INTEGER II
75 CcnhEnd
76
77 CcnhBegin
78 C Pass things through to the sub-region diags
79 C PRINT *, 'DIAGNOSTICS FILL FOR ', charDiag
80 C iB = 0
81 ! DO K=k1,k2
82 ! DO J=j1,j2
83 ! IF ( J .GE. 1 .AND. J .LE. sNy ) THEN
84 ! DO I=i1,i2
85 ! IF ( I .GE. 1 .AND. I .LE. sNx ) THEN
86 ! iB = iB+1
87 ! tempFld(I,J,K) = inpFld(iB)
88 ! ENDIF
89 ! ENDDO
90 ! ENDIF
91 ! ENDDO
92 ! ENDDO
93 CcnhEnd
94
95 scaleFact = 1. _d 0
96 IF ( bibjFlg.EQ.0 ) THEN
97 bi = 1
98 bj = 1
99 ELSE
100 bi = biArg
101 bj = bjArg
102 ENDIF
103 C-- 2D/3D Diagnostics :
104 C Run through list of active diagnostics to make sure
105 C we are trying to fill a valid diagnostic
106 DO n=1,nlists
107 DO m=1,nActive(n)
108 IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
109 ipt = idiag(m,n)
110 IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
111 ndId = jdiag(m,n)
112 ipt = ipt + pdiag(n,bi,bj)*kdiag(ndId)
113 C- diagnostic is valid & active, do the filling:
114 CALL DIAGNOSTICS_FILL_FIELD(
115 I inpFld, inpFld, scaleFact, 1, 0,
116 I ndId, ipt, kLev, nLevs,
117 I bibjFlg, biArg, bjArg,
118 O iFldParms,
119 I myThid )
120 CcnhBegin
121 ! DO II=1,10000
122 CALL SRDIAGS_F77_FILL( charDiag,
123 I inpFld, iFldParms, biArg, bjArg,
124 I myThid)
125 ! ENDDO
126 CcnhEnd
127 ENDIF
128 ENDIF
129 ENDDO
130 ENDDO
131
132
133 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
134 C-- Global/Regional Statistics :
135
136 C Run through list of active statistics-diagnostics to make sure
137 C we are trying to compute & fill a valid diagnostic
138
139 DO n=1,diagSt_nbLists
140 DO m=1,diagSt_nbActv(n)
141 IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
142 iSp = iSdiag(m,n)
143 IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
144 ndId = jSdiag(m,n)
145 C- Find list of regions to fill:
146 DO j=0,nRegions
147 region2fill(j) = diagSt_region(j,n)
148 ENDDO
149 C- if this diagnostics appears in several lists (with same freq)
150 C then add regions from other lists
151 DO l=1,diagSt_nbLists
152 DO k=1,diagSt_nbActv(l)
153 IF ( iSdiag(k,l).EQ.-iSp ) THEN
154 DO j=0,nRegions
155 region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
156 ENDDO
157 ENDIF
158 ENDDO
159 ENDDO
160 C- diagnostics is valid and Active: Now do the filling
161 CALL DIAGSTATS_FILL(
162 I inpFld, inpFld, scaleFact, 1, 0,
163 I ndId, iSp, region2fill, kLev, nLevs,
164 I bibjFlg, biArg, bjArg, myThid )
165 ENDIF
166 ENDIF
167 ENDDO
168 ENDDO
169
170 RETURN
171 END

  ViewVC Help
Powered by ViewVC 1.1.22