/[MITgcm]/MITgcm/pkg/ebm/ebm_atmosphere.F
ViewVC logotype

Diff of /MITgcm/pkg/ebm/ebm_atmosphere.F

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

revision 1.1 by heimbach, Fri May 14 21:10:34 2004 UTC revision 1.10 by jmc, Mon Aug 29 19:38:44 2011 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "EBM_OPTIONS.h"  #include "EBM_OPTIONS.h"
5    
6        SUBROUTINE EBM_ATMOSPHERE ( myTime, myiter, myThid )  CBOP 0
7    C !ROUTINE: EBM_ATMOSPHERE
8    
9  C     |==========================================================|  C !INTERFACE:
10  C     | S/R CALCULATE FORCING FROM ENERGY AND MOISTURE           |        SUBROUTINE EBM_ATMOSPHERE ( myTime, myIter, myThid )
11  C     | BALANCE ATMOSPHERE                                       |  
12  C     |==========================================================|  C     !DESCRIPTION:
13    C     *==========================================================*
14    C     | S/R CALCULATE FORCING FROM ENERGY AND MOISTURE
15    C     | BALANCE ATMOSPHERE
16    C     *==========================================================*
17  C      References:  C      References:
18  C      * X. Wang, P. Stone and J. Marotzke, 1999:  C      * X. Wang, P. Stone and J. Marotzke, 1999:
19  C        Global thermohaline circulation. Part I:  C        Global thermohaline circulation. Part I:
# Line 23  C        Destabilization of the thermoha Line 28  C        Destabilization of the thermoha
28  C        by atmospheric eddy transports.  C        by atmospheric eddy transports.
29  C        J. Climate 7(12), 1870-1882  C        J. Climate 7(12), 1870-1882
30    
31    C     !USES:
32        IMPLICIT NONE        IMPLICIT NONE
   
33  C     === Global variables ===  C     === Global variables ===
34  #include "SIZE.h"  #include "SIZE.h"
35  #include "EEPARAMS.h"  #include "EEPARAMS.h"
36  #include "PARAMS.h"  #include "PARAMS.h"
37  #include "FFIELDS.h"  #include "FFIELDS.h"
 #include "DYNVARS.h"  
38  #include "GRID.h"  #include "GRID.h"
39  #ifdef ALLOW_EBM  #include "EBM.h"
40  # include "EBM.h"  #ifdef ALLOW_AUTODIFF_TAMC
41    # include "tamc.h"
42    # include "tamc_keys.h"
43  #endif  #endif
44    
45    C     !INPUT PARAMETERS:
46  C     === Routine arguments ===  C     === Routine arguments ===
47  C     myThid - Instance number for this innvocation of CALC_FORCING  C     myThid  :: my Thread Id number
       INTEGER myThid  
       INTEGER myIter  
48        _RL myTime        _RL myTime
49  CEndOfInterface        INTEGER myIter
50          INTEGER myThid
51    CEOP
52    
53  #ifdef ALLOW_EBM  #ifdef ALLOW_EBM
54    C     !LOCAL VARIABLES:
55  C     == Local variables ==        INTEGER i, j, bi, bj
       _RL Dy  
       _RL ReCountX(1-OLy:sNy+OLy)  
       INTEGER bi, bj  
       INTEGER i, j  
56        INTEGER no_so        INTEGER no_so
57        LOGICAL TOP_LAYER  #ifdef ALLOW_AUTODIFF_TAMC
58          INTEGER iebmkey
59  C--   Top layer only  #endif /* ALLOW_AUTODIFF_TAMC */
60  cph      TOP_LAYER = k .EQ. 1        _RL ReCountX(1-OLy:sNy+OLy,nSy)
61    
62    C--   Local arrays used for EBM computation (previously declared in EBM.h)
63    C-    sin(lat) and Legendre polynomials
64    cph We will make these three (i,j) arrays to
65    cph avoid AD recomputations
66          _RL S(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSy)
67          _RL P2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSy)
68          _RL P4(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSy)
69    C-    Shortwave and albedo parameters
70          _RL SW(1-OLy:sNy+OLy,nSy)
71    C-    Longwave parameters
72          _RL LW(1-OLy:sNy+OLy,nSy)
73    C-    Heat transport parameters
74          _RL Hd(1-OLy:sNy+OLy,nSy), Hd35(2)
75    C-    Freshwater flux parameters
76          _RL Fw(1-OLy:sNy+OLy,nSy), Fw35(2)
77    C-    Temperature parameterization
78          _RL T(1-OLy:sNy+OLy,nSy)
79          _RL T_var(4), T0(2), T2(2), T35(2), DTDy35(2)
80    C-    Parameters used to calculate the transport efficiency
81          _RL Cl, Cf, Cs, C
82          _RL gamma, kappa, De
83    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
84    
 cph      IF ( TOP_LAYER ) THEN  
         
