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

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

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


Revision 1.6 - (show annotations) (download)
Thu May 19 01:23:39 2005 UTC (19 years ago) by jmc
Branch: MAIN
Changes since 1.5: +10 -202 lines
DIAGNOSTICS_FILL is just calling DIAGNOSTICS_FILL_FIELD if needed
 (preparing for Global/Regional statistics ability)

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_fill.F,v 1.5 2005/02/25 16:43:39 molod Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIAGNOSTICS_FILL
8 C !INTERFACE:
9 SUBROUTINE DIAGNOSTICS_FILL (inpfld, chardiag,
10 I kLev, nLevs, bibjflg, biArg, bjArg, myThid)
11
12 C !DESCRIPTION:
13 C***********************************************************************
14 C Wrapper routine to increment the diagnostics arrays with a field
15 C***********************************************************************
16 C !USES:
17 IMPLICIT NONE
18
19 C == Global variables ===
20 #include "EEPARAMS.h"
21 #include "SIZE.h"
22 #include "DIAGNOSTICS_SIZE.h"
23 #include "DIAGNOSTICS.h"
24
25 C !INPUT PARAMETERS:
26 C***********************************************************************
27 C Arguments Description
28 C ----------------------
29 C inpfld ..... Field to increment diagnostics array
30 C chardiag ... Character expression for diag to fill
31 C kLev ..... Integer flag for vertical levels:
32 C > 0 (any integer): WHICH single level to increment in qdiag.
33 C 0,-1 to increment "nLevs" levels in qdiag,
34 C 0 : fill-in in the same order as the input array
35 C -1: fill-in in reverse order.
36 C nLevs ...... indicates Number of levels of the input field array
37 C (whether to fill-in all the levels (kLev<1) or just one (kLev>0))
38 C bibjflg .... Integer flag to indicate instructions for bi bj loop
39 C 0 indicates that the bi-bj loop must be done here
40 C 1 indicates that the bi-bj loop is done OUTSIDE
41 C 2 indicates that the bi-bj loop is done OUTSIDE
42 C AND that we have been sent a local array (with overlap regions)
43 C 3 indicates that the bi-bj loop is done OUTSIDE
44 C AND that we have been sent a local array
45 C AND that the array has no overlap region (interior only)
46 C NOTE - bibjflg can be NEGATIVE to indicate not to increment counter
47 C biArg ...... X-direction tile number - used for bibjflg=1-3
48 C bjArg ...... Y-direction tile number - used for bibjflg=1-3
49 C myThid :: my thread Id number
50 C***********************************************************************
51 C NOTE: User beware! If a local (1 tile only) array
52 C is sent here, bibjflg MUST NOT be set to 0
53 C or there will be out of bounds problems!
54 C***********************************************************************
55 _RL inpfld(*)
56 CHARACTER*8 chardiag
57 INTEGER kLev, nLevs, bibjflg, biArg, bjArg
58 INTEGER myThid
59 CEOP
60
61 C !LOCAL VARIABLES:
62 C ===============
63 INTEGER m, n, j
64 INTEGER ndiagnum, ipointer, iSp, jSd
65 INTEGER region2fill(0:nRegions)
66
67 C-- 2D/3D Diagnostics :
68 C Run through list of active diagnostics to make sure
69 C we are trying to fill a valid diagnostic
70
71 ndiagnum = 0
72 ipointer = 0
73 DO n=1,nlists
74 DO m=1,nActive(n)
75 IF ( chardiag.EQ.flds(m,n) ) THEN
76 ndiagnum = jdiag(m,n)
77 IF (ndiag(ndiagnum).GE.0) ipointer = idiag(ndiagnum)
78 ENDIF
79 ENDDO
80 ENDDO
81
82 C if we are a valid and an active diagnostic, do the filling:
83 IF ( ipointer.NE.0 ) THEN
84 CALL DIAGNOSTICS_FILL_FIELD( inpfld, ndiagnum, ipointer,
85 I kLev, nLevs, bibjflg, biArg, bjArg, myThid )
86 ENDIF
87
88 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
89
90 RETURN
91 END

  ViewVC Help
Powered by ViewVC 1.1.22