/[MITgcm]/MITgcm/pkg/seaice/seaice_budget_ocean.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_budget_ocean.F

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


Revision 1.7 - (show annotations) (download)
Thu Jun 4 17:27:17 2009 UTC (15 years ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint61p, checkpoint61q
Changes since 1.6: +46 -17 lines
Added SEAICE_CLIM_AIR code, which permits modulation of surface air
temperature and humidity over sea ice based on climatological values.

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_budget_ocean.F,v 1.6 2007/12/05 15:37:12 dimitri Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE SEAICE_BUDGET_OCEAN(
8 I UG,
9 U TSURF,
10 O netHeatFlux, SWHeatFlux,
11 I bi, bj, myTime, myIter, myThid )
12 C /================================================================\
13 C | SUBROUTINE seaice_budget_ocean |
14 C | o Calculate surface heat fluxes over open ocean |
15 C | see Hibler, MWR, 108, 1943-1973, 1980 |
16 C | If SEAICE_EXTERNAL_FLUXES is defined this routine simply |
17 C | simply copies the global fields to the seaice-local fields. |
18 C |================================================================|
19 C \================================================================/
20 IMPLICIT NONE
21
22 C === Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "FFIELDS.h"
26 #include "SEAICE_PARAMS.h"
27 #ifdef SEAICE_VARIABLE_FREEZING_POINT
28 # include "DYNVARS.h"
29 #endif
30 #ifdef ALLOW_EXF
31 # include "EXF_OPTIONS.h"
32 # include "EXF_FIELDS.h"
33 #endif
34 #ifdef SEAICE_CLIM_AIR
35 COMMON/SEAICE_DYNVARS_1/AREA
36 _RL AREA (1-OLx:sNx+OLx,1-OLy:sNy+OLy,3,nSx,nSy)
37 #endif
38
39 C === Routine arguments ===
40 C INPUT:
41 C UG :: thermal wind of atmosphere
42 C TSURF :: surface temperature of ocean in Kelvin
43 C bi,bj :: loop indices
44 C myTime :: Simulation time
45 C myIter :: Simulation timestep number
46 C myThid :: Thread no. that called this routine.
47 C OUTPUT:
48 C netHeatFlux :: net surface heat flux over open water or under ice
49 C SWHeatFlux :: short wave heat flux over open water or under ice
50 _RL UG (1:sNx,1:sNy)
51 _RL TSURF (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
52 _RL netHeatFlux(1:sNx,1:sNy)
53 _RL SWHeatFlux (1:sNx,1:sNy)
54 _RL myTime
55 INTEGER bi, bj, myIter, myThid
56 CEndOfInterface
57
58 C === Local variables ===
59 C i,j - Loop counters
60 INTEGER i, j
61 #ifndef SEAICE_EXTERNAL_FLUXES
62 INTEGER ITER
63 _RL QS1, TB, D1, D1W, D3, TMELT
64 C effective conductivity of combined ice and snow
65 _RL effConduct
66 C specific humidity at ice surface
67 _RL qhIce
68 C powers of temperature
69 _RL t1, t2, t3, t4
70
71 C local copies of global variables
72 _RL tsurfLoc (1:sNx,1:sNy)
73 _RL atempLoc (1:sNx,1:sNy)
74 _RL lwdownLoc (1:sNx,1:sNy)
75 _RL ALB (1:sNx,1:sNy)
76 C coefficients of Hibler (1980), appendix B
77 _RL A1 (1:sNx,1:sNy)
78 _RL A2 (1:sNx,1:sNy)
79 C auxiliary variable
80 _RL B (1:sNx,1:sNy)
81
82 #ifdef SEAICE_CLIM_AIR
83 _RL aqhLoc (1:sNx,1:sNy)
84 _RL fac
85 logical first, changed
86 integer count0, count1
87
88 C-- Compute indices and weights for seasonal interpolation
89 call cal_GetMonthsRec(
90 O fac, first, changed,
91 O count0, count1,
92 I mytime, myiter, mythid
93 & )
94 #endif /* SEAICE_CLIM_AIR */
95
96 C NOW DEFINE ASSORTED CONSTANTS
97 C SATURATION VAPOR PRESSURE CONSTANT
98 QS1=0.622 _d +00/1013.0 _d +00
99 C FREEZING TEMPERATURE OF SEAWATER
100 TB=271.2 _d +00
101 C SENSIBLE HEAT CONSTANT
102 D1=SEAICE_sensHeat
103 C WATER LATENT HEAT CONSTANT
104 D1W=SEAICE_latentWater
105 C STEFAN BOLTZMAN CONSTANT TIMES 0.97 EMISSIVITY
106 D3=SEAICE_emissivity
107 C MELTING TEMPERATURE OF ICE
108 TMELT=273.16 _d +00
109
110 DO J=1,sNy
111 DO I=1,sNx
112 netHeatFlux(I,J) = 0. _d 0
113 SWHeatFlux (I,J) = 0. _d 0
114 C
115 tsurfLoc (I,J) = MIN(273.16 _d 0+MAX_TICE,TSURF(I,J,bi,bj))
116 # ifdef ALLOW_ATM_TEMP
117 C Is this necessary?
118 atempLoc (I,J) = MAX(273.16 _d 0+MIN_ATEMP,ATEMP(I,J,bi,bj))
119 # endif
120 #ifdef SEAICE_CLIM_AIR
121 atempLoc (I,J) = AREA(I,J,1,bi,bj) *
122 & ( fac * SEAICE_clim_atemp(count0) + (1-fac) *
123 & SEAICE_clim_atemp(count1) ) +
124 & (1-AREA(I,J,1,bi,bj)) * atempLoc(I,J)
125 aqhLoc (I,J) = AREA(I,J,1,bi,bj) *
126 & ( fac * SEAICE_clim_aqh(count0) + (1-fac) *
127 & SEAICE_clim_aqh(count1) ) +
128 & (1-AREA(I,J,1,bi,bj)) * aqh(I,J,bi,bj)
129 #endif /* SEAICE_CLIM_AIR */
130 # ifdef ALLOW_DOWNWARD_RADIATION
131 lwdownLoc(I,J) = MAX(MIN_LWDOWN,LWDOWN(I,J,bi,bj))
132 # endif
133 ENDDO
134 ENDDO
135 #endif /* SEAICE_EXTERNAL_FLUXES */
136
137 C NOW DETERMINE OPEN WATER HEAT BUD. ASSUMING TSURF=WATER TEMP.
138 C WATER ALBEDO IS ASSUMED TO BE THE CONSTANT SEAICE_waterAlbedo
139 DO J=1,sNy
140 DO I=1,sNx
141 #ifdef SEAICE_EXTERNAL_FLUXES
142 netHeatFlux(I,J) = Qnet(I,J,bi,bj)
143 SWHeatFlux (I,J) = Qsw(I,J,bi,bj)
144 #else /* SEAICE_EXTERNAL_FLUXES undefined */
145 ALB(I,J)=SEAICE_waterAlbedo
146 # ifdef ALLOW_DOWNWARD_RADIATION
147 # ifdef SEAICE_CLIM_AIR
148 A1(I,J)=(ONE-ALB(I,J))*SWDOWN(I,J,bi,bj)
149 & +lwdownLoc(I,J)*0.97 _d 0
150 & +D1*UG(I,J)*atempLoc(I,J)+D1W*UG(I,J)*aqhLoc (I,J)
151 #else
152 A1(I,J)=(ONE-ALB(I,J))*SWDOWN(I,J,bi,bj)
153 & +lwdownLoc(I,J)*0.97 _d 0
154 & +D1*UG(I,J)*atempLoc(I,J)+D1W*UG(I,J)*AQH(I,J,bi,bj)
155 #endif /* SEAICE_CLIM_AIR */
156 B(I,J)=QS1*6.11 _d +00*EXP(17.2694 _d +00
157 & *(tsurfLoc(I,J)-TMELT)
158 & /(tsurfLoc(I,J)-TMELT+237.3 _d +00))
159 A2(I,J)=-D1*UG(I,J)*tsurfLoc(I,J)-D1W*UG(I,J)*B(I,J)
160 & -D3*(tsurfLoc(I,J)**4)
161 netHeatFlux(I,J)=-A1(I,J)-A2(I,J)
162 SWHeatFlux (I,J)=-(ONE-ALB(I,J))*SWDOWN(I,J,bi,bj)
163 # endif /* ALLOW_DOWNWARD_RADIATION */
164 #endif /* SEAICE_EXTERNAL_FLUXES */
165 ENDDO
166 ENDDO
167
168 RETURN
169 END

  ViewVC Help
Powered by ViewVC 1.1.22