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

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

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


Revision 1.7 - (show annotations) (download)
Wed Apr 4 02:00:36 2007 UTC (17 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint59, checkpoint58y_post
Changes since 1.6: +4 -3 lines
Masking of oceanic mixed layer (using land-fraction):
  moved much earlier, from S/R AIM_AIM2SIOCE to S/R THSICE_INI_VARS.

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_aim2sioce.F,v 1.6 2006/06/02 01:59:48 jmc Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5 #ifdef ALLOW_THSICE
6 #include "THSICE_OPTIONS.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: AIM_AIM2SIOCE
11 C !INTERFACE:
12 SUBROUTINE AIM_AIM2SIOCE(
13 I land_frc, siceFrac,
14 O prcAtm,
15 I bi, bj, myTime, myIter, myThid)
16
17 C !DESCRIPTION: \bv
18 C *==========================================================*
19 C | S/R AIM_AIM2SIOCE
20 C | o Interface between AIM and thSIce pkg or (coupled) ocean
21 C *==========================================================*
22 C | o compute surface fluxes over ocean (ice-free + ice covered)
23 C | for diagnostics, thsice package and (slab, coupled) ocean
24 C *==========================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29
30 C == Global variables ===
31 C-- size for MITgcm & Physics package :
32 #include "AIM_SIZE.h"
33
34 #include "EEPARAMS.h"
35 #include "PARAMS.h"
36 #include "FFIELDS.h"
37
38 C-- Physics package
39 #include "AIM_PARAMS.h"
40 #include "com_physcon.h"
41 #include "com_physvar.h"
42
43 #ifdef ALLOW_THSICE
44 #include "THSICE_SIZE.h"
45 #include "THSICE_PARAMS.h"
46 #include "THSICE_VARS.h"
47 #endif
48
49 C updated fields (in commom blocks):
50 C if using thSIce:
51 C Qsw(inp) :: SW radiation through the sea-ice down to the ocean (+=up)
52 C Qsw(out) :: SW radiation down to the ocean (ice-free + ice-covered)(+=up)
53 C Qnet(out) :: Net heat flux out of the ocean (ice-free ocean only)(+=up)
54 C and the Ice-Covered contribution will be added in S/R THSICE_STEP_FWD
55 C EmPmR(out) :: Net fresh water flux out off the ocean (ice-free ocean only)
56 C and the Ice-Covered contribution will be added in S/R THSICE_STEP_FWD
57 C sHeating(in/out) :: air - seaice surface heat flux left to melt the ice
58 C snowPrc(out):: snow precip over sea-ice
59 C icFrwAtm :: Evaporation over sea-ice [kg/m2/s] (>0 if evaporate)
60 C icFlxSW :: net SW heat flux through the ice to the ocean [W/m2] (+=dw)
61 C if not using thSIce:
62 C Qsw(out) :: SW radiation down to the ocean (ice-free + ice-covered)(+=up)
63 C Qnet(out) :: Net heat flux out of the ocean (ice-free + ice-covered)(+=up)
64 C EmPmR(out) :: Net fresh water flux out off the ocean (ice-free + ice-covered)
65
66 C !INPUT/OUTPUT PARAMETERS:
67 C == Routine arguments ==
68 C land_frc :: land fraction [0-1]
69 C siceFrac :: sea-ice fraction (relative to full grid-cell) [0-1]
70 C prcAtm :: total precip from the atmosphere [kg/m2/s]
71 C bi,bj :: Tile indices
72 C myTime :: Current time of simulation ( s )
73 C myIter :: Current iteration number in simulation
74 C myThid :: My Thread Id number
75 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
76 _RL siceFrac(sNx,sNy)
77 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 INTEGER bi, bj, myIter, myThid
79 _RL myTime
80 CEOP
81
82 #ifdef ALLOW_AIM
83 C == Local variables ==
84 C i,j,I2 :: loop counters
85 C conv_precip :: conversion factor for precip: from g/m2/s to kg/m2/s
86 C conv_EmP :: conversion factor for EmP : from g/m2/s to m/s
87 _RL conv_precip, conv_EmP
88 _RL icFrac, opFrac
89 INTEGER i,j,I2
90
91 C-- Initialisation :
92
93 C-- Atmospheric Physics Fluxes
94
95 C from g/m2/s to kg/m2/s :
96 conv_Precip = 1. _d -3
97 C from g/m2/s to m/s :
98 conv_EmP = conv_Precip / rhoConstFresh
99 #ifdef ALLOW_THSICE
100 IF (useThSIce) conv_EmP = conv_Precip / rhofw
101 #endif
102
103 DO j=1,sNy
104 DO i=1,sNx
105 IF ( land_frc(i,j,bi,bj).GE.1. _d 0 ) THEN
106 C- Full Land grid-cell: set all fluxes to zero (this has no effect on the
107 C model integration and just put this to get meaningfull diagnostics)
108 prcAtm(i,j) = 0. _d 0
109 Qnet(i,j,bi,bj) = 0. _d 0
110 EmPmR(i,j,bi,bj)= 0. _d 0
111 Qsw(i,j,bi,bj) = 0. _d 0
112 ELSE
113 I2 = i+(j-1)*sNx
114
115 C- Total Precip (no distinction between ice-covered / ice-free fraction):
116 prcAtm(i,j) = ( PRECNV(I2,myThid)
117 & + PRECLS(I2,myThid) )
118
119 C- Net surface heat flux over ice-free ocean (+=down)
120 C note: with aim_splitSIOsFx=F, ice-free & ice covered contribution are
121 C already merged together and Qnet is the mean heat flux over the grid box.
122 Qnet(i,j,bi,bj) =
123 & SSR(I2,2,myThid)
124 & - SLR(I2,2,myThid)
125 & - SHF(I2,2,myThid)
126 & - EVAP(I2,2,myThid)*ALHC
127
128 C- E-P over ice-free ocean [m/s]: (same as above is aim_splitSIOsFx=F)
129 EmPmR(i,j,bi,bj) = ( EVAP(I2,2,myThid)
130 & - prcAtm(i,j) ) * conv_EmP
131
132 C- Net short wave (ice-free ocean) into the ocean (+=down)
133 Qsw(i,j,bi,bj) = SSR(I2,2,myThid)
134
135 ENDIF
136 ENDDO
137 ENDDO
138
139 #ifdef ALLOW_THSICE
140 IF ( useThSIce ) THEN
141 DO j=1,sNy
142 DO i=1,sNx
143 I2 = i+(j-1)*sNx
144 C- Mixed-Layer Ocean: (for thsice slab_ocean and coupler)
145 C NOTE: masking is now applied much earlier, during initialisation
146 c IF (land_frc(i,j,bi,bj).EQ.1. _d 0) hOceMxL(i,j,bi,bj) = 0.
147
148 C- Evaporation over sea-ice: (for thsice)
149 icFrwAtm(i,j,bi,bj) = EVAP(I2,3,myThid)*conv_precip
150
151 C- short-wave downward heat flux (ice-free ocean + ice-covered):
152 C note: at this point we already called THSICE_IMPL_TEMP to solve for
153 C seaice temp and SW flux through the ice. SW is not modified after, and
154 C can therefore combine the open-ocean & ice-covered ocean SW fluxes.
155 icFrac = iceMask(i,j,bi,bj)
156 opFrac = 1. _d 0 - icFrac
157 Qsw(i,j,bi,bj) = icFrac*icFlxSW(i,j,bi,bj)
158 & + opFrac*Qsw(i,j,bi,bj)
159
160 ENDDO
161 ENDDO
162
163 IF ( aim_energPrecip ) THEN
164 C-- Add energy flux related to Precip. (snow, T_rain) over sea-ice
165 DO j=1,sNy
166 DO i=1,sNx
167 IF ( iceMask(i,j,bi,bj).GT.0. _d 0 ) THEN
168 I2 = i+(j-1)*sNx
169 IF ( EnPrec(I2,myThid).GE.0. _d 0 ) THEN
170 C- positive => add to surface heating
171 sHeating(i,j,bi,bj) = sHeating(i,j,bi,bj)
172 & + EnPrec(I2,myThid)*prcAtm(i,j)
173 snowPrc(i,j,bi,bj) = 0. _d 0
174 ELSE
175 C- negative => make snow
176 snowPrc(i,j,bi,bj) = prcAtm(i,j)*conv_precip
177 ENDIF
178 ELSE
179 snowPrc(i,j,bi,bj) = 0. _d 0
180 ENDIF
181 ENDDO
182 ENDDO
183 ENDIF
184
185 ELSEIF ( aim_splitSIOsFx ) THEN
186 #else /* ALLOW_THSICE */
187 IF ( aim_splitSIOsFx ) THEN
188 #endif /* ALLOW_THSICE */
189 C- aim_splitSIOsFx=T: fluxes over sea-ice (3) & ice-free ocean (2) were
190 C computed separately and here we merge the 2 fractions
191 DO j=1,sNy
192 DO i=1,sNx
193 I2 = i+(j-1)*sNx
194 IF ( siceFrac(i,j) .GT. 0. ) THEN
195 icFrac = siceFrac(i,j)/(1. _d 0 - land_frc(i,j,bi,bj))
196 opFrac = 1. _d 0 - icFrac
197
198 C- Net surface heat flux over sea-ice + ice-free ocean (+=down)
199 Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj)*opFrac
200 & + ( SSR(I2,3,myThid)
201 & - SLR(I2,3,myThid)
202 & - SHF(I2,3,myThid)
203 & - EVAP(I2,3,myThid)*ALHC
204 & )*icFrac
205 C- E-P over sea-ice + ice-free ocean [m/s]:
206 EmPmR(i,j,bi,bj) = EmPmR(i,j,bi,bj)*opFrac
207 & + ( EVAP(I2,3,myThid)
208 & - prcAtm(i,j) ) * conv_EmP * icFrac
209
210 C- Net short wave (ice-free ocean) into the ocean (+=down)
211 Qsw(i,j,bi,bj) = opFrac*Qsw(i,j,bi,bj)
212 & + icFrac*SSR(I2,3,myThid)
213
214 ENDIF
215 ENDDO
216 ENDDO
217
218 C-- end of If useThSIce / elseif aim_splitSIOsFx blocks
219 ENDIF
220
221 IF ( aim_energPrecip ) THEN
222 C-- Ice free fraction: Add energy flux related to Precip. (snow, T_rain):
223 DO j=1,sNy
224 DO i=1,sNx
225 I2 = i+(j-1)*sNx
226 Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj)
227 & + EnPrec(I2,myThid)*prcAtm(i,j)
228 ENDDO
229 ENDDO
230 ENDIF
231
232 DO j=1,sNy
233 DO i=1,sNx
234 C- Total Precip : convert units
235 prcAtm(i,j) = prcAtm(i,j) * conv_precip
236 C- Oceanic convention: Heat flux are > 0 upward ; reverse sign.
237 Qsw(i,j,bi,bj) = -Qsw(i,j,bi,bj)
238 Qnet(i,j,bi,bj)= -Qnet(i,j,bi,bj)
239 ENDDO
240 ENDDO
241
242 #endif /* ALLOW_AIM */
243
244 RETURN
245 END

  ViewVC Help
Powered by ViewVC 1.1.22