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

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

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


Revision 1.6 - (hide annotations) (download)
Sun Jun 26 16:51:49 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57o_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57r_post, checkpoint57n_post, checkpoint57p_post, checkpoint57q_post, checkpoint57j_post, checkpoint57l_post
Changes since 1.5: +15 -20 lines
change pointers so that 1 diag. can be used several times (with # freq.)

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diag_vegtile_fill.F,v 1.5 2005/02/23 16:01:54 molod Exp $
2 molod 1.1 C $Name: $
3    
4     #include "DIAG_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: DIAG_VEGTILE_FILL
8     C !INTERFACE:
9     SUBROUTINE DIAG_VEGTILE_FILL (field,indx,chfr,ib,numpts,npeice,
10     . check, chardiag, kLev, nLevs, bi, bj, myThid)
11     C !DESCRIPTION:
12     C***********************************************************************
13     C Increment the diagnostics array with a vegetation tile space field
14     C***********************************************************************
15     C !USES:
16     IMPLICIT NONE
17    
18     C == Global variables ===
19     #include "EEPARAMS.h"
20     #include "SIZE.h"
21     #include "DIAGNOSTICS_SIZE.h"
22     #include "DIAGNOSTICS.h"
23    
24     C !INPUT PARAMETERS:
25     C***********************************************************************
26     C field - array to be mapped to grid space [ib,levs] and added to qdiag
27     C indx - array of horizontal indeces of grid points to convert to
28     C tile space[numpts]
29     C chfr - fractional area covered by the tile [ib]
30     C ib - inner dimension of source array AND number of points in
31     C array a that need to be pasted
32     C numpts - total number of points which were stripped
33     C npeice - the current strip number to be filled
34     C check - logical to check for undefined values
35     C chardiag ... Character expression for diag to fill
36     C kLev ..... Integer flag for vertical levels:
37     C > 0 (any integer): WHICH single level to increment
38     C 0,-1 to increment "nLevs" levels in qdiag:
39     C 0 : fill-in in the same order as the input array
40     C -1 : fill-in in reverse order.
41     C nLevs ...... indicates Number of levels of the input field array
42     C bi ...... X-direction tile number
43     C bj ...... Y-direction tile number
44     C myThid :: my thread Id number
45     C
46     c IMPORTANT NOTE:
47     c
48     c This routine will result in roundoff differences if called from
49     c within a parallel region.
50     C***********************************************************************
51     CHARACTER*8 chardiag
52     INTEGER kLev, nLevs, bi, bj
53     INTEGER myThid
54     integer ib,numpts,npeice
55     integer indx(numpts)
56     _RL field(ib,nlevs), chfr(ib)
57     logical check
58     CEOP
59    
60     C !LOCAL VARIABLES:
61     C ===============
62     INTEGER m, n
63     INTEGER ndiagnum, ipointer
64     INTEGER k, kFirst, kLast
65     INTEGER kd, kd0, ksgn, kStore
66     CHARACTER*(MAX_LEN_MBUF) msgBuf
67     integer i,offset,Lena,newindx,jindx
68     _RL undef,getcon
69    
70     C Run through list of active diagnostics to make sure
71     C we are trying to fill a valid diagnostic
72    
73     ndiagnum = 0
74     ipointer = 0
75     DO n=1,nlists
76     DO m=1,nActive(n)
77 jmc 1.6 IF ( chardiag.EQ.flds(m,n) .AND. idiag(m,n).GT.0 ) THEN
78 molod 1.1 ndiagnum = jdiag(m,n)
79 jmc 1.6 ipointer = idiag(m,n)
80     IF ( ndiagnum.NE.0 .AND. ndiag(ipointer,1,1).GE.0 ) THEN
81     C-- do the filling: start here:
82    
83     IF ( (ABS(kLev).LE.1) .AND. (npeice.eq.1) ) THEN
84     C Increment the counter for the diagnostic
85     ndiag(ipointer,bi,bj) = ndiag(ipointer,bi,bj) + 1
86     ENDIF
87 molod 1.1
88     offset = ib*(npeice-1)
89     Lena = min(ib,numpts-offset)
90     offset = offset+1
91    
92     C- Which part of field to add : k = 3rd index,
93     C and do the loop >> do k=kFirst,kLast <<
94     IF (kLev.LE.0) THEN
95     kFirst = 1
96     kLast = nLevs
97     ELSEIF ( nLevs.EQ.1 ) THEN
98     kFirst = 1
99     kLast = 1
100     ELSEIF ( kLev.LE.nLevs ) THEN
101     kFirst = kLev
102     kLast = kLev
103     ELSE
104     STOP 'ABNORMAL END: S/R DIAGNOSTICS_FILL kLev > nLevs > 0'
105     ENDIF
106     C- Which part of qdiag to update: kd = 3rd index,
107     C and do the loop >> do k=kFirst,kLast ; kd = kd0 + k*ksgn <<
108     IF ( kLev.EQ.-1 ) THEN
109     ksgn = -1
110     kd0 = ipointer + nLevs
111     ELSEIF ( kLev.EQ.0 ) THEN
112     ksgn = 1
113     kd0 = ipointer - 1
114     ELSE
115     ksgn = 0
116     kd0 = ipointer + kLev - 1
117     ENDIF
118    
119     C- Check for consistency with Nb of levels reserved in storage array
120     kStore = kd0 + MAX(ksgn*kFirst,ksgn*kLast) - ipointer + 1
121     IF ( kStore.GT.kdiag(ndiagnum) ) THEN
122     _BEGIN_MASTER(myThid)
123     WRITE(msgBuf,'(2A,I3,A)') 'DIAGNOSTICS_FILL: ',
124     . 'exceed Nb of levels(=',kdiag(ndiagnum),' ) reserved '
125     CALL PRINT_ERROR( msgBuf , myThid )
126     WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_FILL: ',
127     . 'for Diagnostics #', ndiagnum, ' : ', chardiag
128     CALL PRINT_ERROR( msgBuf , myThid )
129     WRITE(msgBuf,'(2A,2I4,I3)') 'calling DIAGNOSTICS_FILL ',
130     . 'with kLev,nLevs=', kLev,nLevs
131     CALL PRINT_ERROR( msgBuf , myThid )
132     WRITE(msgBuf,'(2A,I6,A)') 'DIAGNOSTICS_FILL: ',
133     . '==> trying to store up to ', kStore, ' levels'
134     CALL PRINT_ERROR( msgBuf , myThid )
135     STOP 'ABNORMAL END: S/R DIAGNOSTICS_FILL'
136     _END_MASTER(myThid)
137     ENDIF
138    
139     DO k = kFirst,kLast
140     kd = kd0 + ksgn*k
141     if( check ) then
142     undef = getcon('UNDEF')
143     do i= 1,Lena
144 molod 1.3 jindx = 1 + int((indx(i+offset-1)-1)/sNx)
145 molod 1.4 newindx = indx(i+offset-1)+(jindx-1)*2*Olx
146 molod 1.1 if(qdiag(newindx,1,kd,bi,bj).eq.undef
147     . .or.field(i,k).eq.undef)then
148     qdiag(newindx,1,kd,bi,bj) = undef
149     else
150     qdiag(newindx,1,kd,bi,bj)=qdiag(newindx,1,kd,bi,bj)+
151 molod 1.4 . field(i,k)*chfr(i)
152 molod 1.1 endif
153     enddo
154     else
155     do i= 1,Lena
156 molod 1.3 jindx = 1 + int((indx(i+offset-1)-1)/sNx)
157 molod 1.4 newindx = indx(i+offset-1)+(jindx-1)*2*Olx
158 molod 1.1 qdiag(newindx,1,kd,bi,bj)=qdiag(newindx,1,kd,bi,bj)+
159 molod 1.4 . field(i,k)*chfr(i)
160 molod 1.1 enddo
161     endif
162     ENDDO
163    
164 jmc 1.6 C-- do the filling: ends here.
165     ENDIF
166     ENDIF
167     ENDDO
168     ENDDO
169 molod 1.1
170     1000 format(' ',' Warning: Trying to write to diagnostic ',a8,
171     . ' But it is not a valid (or active) name ')
172     RETURN
173     END

  ViewVC Help
Powered by ViewVC 1.1.22