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

Contents of /MITgcm/pkg/diagnostics/diagnostics_scale_fill.F

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


Revision 1.1 - (show annotations) (download)
Sun Jul 10 00:58:11 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
fill the diagnostics array using a scaling factor.

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_fill.F,v 1.9 2005/06/26 16:51:49 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIAGNOSTICS_SCALE_FILL
8 C !INTERFACE:
9 SUBROUTINE DIAGNOSTICS_SCALE_FILL(
10 I inpFld, scaleFact, 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 using a scaling factor
17 C***********************************************************************
18 C !USES:
19 IMPLICIT NONE
20
21 C == Global variables ===
22 #include "EEPARAMS.h"
23 #include "SIZE.h"
24 #include "DIAGNOSTICS_SIZE.h"
25 #include "DIAGNOSTICS.h"
26
27 C !INPUT PARAMETERS:
28 C***********************************************************************
29 C Arguments Description
30 C ----------------------
31 C inpFld :: Field to increment diagnostics array
32 C scaleFact :: scaling factor
33 C chardiag :: Character expression for diag to fill
34 C kLev :: Integer flag for vertical levels:
35 C > 0 (any integer): WHICH single level to increment in qdiag.
36 C 0,-1 to increment "nLevs" levels in qdiag,
37 C 0 : fill-in in the same order as the input array
38 C -1: fill-in in reverse order.
39 C nLevs :: indicates Number of levels of the input field array
40 C (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
41 C bibjFlg :: Integer flag to indicate instructions for bi bj loop
42 C 0 indicates that the bi-bj loop must be done here
43 C 1 indicates that the bi-bj loop is done OUTSIDE
44 C 2 indicates that the bi-bj loop is done OUTSIDE
45 C AND that we have been sent a local array (with overlap regions)
46 C 3 indicates that the bi-bj loop is done OUTSIDE
47 C AND that we have been sent a local array
48 C AND that the array has no overlap region (interior only)
49 C NOTE - bibjFlg can be NEGATIVE to indicate not to increment counter
50 C biArg :: X-direction tile number - used for bibjFlg=1-3
51 C bjArg :: Y-direction tile number - used for bibjFlg=1-3
52 C myThid :: my thread Id number
53 C***********************************************************************
54 C NOTE: User beware! If a local (1 tile only) array
55 C is sent here, bibjFlg MUST NOT be set to 0
56 C or there will be out of bounds problems!
57 C***********************************************************************
58 _RL inpFld(*)
59 _RL scaleFact
60 CHARACTER*8 chardiag
61 INTEGER kLev, nLevs, bibjFlg, biArg, bjArg
62 INTEGER myThid
63 CEOP
64
65 C !LOCAL VARIABLES:
66 C ndId :: diagnostic Id number (in available diagnostics list)
67 C ===============
68 INTEGER m, n, j, k, l, bi, bj
69 INTEGER ndId, ipt, iSp
70 INTEGER region2fill(0:nRegions)
71
72 IF ( bibjFlg.EQ.0 ) THEN
73 bi = 1
74 bj = 1
75 ELSE
76 bi = biArg
77 bj = bjArg
78 ENDIF
79 C-- 2D/3D Diagnostics :
80 C Run through list of active diagnostics to make sure
81 C we are trying to fill a valid diagnostic
82 DO n=1,nlists
83 DO m=1,nActive(n)
84 IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
85 ipt = idiag(m,n)
86 IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
87 ndId = jdiag(m,n)
88 C- diagnostic is valid & active, do the filling:
89 CALL DIAGNOSTICS_FILL_FIELD(
90 I inpFld, inpFld, scaleFact, 0,
91 I ndId, ipt, kLev, nLevs,
92 I bibjFlg, biArg, bjArg, myThid )
93 ENDIF
94 ENDIF
95 ENDDO
96 ENDDO
97
98 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
99 C-- Global/Regional Statistics :
100
101 C Run through list of active statistics-diagnostics to make sure
102 C we are trying to compute & fill a valid diagnostic
103
104 DO n=1,diagSt_nbLists
105 DO m=1,diagSt_nbActv(n)
106 IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
107 iSp = iSdiag(m,n)
108 IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
109 ndId = jSdiag(m,n)
110 C- Find list of regions to fill:
111 DO j=0,nRegions
112 region2fill(j) = diagSt_region(j,n)
113 ENDDO
114 C- if this diagnostics appears in several lists (with same freq)
115 C then add regions from other lists
116 DO l=1,diagSt_nbLists
117 DO k=1,diagSt_nbActv(l)
118 IF ( iSdiag(k,l).EQ.-iSp ) THEN
119 DO j=0,nRegions
120 region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
121 ENDDO
122 ENDIF
123 ENDDO
124 ENDDO
125 C- diagnostics is valid and Active: Now do the filling
126 CALL DIAGSTATS_FILL(
127 I inpFld, inpFld, scaleFact, 0,
128 I ndId, iSp, region2fill, kLev, nLevs,
129 I bibjFlg, biArg, bjArg, myThid )
130 ENDIF
131 ENDIF
132 ENDDO
133 ENDDO
134
135 RETURN
136 END

  ViewVC Help
Powered by ViewVC 1.1.22