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

Diff of /MITgcm/pkg/exf/exf_getffields.F

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

revision 1.2.4.10.2.1 by dimitri, Tue Jun 17 16:22:56 2003 UTC revision 1.70 by jmc, Sun Feb 12 00:55:12 2017 UTC
# Line 1  Line 1 
1  c $Header$  C $Header$
2    C $Name$
3    
4  #include "EXF_CPPOPTIONS.h"  #include "EXF_OPTIONS.h"
5    #ifdef ALLOW_CTRL
6    # include "CTRL_OPTIONS.h"
7    #endif
8    #ifdef ALLOW_ECCO
9    # include "ECCO_OPTIONS.h"
10    #endif
11    
12          SUBROUTINE EXF_GETFFIELDS( myTime, myIter, myThid )
13    
14    C     ==================================================================
15    C     SUBROUTINE exf_getffields
16    C     ==================================================================
17    C
18    C     o Read-in atmospheric state and/or surface fluxes from files.
19    C
20    C       heimbach@mit.edu, 23-May-2003 totally re-structured
21    C       5-Aug-2003: added USE_EXF_INTERPOLATION for arbitrary input grid
22    C
23    C     ==================================================================
24    C     SUBROUTINE exf_getffields
25    C     ==================================================================
26    
27        subroutine exf_GetFFields( mycurrenttime, mycurrentiter, mythid )        IMPLICIT NONE
28    
29  c     ==================================================================  C     == global variables ==
 c     SUBROUTINE exf_GetFFields  
 c     ==================================================================  
 c  
 c     o Read-in atmospheric state and/or surface fluxes from files.  
 c  
 c     o Use bulk formulae to estimate turbulent and/or radiative  
 c       fluxes at the surface.  
 c  
 c     NOTES:  
 c     ======  
 c  
 c     See EXF_CPPOPTIONS.h for a description of the various possible  
 c     ocean-model forcing configurations.  
 c  
 c     The bulk formulae of pkg/exf are not valid for sea-ice covered  
 c     oceans but they can be used in combination with a sea-ice model,  
 c     for example, pkg/seaice, to specify open water flux contributions.  
 c  
 c     ==================================================================  
 c  
 c       The calculation of the bulk surface fluxes has been adapted from  
 c       the NCOM model which uses the formulae given in Large and Pond  
 c       (1981 & 1982 )  
 c  
 c  
 c       Header taken from NCOM version: ncom1.4.1  
 c       -----------------------------------------  
 c  
 c       Following procedures and coefficients in Large and Pond  
 c       (1981 ; 1982)  
 c  
 c       Output: Bulk estimates of the turbulent surface fluxes.  
 c       -------  
 c  
 c       hs  - sensible heat flux  (W/m^2), into ocean  
 c       hl  - latent   heat flux  (W/m^2), into ocean  
 c  
 c       Input:  
 c       ------  
 c  
 c       us  - mean wind speed (m/s)     at height hu (m)  
 c       th  - mean air temperature (K)  at height ht (m)  
 c       qh  - mean air humidity (kg/kg) at height hq (m)  
 c       sst - sea surface temperature (K)  
 c       tk0 - Kelvin temperature at 0 Celsius (K)  
 c  
 c       Assume 1) a neutral 10m drag coefficient =  
 c  
 c                 cdn = .0027/u10 + .000142 + .0000764 u10  
 c  
 c              2) a neutral 10m stanton number =  
 c  
 c                 ctn = .0327 sqrt(cdn), unstable  
 c                 ctn = .0180 sqrt(cdn), stable  
 c  
 c              3) a neutral 10m dalton number =  
 c  
 c                 cen = .0346 sqrt(cdn)  
 c  
 c              4) the saturation humidity of air at  
 c  
 c                 t(k) = exf_BulkqSat(t)  (kg/m^3)  
 c  
 c       Note:  1) here, tstar = <wt>/u*, and qstar = <wq>/u*.  
 c              2) wind speeds should all be above a minimum speed,  
 c                 say 0.5 m/s.  
 c              3) with optional iteration loop, niter=3, should suffice.  
 c              4) this version is for analyses inputs with hu = 10m and  
 c                 ht = hq.  
 c              5) sst enters in Celsius.  
 c  
 c     ==================================================================  
 c  
 c       started: Christian Eckert eckert@mit.edu 27-Aug-1999  
 c  
 c       changed: Christian Eckert eckert@mit.edu 14-Jan-2000  
 c              - restructured the original version in order to have a  
 c                better interface to the MITgcmUV.  
 c  
 c              Christian Eckert eckert@mit.edu  12-Feb-2000  
 c              - Changed Routine names (package prefix: exf_)  
 c  
 c              Patrick Heimbach, heimbach@mit.edu  04-May-2000  
 c              - changed the handling of precip and sflux with respect  
 c                to CPP options ALLOW_BULKFORMULAE and ALLOW_ATM_TEMP  
 c              - included some CPP flags ALLOW_BULKFORMULAE to make  
 c                sure ALLOW_ATM_TEMP, ALLOW_ATM_WIND are used only in  
 c                conjunction with defined ALLOW_BULKFORMULAE  
 c              - statement functions discarded  
 c  
 c              Ralf.Giering@FastOpt.de 25-Mai-2000  
 c              - total rewrite using new subroutines  
 c  
 c              Detlef Stammer: include river run-off. Nov. 21, 2001  
 c  
 c              heimbach@mit.edu, 10-Jan-2002  
 c              - changes to enable field swapping  
 c  
 c       mods for pkg/seaice: menemenlis@jpl.nasa.gov 20-Dec-2002  
 c  
 c     ==================================================================  
 c     SUBROUTINE exf_GetFFields  
 c     ==================================================================  
   
       implicit none  
   
 c     == global variables ==  
