/[MITgcm]/MITgcm/pkg/exf/exf_mapfields.F
ViewVC logotype

Annotation of /MITgcm/pkg/exf/exf_mapfields.F

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


Revision 1.23 - (hide annotations) (download)
Tue Apr 28 18:15:33 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint62, checkpoint63, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62b, checkpoint61n, checkpoint61q, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.22: +7 -7 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable

1 jmc 1.23 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_mapfields.F,v 1.22 2007/10/01 13:36:05 jmc Exp $
2 jmc 1.17 C $Name: $
3 heimbach 1.1
4 edhill 1.7 #include "EXF_OPTIONS.h"
5 heimbach 1.1
6 heimbach 1.16 subroutine exf_mapfields( mytime, myiter, mythid )
7 heimbach 1.1
8     c ==================================================================
9 heimbach 1.2 c SUBROUTINE exf_mapfields
10 heimbach 1.1 c ==================================================================
11     c
12 dimitri 1.5 c o Map external forcing fields (ustress, vstress, hflux, sflux,
13     c swflux, apressure, climsss, climsst, etc.) onto ocean model
14     c arrays (fu, fv, Qnet, EmPmR, Qsw, pload, sss, sst, etc.).
15     c This routine is included to separate the ocean state estimation
16     c tool as much as possible from the ocean model. Unit and sign
17     c conventions can be customized using variables exf_outscal_*,
18     c which are set in exf_readparms.F. See the header files
19 jmc 1.17 c EXF_FIELDS.h and FFIELDS.h for definitions of the various input
20 dimitri 1.5 c and output fields and for default unit and sign convetions.
21 heimbach 1.1 c
22     c started: Christian Eckert eckert@mit.edu 09-Aug-1999
23     c
24     c changed: Christian Eckert eckert@mit.edu 11-Jan-2000
25     c - Restructured the code in order to create a package
26     c for the MITgcmUV.
27     c
28     c Christian Eckert eckert@mit.edu 12-Feb-2000
29     c - Changed Routine names (package prefix: exf_)
30     c
31     c Patrick Heimbach, heimbach@mit.edu 06-May-2000
32     c - added and changed CPP flag structure for
33     c ALLOW_BULKFORMULAE, ALLOW_ATM_TEMP
34     c
35     c Patrick Heimbach, heimbach@mit.edu 23-May-2000
36     c - sign change of ustress/vstress incorporated into
37 dimitri 1.5 c scaling factors exf_outscal_ust, exf_outscal_vst
38 dimitri 1.4 c
39 dimitri 1.5 c mods for pkg/seaice: menemenlis@jpl.nasa.gov 20-Dec-2002
40 dimitri 1.4 c
41 heimbach 1.1 c ==================================================================
42 heimbach 1.2 c SUBROUTINE exf_mapfields
43 heimbach 1.1 c ==================================================================
44    
45     implicit none
46    
47     c == global variables ==
48    
49     #include "EEPARAMS.h"
50     #include "SIZE.h"
51 heimbach 1.16 #include "PARAMS.h"
52 heimbach 1.1 #include "FFIELDS.h"
53 heimbach 1.8 #include "GRID.h"
54    
55 jmc 1.17 #include "EXF_PARAM.h"
56     #include "EXF_CONSTANTS.h"
57     #include "EXF_FIELDS.h"
58 heimbach 1.2 #ifdef ALLOW_AUTODIFF_TAMC
59     # include "tamc.h"
60     # include "tamc_keys.h"
61     #endif
62 heimbach 1.1 c == routine arguments ==
63    
64     c mythid - thread number for this instance of the routine.
65    
66 jmc 1.20 _RL mytime
67     integer myiter
68 heimbach 1.1 integer mythid
69    
70     c == local variables ==
71    
72     integer bi,bj
73 heimbach 1.13 integer i,j,k
74 jmc 1.20 INTEGER imin, imax
75     INTEGER jmin, jmax
76     PARAMETER ( imin = 1-OLx , imax = sNx+OLx )
77     PARAMETER ( jmin = 1-OLy , jmax = sNy+OLy )
78 heimbach 1.1
79     c == end of interface ==
80    
81 jmc 1.20 DO bj = myByLo(myThid),myByHi(myThid)
82     DO bi = myBxLo(myThid),myBxHi(myThid)
83 heimbach 1.2
84     #ifdef ALLOW_AUTODIFF_TAMC
85     act1 = bi - myBxLo(myThid)
86     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
87     act2 = bj - myByLo(myThid)
88     max2 = myByHi(myThid) - myByLo(myThid) + 1
89     act3 = myThid - 1
90     max3 = nTx*nTy
91     act4 = ikey_dynamics - 1
92     ikey = (act1 + 1) + act2*max1
93     & + act3*max1*max2
94     & + act4*max1*max2*max3
95     #endif /* ALLOW_AUTODIFF_TAMC */
96    
97 mlosch 1.21 c Heat flux.
98 heimbach 1.1 do j = jmin,jmax
99     do i = imin,imax
100 heimbach 1.6 qnet(i,j,bi,bj) = exf_outscal_hflux*hflux(i,j,bi,bj)
101 mlosch 1.21 enddo
102     enddo
103     if ( hfluxfile .EQ. ' ' ) then
104     do j = jmin,jmax
105     do i = imin,imax
106     qnet(i,j,bi,bj) = qnet(i,j,bi,bj) -
107 heimbach 1.16 & exf_outscal_hflux * ( hflux_exfremo_intercept +
108     & hflux_exfremo_slope*(mytime-starttime) )
109 heimbach 1.2 enddo
110 mlosch 1.21 enddo
111     endif
112 heimbach 1.2
113 mlosch 1.21 c Salt flux.
114 heimbach 1.2 do j = jmin,jmax
115     do i = imin,imax
116 jmc 1.22 EmPmR(i,j,bi,bj)= exf_outscal_sflux*sflux(i,j,bi,bj)
117     & *rhoConstFresh
118 mlosch 1.21 enddo
119     enddo
120     if ( sfluxfile .EQ. ' ' ) then
121     do j = jmin,jmax
122     do i = imin,imax
123 jmc 1.22 EmPmR(i,j,bi,bj) = EmPmR(i,j,bi,bj) - rhoConstFresh*
124 heimbach 1.16 & exf_outscal_sflux * ( sflux_exfremo_intercept +
125     & sflux_exfremo_slope*(mytime-starttime) )
126 heimbach 1.2 enddo
127 mlosch 1.21 enddo
128     endif
129 heimbach 1.1
130 heimbach 1.2 #ifdef ALLOW_AUTODIFF_TAMC
131     CADJ STORE ustress(:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
132     #endif
133     do j = jmin,jmax
134     do i = imin,imax
135 heimbach 1.1 c Zonal wind stress.
136 mlosch 1.10 if (ustress(i,j,bi,bj).gt.windstressmax) then
137     ustress(i,j,bi,bj)=windstressmax
138 heimbach 1.2 endif
139     enddo
140     enddo
141     #ifdef ALLOW_AUTODIFF_TAMC
142     CADJ STORE ustress(:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
143     #endif
144     do j = jmin,jmax
145     do i = imin,imax
146 mlosch 1.10 if (ustress(i,j,bi,bj).lt.-windstressmax) then
147     ustress(i,j,bi,bj)=-windstressmax
148 heimbach 1.2 endif
149     enddo
150     enddo
151 jmc 1.20 IF ( stressIsOnCgrid ) THEN
152     do j = jmin,jmax
153     do i = imin+1,imax
154     fu(i,j,bi,bj) = exf_outscal_ustress*ustress(i,j,bi,bj)
155     enddo
156     enddo
157     ELSE
158     do j = jmin,jmax
159 heimbach 1.8 do i = imin+1,imax
160 jmc 1.20 c Shift wind stresses calculated at Grid-center to W/S points
161 heimbach 1.8 fu(i,j,bi,bj) = exf_outscal_ustress*
162 jmc 1.20 & (ustress(i,j,bi,bj)+ustress(i-1,j,bi,bj))
163     & *exf_half*maskW(i,j,1,bi,bj)
164 heimbach 1.2 enddo
165 jmc 1.20 enddo
166     ENDIF
167 heimbach 1.1
168 heimbach 1.2 #ifdef ALLOW_AUTODIFF_TAMC
169     CADJ STORE vstress(:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
170     #endif
171     do j = jmin,jmax
172     do i = imin,imax
173 heimbach 1.1 c Meridional wind stress.
174 mlosch 1.10 if (vstress(i,j,bi,bj).gt.windstressmax) then
175     vstress(i,j,bi,bj)=windstressmax
176 heimbach 1.2 endif
177     enddo
178     enddo
179     #ifdef ALLOW_AUTODIFF_TAMC
180     CADJ STORE vstress(:,:,bi,bj) = comlev1_bibj, key=ikey, byte=isbyte
181     #endif
182     do j = jmin,jmax
183     do i = imin,imax
184 mlosch 1.10 if (vstress(i,j,bi,bj).lt.-windstressmax) then
185     vstress(i,j,bi,bj)=-windstressmax
186 heimbach 1.2 endif
187     enddo
188     enddo
189 jmc 1.20 IF ( stressIsOnCgrid ) THEN
190     do j = jmin+1,jmax
191     do i = imin,imax
192     fv(i,j,bi,bj) = exf_outscal_vstress*vstress(i,j,bi,bj)
193     enddo
194     enddo
195     ELSE
196     do j = jmin+1,jmax
197 heimbach 1.2 do i = imin,imax
198 heimbach 1.8 c Shift wind stresses calculated at C-points to W/S points
199     fv(i,j,bi,bj) = exf_outscal_vstress*
200 jmc 1.20 & (vstress(i,j,bi,bj)+vstress(i,j-1,bi,bj))
201     & *exf_half*maskS(i,j,1,bi,bj)
202 heimbach 1.2 enddo
203 jmc 1.20 enddo
204     ENDIF
205 heimbach 1.1
206 dimitri 1.5 #ifdef SHORTWAVE_HEATING
207 heimbach 1.1 c Short wave radiative flux.
208 heimbach 1.2 do j = jmin,jmax
209     do i = imin,imax
210 heimbach 1.6 qsw(i,j,bi,bj) = exf_outscal_swflux*swflux(i,j,bi,bj)
211 heimbach 1.2 enddo
212     enddo
213 heimbach 1.1 #endif
214    
215     #ifdef ALLOW_CLIMSST_RELAXATION
216 heimbach 1.2 do j = jmin,jmax
217     do i = imin,imax
218 dimitri 1.5 sst(i,j,bi,bj) = exf_outscal_sst*climsst(i,j,bi,bj)
219 heimbach 1.2 enddo
220     enddo
221 heimbach 1.1 #endif
222    
223     #ifdef ALLOW_CLIMSSS_RELAXATION
224 heimbach 1.2 do j = jmin,jmax
225     do i = imin,imax
226 dimitri 1.5 sss(i,j,bi,bj) = exf_outscal_sss*climsss(i,j,bi,bj)
227 heimbach 1.2 enddo
228     enddo
229 heimbach 1.1 #endif
230    
231 heimbach 1.2 #ifdef ATMOSPHERIC_LOADING
232     do j = jmin,jmax
233     do i = imin,imax
234 dimitri 1.5 pload(i,j,bi,bj)=exf_outscal_apressure*apressure(i,j,bi,bj)
235 heimbach 1.1 enddo
236     enddo
237 heimbach 1.2 #endif
238    
239 jmc 1.20 ENDDO
240     ENDDO
241 heimbach 1.1
242     c Update the tile edges.
243    
244 jmc 1.23 _EXCH_XY_RS( qnet, mythid )
245     _EXCH_XY_RS( empmr, mythid )
246 cheisey 1.3 CALL EXCH_UV_XY_RS(fu, fv, .TRUE., myThid)
247 dimitri 1.5 #ifdef SHORTWAVE_HEATING
248 jmc 1.23 _EXCH_XY_RS( qsw, mythid )
249 heimbach 1.1 #endif
250     #ifdef ALLOW_CLIMSST_RELAXATION
251 jmc 1.23 _EXCH_XY_RS( sst, mythid )
252 heimbach 1.1 #endif
253     #ifdef ALLOW_CLIMSSS_RELAXATION
254 jmc 1.23 _EXCH_XY_RS( sss, mythid )
255 heimbach 1.2 #endif
256     #ifdef ATMOSPHERIC_LOADING
257 jmc 1.23 _EXCH_XY_RS( pload, mythid )
258 heimbach 1.1 #endif
259    
260 jmc 1.20 RETURN
261     END

  ViewVC Help
Powered by ViewVC 1.1.22