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

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

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


Revision 1.13 - (hide annotations) (download)
Mon Jul 31 16:26:32 2006 UTC (17 years, 10 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.12: +3 -3 lines
safer in multi-threaded environment

1 jmc 1.13 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_fill.F,v 1.12 2006/06/05 18:17:22 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6 jmc 1.2 CBOP
7     C !ROUTINE: DIAGNOSTICS_FILL
8     C !INTERFACE:
9 jmc 1.10 SUBROUTINE DIAGNOSTICS_FILL(
10 jmc 1.11 I inpFld, chardiag,
11     I kLev, nLevs, bibjFlg, biArg, bjArg, myThid )
12 jmc 1.2
13     C !DESCRIPTION:
14 jmc 1.1 C***********************************************************************
15 jmc 1.6 C Wrapper routine to increment the diagnostics arrays with a field
16 jmc 1.2 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 jmc 1.1 C Arguments Description
29     C ----------------------
30 jmc 1.10 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 jmc 1.3 C > 0 (any integer): WHICH single level to increment in qdiag.
34     C 0,-1 to increment "nLevs" levels in qdiag,
35 jmc 1.9 C 0 : fill-in in the same order as the input array
36 jmc 1.3 C -1: fill-in in reverse order.
37 jmc 1.10 C nLevs :: indicates Number of levels of the input field array
38 jmc 1.3 C (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
39 jmc 1.10 C bibjFlg :: Integer flag to indicate instructions for bi bj loop
40 jmc 1.1 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 jmc 1.9 C NOTE - bibjFlg can be NEGATIVE to indicate not to increment counter
48 jmc 1.10 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 jmc 1.1 C***********************************************************************
52     C NOTE: User beware! If a local (1 tile only) array
53 jmc 1.9 C is sent here, bibjFlg MUST NOT be set to 0
54 jmc 1.1 C or there will be out of bounds problems!
55     C***********************************************************************
56 jmc 1.10 _RL inpFld(*)
57 jmc 1.2 CHARACTER*8 chardiag
58 jmc 1.9 INTEGER kLev, nLevs, bibjFlg, biArg, bjArg
59 jmc 1.2 INTEGER myThid
60     CEOP
61    
62     C !LOCAL VARIABLES:
63 jmc 1.9 C ndId :: diagnostic Id number (in available diagnostics list)
64 jmc 1.2 C ===============
65 jmc 1.9 INTEGER m, n, j, k, l, bi, bj
66     INTEGER ndId, ipt, iSp
67 jmc 1.8 INTEGER region2fill(0:nRegions)
68 jmc 1.10 _RL scaleFact
69 jmc 1.1
70 jmc 1.10 scaleFact = 1. _d 0
71 jmc 1.9 IF ( bibjFlg.EQ.0 ) THEN
72 jmc 1.13 bi = myBxLo(myThid)
73     bj = myByLo(myThid)
74 jmc 1.9 ELSE
75     bi = biArg
76     bj = bjArg
77     ENDIF
78 jmc 1.6 C-- 2D/3D Diagnostics :
79 jmc 1.1 C Run through list of active diagnostics to make sure
80     C we are trying to fill a valid diagnostic
81     DO n=1,nlists
82     DO m=1,nActive(n)
83 jmc 1.9 IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
84     ipt = idiag(m,n)
85     IF ( ndiag(ipt,bi,bj).GE.0 ) THEN
86     ndId = jdiag(m,n)
87 jmc 1.12 ipt = ipt + pdiag(n,bi,bj)*kdiag(ndId)
88 jmc 1.10 C- diagnostic is valid & active, do the filling:
89     CALL DIAGNOSTICS_FILL_FIELD(
90 jmc 1.11 I inpFld, inpFld, scaleFact, 1, 0,
91     I ndId, ipt, kLev, nLevs,
92     I bibjFlg, biArg, bjArg, myThid )
93 jmc 1.9 ENDIF
94 jmc 1.1 ENDIF
95     ENDDO
96     ENDDO
97    
98     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
99 jmc 1.8 C-- Global/Regional Statistics :
100    
101     C Run through list of active statistics-diagnostics to make sure
102     C we are trying to compute & fill a valid diagnostic
103    
104     DO n=1,diagSt_nbLists
105     DO m=1,diagSt_nbActv(n)
106 jmc 1.9 IF ( chardiag.EQ.diagSt_Flds(m,n) .AND. iSdiag(m,n).GT.0 ) THEN
107     iSp = iSdiag(m,n)
108     IF ( qSdiag(0,0,iSp,bi,bj).GE.0. ) THEN
109 jmc 1.10 ndId = jSdiag(m,n)
110     C- Find list of regions to fill:
111 jmc 1.8 DO j=0,nRegions
112     region2fill(j) = diagSt_region(j,n)
113     ENDDO
114 jmc 1.10 C- if this diagnostics appears in several lists (with same freq)
115     C then add regions from other lists
116 jmc 1.9 DO l=1,diagSt_nbLists
117     DO k=1,diagSt_nbActv(l)
118     IF ( iSdiag(k,l).EQ.-iSp ) THEN
119     DO j=0,nRegions
120     region2fill(j) = MAX(region2fill(j),diagSt_region(j,l))
121     ENDDO
122     ENDIF
123     ENDDO
124 jmc 1.8 ENDDO
125 jmc 1.10 C- diagnostics is valid and Active: Now do the filling
126     CALL DIAGSTATS_FILL(
127 jmc 1.11 I inpFld, inpFld, scaleFact, 1, 0,
128     I ndId, iSp, region2fill, kLev, nLevs,
129     I bibjFlg, biArg, bjArg, myThid )
130 jmc 1.8 ENDIF
131     ENDIF
132     ENDDO
133     ENDDO
134    
135 jmc 1.9 RETURN
136 jmc 1.2 END

  ViewVC Help
Powered by ViewVC 1.1.22