30    
31  #include "EEPARAMS.h"  #include "EEPARAMS.h"
32  #include "SIZE.h"  #include "SIZE.h"
# Line 119  c     == global variables == Line 34  c     == global variables ==
34  #include "DYNVARS.h"  #include "DYNVARS.h"
35  #include "GRID.h"  #include "GRID.h"
36    
37  #include "exf_param.h"  #include "EXF_PARAM.h"
38  #include "exf_fields.h"  #include "EXF_FIELDS.h"
39  #include "exf_constants.h"  #include "EXF_CONSTANTS.h"
40    
41  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_CTRL
42  #include "tamc.h"  # include "CTRL_SIZE.h"
43  #endif  # include "ctrl.h"
44    # include "ctrl_dummy.h"
45  c     == routine arguments ==  # ifdef ALLOW_GENTIM2D_CONTROL
46    #  include "CTRL_GENARR.h"
47        integer mythid  # endif
48        integer mycurrentiter  #endif
49        _RL     mycurrenttime  #if (defined (ALLOW_ECCO) && defined (ECCO_CTRL_DEPRECATED))
50    #  include "ecco_cost.h"
51  c     == local variables ==  #endif
52    
53        integer bi,bj  C     == routine arguments ==
54        integer i,j,k        _RL     myTime
55          INTEGER myIter
56  #ifdef ALLOW_BULKFORMULAE        INTEGER myThid
57    
58        _RL     aln  C     == local variables ==
59          INTEGER i, j, bi, bj
60  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_ROTATE_UV_CONTROLS
61        integer iter        _RL     tmpUE(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nsx,nsy)
62        _RL     delq        _RL     tmpVN(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nsx,nsy)
63        _RL     deltap        _RL     tmpUX(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nsx,nsy)
64        _RL     hqol        _RL     tmpVY(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nsx,nsy)
65        _RL     htol  #endif
66        _RL     huol  #if (defined (ALLOW_CTRL) && \
67        _RL     psimh       defined (ALLOW_GENTIM2D_CONTROL))
68        _RL     psixh        INTEGER iarr
69        _RL     qstar  #endif
70        _RL     rd  
71        _RL     re  C     == end of interface ==
72        _RL     rdn  
73        _RL     rh  C--   read forcing fields from files and temporal interpolation
74        _RL     ssttmp  
75        _RL     ssq  C     Zonal and meridional wind stress.
76        _RL     stable        IF ( .NOT.useAtmWind ) THEN
77        _RL     tstar         CALL EXF_SET_UV(
78        _RL     t0       I     ustressfile, ustressStartTime, ustressperiod,
79        _RL     ustar       I     exf_inscal_ustress,
80        _RL     uzn       I     ustress_exfremo_intercept, ustress_exfremo_slope,
81        _RL     shn       U     ustress, ustress0, ustress1, ustressmask,
82        _RL     xsq       I     vstressfile, vstressStartTime, vstressperiod,
83        _RL     x       I     exf_inscal_vstress,
84        _RL     tau       I     vstress_exfremo_intercept, vstress_exfremo_slope,
85  #ifdef ALLOW_AUTODIFF_TAMC       U     vstress, vstress0, vstress1, vstressmask,
86        integer ikey_1  #ifdef USE_EXF_INTERPOLATION
87        integer ikey_2       I     ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
88  #endif       I     ustress_nlon, ustress_nlat, ustress_interpMethod,
89  #endif /* ALLOW_ATM_TEMP */       I     vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
90         I     vstress_nlon, vstress_nlat, vstress_interpMethod,
91        _RL     ustmp       I     uvInterp_stress,
92        _RL     us  #endif /* USE_EXF_INTERPOLATION */
93        _RL     cw       I     myTime, myIter, myThid )
94        _RL     sw        ELSE
95        _RL     sh         DO bj = myByLo(myThid),myByHi(myThid)
96        _RL     hs(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)          DO bi = myBxLo(myThid),mybxhi(myThid)
97        _RL     hl(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)           DO j=1-OLy,sNy+OLy
98        _RL     hfl            DO i=1-OLx,sNx+OLx
99               ustress(i,j,bi,bj) = 0. _d 0
100  #endif /* ALLOW_BULKFORMULAE */             vstress(i,j,bi,bj) = 0. _d 0
101              ENDDO
102  c     == external functions ==           ENDDO
103            ENDDO
104        integer  ilnblnk         ENDDO
105        external ilnblnk        ENDIF
106    
107  #ifdef ALLOW_BULKFORMULAE  C--   wind speed
108        _RL       exf_BulkqSat        CALL EXF_SET_GEN(
109        external  exf_BulkqSat       &     wspeedfile, wspeedStartTime, wspeedperiod,
110        _RL       exf_BulkCdn       &     exf_inscal_wspeed,
111        external  exf_BulkCdn       &     wspeed_exfremo_intercept, wspeed_exfremo_slope,
112        _RL       exf_BulkRhn       &     wspeed, wspeed0, wspeed1, wspeedmask,
113        external  exf_BulkRhn  #ifdef USE_EXF_INTERPOLATION
114  #endif /* ALLOW_BULKFORMULAE */       &     wspeed_lon0, wspeed_lon_inc,
115         &     wspeed_lat0, wspeed_lat_inc,
116  #ifndef ALLOW_ATM_WIND       &     wspeed_nlon, wspeed_nlat, xC, yC, wspeed_interpMethod,
117        _RL       TMP1  #endif
118        _RL       TMP2       &     myTime, myIter, myThid )
119        _RL       TMP3  
120        _RL       TMP4  C     Zonal and meridional wind.
121        _RL       TMP5        IF ( useAtmWind ) THEN
122  #endif         CALL EXF_SET_UV(
123         I     uwindfile, uwindStartTime, uwindperiod,
124  c     == end of interface ==       I     exf_inscal_uwind,
125         I     uwind_exfremo_intercept, uwind_exfremo_slope,
126  #ifdef ALLOW_BULKFORMULAE       U     uwind, uwind0, uwind1, uwindmask,
127  cph   This statement cannot be a PARAMETER statement in the header,       I     vwindfile, vwindStartTime, vwindperiod,
128  cph   but must come here; it's not fortran77 standard       I     exf_inscal_vwind,
129        aln = log(ht/zref)       I     vwind_exfremo_intercept, vwind_exfremo_slope,
130  #endif       U     vwind, vwind0, vwind1, vwindmask,
131    #ifdef USE_EXF_INTERPOLATION
132  c--   read forcing fields from files and temporal interpolation       I     uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
133         I     uwind_nlon, uwind_nlat, uwind_interpMethod,
134  c     Zonal wind stress.       I     vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
135        call exf_set_ustress( mycurrenttime, mycurrentiter, mythid )       I     vwind_nlon, vwind_nlat, vwind_interpMethod, uvInterp_wind,
136    #endif /* USE_EXF_INTERPOLATION */
137  c     Meridional wind stress.       I     myTime, myIter, myThid )
138        call exf_set_vstress( mycurrenttime, mycurrentiter, mythid )  
139           IF (useRelativeWind) THEN
140  #ifdef ALLOW_ATM_WIND  C     Subtract UVEL and VVEL from UWIND and VWIND.
141            DO bj = myByLo(myThid),myByHi(myThid)
142  c     Zonal wind.           DO bi = myBxLo(myThid),mybxhi(myThid)
143        call exf_set_uwind  ( mycurrenttime, mycurrentiter, mythid )            DO j = 1,sNy
144               DO i = 1,sNx
145  c     Meridional wind.              uwind(i,j,bi,bj) = uwind(i,j,bi,bj) - 0.5 _d 0
146        call exf_set_vwind  ( mycurrenttime, mycurrentiter, mythid )       &         * (uVel(i,j,1,bi,bj)+uVel(i+1,j,1,bi,bj))
147                vwind(i,j,bi,bj) = vwind(i,j,bi,bj) - 0.5 _d 0
148  #ifdef ALLOW_UWIND_CONTROL       &         * (vVel(i,j,1,bi,bj)+vVel(i,j+1,1,bi,bj))
149        call ctrl_getuwind  ( mycurrenttime, mycurrentiter, mythid )             ENDDO
150              ENDDO
151             ENDDO
152            ENDDO
153           ENDIF
154    
155          ELSE
156           DO bj = myByLo(myThid),myByHi(myThid)
157            DO bi = myBxLo(myThid),mybxhi(myThid)
158             DO j=1-OLy,sNy+OLy
159              DO i=1-OLx,sNx+OLx
160               uwind(i,j,bi,bj) = 0. _d 0
161               vwind(i,j,bi,bj) = 0. _d 0
162              ENDDO
163             ENDDO
164            ENDDO
165           ENDDO
166          ENDIF
167    
168    C     Atmospheric heat flux.
169          CALL EXF_SET_GEN  (
170         &     hfluxfile, hfluxStartTime, hfluxperiod,
171         &     exf_inscal_hflux,
172         &     hflux_exfremo_intercept, hflux_exfremo_slope,
173         &     hflux, hflux0, hflux1, hfluxmask,
174    #ifdef USE_EXF_INTERPOLATION
175         &     hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
176         &     hflux_nlon, hflux_nlat, xC, yC, hflux_interpMethod,
177    #endif
178         &     myTime, myIter, myThid )
179    
180    C     Freshwater flux.
181          CALL EXF_SET_GEN  (
182         &     sfluxfile, sfluxStartTime, sfluxperiod,
183         &     exf_inscal_sflux,
184         &     sflux_exfremo_intercept, sflux_exfremo_slope,
185         &     sflux, sflux0, sflux1, sfluxmask,
186    #ifdef USE_EXF_INTERPOLATION
187         &     sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
188         &     sflux_nlon, sflux_nlat, xC, yC, sflux_interpMethod,
189  #endif  #endif
190         &     myTime, myIter, myThid )
 #ifdef ALLOW_VWIND_CONTROL  
       call ctrl_getvwind  ( mycurrenttime, mycurrentiter, mythid )  
 #endif  
   
 #endif /* ALLOW_ATM_WIND */  
   
 c     Atmospheric heat flux.  
       call exf_set_hflux  ( mycurrenttime, mycurrentiter, mythid )  
   
 c     Salt flux.  
       call exf_set_sflux  ( mycurrenttime, mycurrentiter, mythid )  
