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

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

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


Revision 1.1 - (hide annotations) (download)
Thu Sep 3 20:47:14 2009 UTC (14 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
RS version of RL subroutine DIAGNOSTICS_FILL & DIAGNOSTICS_SCALE_FILL

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

  ViewVC Help
Powered by ViewVC 1.1.22