/[MITgcm]/MITgcm/pkg/aim_v23/phy_suflux_sice.F
ViewVC logotype

Contents of /MITgcm/pkg/aim_v23/phy_suflux_sice.F

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


Revision 1.1 - (show annotations) (download)
Thu Mar 11 14:33:19 2004 UTC (20 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_post
a) Treat separately land / ocean / sea-ice surface fluxes
   to allow implicit computation of land & sea-ice surface temp.
b) add snow precipitation
c) other (little) modifications for new land formulation.

1 C $Header: $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: SUFLUX_SICE
8 C !INTERFACE:
9 SUBROUTINE SUFLUX_SICE(
10 I PSA, FMASK, EMISloc,
11 I Tsurf, dTskin, SSR, SLRD,
12 I T0, Q0, EnPrec, CDENVV,
13 O SHF, EVAP, SLRU,
14 O Evp0, dEvp, Slr0, dSlr, sFlx,
15 O TSFC, TSKIN,
16 I bi,bj,myThid)
17
18 C !DESCRIPTION: \bv
19 C *==========================================================*
20 C | S/R SUFLUX_SICE
21 C | o compute surface flux over sea-ice
22 C *==========================================================*
23 C | o contains part of original S/R SUFLUX (Speedy code)
24 C *==========================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29
30 C Resolution parameters
31
32 C-- size for MITgcm & Physics package :
33 #include "AIM_SIZE.h"
34 #include "EEPARAMS.h"
35
36 C-- Physics package
37 #include "AIM_PARAMS.h"
38
39 C Physical constants + functions of sigma and latitude
40 #include "com_physcon.h"
41
42 C Surface flux constants
43 #include "com_sflcon.h"
44
45 C !INPUT/OUTPUT PARAMETERS:
46 C == Routine Arguments ==
47 C-- Input:
48 C PSA :: norm. surface pressure [p/p0] (2-dim)
49 C FMASK :: fractional land-sea mask (2-dim)
50 C EMISloc:: longwave surface emissivity
51 C Tsurf :: surface temperature (2-dim)
52 C dTskin :: temp. correction for daily-cycle heating [K]
53 C SSR :: sfc sw radiation (net flux) (2-dim)
54 C SLRD :: sfc lw radiation (downward flux)(2-dim)
55 C T0 :: near-surface air temperature (2-dim)
56 C Q0 :: near-surface sp. humidity [g/kg](2-dim)
57 C EnPrec :: energy of precipitation (snow, rain temp) [J/g]
58 C CDENVV :: sensible heat flux coefficient (2-dim)
59 C-- Output:
60 C SHF :: sensible heat flux (2-dim)
61 C EVAP :: evaporation [g/(m^2 s)] (2-dim)
62 C SLRU :: sfc lw radiation (upward flux) (2-dim)
63 C Evp0 :: evaporation computed over freezing surface (Ts=0.oC)
64 C dEvp :: evaporation derivative relative to surf. temp
65 C Slr0 :: upward long wave radiation over freezing surf.
66 C dSlr :: upward long wave rad. derivative relative to surf. temp
67 C sFlx :: net surface flux (+=down) function of surf. temp Ts:
68 C 0: Flux(Ts=0.oC) ; 1: Flux(Ts^n) ; 2: d.Flux/d.Ts(Ts^n)
69 C TSFC :: surface temperature (clim.) (2-dim)
70 C TSKIN :: skin surface temperature (2-dim)
71 C-- Input:
72 C bi,bj :: tile index
73 C myThid :: Thread number for this instance of the routine
74 C--
75 _RL PSA(NGP), FMASK(NGP), EMISloc
76 _RL Tsurf(NGP), dTskin(NGP)
77 _RL SSR(NGP), SLRD(NGP)
78 _RL T0(NGP), Q0(NGP), CDENVV(NGP), EnPrec(NGP)
79
80 _RL SHF(NGP), EVAP(NGP), SLRU(NGP)
81 _RL Evp0(NGP), dEvp(NGP), Slr0(NGP), dSlr(NGP), sFlx(NGP,0:2)
82 _RL TSFC(NGP), TSKIN(NGP)
83
84 INTEGER bi,bj,myThid
85 CEOP
86
87 #ifdef ALLOW_AIM
88
89 C-- Local variables:
90 _RL QSAT0(NGP,2)
91 _RL QDUMMY(1), RDUMMY(1), TS2
92 INTEGER J
93
94 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
95
96 C 1.5 Define effective skin temperature to compensate for
97 C non-linearity of heat/moisture fluxes during the daily cycle
98
99 DO J=1,NGP
100 c TSKIN(J) = Tsurf(J) + dTskin(J)
101 c TSFC(J)=273.16 _d 0 + dTskin(J)
102 TSKIN(J) = Tsurf(J)
103 TSFC(J)=273.16 _d 0
104 ENDDO
105
106
107 C-- 2. Computation of fluxes over land and sea
108
109 C 2.1 Wind stress
110
111 C 2.2 Sensible heat flux (from clim. TS over land)
112
113 DO J=1,NGP
114 SHF(J) = CDENVV(J)*CP*(TSKIN(J)-T0(J))
115 sFlx(J,0)= -CDENVV(J)*CP*(TSFC(J) -T0(J))
116 sFlx(J,1)= -SHF(J)
117 sFlx(J,2)= -CDENVV(J)*CP
118 ENDDO
119
120 C 2.3 Evaporation
121
122 CALL SHTORH (2, NGP, TSKIN, PSA, 1. _d 0, QDUMMY, dEvp,
123 & QSAT0(1,1), myThid)
124 CALL SHTORH (0, NGP, TSFC, PSA, 1. _d 0, QDUMMY, RDUMMY,
125 & QSAT0(1,2), myThid)
126
127 DO J=1,NGP
128 EVAP(J) = CDENVV(J)*(QSAT0(J,1)-Q0(J))
129 Evp0(J) = CDENVV(J)*(QSAT0(J,2)-Q0(J))
130 dEvp(J) = CDENVV(J)*dEvp(J)
131 ENDDO
132
133 C 2.4 Emission of lw radiation from the surface
134
135 DO J=1,NGP
136 TS2 = TSFC(J)*TSFC(J)
137 Slr0(J) = SBC*TS2*TS2
138 TS2 = TSKIN(J)*TSKIN(J)
139 SLRU(J) = SBC*TS2*TS2
140 dSlr(J) = 4. _d 0 *SBC*TS2*TSKIN(J)
141 ENDDO
142
143 C-- Compute net surface heat flux and its derivative ./. surf. temp.
144 DO J=1,NGP
145 sFlx(J,0)= sFlx(J,0)
146 & - ALHC*Evp0(J) - EMISloc*Slr0(J) + SLRD(J) + SSR(J)
147 sFlx(J,1)= sFlx(J,1)
148 & - ALHC*EVAP(J) - EMISloc*SLRU(J) + SLRD(J) + SSR(J)
149 sFlx(J,2)= sFlx(J,2)
150 & - ALHC*dEvp(J) - EMISloc*dSlr(J)
151 ENDDO
152 IF ( aim_energPrecip ) THEN
153 C- Evap of snow: substract Latent Heat of freezing from heatFlux
154 DO J=1,NGP
155 IF ( EnPrec(J) .LT. 0. ) THEN
156 sFlx(J,0) = sFlx(J,0) - ALHF*Evp0(J)
157 sFlx(J,1) = sFlx(J,1) - ALHF*EVAP(J)
158 sFlx(J,2) = sFlx(J,2) - ALHF*dEvp(J)
159 ENDIF
160 ENDDO
161 ENDIF
162
163 C-- 3. Adjustment of skin temperature and fluxes over land
164 C-- based on energy balance (to be implemented)
165 C <= done separately for each surface type (land,ocean,sea-ice)
166
167 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
168 #endif /* ALLOW_AIM */
169
170 RETURN
171 END

  ViewVC Help
Powered by ViewVC 1.1.22