191    
192  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_ATM_TEMP
193    
194  c     Atmospheric temperature.  C     Atmospheric temperature.
195        call exf_set_atemp  ( mycurrenttime, mycurrentiter, mythid )        CALL EXF_SET_GEN(
196         &     atempfile, atempStartTime, atempperiod,
197  c     Atmospheric humidity.       &     exf_inscal_atemp,
198        call exf_set_aqh    ( mycurrenttime, mycurrentiter, mythid )       &     atemp_exfremo_intercept, atemp_exfremo_slope,
199         &     atemp, atemp0, atemp1, atempmask,
200  c     Net long wave radiative flux.  #ifdef USE_EXF_INTERPOLATION
201        call exf_set_lwflux ( mycurrenttime, mycurrentiter, mythid )       &     atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
202         &     atemp_nlon, atemp_nlat, xC, yC, atemp_interpMethod,
203  c     Precipitation.  #endif
204        call exf_set_precip ( mycurrenttime, mycurrentiter, mythid )       &     myTime, myIter, myThid )
205          DO bj = myByLo(myThid),myByHi(myThid)
206  #ifdef ALLOW_ATEMP_CONTROL         DO bi = myBxLo(myThid),mybxhi(myThid)
207        call ctrl_getatemp  ( mycurrenttime, mycurrentiter, mythid )          DO j = 1,sNy
208             DO i = 1,sNx
209              atemp(i,j,bi,bj) = atemp(i,j,bi,bj) + exf_offset_atemp
210             ENDDO
211            ENDDO
212           ENDDO
213          ENDDO
214    
215    C     Atmospheric humidity.
216          CALL EXF_SET_GEN(
217         &     aqhfile, aqhStartTime, aqhperiod,
218         &     exf_inscal_aqh,
219         &     aqh_exfremo_intercept, aqh_exfremo_slope,
220         &     aqh, aqh0, aqh1, aqhmask,
221    #ifdef USE_EXF_INTERPOLATION
222         &     aqh_lon0, aqh_lon_inc, aqh_lat0, aqh_lat_inc,
223         &     aqh_nlon, aqh_nlat, xC, yC, aqh_interpMethod,
224    #endif
225         &     myTime, myIter, myThid )
226    
227    # ifdef ALLOW_READ_TURBFLUXES
228    
229    C     Sensible Heat flux
230          CALL EXF_SET_GEN(
231         &     hs_file, hs_StartTime, hs_period,
232         &     exf_inscal_hs,
233         &     hs_exfremo_intercept, hs_exfremo_slope,
234         &     hs, hs0, hs1, hs_mask,
235    #  ifdef USE_EXF_INTERPOLATION
236         &     hs_lon0, hs_lon_inc, hs_lat0, hs_lat_inc,
237         &     hs_nlon, hs_nlat, xC, yC, hs_interpMethod,
238    #  endif
239         &     myTime, myIter, myThid )
240    
241    C     Latent Heat flux
242          CALL EXF_SET_GEN(
243         &     hl_file, hl_StartTime, hl_period,
244         &     exf_inscal_hl,
245         &     hl_exfremo_intercept, hl_exfremo_slope,
246         &     hl, hl0, hl1, hl_mask,
247    #  ifdef USE_EXF_INTERPOLATION
248         &     hl_lon0, hl_lon_inc, hl_lat0, hl_lat_inc,
249         &     hl_nlon, hl_nlat, xC, yC, hl_interpMethod,
250    #  endif
251         &     myTime, myIter, myThid )
252    
253    # endif /* ALLOW_READ_TURBFLUXES */
254    
255    C     Net long wave radiative flux.
256          CALL EXF_SET_GEN(
257         &     lwfluxfile, lwfluxStartTime, lwfluxperiod,
258         &     exf_inscal_lwflux,
259         &     lwflux_exfremo_intercept, lwflux_exfremo_slope,
260         &     lwflux, lwflux0, lwflux1, lwfluxmask,
261    #ifdef USE_EXF_INTERPOLATION
262         &     lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
263         &     lwflux_nlon, lwflux_nlat, xC, yC, lwflux_interpMethod,
264  #endif  #endif
265         &     myTime, myIter, myThid )
266    
267  #ifdef ALLOW_AQH_CONTROL  #ifdef EXF_READ_EVAP
268        call ctrl_getaqh    ( mycurrenttime, mycurrentiter, mythid )  C     Evaporation
269  #endif        CALL EXF_SET_GEN  (
270         &     evapfile, evapStartTime, evapperiod,
271         &     exf_inscal_evap,
272         &     evap_exfremo_intercept, evap_exfremo_slope,
273         &     evap, evap0, evap1, evapmask,
274    #ifdef USE_EXF_INTERPOLATION
275         &     evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
276         &     evap_nlon, evap_nlat, xC, yC, evap_interpMethod,
277    #endif
278         &     myTime, myIter, myThid )
279    #endif /* EXF_READ_EVAP */
280    
281    C     Precipitation.
282          CALL EXF_SET_GEN(
283         &     precipfile, precipStartTime, precipperiod,
284         &     exf_inscal_precip,
285         &     precip_exfremo_intercept, precip_exfremo_slope,
286         &     precip, precip0, precip1, precipmask,
287    #ifdef USE_EXF_INTERPOLATION
288         &     precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
289         &     precip_nlon, precip_nlat, xC, yC, precip_interpMethod,
290    #endif
291         &     myTime, myIter, myThid )
292    
293    C     Snow.
294          CALL EXF_SET_GEN(
295         &     snowprecipfile, snowprecipStartTime, snowprecipperiod,
296         &     exf_inscal_snowprecip,
297         &     snowprecip_exfremo_intercept, snowprecip_exfremo_slope,
298         &     snowprecip, snowprecip0, snowprecip1, snowprecipmask,
299    #ifdef USE_EXF_INTERPOLATION
300         &     snowprecip_lon0, snowprecip_lon_inc,
301         &     snowprecip_lat0, snowprecip_lat_inc,
302         &     snowprecip_nlon, snowprecip_nlat, xC, yC,
303         &     snowprecip_interpMethod,
304    #endif
305         &     myTime, myIter, myThid )
306    C     Take care of case where total precip is not defined
307          IF ( snowPrecipFile .NE. ' ' ) THEN
308           DO bj = myByLo(myThid),myByHi(myThid)
309            DO bi = myBxLo(myThid),mybxhi(myThid)
310             DO j = 1,sNy
311              DO i = 1,sNx
312               precip(i,j,bi,bj) =
313         &          max( precip(i,j,bi,bj), snowPrecip(i,j,bi,bj) )
314              ENDDO
315             ENDDO
316            ENDDO
317           ENDDO
318          ENDIF
319    
320  #endif /* ALLOW_ATM_TEMP */  #endif /* ALLOW_ATM_TEMP */
321    
322  #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)  #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
323  c     Net short wave radiative flux.  C     Net short wave radiative flux.
324        call exf_set_swflux ( mycurrenttime, mycurrentiter, mythid )        CALL EXF_SET_GEN  (
325         &     swfluxfile, swfluxStartTime, swfluxperiod,
326         &     exf_inscal_swflux,
327         &     swflux_exfremo_intercept, swflux_exfremo_slope,
328         &     swflux, swflux0, swflux1, swfluxmask,
329    #ifdef USE_EXF_INTERPOLATION
330         &     swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
331         &     swflux_nlon, swflux_nlat, xC, yC, swflux_interpMethod,
332  #endif  #endif
333         &     myTime, myIter, myThid )
 #ifdef EXF_READ_EVAP  
 c     Evaporation  
       call exf_set_evap   ( mycurrenttime, mycurrentiter, mythid )  