85        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
86         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
87    
88          DO j=1-OLy,sNy+OLy  #ifdef ALLOW_AUTODIFF_TAMC
89           S(j) = 0.0            act1 = bi - myBxLo(myThid)
90           P2(j) = 0.0            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
91           P4(j) = 0.0            act2 = bj - myByLo(myThid)
92           SW(j) = 0.0            max2 = myByHi(myThid) - myByLo(myThid) + 1
93           LW(j) = 0.0            act3 = myThid - 1
94           Hd(j) = 0.0            max3 = nTx*nTy
95           Fw(j) = 0.0            act4 = ikey_dynamics - 1
96           T(j) = 0.0            iebmkey = (act1 + 1) + act2*max1
97           ReCountX(j) = 0.0       &                      + act3*max1*max2
98         &                      + act4*max1*max2*max3
99    #endif /* ALLOW_AUTODIFF_TAMC */
100    
101            DO j=1-oLy,sNy+oLy
102             DO i=1-oLx,sNx+oLx
103              S(i,j,bj) = 0.0
104              P2(i,j,bj) = 0.0
105              P4(i,j,bj) = 0.0
106             ENDDO
107             SW(j,bj) = 0.0
108             LW(j,bj) = 0.0
109             Hd(j,bj) = 0.0
110             Fw(j,bj) = 0.0
111             T(j,bj) = 0.0
112             ReCountX(j,bj) = 0.0
113          ENDDO          ENDDO
114    
115          print *, 'SH', TmlS-t_mlt, TtS-t_mlt          print *, 'SH', TmlS-t_mlt, TtS-t_mlt
# Line 78  cph      IF ( TOP_LAYER ) THEN Line 117  cph      IF ( TOP_LAYER ) THEN
117    
118  C--   account for ice (can absorb heat on an annual averaged basis)  C--   account for ice (can absorb heat on an annual averaged basis)
119  C--   Greenland in Northern Hemisphere, Antarctica in Southern  C--   Greenland in Northern Hemisphere, Antarctica in Southern
120          DO j = 1-OLy,sNy+OLy          DO j = 1,sNy
121           ReCountX(j) = CountX(j)           ReCountX(j,bj) = CountX(j,bj)
122           IF (yC(1,j,bi,bj) .LE. -62.0) THEN           IF (yC(1,j,bi,bj) .LE. -62.0) THEN
123              ReCountX(j) = 90.              ReCountX(j,bj) = 90.
124           ELSE IF (yC(1,j,bi,bj) .EQ. 74.0) THEN           ELSE IF (yC(1,j,bi,bj) .EQ. 74.0) THEN
125              ReCountX(j) = CountX(j) + 9.0              ReCountX(j,bj) = CountX(j,bj) + 9.0
126           ELSE IF (yC(1,j,bi,bj) .EQ. 70.0) THEN           ELSE IF (yC(1,j,bi,bj) .EQ. 70.0) THEN
127              ReCountX(j) = CountX(j) + 8.0              ReCountX(j,bj) = CountX(j,bj) + 8.0
128           ELSE IF (yC(1,j,bi,bj) .EQ. 66.0) THEN           ELSE IF (yC(1,j,bi,bj) .EQ. 66.0) THEN
129              ReCountX(j) = CountX(j) + 5.0              ReCountX(j,bj) = CountX(j,bj) + 5.0
130           ELSE IF (yC(1,j,bi,bj) .EQ. 62.0) THEN           ELSE IF (yC(1,j,bi,bj) .EQ. 62.0) THEN
131              ReCountX(j) = CountX(j) + 1.0              ReCountX(j,bj) = CountX(j,bj) + 1.0
132           ENDIF           ENDIF
133          ENDDO          ENDDO
134            #ifdef ALLOW_AUTODIFF_TAMC
135    CADJ STORE ReCountX(:,bj) = comlev1_bibj, key=iebmkey, byte=isbyte
136    #endif
137    
138  c=====================================================  c=====================================================
139  c     Fit area-weighed  averaged SST north/south of 34  c     Fit area-weighed  averaged SST north/south of 34
140  c     degree  to second  Legendre polynomial:  c     degree  to second  Legendre polynomial:
141  c=======================================================  c=======================================================
142          T_var(1) = SIN(lat(2)*deg2rad) - SIN(lat(1)*deg2rad)          T_var(1) = SIN(latBnd(2)*deg2rad) - SIN(latBnd(1)*deg2rad)
143          T_var(2) = SIN(lat(3)*deg2rad) - SIN(lat(2)*deg2rad)          T_var(2) = SIN(latBnd(3)*deg2rad) - SIN(latBnd(2)*deg2rad)
144          T_var(3) = SIN(lat(2)*deg2rad)**3. - SIN(lat(1)*deg2rad)**3.          T_var(3) = SIN(latBnd(2)*deg2rad)**3 - SIN(latBnd(1)*deg2rad)**3
145          T_var(4) = SIN(lat(3)*deg2rad)**3. - SIN(lat(2)*deg2rad)**3.          T_var(4) = SIN(latBnd(3)*deg2rad)**3 - SIN(latBnd(2)*deg2rad)**3
146    #ifdef ALLOW_AUTODIFF_TAMC
147    CADJ STORE T_var(:) = comlev1_bibj, key=iebmkey, byte=isbyte
148    #endif
149    
150  c----------------------------------------  c----------------------------------------
151  c     Southern hemisphere:  c     Southern hemisphere:
152  c----------------------------------------  c----------------------------------------
153          T2(1) =  2.*(TtS - TmlS)*T_var(1)*T_var(2)/          T2(1) =  2.*(TtS - TmlS)*T_var(1)*T_var(2)/
154       <     (T_var(3)*T_var(2) - T_var(4)*T_var(1))       &     (T_var(3)*T_var(2) - T_var(4)*T_var(1))
155          T0(1) = TtS - 0.5*T2(1)*((T_var(3)/T_var(1)) - 1.)          T0(1) = TtS - 0.5*T2(1)*((T_var(3)/T_var(1)) - 1.)
156  c----------------------------------------  c----------------------------------------
157  c       Northern hemisphere  c     Northern hemisphere
158  c----------------------------------------  c----------------------------------------
159          T2(2) =  2.*(TtN - TmlN)*T_var(1)*T_var(2)/          T2(2) =  2.*(TtN - TmlN)*T_var(1)*T_var(2)/
160       <     (T_var(3)*T_var(2) - T_var(4)*T_var(1))       &     (T_var(3)*T_var(2) - T_var(4)*T_var(1))
161          T0(2) = TtN - 0.5*T2(2)*((T_var(3)/T_var(1)) - 1.)          T0(2) = TtN - 0.5*T2(2)*((T_var(3)/T_var(1)) - 1.)
162  c-----------------------------------------  c-----------------------------------------
163  c     Temperature  at 35 N/S  c     Temperature  at 35 N/S
164  c-----------------------------------------  c-----------------------------------------
165          DO no_so = 1,2          DO no_so = 1,2
166           T35(no_so)= T0(no_so) +           T35(no_so)= T0(no_so) +
167       <        T2(no_so)*0.5*       &        T2(no_so)*0.5*
168       <        ((3.*SIN(lat(2)*deg2rad)**2. - 1.))       &        ( 3.*SIN(latBnd(2)*deg2rad)**2 - 1. )
169          ENDDO          ENDDO
170  c-----------------------------------------  c-----------------------------------------
171  c     Temperature gradient at 35 N/S  c     Temperature gradient at 35 N/S
172  c-----------------------------------------  c-----------------------------------------
173          DO no_so = 1, 2          DO no_so = 1, 2
174           DTDy35(no_so) = 3.*T2(no_so)*           DTDy35(no_so) = 3.*T2(no_so)*
175       <        SIN(lat(2)*deg2rad)/rSphere       &        SIN(latBnd(2)*deg2rad)/rSphere
176          ENDDO          ENDDO
177  c-----------------------------------------------------------  c-----------------------------------------------------------
178  c     Magnitude of the heat and moisture transport at 35 N/S  c     Magnitude of the heat and moisture transport at 35 N/S
179  c-----------------------------------------------------------  c-----------------------------------------------------------
180    
181    #ifdef ALLOW_AUTODIFF_TAMC
182    CADJ STORE T35(:)    = comlev1_bibj, key=iebmkey, byte=isbyte
183    CADJ STORE DTDy35(:) = comlev1_bibj, key=iebmkey, byte=isbyte
184    #endif
185          DO no_so = 1, 2          DO no_so = 1, 2
186           gamma = -T35(no_so)*beta*Hw*Nw*Nw/           IF ( DTDy35(no_so).NE.0. .AND. T35(no_so).NE.0. ) THEN
187       <        (gravity*f0*DTDy35(no_so))            gamma = -T35(no_so)*beta*Hw*Nw*Nw/
188           kappa = Hw/(1 + gamma)       &        (gravity*f0*DTDy35(no_so))
189           De = Hw/(0.48 + 1.48*gamma)            kappa = Hw/(1. _d 0 + gamma)
190           C = 0.6*gravity*kappa*kappa*Nw/            De = Hw/(0.48 _d 0 + 1.48 _d 0 *gamma)
191       <        (Tw*f0*f0)            C = 0.6 _d 0 *gravity*kappa*kappa*Nw/
192           Cs = rho_air*cp*C*       &        (Tw*f0*f0)
193       <        (1/(1/Hw+1/De) - 1/(1/Hw+1/De+1/dz))            Cs = rho_air*cp*C*
194           Cf = htil*2.97e12*C/(T35(no_so)**3)*(       &        ( 1. _d 0 /(1. _d 0 /Hw + 1. _d 0 /De)
195       <        1/(1/De + (5420*tau /(T35(no_so)**2)))       &         -1. _d 0 /(1. _d 0 /Hw+1. _d 0 /De+1. _d 0 /dz) )
196       <     - 1/(1/De+5420*tau/(T35(no_so)**2)+1/dz))            Cf = htil*2.97 _d 12*C/(T35(no_so)**3)*(
197           Cl = Cf*lv       &        1. _d 0/(1. _d 0/De + (5420. _d 0*tau /(T35(no_so)**2)))
198           Hd35(no_so) = 2.*PI*rSphere*COS(lat(2)*deg2rad)       &        -1. _d 0/(1. _d 0/De+5420. _d 0*tau/(T35(no_so)**2)
199       <        *(Cs + Cl*exp(-5420./T35(no_so)))       &        +1. _d 0/dz))
200       <        *(abs(DTDy35(no_so))**trans_eff)            Cl = Cf*lv
201           Fw35(no_so) = 2.*PI*rSphere*COS(lat(2)*deg2rad)            Hd35(no_so) = 2.*PI*rSphere*COS(latBnd(2)*deg2rad)
202       <        *(abs(DTDy35(no_so))**trans_eff)       &        *(Cs + Cl*exp(-5420./T35(no_so)))
203       <        *Cf*exp(-5420./T35(no_so))       &        *(abs(DTDy35(no_so))**trans_eff)
204  c        write(0,*) no_so, Hd35(no_so), Fw35(no_so)            Fw35(no_so) = 2.*PI*rSphere*COS(latBnd(2)*deg2rad)
205         &        *(abs(DTDy35(no_so))**trans_eff)
206         &        *Cf*exp(-5420./T35(no_so))
207             ELSE
208              Hd35(no_so) = 0.
209              Fw35(no_so) = 0.
210             ENDIF
211          ENDDO          ENDDO
212    c
213          Fw35(1) = 929944128.          Fw35(1) = 929944128.
214          Fw35(2) = 678148032.          Fw35(2) = 678148032.
215    c
216  #ifdef EBM_VERSION_1BASIN  #ifdef EBM_VERSION_1BASIN
217  c      Fw35(2) = 0.7*Fw35(2)  c      Fw35(2) = 0.7*Fw35(2)
218  #else  #else
219          Hd35(2) = 1.6*Hd35(2)          Hd35(2) = 1.6 _d 0*Hd35(2)
220  #endif  #endif
221  c======================================================  c======================================================
222  c     Calculation of latitudinal profiles  c     Calculation of latitudinal profiles
223  c======================================================  c======================================================
224  c    c
225          DO j=1-OLy,sNy+OLy          DO j=1,sNy
226           DO i=1-Olx,sNx+Olx           DO i=1,sNx
227    C     sin(lat)
228              S(i,j,bj) = SIN(yC(i,j,bi,bj)*deg2rad)
229    C     setup Legendre polynomials and  derivatives
230              P2(i,j,bj) = 0.5*(3.*S(i,j,bj)**2 - 1.)
231              P4(i,j,bj) = 0.12 _d 0 *
232         &                (35.*S(i,j,bj)**4 - 30.*S(i,j,bj)**2 + 3.)
233             ENDDO
234            ENDDO
235    #ifdef ALLOW_AUTODIFF_TAMC
236    CADJ STORE S(:,:,bj)    = comlev1_bibj, key=iebmkey, byte=isbyte
237    CADJ STORE P2(:,:,bj)   = comlev1_bibj, key=iebmkey, byte=isbyte
238    CADJ STORE P4(:,:,bj)   = comlev1_bibj, key=iebmkey, byte=isbyte
239    #endif
240    c
241            DO j=1,sNy
242             DO i=1,sNx
243    
244            IF (yC(i,j,bi,bj) .LT. 0.) THEN            IF (yC(i,j,bi,bj) .LT. 0.) THEN
245               no_so = 1               no_so = 1
246            ELSE            ELSE
247               no_so = 2               no_so = 2
248            ENDIF            ENDIF
 C     sin(lat)  
           S(j) = sin(yC(i,j,bi,bj)*deg2rad)  
 C     setup Legendre polynomials and  derivatives  
           P2(j) = 0.5*(3.*S(j)**2 - 1.)  
           P4(j) = 0.12*(35.*S(j)**4 - 30.*S(j)**2 + 3.)  
