/[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.4 - (show annotations) (download)
Mon Jul 31 16:26:32 2006 UTC (17 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58o_post, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.3: +3 -3 lines
safer in multi-threaded environment

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_scale_fill.F,v 1.3 2006/06/05 18:17:22 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, 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 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 _RL 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 C ===============
70 INTEGER m, n, j, k, l, bi, bj
71 INTEGER ndId, ipt, iSp
72 INTEGER region2fill(0:nRegions)
73
74 IF ( bibjFlg.EQ.0 ) THEN
75 bi = myBxLo(myThid)
76 bj = myByLo(myThid)
77 ELSE
78 bi = biArg
79 bj = bjArg
80 ENDIF
81 C-- 2D/3D Diagnostics :
82 C Run through list of active diagnostics to make sure
83 C we are trying to fill a valid diagnostic
84 DO n=1,nlists
85 DO m=1,nActive(n)
86 IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
87 ipt = idiag(m,n)
88 IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
89 ndId = jdiag(m,n)
90 ipt = ipt + pdiag(n,bi,bj)*kdiag(ndId)
91 C- diagnostic is valid & active, do the filling:
92 CALL DIAGNOSTICS_FILL_FIELD(
93 I inpFld, inpFld, scaleFact, power, 0,
94 I ndId, ipt, kLev, nLevs,
95 I bibjFlg, biArg, bjArg, myThid )
96 ENDIF
97 ENDIF
98 ENDDO
99 ENDDO
100
101 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
102 C-- Global/Regional Statistics :
103
104 C Run through list of active statistics-diagnostics to make sure
105 C we are trying to compute & fill a valid diagnostic
106
107 DO n=1,diagSt_nbLists
108 DO m=1,diagSt_nbActv(n)
109 IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
110 iSp = iSdiag(m,n)
111 IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
112 ndId = jSdiag(m,n)
113 C- Find list of regions to fill:
114 DO j=0,nRegions
115 region2fill(j) = diagSt_region(j,n)
116 ENDDO
117 C- if this diagnostics appears in several lists (with same freq)
118 C then add regions from other lists
119 DO l=1,diagSt_nbLists
120 DO k=1,diagSt_nbActv(l)
121 IF ( iSdiag(k,l).EQ.-iSp ) THEN
122 DO j=0,nRegions
123 region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
124 ENDDO
125 ENDIF
126 ENDDO
127 ENDDO
128 C- diagnostics is valid and Active: Now do the filling
129 CALL DIAGSTATS_FILL(
130 I inpFld, inpFld, scaleFact, power, 0,
131 I ndId, iSp, region2fill, kLev, nLevs,
132 I bibjFlg, biArg, bjArg, myThid )
133 ENDIF
134 ENDIF
135 ENDDO
136 ENDDO
137
138 RETURN
139 END

  ViewVC Help
Powered by ViewVC 1.1.22