334  #endif  #endif
335    
336  #ifdef ALLOW_DOWNWARD_RADIATION  #ifdef ALLOW_DOWNWARD_RADIATION
337    
338  c     Downward shortwave radiation.  C     Downward shortwave radiation.
339        call exf_set_swdown ( mycurrenttime, mycurrentiter, mythid )        CALL EXF_SET_GEN  (
340         &     swdownfile, swdownStartTime, swdownperiod,
341  c     Downward longwave radiation.       &     exf_inscal_swdown,
342        call exf_set_lwdown ( mycurrenttime, mycurrentiter, mythid )       &     swdown_exfremo_intercept, swdown_exfremo_slope,
343         &     swdown, swdown0, swdown1, swdownmask,
344    #ifdef USE_EXF_INTERPOLATION
345         &     swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
346         &     swdown_nlon, swdown_nlat, xC, yC, swdown_interpMethod,
347    #endif
348         &     myTime, myIter, myThid )
349    
350    C     Downward longwave radiation.
351          CALL EXF_SET_GEN  (
352         &     lwdownfile, lwdownStartTime, lwdownperiod,
353         &     exf_inscal_lwdown,
354         &     lwdown_exfremo_intercept, lwdown_exfremo_slope,
355         &     lwdown, lwdown0, lwdown1, lwdownmask,
356    #ifdef USE_EXF_INTERPOLATION
357         &     lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
358         &     lwdown_nlon, lwdown_nlat, xC, yC, lwdown_interpMethod,
359  #endif  #endif
360         &     myTime, myIter, myThid )
361    
362    #endif /* ALLOW_DOWNWARD_RADIATION */
363    
364  #ifdef ATMOSPHERIC_LOADING  #ifdef ATMOSPHERIC_LOADING
365  c     Atmos. pressure forcing  C     Atmos. pressure forcing
366        call exf_set_apressure ( mycurrenttime, mycurrentiter, mythid )        CALL EXF_SET_GEN  (
367         &     apressurefile, apressureStartTime, apressureperiod,
368         &     exf_inscal_apressure,
369         &     apressure_exfremo_intercept, apressure_exfremo_slope,
370         &     apressure, apressure0, apressure1, apressuremask,
371    #ifdef USE_EXF_INTERPOLATION
372         &     apressure_lon0, apressure_lon_inc,
373         &     apressure_lat0, apressure_lat_inc,
374         &     apressure_nlon,apressure_nlat,xC,yC, apressure_interpMethod,
375    #endif
376         &     myTime, myIter, myThid )
377    #endif
378    
379    #ifdef EXF_SEAICE_FRACTION
380    C     fractional ice-covered area MASK
381          CALL EXF_SET_GEN  (
382         &     areamaskfile, areamaskStartTime, areamaskperiod,
383         &     exf_inscal_areamask,
384         &     areamask_exfremo_intercept, areamask_exfremo_slope,
385         &     areamask, areamask0, areamask1, areamaskmask,
386    #ifdef USE_EXF_INTERPOLATION
387         &     areamask_lon0, areamask_lon_inc,
388         &     areamask_lat0, areamask_lat_inc,
389         &     areamask_nlon, areamask_nlat, xC, yC, areamask_interpMethod,
390  #endif  #endif
391         &     myTime, myIter, myThid )
 c--   Use atmospheric state to compute surface fluxes.  
   
 c     Loop over tiles.  
 #ifdef ALLOW_AUTODIFF_TAMC  
 C--   HPF directive to help TAMC  
 CHPF$ INDEPENDENT  
 #endif  
       do bj = mybylo(mythid),mybyhi(mythid)  
 #ifdef ALLOW_AUTODIFF_TAMC  
 C--    HPF directive to help TAMC  
 CHPF$  INDEPENDENT  
 #endif  
         do bi = mybxlo(mythid),mybxhi(mythid)  
   
           k = 1  
   
           do j = 1,sny  
             do i = 1,snx  
   
 #ifdef ALLOW_BULKFORMULAE  
   
 #ifdef ALLOW_AUTODIFF_TAMC  
                act1 = bi - myBxLo(myThid)  
                max1 = myBxHi(myThid) - myBxLo(myThid) + 1  
                act2 = bj - myByLo(myThid)  
                max2 = myByHi(myThid) - myByLo(myThid) + 1  
                act3 = myThid - 1  
                max3 = nTx*nTy  
                act4 = ikey_dynamics - 1  
   
                ikey_1 = i  
      &              + sNx*(j-1)  
      &              + sNx*sNy*act1  
      &              + sNx*sNy*max1*act2  
      &              + sNx*sNy*max1*max2*act3  
      &              + sNx*sNy*max1*max2*max3*act4  