249  c     net shortwave  c     net shortwave
250            SW(j) = 0.25*Q0*(1 + Q2*P2(j))*            SW(j,bj) = 0.25 _d 0 *Q0*(1. _d 0 + Q2*P2(i,j,bj))*
251       <         (1 - A0 - A2*P2(j) - A4*P4(j) )       &         (1. _d 0 - A0 - A2*P2(i,j,bj) - A4*P4(i,j,bj) )
252  c     temperature  c     temperature
253            T(j) = T0(no_so) + T2(no_so)*P2(j)            T(j,bj) = T0(no_so) + T2(no_so)*P2(i,j,bj)
254  c     net longwave  c     net longwave
255            LW(j) = LW0 + LW1*(T(j)-t_mlt)            LW(j,bj) = LW0 + LW1*(T(j,bj)-t_mlt)
256  c     climate change run, the parameter to change is DLW  c     climate change run, the parameter to change is DLW
257  #ifdef EBM_CLIMATE_CHANGE  #ifdef EBM_CLIMATE_CHANGE
258               LW(j) = LW(j) -               LW(j,bj) = LW(j,bj) -
259       <            (myTime-startTime)*3.215e-8*DLW       &            (myTime-startTime)*3.215 _d -8*DLW
260  c     <            - 6.0  c     <            - 6.0
261  c     <            *75.0*0.0474*  c     <            *75.0*0.0474*
262  c     <            (-2.62*S(j)**8 + 0.73*S(j)**7 +  c     <            (-2.62*S(i,j,bj)**8 + 0.73*S(i,j,bj)**7 +
263  c     <            4.82*S(j)**6 -  c     <            4.82*S(i,j,bj)**6 -
264  c     <            1.12*S(j)**5 - 2.69*S(j)**4 + 0.47*S(j)**3 +  c     <            1.12*S(i,j,bj)**5 - 2.69*S(i,j,bj)**4 + 0.47*S(i,j,bj)**3 +
265  c     <            0.51*S(j)**2 - 0.05*S(j)**1 + 0.17)  c     <            0.51*S(i,j,bj)**2 - 0.05*S(i,j,bj)**1 + 0.17)
266  #endif  #endif
267  c     fluxes at ocean/atmosphere interface  c     fluxes at ocean/atmosphere interface
268  c     Heat Flux = -Div(atmospheric heat transport) + SW - LW  c     Heat Flux = -Div(atmospheric heat transport) + SW - LW
269  #ifdef EBM_VERSION_1BASIN  #ifdef EBM_VERSION_1BASIN
270           Qnet(i,j,bi,bj) = -1.0*( SW(j) - LW(j) -           Qnet(i,j,bi,bj) = -1.0 _d 0 *( SW(j,bj) - LW(j,bj) -
271       <        Hd35(no_so)*(       &        Hd35(no_so)*(
272       <        0.000728e4      - 0.00678e4*S(j) +       &        0.000728 _d 4      - 0.00678 _d 4*S(i,j,bj) +
273       <        0.0955e4*S(j)**2 + 0.0769e4*S(j)**3 -       &        0.0955 _d 4*S(i,j,bj)**2 + 0.0769 _d 4*S(i,j,bj)**3 -
274       <        0.8508e4*S(j)**4 - 0.3581e4*S(j)**5 +       &        0.8508 _d 4*S(i,j,bj)**4 - 0.3581 _d 4*S(i,j,bj)**5 +
275       <        2.9240e4*S(j)**6 + 0.8311e4*S(j)**7 -         &        2.9240 _d 4*S(i,j,bj)**6 + 0.8311 _d 4*S(i,j,bj)**7 -
276       <        4.9548e4*S(j)**8 - 0.8808e4*S(j)**9 +       &        4.9548 _d 4*S(i,j,bj)**8 - 0.8808 _d 4*S(i,j,bj)**9 +
277       <        4.0644e4*S(j)**10 +0.3409e4*S(j)**11 -       &        4.0644 _d 4*S(i,j,bj)**10 +0.3409 _d 4*S(i,j,bj)**11 -
278       <        1.2893e4*S(j)**12 )       &        1.2893 _d 4*S(i,j,bj)**12 )
279       <        /(2*PI*rSphere*rSphere*25.0) )       &        /(2.*PI*rSphere*rSphere*25.) )
280  c             Qnet(i,j,bi,bj) = -1.0*( SW(j) - LW(j) -  c             Qnet(i,j,bi,bj) = -1.0*( SW(j,bj) - LW(j,bj) -
281  c     <            0.5*Hd35(no_so)*(3.054e1 - 3.763e1*S(j) +  c     <            0.5*Hd35(no_so)*(3.054e1 - 3.763e1*S(i,j,bj) +
282  c     <        1.892e2*S(j)**2 + 3.041e2*S(j)**3 -  c     <        1.892e2*S(i,j,bj)**2 + 3.041e2*S(i,j,bj)**3 -
283  c     <        1.540e3*S(j)**4 - 9.586e2*S(j)**5 +  c     <        1.540e3*S(i,j,bj)**4 - 9.586e2*S(i,j,bj)**5 +
284  c     <        2.939e3*S(j)**6 + 1.219e3*S(j)**7 -    c     <        2.939e3*S(i,j,bj)**6 + 1.219e3*S(i,j,bj)**7 -
285  c     <        2.550e3*S(j)**8 - 5.396e2*S(j)**9 +  c     <        2.550e3*S(i,j,bj)**8 - 5.396e2*S(i,j,bj)**9 +
286  c     <        8.119e2*S(j)**10)  c     <        8.119e2*S(i,j,bj)**10)
287  c     <            /(2*PI*rSphere*rSphere*22.3) )  c     <            /(2*PI*rSphere*rSphere*22.3) )
288  #else  #else
289            IF (ReCountX(j) .GT. 0.) THEN            IF (ReCountX(j,bj) .GT. 0.) THEN
290               Qnet(i,j,bi,bj) = (-90./ReCountX(j))*               Qnet(i,j,bi,bj) = (-90. _d 0 /ReCountX(j,bj))*
291       <            ( SW(j) - LW(j) -       &            ( SW(j,bj) - LW(j,bj) -
292       <            Hd35(no_so)*(3.054e1 - 3.763e1*S(j) +       &            Hd35(no_so)*(3.054 _d 1 - 3.763 _d 1*S(i,j,bj) +
293       <        1.892e2*S(j)**2 + 3.041e2*S(j)**3 -       &        1.892 _d 2*S(i,j,bj)**2 + 3.041 _d 2*S(i,j,bj)**3 -
294       <        1.540e3*S(j)**4 - 9.586e2*S(j)**5 +       &        1.540 _d 3*S(i,j,bj)**4 - 9.586 _d 2*S(i,j,bj)**5 +
295       <        2.939e3*S(j)**6 + 1.219e3*S(j)**7 -         &        2.939 _d 3*S(i,j,bj)**6 + 1.219 _d 3*S(i,j,bj)**7 -
296       <        2.550e3*S(j)**8 - 5.396e2*S(j)**9 +       &        2.550 _d 3*S(i,j,bj)**8 - 5.396 _d 2*S(i,j,bj)**9 +
297       <        8.119e2*S(j)**10)       &        8.119 _d 2*S(i,j,bj)**10)
298       <            /(2*PI*rSphere*rSphere*22.3) )       &            /(2.*PI*rSphere*rSphere*22.3 _d 0) )
299            ELSE            ELSE
300               Qnet(i,j,bi,bj) = 0.               Qnet(i,j,bi,bj) = 0.
301            ENDIF            ENDIF
# Line 237  c     <            /(2*PI*rSphere*rSpher Line 303  c     <            /(2*PI*rSphere*rSpher
303  c     Freshwater Flux = Div(atmospheric moisture transport)  c     Freshwater Flux = Div(atmospheric moisture transport)
304  c---  conversion of E-P from kg/(s m^2) -> m/s -> psu/s: 1e-3*35/delZ(1)  c---  conversion of E-P from kg/(s m^2) -> m/s -> psu/s: 1e-3*35/delZ(1)
305  #ifdef EBM_VERSION_1BASIN  #ifdef EBM_VERSION_1BASIN
306            EmPmR(i,j,bi,bj) = -1.e-3*Fw35(no_so)            EmPmR(i,j,bi,bj) = -1. _d -3*Fw35(no_so)
307       <    *(-0.8454e5*S(j)**14 + 0.5367e5*S(j)**13       &    *(-0.8454 _d 5*S(i,j,bj)**14 + 0.5367 _d 5*S(i,j,bj)**13
308       <    +3.3173e5*S(j)**12 - 1.8965e5*S(j)**11 - 5.1701e5*S(j)**10       &    +3.3173 _d 5*S(i,j,bj)**12 - 1.8965 _d 5*S(i,j,bj)**11
309       <    +2.6240e5*S(j)**9 + 4.077e5*S(j)**8 - 1.791e5*S(j)**7       &    -5.1701 _d 5*S(i,j,bj)**10
310       <    -1.7231e5*S(j)**6 + 0.6229e5*S(j)**5 + 0.3824e5*S(j)**4       &    +2.6240 _d 5*S(i,j,bj)**9 + 4.077 _d 5*S(i,j,bj)**8
311       <    -0.1017e5*S(j)**3 - 0.0387e5*S(j)**2       &    -1.791 _d 5*S(i,j,bj)**7
312       <    +0.00562e5*S(j)  + 0.0007743e5)       &    -1.7231 _d 5*S(i,j,bj)**6 + 0.6229 _d 5*S(i,j,bj)**5
313       <    /(2.0*12.0*PI*rSphere*rSphere)       &    +0.3824 _d 5*S(i,j,bj)**4
314         &    -0.1017 _d 5*S(i,j,bj)**3 - 0.0387 _d 5*S(i,j,bj)**2
315         &    +0.00562 _d 5*S(i,j,bj)  + 0.0007743 _d 5)
316         &    /(2.0*12.0*PI*rSphere*rSphere)
317  c             EmPmR(i,j,bi,bj) = 1.e-3*Fw35(no_so)  c             EmPmR(i,j,bi,bj) = 1.e-3*Fw35(no_so)
318  c     <            *(50.0 + 228.0*S(j) -1.593e3*S(j)**2  c     <            *(50.0 + 228.0*S(i,j,bj) -1.593e3*S(i,j,bj)**2
319  c     <            - 2.127e3*S(j)**3 + 7.3e3*S(j)**4  c     <            - 2.127e3*S(i,j,bj)**3 + 7.3e3*S(i,j,bj)**4
320  c     <            + 5.799e3*S(j)**5 - 1.232e4*S(j)**6  c     <            + 5.799e3*S(i,j,bj)**5 - 1.232e4*S(i,j,bj)**6
321  c     <            - 6.389e3*S(j)**7 + 9.123e3*S(j)**8  c     <            - 6.389e3*S(i,j,bj)**7 + 9.123e3*S(i,j,bj)**8
322  c     <            + 2.495e3*S(j)**9 - 2.567e3*S(j)**10)  c     <            + 2.495e3*S(i,j,bj)**9 - 2.567e3*S(i,j,bj)**10)
323  c     <            /(2*PI*rSphere*rSphere*15.0)  c     <            /(2*PI*rSphere*rSphere*15.0)
324  #else  #else
325            IF (yC(i,j,bi,bj) .LT. -40.) THEN            IF (yC(i,j,bi,bj) .LT. -40.) THEN
326  c--   Southern Hemisphere  c--   Southern Hemisphere
327             EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)*             EmPmR(i,j,bi,bj) = -1. _d -3*(Fw35(no_so)*
328       <            (-6.5 + 35.3 + 71.7*S(j)         &            (-6.5 _d 0 + 35.3 _d 0 + 71.7 _d 0*S(i,j,bj)
329       <           - 1336.3*S(j)**2 - 425.8*S(j)**3       &           - 1336.3 _d 0*S(i,j,bj)**2 - 425.8 _d 0*S(i,j,bj)**3
330       <           + 5434.8*S(j)**4 + 707.9*S(j)**5       &           + 5434.8 _d 0*S(i,j,bj)**4 + 707.9 _d 0*S(i,j,bj)**5
331       <           - 6987.7*S(j)**6 - 360.4*S(j)**7       &           - 6987.7 _d 0*S(i,j,bj)**6 - 360.4 _d 0*S(i,j,bj)**7
332       <           + 2855.0*S(j)**8)       &           + 2855.0 _d 0*S(i,j,bj)**8)
333       <            /(2*PI*rSphere*rSphere*18.0))       &            /(2.*PI*rSphere*rSphere*18.0))
334            ELSE            ELSE
335  c--   Atlantic  c--   Atlantic
336             IF (xC(i,j,bi,bj) .GT. 284.             IF (xC(i,j,bi,bj) .GT. 284.
337       <      .OR. xC(i,j,bi,bj) .LT. 28.) THEN       &      .OR. xC(i,j,bi,bj) .LT. 28.) THEN
338                EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)*                EmPmR(i,j,bi,bj) = -1. _d -3*(Fw35(no_so)*
339       <             (-6.5 -2.878 + 3.157e2*S(j) -       &             (-6.5 _d 0 -2.878 _d 0 + 3.157 _d 2*S(i,j,bj) -
340       <             2.388e3*S(j)**2 - 4.101e3*S(j)**3 +       &             2.388 _d 3*S(i,j,bj)**2 - 4.101 _d 3*S(i,j,bj)**3 +
341       <             1.963e4*S(j)**4 + 1.534e4*S(j)**5 -       &             1.963 _d 4*S(i,j,bj)**4 + 1.534 _d 4*S(i,j,bj)**5 -
342       <             6.556e4*S(j)**6 - 2.478e4*S(j)**7 +       &             6.556 _d 4*S(i,j,bj)**6 - 2.478 _d 4*S(i,j,bj)**7 +
343       <             1.083e5*S(j)**8 + 1.85e4*S(j)**9 -       &             1.083 _d 5*S(i,j,bj)**8 + 1.85 _d 4*S(i,j,bj)**9 -
344       <             8.703e4*S(j)**10 - 5.276e3*S(j)**11 +       &             8.703 _d 4*S(i,j,bj)**10 - 5.276 _d 3*S(i,j,bj)**11 +
345       <             2.703e4*S(j)**12)       &             2.703 _d 4*S(i,j,bj)**12)
346       <             /(2*PI*rSphere*rSphere*12.0))       &             /(2.*PI*rSphere*rSphere*12.0))
347             ELSE             ELSE
348  c--   Pacific  c--   Pacific
349                EmPmR(i,j,bi,bj) = -1.e-3*(Fw35(no_so)                EmPmR(i,j,bi,bj) = -1. _d -3*(Fw35(no_so)
350       <             *(-6.5 +51.89 + 4.916e2*S(j) -       &             *(-6.5 _d 0 +51.89 _d 0 + 4.916 _d 2*S(i,j,bj) -
351       <             1.041e3*S(j)**2 - 7.546e3*S(j)**3 +       &             1.041 _d 3*S(i,j,bj)**2 - 7.546 _d 3*S(i,j,bj)**3 +
352       <             2.335e3*S(j)**4 + 3.449e4*S(j)**5 +       &             2.335 _d 3*S(i,j,bj)**4 + 3.449 _d 4*S(i,j,bj)**5 +
353       <             6.702e3*S(j)**6 - 6.601e4*S(j)**7 -       &             6.702 _d 3*S(i,j,bj)**6 - 6.601 _d 4*S(i,j,bj)**7 -
354       <             2.594e4*S(j)**8 + 5.652e4*S(j)**9 +       &             2.594 _d 4*S(i,j,bj)**8 + 5.652 _d 4*S(i,j,bj)**9 +
355       <             2.738e4*S(j)**10 - 1.795e4*S(j)**11 -       &             2.738 _d 4*S(i,j,bj)**10 - 1.795 _d 4*S(i,j,bj)**11 -
356       <             9.486e3*S(j)**12)       &             9.486 _d 3*S(i,j,bj)**12)
357       <             /(2*PI*rSphere*rSphere*12.0))       &             /(2.*PI*rSphere*rSphere*12.0))
358             ENDIF             ENDIF
359            ENDIF            ENDIF
360  #endif  #endif
361              EmPmR(i,j,bi,bj) = EmPmR(i,j,bi,bj)
362         &                     - Run(i,j,bi,bj)*scale_runoff
363              EmPmR(i,j,bi,bj) = EmPmR(i,j,bi,bj)*rhoConstFresh
364           ENDDO           ENDDO
365          ENDDO          ENDDO
366         ENDDO         ENDDO
367        ENDDO        ENDDO
368    
369          _EXCH_XY_RS(Qnet , myThid )
370          _EXCH_XY_RS(EmPmR , myThid )
371    
372  C      CALL PLOT_FIELD_XYRS( Qnet, 'Qnet' , 1, myThid )  C      CALL PLOT_FIELD_XYRS( Qnet, 'Qnet' , 1, myThid )
373  C      CALL PLOT_FIELD_XYRS( EmPmR, 'EmPmR' , 1, myThid )  C      CALL PLOT_FIELD_XYRS( EmPmR, 'EmPmR' , 1, myThid )
374    
 cph  end of IF TOP_LAYER  
 cph      ENDIF  
   
375  #endif /* ALLOW_EBM */  #endif /* ALLOW_EBM */
376    
377          RETURN
378        END        END
   
       
         
   
   

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22