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

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

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


Revision 1.4 - (show annotations) (download)
Sun Jul 23 00:38:52 2017 UTC (6 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, HEAD
Changes since 1.3: +5 -4 lines
implement thickness-factor averaged by calling S/R DIAGNOSTICS_FILL_FIELD
with negative "nLevFrac".

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_fill_rs.F,v 1.3 2013/08/14 01:00:11 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 (local array here means that it has no bi-bj dimensions)
45 C 3 indicates that the bi-bj loop is done OUTSIDE
46 C AND that we have been sent a local array
47 C AND that the array has no overlap region (interior only)
48 C NOTE - bibjFlg can be NEGATIVE to indicate not to increment counter
49 C biArg :: X-direction tile number - used for bibjFlg=1-3
50 C bjArg :: Y-direction tile number - used for bibjFlg=1-3
51 C myThid :: my thread Id number
52 C***********************************************************************
53 C NOTE: User beware! If a local (1 tile only) array
54 C is sent here, bibjFlg MUST NOT be set to 0
55 C or there will be out of bounds problems!
56 C***********************************************************************
57 _RS inpFld(*)
58 CHARACTER*8 chardiag
59 INTEGER kLev, nLevs, bibjFlg, biArg, bjArg
60 INTEGER myThid
61 CEOP
62
63 C !LOCAL VARIABLES:
64 C ndId :: diagnostic Id number (in available diagnostics list)
65 INTEGER m, n, j, k, l, bi, bj
66 INTEGER ndId, ipt, iSp
67 INTEGER region2fill(0:nRegions)
68 INTEGER arrType, wFac
69 _RL scaleFact
70 _RL dummyRL(1)
71 _RS dummyRS(1)
72 C ===============
73
74 C-- Check if this S/R is called from the right place ;
75 C needs to be after DIAGNOSTICS_SWITCH_ONOFF and before DIAGNOSTICS_WRITE
76 IF ( diag_pkgStatus.NE.ready2fillDiags ) THEN
77 CALL DIAGNOSTICS_STATUS_ERROR( 'DIAGNOSTICS_FILL_RS',
78 & ' ', chardiag, ready2fillDiags, myThid )
79 ENDIF
80
81 arrType = 2
82 scaleFact = 1. _d 0
83 IF ( bibjFlg.EQ.0 ) THEN
84 bi = myBxLo(myThid)
85 bj = myByLo(myThid)
86 ELSE
87 bi = biArg
88 bj = bjArg
89 ENDIF
90 C-- 2D/3D Diagnostics :
91 C Run through list of active diagnostics to make sure
92 C we are trying to fill a valid diagnostic
93 DO n=1,nlists
94 DO m=1,nActive(n)
95 IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
96 ipt = idiag(m,n)
97 IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
98 ndId = ABS(jdiag(m,n))
99 wFac = MIN( jdiag(m,n), 0 )
100 ipt = ipt + pdiag(n,bi,bj)*kdiag(ndId)
101 C- diagnostic is valid & active, do the filling:
102 CALL DIAGNOSTICS_FILL_FIELD(
103 I dummyRL, dummyRL, inpFld, dummyRS,
104 I scaleFact, 1, arrType, wFac,
105 I ndId, ipt, kLev, nLevs,
106 I bibjFlg, biArg, bjArg, myThid )
107 ENDIF
108 ENDIF
109 ENDDO
110 ENDDO
111
112 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
113 C-- Global/Regional Statistics :
114
115 C Run through list of active statistics-diagnostics to make sure
116 C we are trying to compute & fill a valid diagnostic
117
118 DO n=1,diagSt_nbLists
119 DO m=1,diagSt_nbActv(n)
120 IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
121 iSp = iSdiag(m,n)
122 IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
123 ndId = jSdiag(m,n)
124 C- Find list of regions to fill:
125 DO j=0,nRegions
126 region2fill(j) = diagSt_region(j,n)
127 ENDDO
128 C- if this diagnostics appears in several lists (with same freq)
129 C then add regions from other lists
130 DO l=1,diagSt_nbLists
131 DO k=1,diagSt_nbActv(l)
132 IF ( iSdiag(k,l).EQ.-iSp ) THEN
133 DO j=0,nRegions
134 region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
135 ENDDO
136 ENDIF
137 ENDDO
138 ENDDO
139 C- diagnostics is valid and Active: Now do the filling
140 CALL DIAGSTATS_FILL(
141 #ifdef REAL4_IS_SLOW
142 I inpFld, dummyRL,
143 #else
144 I dummyRL, dummyRL,
145 I inpFld, dummyRS,
146 #endif
147 I scaleFact, 1, arrType, 0,
148 I ndId, iSp, region2fill, kLev, nLevs,
149 I bibjFlg, biArg, bjArg, myThid )
150 ENDIF
151 ENDIF
152 ENDDO
153 ENDDO
154
155 RETURN
156 END

  ViewVC Help
Powered by ViewVC 1.1.22