/[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.5 - (hide annotations) (download)
Wed Feb 23 16:01:54 2005 UTC (19 years, 2 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint57g_post, checkpoint57i_post, checkpoint57e_post, checkpoint57g_pre, checkpoint57f_pre, eckpoint57e_pre, checkpoint57h_done, checkpoint57f_post, checkpoint57h_pre, checkpoint57h_post
Changes since 1.4: +1 -5 lines
remove print statements - oops! (sorry)

1 molod 1.5 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diag_vegtile_fill.F,v 1.4 2005/02/18 19:44:11 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     IF ( chardiag.EQ.flds(m,n) ) THEN
78     ndiagnum = jdiag(m,n)
79     IF (ndiag(ndiagnum).GE.0) ipointer = idiag(ndiagnum)
80     ENDIF
81     ENDDO
82     ENDDO
83    
84     C If-sequence to see if we are a valid and an active diagnostic
85    
86     IF ( ndiagnum.NE.0 .AND. ipointer.NE.0 ) THEN
87    
88     C Increment the counter for the diagnostic (if we are at bi=bj=myThid=1)
89     _BEGIN_MASTER(myThid)
90     IF((bi.EQ.1).AND.(bj.EQ.1).AND.(ABS(kLev).LE.1)
91     . .AND.(npeice.eq.1))
92     . ndiag(ndiagnum) = ndiag(ndiagnum) + 1
93     _END_MASTER(myThid)
94    
95     offset = ib*(npeice-1)
96     Lena = min(ib,numpts-offset)
97     offset = offset+1
98    
99     C- Which part of field to add : k = 3rd index,
100     C and do the loop >> do k=kFirst,kLast <<
101     IF (kLev.LE.0) THEN
102     kFirst = 1
103     kLast = nLevs
104     ELSEIF ( nLevs.EQ.1 ) THEN
105     kFirst = 1
106     kLast = 1
107     ELSEIF ( kLev.LE.nLevs ) THEN
108     kFirst = kLev
109     kLast = kLev
110     ELSE
111     STOP 'ABNORMAL END: S/R DIAGNOSTICS_FILL kLev > nLevs > 0'
112     ENDIF
113     C- Which part of qdiag to update: kd = 3rd index,
114     C and do the loop >> do k=kFirst,kLast ; kd = kd0 + k*ksgn <<
115     IF ( kLev.EQ.-1 ) THEN
116     ksgn = -1
117     kd0 = ipointer + nLevs
118     ELSEIF ( kLev.EQ.0 ) THEN
119     ksgn = 1
120     kd0 = ipointer - 1
121     ELSE
122     ksgn = 0
123     kd0 = ipointer + kLev - 1
124     ENDIF
125    
126     C- Check for consistency with Nb of levels reserved in storage array
127     kStore = kd0 + MAX(ksgn*kFirst,ksgn*kLast) - ipointer + 1
128     IF ( kStore.GT.kdiag(ndiagnum) ) THEN
129     _BEGIN_MASTER(myThid)
130     WRITE(msgBuf,'(2A,I3,A)') 'DIAGNOSTICS_FILL: ',
131     . 'exceed Nb of levels(=',kdiag(ndiagnum),' ) reserved '
132     CALL PRINT_ERROR( msgBuf , myThid )
133     WRITE(msgBuf,'(2A,I4,2A)') 'DIAGNOSTICS_FILL: ',
134     . 'for Diagnostics #', ndiagnum, ' : ', chardiag
135     CALL PRINT_ERROR( msgBuf , myThid )
136     WRITE(msgBuf,'(2A,2I4,I3)') 'calling DIAGNOSTICS_FILL ',
137     . 'with kLev,nLevs=', kLev,nLevs
138     CALL PRINT_ERROR( msgBuf , myThid )
139     WRITE(msgBuf,'(2A,I6,A)') 'DIAGNOSTICS_FILL: ',
140     . '==> trying to store up to ', kStore, ' levels'
141     CALL PRINT_ERROR( msgBuf , myThid )
142     STOP 'ABNORMAL END: S/R DIAGNOSTICS_FILL'
143     _END_MASTER(myThid)
144     ENDIF
145    
146     DO k = kFirst,kLast
147     kd = kd0 + ksgn*k
148     if( check ) then
149     undef = getcon('UNDEF')
150     do i= 1,Lena
151 molod 1.3 jindx = 1 + int((indx(i+offset-1)-1)/sNx)
152 molod 1.4 newindx = indx(i+offset-1)+(jindx-1)*2*Olx
153 molod 1.1 if(qdiag(newindx,1,kd,bi,bj).eq.undef
154     . .or.field(i,k).eq.undef)then
155     qdiag(newindx,1,kd,bi,bj) = undef
156     else
157     qdiag(newindx,1,kd,bi,bj)=qdiag(newindx,1,kd,bi,bj)+
158 molod 1.4 . field(i,k)*chfr(i)
159 molod 1.1 endif
160     enddo
161     else
162     do i= 1,Lena
163 molod 1.3 jindx = 1 + int((indx(i+offset-1)-1)/sNx)
164 molod 1.4 newindx = indx(i+offset-1)+(jindx-1)*2*Olx
165 molod 1.1 qdiag(newindx,1,kd,bi,bj)=qdiag(newindx,1,kd,bi,bj)+
166 molod 1.4 . field(i,k)*chfr(i)
167 molod 1.1 enddo
168     endif
169     ENDDO
170    
171     ELSE
172     C IF (myThid.EQ.1) WRITE(6,1000) chardiag
173     ENDIF
174    
175     1000 format(' ',' Warning: Trying to write to diagnostic ',a8,
176     . ' But it is not a valid (or active) name ')
177     RETURN
178     END

  ViewVC Help
Powered by ViewVC 1.1.22