392  #endif  #endif
393    
394  #ifdef ALLOW_DOWNWARD_RADIATION  #ifdef ALLOW_RUNOFF
395  c--   Compute net from downward and downward from net longwave and  C     Runoff
396  c     shortwave radiation, if needed.        CALL EXF_SET_GEN  (
397  c     lwflux = Stefan-Boltzman constant * emissivity * SST - lwdown       &     runofffile, runoffStartTime, runoffperiod,
398  c     swflux = - ( 1 - albedo ) * swdown       &     exf_inscal_runoff,
399         &     runoff_exfremo_intercept, runoff_exfremo_slope,
400         &     runoff, runoff0, runoff1, runoffmask,
401    #ifdef USE_EXF_INTERPOLATION
402         &     runoff_lon0, runoff_lon_inc, runoff_lat0, runoff_lat_inc,
403         &     runoff_nlon, runoff_nlat, xC, yC, runoff_interpMethod,
404    #endif
405         &     myTime, myIter, myThid )
406    #endif /* ALLOW_RUNOFF */
407    
408    #ifdef ALLOW_RUNOFTEMP
409    C     Runoff temperature
410          CALL EXF_SET_GEN  (
411         &     runoftempfile, runoffStartTime, runoffperiod,
412         &     exf_inscal_runoftemp,
413         &     runoftemp_exfremo_intercept, runoftemp_exfremo_slope,
414         &     runoftemp, runoftemp0, runoftemp1, runoffmask,
415    #ifdef USE_EXF_INTERPOLATION
416         &     runoff_lon0, runoff_lon_inc, runoff_lat0, runoff_lat_inc,
417         &     runoff_nlon, runoff_nlat, xC, yC, runoff_interpMethod,
418    #endif
419         &     myTime, myIter, myThid )
420    #endif /* ALLOW_RUNOFTEMP */
421    
422    #ifdef ALLOW_SALTFLX
423    C     Salt flux
424          CALL EXF_SET_GEN  (
425         &     saltflxfile, saltflxStartTime, saltflxperiod,
426         &     exf_inscal_saltflx,
427         &     saltflx_exfremo_intercept, saltflx_exfremo_slope,
428         &     saltflx, saltflx0, saltflx1, saltflxmask,
429    #ifdef USE_EXF_INTERPOLATION
430         &     saltflx_lon0, saltflx_lon_inc,
431         &     saltflx_lat0, saltflx_lat_inc,
432         &     saltflx_nlon, saltflx_nlat, xC, yC, saltflx_interpMethod,
433    #endif
434         &     myTime, myIter, myThid )
435    #endif
436    
437    #ifdef ALLOW_ROTATE_UV_CONTROLS
438          IF ( useCTRL ) THEN
439            DO bj = myByLo(myThid),myByHi(myThid)
440             DO bi = myBxLo(myThid),mybxhi(myThid)
441              DO j = 1-OLy,sNy+OLy
442               DO i = 1-OLx,sNx+OLx
443                 tmpUE(i,j,bi,bj) = 0. _d 0
444                 tmpVN(i,j,bi,bj) = 0. _d 0
445                 tmpUX(i,j,bi,bj) = 0. _d 0
446                 tmpVY(i,j,bi,bj) = 0. _d 0
447               ENDDO
448              ENDDO
449             ENDDO
450            ENDDO
451          ENDIF
452    #endif
453    
454    # if (!defined (ALLOW_ECCO) || defined (ECCO_CTRL_DEPRECATED))
455    
456    C-- Control variables for atmos. state
457    #ifdef ALLOW_CTRL
458          IF (.NOT.ctrlUseGen) THEN
459    
460  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_ATEMP_CONTROL
461        if ( lwfluxfile .EQ. ' ' .AND. lwdownfile .NE. ' ' )        CALL CTRL_GET_GEN (
462       &     lwflux(i,j,bi,bj) = 5.5 _d -08 *       &     xx_atemp_file, xx_atempstartdate, xx_atempperiod,
463       &              ((theta(i,j,k,bi,bj)+cen2kel)**4)       &     maskc, atemp, xx_atemp0, xx_atemp1, xx_atemp_dummy,
464       &              - lwdown(i,j,bi,bj)       &     xx_atemp_remo_intercept, xx_atemp_remo_slope,
465        if ( lwfluxfile .NE. ' ' .AND. lwdownfile .EQ. ' ' )       &     watemp, myTime, myIter, myThid )
      &     lwdown(i,j,bi,bj) = 5.5 _d -08 *  
      &              ((theta(i,j,k,bi,bj)+cen2kel)**4)  
      &              - lwflux(i,j,bi,bj)  
466  #endif  #endif
467    
468  #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)  #ifdef ALLOW_AQH_CONTROL
469        if ( swfluxfile .EQ. ' ' .AND. swdownfile .NE. ' ' )        CALL CTRL_GET_GEN (
470       &     swflux(i,j,bi,bj) = -0.9 _d 0 * swdown(i,j,bi,bj)       &     xx_aqh_file, xx_aqhstartdate, xx_aqhperiod,
471        if ( swfluxfile .NE. ' ' .AND. swdownfile .EQ. ' ' )       &     maskc, aqh, xx_aqh0, xx_aqh1, xx_aqh_dummy,
472       &     swdown(i,j,bi,bj) = -1.111111 _d 0 * swflux(i,j,bi,bj)       &     xx_aqh_remo_intercept, xx_aqh_remo_slope,
473         &     waqh, myTime, myIter, myThid )
474    #endif
475    
476    #ifdef ALLOW_PRECIP_CONTROL
477          CALL CTRL_GET_GEN (
478         &     xx_precip_file, xx_precipstartdate, xx_precipperiod,
479         &     maskc, precip, xx_precip0, xx_precip1, xx_precip_dummy,
480         &     xx_precip_remo_intercept, xx_precip_remo_slope,
481         &     wprecip, myTime, myIter, myThid )
482    #endif
483    
484    #ifdef ALLOW_SWDOWN_CONTROL
485          CALL CTRL_GET_GEN (
486         &     xx_swdown_file, xx_swdownstartdate, xx_swdownperiod,
487         &     maskc, swdown, xx_swdown0, xx_swdown1, xx_swdown_dummy,
488         &     xx_swdown_remo_intercept, xx_swdown_remo_slope,
489         &     wswdown, myTime, myIter, myThid )
490    #endif
491    
492    #ifdef ALLOW_LWDOWN_CONTROL
493          CALL CTRL_GET_GEN (
494         &     xx_lwdown_file, xx_lwdownstartdate, xx_lwdownperiod,
495         &     maskc, lwdown, xx_lwdown0, xx_lwdown1, xx_lwdown_dummy,
496         &     xx_lwdown_remo_intercept, xx_lwdown_remo_slope,
497         &     wlwdown, myTime, myIter, myThid )
498    #endif
499    
500          ENDIF !if (.NOT.ctrlUseGen) then
501    
502    #ifdef ALLOW_SWFLUX_CONTROL
503          CALL CTRL_GET_GEN (
504         &     xx_swflux_file, xx_swfluxstartdate, xx_swfluxperiod,
505         &     maskc, swflux, xx_swflux0, xx_swflux1, xx_swflux_dummy,
506         &     xx_swflux_remo_intercept, xx_swflux_remo_slope,
507         &     wswflux, myTime, myIter, myThid )
508    #endif
509    
510    #ifdef ALLOW_LWFLUX_CONTROL
511          CALL CTRL_GET_GEN (
512         &     xx_lwflux_file, xx_lwfluxstartdate, xx_lwfluxperiod,
513         &     maskc, lwflux, xx_lwflux0, xx_lwflux1, xx_lwflux_dummy,
514         &     xx_lwflux_remo_intercept, xx_lwflux_remo_slope,
515         &     wswflux, myTime, myIter, myThid )
516    #endif
517    
518    #ifdef ALLOW_EVAP_CONTROL
519          CALL CTRL_GET_GEN (
520         &     xx_evap_file, xx_evapstartdate, xx_evapperiod,
521         &     maskc, evap, xx_evap0, xx_evap1, xx_evap_dummy,
522         &     xx_evap_remo_intercept, xx_evap_remo_slope,
523         &     wevap, myTime, myIter, myThid )
524    #endif
525    
526    #ifdef ALLOW_SNOWPRECIP_CONTROL
527          CALL CTRL_GET_GEN (
528         &     xx_snowprecip_file, xx_snowprecipstartdate,
529         &     xx_snowprecipperiod,
530         &     maskc, snowprecip, xx_snowprecip0, xx_snowprecip1,
531         &     xx_snowprecip_dummy,
532         &     xx_snowprecip_remo_intercept, xx_snowprecip_remo_slope,
533         &     wsnowprecip, myTime, myIter, myThid )
534    #endif
535    
536    #ifdef ALLOW_APRESSURE_CONTROL
537          CALL CTRL_GET_GEN (
538         &     xx_apressure_file, xx_apressurestartdate,
539         &     xx_apressureperiod,
540         &     maskc, apressure, xx_apressure0, xx_apressure1,
541         &     xx_apressure_dummy,
542         &     xx_apressure_remo_intercept, xx_apressure_remo_slope,
543         &     wapressure, myTime, myIter, myThid )
544  #endif  #endif
545    
546  #endif /* ALLOW_DOWNWARD_RADIATION */        IF ( useAtmWind ) THEN
547    #ifndef ALLOW_ROTATE_UV_CONTROLS
 c--   Compute the turbulent surface fluxes.  
   
 #ifdef ALLOW_ATM_WIND  
 c             Wind speed and direction.  
               ustmp = uwind(i,j,bi,bj)*uwind(i,j,bi,bj) +  
      &                vwind(i,j,bi,bj)*vwind(i,j,bi,bj)  
               if ( ustmp .ne. 0. _d 0 ) then  
                 us = sqrt(ustmp)  
                 cw = uwind(i,j,bi,bj)/us  
                 sw = vwind(i,j,bi,bj)/us  
               else  
                 us = 0. _d 0  
                 cw = 0. _d 0  
                 sw = 0. _d 0  
               endif  
               sh = max(us,umin)  
 #else  /* ifndef ALLOW_ATM_WIND */  
 #ifdef ALLOW_ATM_TEMP  
   
 c             The variables us, sh and rdn have to be computed from  
 c             given wind stresses inverting relationship for neutral  
 c             drag coeff. cdn.  
 c             The inversion is based on linear and quadratic form of  
 c             cdn(umps); ustar can be directly computed from stress;  
   
               ustmp = ustress(i,j,bi,bj)*ustress(i,j,bi,bj) +  
      &                vstress(i,j,bi,bj)*vstress(i,j,bi,bj)  
               if ( ustmp .ne. 0. _d 0 ) then  
                 ustar = sqrt(ustmp/atmrho)  
                 cw = ustress(i,j,bi,bj)/sqrt(ustmp)  
                 sw = vstress(i,j,bi,bj)/sqrt(ustmp)  
               else  
                  ustar = 0. _d 0  
                  cw    = 0. _d 0  
                  sw    = 0. _d 0  
               endif  
   
               if ( ustar .eq. 0. _d 0 ) then  
                 us = 0. _d 0  
               else if ( ustar .lt. ustofu11 ) then  
                 tmp1 = -cquadrag_2/cquadrag_1/2  
                 tmp2 = sqrt(tmp1*tmp1 + ustar*ustar/cquadrag_1)  
                 us   = sqrt(tmp1 + tmp2)  
               else  
                 tmp3 = clindrag_2/clindrag_1/3  
                 tmp4 = ustar*ustar/clindrag_1/2 - tmp3**3  
                 tmp5 = sqrt(ustar*ustar/clindrag_1*  
      &                      (ustar*ustar/clindrag_1/4 - tmp3**3))  
                 us   = (tmp4 + tmp5)**(1/3) +  
      &                 tmp3**2 * (tmp4 + tmp5)**(-1/3) - tmp3  
               endif  
   
               if ( us .ne. 0 ) then  
                  rdn = ustar/us  
               else  
                  rdn = 0. _d 0  
               end if  
   
               sh    = max(us,umin)  
 #endif /* ALLOW_ATM_TEMP */  
 #endif /* ifndef ALLOW_ATM_WIND */  
