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

Annotation of /MITgcm/pkg/diagnostics/diagnostics_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: checkpoint62, checkpoint62b, checkpoint62a, 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_fill.F,v 1.13 2006/07/31 16:26:32 jmc Exp $
2     C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DIAGNOSTICS_FILL_RS
8     C !INTERFACE:
9     SUBROUTINE DIAGNOSTICS_FILL_RS(
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 RS 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     _RS 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     INTEGER m, n, j, k, l, bi, bj
65     INTEGER ndId, ipt, iSp
66     INTEGER region2fill(0:nRegions)
67     INTEGER arrType
68     _RL scaleFact
69     _RL dummyRL(1)
70     _RS dummyRS(1)
71     C ===============
72    
73     arrType = 2
74     scaleFact = 1. _d 0
75     IF ( bibjFlg.EQ.0 ) THEN
76     bi = myBxLo(myThid)
77     bj = myByLo(myThid)
78     ELSE
79     bi = biArg
80     bj = bjArg
81     ENDIF
82     C-- 2D/3D Diagnostics :
83     C Run through list of active diagnostics to make sure
84     C we are trying to fill a valid diagnostic
85     DO n=1,nlists
86     DO m=1,nActive(n)
87     IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
88     ipt = idiag(m,n)
89     IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
90     ndId = jdiag(m,n)
91     ipt = ipt + pdiag(n,bi,bj)*kdiag(ndId)
92     C- diagnostic is valid & active, do the filling:
93     CALL DIAGNOSTICS_FILL_FIELD(
94     I dummyRL, dummyRL, inpFld, dummyRS,
95     I scaleFact, 1, arrType, 0,
96     I ndId, ipt, kLev, nLevs,
97     I bibjFlg, biArg, bjArg, myThid )
98     ENDIF
99     ENDIF
100     ENDDO
101     ENDDO
102    
103     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
104     C-- Global/Regional Statistics :
105    
106     C Run through list of active statistics-diagnostics to make sure
107     C we are trying to compute & fill a valid diagnostic
108    
109     DO n=1,diagSt_nbLists
110     DO m=1,diagSt_nbActv(n)
111     IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
112     iSp = iSdiag(m,n)
113     IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
114     ndId = jSdiag(m,n)
115     C- Find list of regions to fill:
116     DO j=0,nRegions
117     region2fill(j) = diagSt_region(j,n)
118     ENDDO
119     C- if this diagnostics appears in several lists (with same freq)
120     C then add regions from other lists
121     DO l=1,diagSt_nbLists
122     DO k=1,diagSt_nbActv(l)
123     IF ( iSdiag(k,l).EQ.-iSp ) THEN
124     DO j=0,nRegions
125     region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
126     ENDDO
127     ENDIF
128     ENDDO
129     ENDDO
130     C- diagnostics is valid and Active: Now do the filling
131     CALL DIAGSTATS_FILL(
132     #ifdef REAL4_IS_SLOW
133     I inpFld, dummyRL,
134     #else
135     I dummyRL, dummyRL,
136     I inpFld, dummyRS,
137     #endif
138     I scaleFact, 1, arrType, 0,
139     I ndId, iSp, region2fill, kLev, nLevs,
140     I bibjFlg, biArg, bjArg, myThid )
141     ENDIF
142     ENDIF
143     ENDDO
144     ENDDO
145    
146     RETURN
147     END

  ViewVC Help
Powered by ViewVC 1.1.22