/[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.2 - (hide annotations) (download)
Wed Aug 14 01:00:12 2013 UTC (10 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64o, checkpoint64n, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.1: +8 -1 lines
check pkgStatus (stop if not right) before doing anything

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_scale_fill_rs.F,v 1.1 2009/09/03 20:47:14 jmc Exp $
2 jmc 1.1 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 jmc 1.2 C-- Check if this S/R is called from the right place ;
78     C needs to be after DIAGNOSTICS_SWITCH_ONOFF and before DIAGNOSTICS_WRITE
79     IF ( diag_pkgStatus.NE.ready2fillDiags ) THEN
80     CALL DIAGNOSTICS_STATUS_ERROR( 'DIAGNOSTICS_SCALE_FILL_RS',
81     & ' ', chardiag, ready2fillDiags, myThid )
82     ENDIF
83    
84 jmc 1.1 arrType = 2
85     IF ( bibjFlg.EQ.0 ) THEN
86     bi = myBxLo(myThid)
87     bj = myByLo(myThid)
88     ELSE
89     bi = biArg
90     bj = bjArg
91     ENDIF
92     C-- 2D/3D Diagnostics :
93     C Run through list of active diagnostics to make sure
94     C we are trying to fill a valid diagnostic
95     DO n=1,nlists
96     DO m=1,nActive(n)
97     IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
98     ipt = idiag(m,n)
99     IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
100     ndId = jdiag(m,n)
101     ipt = ipt + pdiag(n,bi,bj)*kdiag(ndId)
102     C- diagnostic is valid & active, do the filling:
103     CALL DIAGNOSTICS_FILL_FIELD(
104     I dummyRL, dummyRL, inpFld, dummyRS,
105     I scaleFact, power, arrType, 0,
106     I ndId, ipt, kLev, nLevs,
107     I bibjFlg, biArg, bjArg, myThid )
108     ENDIF
109     ENDIF
110     ENDDO
111     ENDDO
112    
113     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
114     C-- Global/Regional Statistics :
115    
116     C Run through list of active statistics-diagnostics to make sure
117     C we are trying to compute & fill a valid diagnostic
118    
119     DO n=1,diagSt_nbLists
120     DO m=1,diagSt_nbActv(n)
121     IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
122     iSp = iSdiag(m,n)
123     IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
124     ndId = jSdiag(m,n)
125     C- Find list of regions to fill:
126     DO j=0,nRegions
127     region2fill(j) = diagSt_region(j,n)
128     ENDDO
129     C- if this diagnostics appears in several lists (with same freq)
130     C then add regions from other lists
131     DO l=1,diagSt_nbLists
132     DO k=1,diagSt_nbActv(l)
133     IF ( iSdiag(k,l).EQ.-iSp ) THEN
134     DO j=0,nRegions
135     region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
136     ENDDO
137     ENDIF
138     ENDDO
139     ENDDO
140     C- diagnostics is valid and Active: Now do the filling
141     CALL DIAGSTATS_FILL(
142     #ifdef REAL4_IS_SLOW
143     I inpFld, dummyRL,
144     #else
145     I dummyRL, dummyRL,
146     I inpFld, dummyRS,
147     #endif
148     I scaleFact, power, arrType, 0,
149     I ndId, iSp, region2fill, kLev, nLevs,
150     I bibjFlg, biArg, bjArg, myThid )
151     ENDIF
152     ENDIF
153     ENDDO
154     ENDDO
155    
156     RETURN
157     END

  ViewVC Help
Powered by ViewVC 1.1.22