548    
549  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_UWIND_CONTROL
550          CALL CTRL_GET_GEN (
551         &     xx_uwind_file, xx_uwindstartdate, xx_uwindperiod,
552         &     maskc, uwind, xx_uwind0, xx_uwind1, xx_uwind_dummy,
553         &     xx_uwind_remo_intercept, xx_uwind_remo_slope,
554         &     wuwind, myTime, myIter, myThid )
555    #endif /* ALLOW_UWIND_CONTROL */
556    
557  c             Initial guess: z/l=0.0; hu=ht=hq=z  #ifdef ALLOW_VWIND_CONTROL
558  c             Iterations:    converge on z/l and hence the fluxes.        CALL CTRL_GET_GEN (
559  c             t0     : virtual temperature (K)       &     xx_vwind_file, xx_vwindstartdate, xx_vwindperiod,
560  c             ssq    : sea surface humidity (kg/kg)       &     maskc, vwind, xx_vwind0, xx_vwind1, xx_vwind_dummy,
561  c             deltap : potential temperature diff (K)       &     xx_vwind_remo_intercept, xx_vwind_remo_slope,
562         &     wvwind, myTime, myIter, myThid )
563                if ( atemp(i,j,bi,bj) .ne. 0. _d 0 ) then  #endif /* ALLOW_VWIND_CONTROL */
564                  t0     = atemp(i,j,bi,bj)*  
565       &                   (exf_one + humid_fac*aqh(i,j,bi,bj))  #else
566                  ssttmp = theta(i,j,k,bi,bj)  
567                  ssq    = saltsat*  #if defined(ALLOW_UWIND_CONTROL) && defined(ALLOW_VWIND_CONTROL)
568       &                   exf_BulkqSat(ssttmp + cen2kel)/        CALL CTRL_GET_GEN (
569       &                   atmrho       &     xx_uwind_file, xx_uwindstartdate, xx_uwindperiod,
570                  deltap = atemp(i,j,bi,bj)   + gamma_blk*ht -       &     maskc, tmpUE, xx_uwind0, xx_uwind1, xx_uwind_dummy,
571       &                   ssttmp - cen2kel       &     xx_uwind_remo_intercept, xx_uwind_remo_slope,
572                  delq   = aqh(i,j,bi,bj) - ssq       &     wuwind, myTime, myIter, myThid )
573                  stable = exf_half + sign(exf_half, deltap)  
574  #ifdef ALLOW_AUTODIFF_TAMC        CALL CTRL_GET_GEN (
575  CADJ STORE sh     = comlev1_exf_1, key = ikey_1       &     xx_vwind_file, xx_vwindstartdate, xx_vwindperiod,
576  #endif       &     maskc, tmpVN, xx_vwind0, xx_vwind1, xx_vwind_dummy,
577                  rdn    = sqrt(exf_BulkCdn(sh))       &     xx_vwind_remo_intercept, xx_vwind_remo_slope,
578                  ustar  = rdn*sh       &     wvwind, myTime, myIter, myThid )
579                  tstar  = exf_BulkRhn(stable)*deltap  
580                  qstar  = cdalton*delq        CALL ROTATE_UV2EN_RL(tmpUX,tmpVY,tmpUE,tmpVN,
581         &     .FALSE.,.FALSE.,.TRUE.,1,myThid)
582                  do iter = 1,niter_bulk  
583            DO bj = myByLo(myThid),myByHi(myThid)
584  #ifdef ALLOW_AUTODIFF_TAMC           DO bi = myBxLo(myThid),mybxhi(myThid)
585                     ikey_2 = iter            DO j = 1,sNy
586       &                  + niter_bulk*(i-1)             DO i = 1,sNx
587       &                  + sNx*niter_bulk*(j-1)               uwind(i,j,bi,bj)=uwind(i,j,bi,bj)+tmpUX(i,j,bi,bj)
588       &                  + sNx*niter_bulk*sNy*act1               vwind(i,j,bi,bj)=vwind(i,j,bi,bj)+tmpVY(i,j,bi,bj)
589       &                  + sNx*niter_bulk*sNy*max1*act2             ENDDO
590       &                  + sNx*niter_bulk*sNy*max1*max2*act3            ENDDO
591       &                  + sNx*niter_bulk*sNy*max1*max2*max3*act4           ENDDO
592            ENDDO
593  CADJ STORE rdn    = comlev1_exf_2, key = ikey_2  #endif
594  CADJ STORE ustar  = comlev1_exf_2, key = ikey_2  
595  CADJ STORE qstar  = comlev1_exf_2, key = ikey_2  #endif /* ALLOW_ROTATE_UV_CONTROLS */
596  CADJ STORE tstar  = comlev1_exf_2, key = ikey_2        ENDIF
597  CADJ STORE sh     = comlev1_exf_2, key = ikey_2  
598  CADJ STORE us     = comlev1_exf_2, key = ikey_2  #ifdef ALLOW_ATM_MEAN_CONTROL
599  #endif        DO bj = myByLo(myThid),myByHi(myThid)
600           DO bi = myBxLo(myThid),mybxhi(myThid)
601                    huol   = czol*(tstar/t0 +          DO j = 1,sNy
602       &                     qstar/(exf_one/humid_fac+aqh(i,j,bi,bj)))/           DO i = 1,sNx
603       &                           ustar**2  # ifdef ALLOW_ATEMP_CONTROL
604                    huol   = max(huol,zolmin)            atemp(i,j,bi,bj) =atemp(i,j,bi,bj) +xx_atemp_mean(i,j,bi,bj)
605                    stable = exf_half + sign(exf_half, huol)  # endif
606                    htol   = huol*ht/hu  # ifdef ALLOW_AQH_CONTROL
607                    hqol   = huol*hq/hu            aqh(i,j,bi,bj)   =aqh(i,j,bi,bj)   +xx_aqh_mean(i,j,bi,bj)
608    # endif
609  c                 Evaluate all stability functions assuming hq = ht.  # ifdef ALLOW_PRECIP_CONTROL
610                    xsq    = max(sqrt(abs(exf_one - 16.*huol)),exf_one)            precip(i,j,bi,bj)=precip(i,j,bi,bj)+xx_precip_mean(i,j,bi,bj)
611                     x     = sqrt(xsq)  # endif
612                    psimh  = -psim_fac*huol*stable +  # ifdef ALLOW_SWDOWN_CONTROL
613       &                     (exf_one - stable)*            swdown(i,j,bi,bj)=swdown(i,j,bi,bj)+xx_swdown_mean(i,j,bi,bj)
614       &                     log((exf_one + x*(exf_two + x))*  # endif
615       &                     (exf_one + xsq)/8.) - exf_two*atan(x) +  # ifdef ALLOW_UWIND_CONTROL
616       &                     pi*exf_half            uwind(i,j,bi,bj) =uwind(i,j,bi,bj) +xx_uwind_mean(i,j,bi,bj)
617                    xsq    = max(sqrt(abs(exf_one - 16.*htol)),exf_one)  # endif
618                    psixh  = -psim_fac*htol*stable + (exf_one - stable)*  # ifdef ALLOW_VWIND_CONTROL
619       &                     exf_two*log((exf_one + xsq)/exf_two)            vwind(i,j,bi,bj) =vwind(i,j,bi,bj) +xx_vwind_mean(i,j,bi,bj)
620    # endif
621  c                 Shift wind speed using old coefficient           ENDDO
622  ccc                  rd   = rdn/(exf_one + rdn/karman*          ENDDO
623  ccc     &                 (log(hu/zref) - psimh) )         ENDDO
624                    rd   = rdn/(exf_one - rdn/karman*psimh )        ENDDO
625                    shn  = sh*rd/rdn  #endif /* ALLOW_ATM_MEAN_CONTROL */
626                    uzn  = max(shn, umin)  
627    cdm transferred from exf_init_runoff.F
628  c                 Update the transfer coefficients at 10 meters  cdm functionality needs to be checked before turning on
629  c                 and neutral stability.  cdm #ifdef ALLOW_RUNOFF_CONTROL
630    cdm       CALL CTRL_GET_GEN (
631                    rdn = sqrt(exf_BulkCdn(uzn))  cdm      &     xx_runoff_file, xx_runoffstartdate, xx_runoffperiod,
632    cdm      &     maskc, runoff, xx_runoff0, xx_runoff1, xx_runoff_dummy,
633  c                 Shift all coefficients to the measurement height  cdm      &     xx_runoff_remo_intercept, xx_runoff_remo_slope,
634  c                 and stability.  cdm      &     wrunoff, 0., 0., myThid )
635  c                 rd = rdn/(exf_one + rdn/karman*(log(hu/zref) - psimh))  cdm #endif
636                    rd = rdn/(exf_one - rdn/karman*psimh)  
637                    rh = exf_BulkRhn(stable)/(exf_one +  #endif /* ALLOW_CTRL */
638       &                                      exf_BulkRhn(stable)/  
639       &                                     karman*(aln - psixh))  #endif /* undef ALLOW_ECCO) || def ECCO_CTRL_DEPRECATED */
640                    re = cdalton/(exf_one + cdalton/karman*(aln - psixh))  
641    #if (defined (ALLOW_CTRL) && defined (ALLOW_GENTIM2D_CONTROL))
642  c                 Update ustar, tstar, qstar using updated, shifted        IF ( useCTRL.AND.ctrlUseGen ) THEN
643  c                 coefficients.         DO bj = myByLo(myThid),myByHi(myThid)
644                    ustar = rd*sh           DO bi = myBxLo(myThid),mybxhi(myThid)
645                    qstar = re*delq          DO j = 1,sNy
646                    tstar = rh*deltap           DO i = 1,sNx
647                    tau   = atmrho*ustar**2            DO iarr = 1, maxCtrlTim2D
                   tau   = tau*us/sh  
   
                 enddo  
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 CADJ STORE ustar  = comlev1_exf_1, key = ikey_1  
 CADJ STORE qstar  = comlev1_exf_1, key = ikey_1  
 CADJ STORE tstar  = comlev1_exf_1, key = ikey_1  
 CADJ STORE tau    = comlev1_exf_1, key = ikey_1  
 CADJ STORE cw     = comlev1_exf_1, key = ikey_1  
 CADJ STORE sw     = comlev1_exf_1, key = ikey_1  
 #endif  
   
                 hs(i,j,bi,bj)      = atmcp*tau*tstar/ustar  
                 hl(i,j,bi,bj)      = flamb*tau*qstar/ustar  
 #ifndef EXF_READ_EVAP  
 cdm             evap(i,j,bi,bj)    = tau*qstar/ustar  
 cdm !!! need to change sign and to convert from kg/m^2/s to m/s !!!  
                 evap(i,j,bi,bj)    = -recip_rhonil*tau*qstar/ustar  
 #endif  
                 ustress(i,j,bi,bj) = tau*cw  
                 vstress(i,j,bi,bj) = tau*sw  
               else  
                 ustress(i,j,bi,bj) = 0. _d 0  
                 vstress(i,j,bi,bj) = 0. _d 0  
                 hflux  (i,j,bi,bj) = 0. _d 0  
                 hs(i,j,bi,bj)      = 0. _d 0  
                 hl(i,j,bi,bj)      = 0. _d 0  
               endif  
   
 #else  /* ifndef ALLOW_ATM_TEMP */  
 #ifdef ALLOW_ATM_WIND  
               ustress(i,j,bi,bj) = atmrho*exf_BulkCdn(sh)*us*  
      &                             uwind(i,j,bi,bj)  
               vstress(i,j,bi,bj) = atmrho*exf_BulkCdn(sh)*us*  
      &                             vwind(i,j,bi,bj)  
 #endif  
 #endif /* ifndef ALLOW_ATM_TEMP */  
             enddo  
           enddo  
         enddo  
       enddo  
   
 c     Add all contributions.  
       do bj = mybylo(mythid),mybyhi(mythid)  
         do bi = mybxlo(mythid),mybxhi(mythid)  
           do j = 1,sny  
             do i = 1,snx  
 c             Net surface heat flux.  
648  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_ATM_TEMP
649                hfl = 0. _d 0             IF (xx_gentim2d_file(iarr)(1:8).EQ.'xx_atemp')
650                hfl = hfl - hs(i,j,bi,bj)       &       atemp(i,j,bi,bj)=atemp(i,j,bi,bj)+
651                hfl = hfl - hl(i,j,bi,bj)       &                         xx_gentim2d(i,j,bi,bj,iarr)
652                hfl = hfl + lwflux(i,j,bi,bj)             IF (xx_gentim2d_file(iarr)(1:6).EQ.'xx_aqh')
653  #ifndef SHORTWAVE_HEATING       &       aqh(i,j,bi,bj)=aqh(i,j,bi,bj)+
654                hfl = hfl + swflux(i,j,bi,bj)       &                         xx_gentim2d(i,j,bi,bj,iarr)
655  #endif             IF (xx_gentim2d_file(iarr)(1:9).EQ.'xx_precip')
656  c             Heat flux:       &       precip(i,j,bi,bj)=precip(i,j,bi,bj)+
657                hflux(i,j,bi,bj) = hfl       &                         xx_gentim2d(i,j,bi,bj,iarr)
658  c             Salt flux from Precipitation and Evaporation.             IF (xx_gentim2d_file(iarr)(1:9).EQ.'xx_lwflux')
659                sflux(i,j,bi,bj) = evap(i,j,bi,bj) - precip(i,j,bi,bj)       &       lwflux(i,j,bi,bj)=lwflux(i,j,bi,bj)+
660  #endif /* ALLOW_ATM_TEMP */       &                         xx_gentim2d(i,j,bi,bj,iarr)
661    #endif
662  #endif /* ALLOW_BULKFORMULAE */  #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
663               IF (xx_gentim2d_file(iarr)(1:9).EQ.'xx_swflux')
664         &       swflux(i,j,bi,bj)=swflux(i,j,bi,bj)+
665         &                         xx_gentim2d(i,j,bi,bj,iarr)
666    #endif
667    #ifdef ALLOW_DOWNWARD_RADIATION
668               IF (xx_gentim2d_file(iarr)(1:9).EQ.'xx_swdown')
669         &       swdown(i,j,bi,bj)=swdown(i,j,bi,bj)+
670         &                         xx_gentim2d(i,j,bi,bj,iarr)
671               IF (xx_gentim2d_file(iarr)(1:9).EQ.'xx_lwdown')
672         &       lwdown(i,j,bi,bj)=lwdown(i,j,bi,bj)+
673         &                         xx_gentim2d(i,j,bi,bj,iarr)
674    #endif
675  #ifdef ALLOW_RUNOFF  #ifdef ALLOW_RUNOFF
676                sflux(i,j,bi,bj) = sflux(i,j,bi,bj) - runoff(i,j,bi,bj)             IF (xx_gentim2d_file(iarr)(1:9).EQ.'xx_runoff')
677         &       runoff(i,j,bi,bj)=runoff(i,j,bi,bj)+
678         &                         xx_gentim2d(i,j,bi,bj,iarr)
679  #endif  #endif
680    #ifdef EXF_READ_EVAP
681                hflux(i,j,bi,bj) = hflux(i,j,bi,bj)*maskc(i,j,1,bi,bj)             IF (xx_gentim2d_file(iarr)(1:7).EQ.'xx_evap')
682                sflux(i,j,bi,bj) = sflux(i,j,bi,bj)*maskc(i,j,1,bi,bj)       &       evap(i,j,bi,bj)=evap(i,j,bi,bj)+
683         &                         xx_gentim2d(i,j,bi,bj,iarr)
             enddo  
           enddo  
         enddo  
       enddo  
   
 c     Update the tile edges.  
       _EXCH_XY_R8(hflux,   mythid)  
       _EXCH_XY_R8(sflux,   mythid)  
 c      _EXCH_XY_R8(ustress, mythid)  
 c      _EXCH_XY_R8(vstress, mythid)  
        CALL EXCH_UV_XY_RL(ustress, vstress, .TRUE., myThid)  
   
 #ifdef SHORTWAVE_HEATING  
       _EXCH_XY_R8(swflux, mythid)  
684  #endif  #endif
   
685  #ifdef ATMOSPHERIC_LOADING  #ifdef ATMOSPHERIC_LOADING
686        _EXCH_XY_R8(apressure, mythid)             IF (xx_gentim2d_file(iarr)(1:12).EQ.'xx_apressure')
687         &       apressure(i,j,bi,bj)=apressure(i,j,bi,bj)+
688         &                         xx_gentim2d(i,j,bi,bj,iarr)
689    #endif
690    #ifdef EXF_SEAICE_FRACTION
691               IF (xx_gentim2d_file(iarr)(1:11).EQ.'xx_areamask')
692         &       areamask(i,j,bi,bj)=areamask(i,j,bi,bj)+
693         &                         xx_gentim2d(i,j,bi,bj,iarr)
694    #endif
695    #ifndef ALLOW_ROTATE_UV_CONTROLS
696               IF (xx_gentim2d_file(iarr)(1:8).EQ.'xx_uwind')
697         &       uwind(i,j,bi,bj)=uwind(i,j,bi,bj)+
698         &                         xx_gentim2d(i,j,bi,bj,iarr)
699               IF (xx_gentim2d_file(iarr)(1:8).EQ.'xx_vwind')
700         &       vwind(i,j,bi,bj)=vwind(i,j,bi,bj)+
701         &                         xx_gentim2d(i,j,bi,bj,iarr)
702    #else
703               IF (xx_gentim2d_file(iarr)(1:8).EQ.'xx_uwind')
704         &       tmpUE(i,j,bi,bj)=tmpUE(i,j,bi,bj)+
705         &                         xx_gentim2d(i,j,bi,bj,iarr)
706               IF (xx_gentim2d_file(iarr)(1:8).EQ.'xx_vwind')
707         &       tmpVN(i,j,bi,bj)=tmpVN(i,j,bi,bj)+
708         &                         xx_gentim2d(i,j,bi,bj,iarr)
709    #endif
710              ENDDO
711             ENDDO
712            ENDDO
713           ENDDO
714           ENDDO
715    #ifdef ALLOW_ROTATE_UV_CONTROLS
716           CALL ROTATE_UV2EN_RL(tmpUX,tmpVY,tmpUE,tmpVN,
717         &      .FALSE.,.FALSE.,.TRUE.,1,myThid)
718    
719           DO bj = myByLo(myThid),myByHi(myThid)
720             DO bi = myBxLo(myThid),mybxhi(myThid)
721              DO j = 1,sNy
722               DO i = 1,sNx
723                 uwind(i,j,bi,bj)=uwind(i,j,bi,bj)+tmpUX(i,j,bi,bj)
724                 vwind(i,j,bi,bj)=vwind(i,j,bi,bj)+tmpVY(i,j,bi,bj)
725               ENDDO
726              ENDDO
727             ENDDO
728           ENDDO
729    #endif /* ALLOW_ROTATE_UV_CONTROLS */
730    
731          ENDIF !if (ctrlUseGen) then
732  #endif  #endif
733    
734        end        RETURN
735          END

Legend:
Removed from v.1.2.4.10.2.1  
changed lines
  Added in v.1.70

  ViewVC Help
Powered by ViewVC 1.1.22