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

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

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


Revision 1.3 - (hide annotations) (download)
Mon Mar 13 04:09:26 2006 UTC (18 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58b_post
Changes since 1.2: +60 -35 lines
- fix bug related to sign of Short-Wave flux through the ice
- fix bug (if useThSIce but not aim_energPrecip)
- improve description (updated variables in common blocks)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_aim2sioce.F,v 1.2 2004/05/21 17:34:16 jmc Exp $
2 jmc 1.1 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 jmc 1.2 I land_frc, siceFrac,
14 jmc 1.1 O prcAtm, evpAtm, flxSW,
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 jmc 1.3 #include "AIM_SIZE.h"
33 jmc 1.1
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 jmc 1.3 #include "THSICE_SIZE.h"
45 jmc 1.1 #include "THSICE_PARAMS.h"
46     #include "THSICE_VARS.h"
47     #endif
48    
49 jmc 1.3 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 if not using thSIce:
60     C Qsw(out) :: SW radiation down to the ocean (ice-free + ice-covered)(+=up)
61     C Qnet(out) :: Net heat flux out of the ocean (ice-free + ice-covered)(+=up)
62     C EmPmR(out) :: Net fresh water flux out off the ocean (ice-free + ice-covered)
63    
64 jmc 1.1 C !INPUT/OUTPUT PARAMETERS:
65     C == Routine arguments ==
66     C land_frc :: land fraction [0-1]
67 jmc 1.2 C siceFrac :: sea-ice fraction (relative to full grid-cell) [0-1]
68 jmc 1.1 C prcAtm :: total precip from the atmosphere [kg/m2/s]
69 jmc 1.3 C evpAtm :: Evaporation over sea-ice [kg/m2/s] (>0 if evaporate)
70     C flxSW :: net SW heat flux through the ice to the ocean [W/m2] (+=dw)
71 jmc 1.1 C bi,bj :: Tile index
72     C myTime :: Current time of simulation ( s )
73     C myIter :: Current iteration number in simulation
74 jmc 1.3 C myThid :: My Thread Id number
75 jmc 1.1 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
76 jmc 1.2 _RL siceFrac(sNx,sNy)
77 jmc 1.1 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78     _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79     _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80     INTEGER bi, bj, myIter, myThid
81     _RL myTime
82     CEOP
83    
84     #ifdef ALLOW_AIM
85     C == Local variables ==
86     C i,j,I2 :: loop counters
87     C conv_precip :: conversion factor for precip: from g/m2/s to kg/m2/s
88     C conv_EmP :: conversion factor for EmP : from g/m2/s to m/s
89     _RL conv_precip, conv_EmP
90     _RL icFrac, opFrac
91     INTEGER i,j,I2
92    
93     C-- Initialisation :
94    
95     C-- Atmospheric Physics Fluxes
96    
97 jmc 1.2 C from g/m2/s to kg/m2/s :
98     conv_Precip = 1. _d -3
99     C from g/m2/s to m/s :
100 jmc 1.3 conv_EmP = conv_Precip / rhoConstFresh
101 jmc 1.1 #ifdef ALLOW_THSICE
102 jmc 1.3 IF (useThSIce) conv_EmP = conv_Precip / rhofw
103 jmc 1.1 #endif
104    
105     DO j=1,sNy
106     DO i=1,sNx
107     I2 = i+(j-1)*sNx
108    
109 jmc 1.3 C- Total Precip (no distinction between ice-covered / ice-free fraction):
110 jmc 1.1 prcAtm(i,j) = ( PRECNV(I2,myThid)
111     & + PRECLS(I2,myThid) )
112    
113     C- Net surface heat flux over ice-free ocean (+=down)
114 jmc 1.3 C note: with aim_splitSIOsFx=F, ice-free & ice covered contribution are
115     C already merged together and Qnet is the mean heat flux over the grid box.
116     Qnet(i,j,bi,bj) =
117 jmc 1.1 & SSR(I2,2,myThid)
118     & - SLR(I2,2,myThid)
119     & - SHF(I2,2,myThid)
120     & - EVAP(I2,2,myThid)*ALHC
121    
122 jmc 1.3 C- E-P over ice-free ocean [m/s]: (same as above is aim_splitSIOsFx=F)
123 jmc 1.1 EmPmR(i,j,bi,bj) = ( EVAP(I2,2,myThid)
124     & - prcAtm(i,j) ) * conv_EmP
125    
126 jmc 1.3 C- Transfert SW flux at the base of the sea-ice, from Qsw(+=up) to flxSW (+=dw)
127     flxSW(i,j) = -Qsw(i,j,bi,bj)
128 jmc 1.1 C- Net short wave (ice-free ocean) into the ocean (+=down)
129     Qsw(i,j,bi,bj) = SSR(I2,2,myThid)
130    
131     ENDDO
132     ENDDO
133    
134     #ifdef ALLOW_THSICE
135     IF ( useThSIce ) THEN
136     DO j=1,sNy
137     DO i=1,sNx
138     I2 = i+(j-1)*sNx
139 jmc 1.3 C- Mixed-Layer Ocean: (for thsice slab_ocean and coupler)
140 jmc 1.1 IF (land_frc(i,j,bi,bj).EQ.1. _d 0) hOceMxL(i,j,bi,bj) = 0.
141    
142 jmc 1.3 C- Evaporation over sea-ice: (for thsice)
143 jmc 1.1 evpAtm(i,j) = EVAP(I2,3,myThid)*conv_precip
144    
145 jmc 1.3 C- short-wave downward heat flux (ice-free ocean + ice-covered):
146     C note: at this point we already called THSICE_IMPL_TEMP to solved for
147     C seaice temp and SW flux through the ice. SW is not modified after, and
148     C can therefore combine the open-ocean & ice-covered ocean SW fluxes.
149 jmc 1.1 icFrac = iceMask(i,j,bi,bj)
150     opFrac = 1. _d 0 - icFrac
151     Qsw(i,j,bi,bj) = icFrac*flxSW(i,j) + opFrac*Qsw(i,j,bi,bj)
152    
153     ENDDO
154     ENDDO
155    
156 jmc 1.3 IF ( aim_energPrecip ) THEN
157 jmc 1.1 C-- Add energy flux related to Precip. (snow, T_rain) over sea-ice
158 jmc 1.3 DO j=1,sNy
159     DO i=1,sNx
160     IF ( iceMask(i,j,bi,bj).GT.0. _d 0 ) THEN
161     I2 = i+(j-1)*sNx
162     IF ( EnPrec(I2,myThid).GE.0. _d 0 ) THEN
163 jmc 1.1 C- positive => add to surface heating
164 jmc 1.3 sHeating(i,j,bi,bj) = sHeating(i,j,bi,bj)
165     & + EnPrec(I2,myThid)*prcAtm(i,j)
166     snowPrc(i,j,bi,bj) = 0. _d 0
167     ELSE
168 jmc 1.1 C- negative => make snow
169 jmc 1.3 snowPrc(i,j,bi,bj) = prcAtm(i,j)*conv_precip
170     ENDIF
171     ELSE
172     snowPrc(i,j,bi,bj) = 0. _d 0
173     ENDIF
174     ENDDO
175     ENDDO
176     ENDIF
177    
178 jmc 1.2 ELSEIF ( aim_splitSIOsFx ) THEN
179     #else /* ALLOW_THSICE */
180     IF ( aim_splitSIOsFx ) THEN
181     #endif /* ALLOW_THSICE */
182 jmc 1.3 C- aim_splitSIOsFx=T: fluxes over sea-ice (3) & ice-free ocean (2) were
183     C computed separately and here we merge the 2 fractions
184 jmc 1.2 DO j=1,sNy
185     DO i=1,sNx
186     I2 = i+(j-1)*sNx
187     IF ( siceFrac(i,j) .GT. 0. ) THEN
188     icFrac = siceFrac(i,j)/(1. _d 0 - land_frc(i,j,bi,bj))
189     opFrac = 1. _d 0 - icFrac
190    
191     C- Net surface heat flux over sea-ice + ice-free ocean (+=down)
192     Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj)*opFrac
193     & + ( SSR(I2,3,myThid)
194     & - SLR(I2,3,myThid)
195     & - SHF(I2,3,myThid)
196     & - EVAP(I2,3,myThid)*ALHC
197     & )*icFrac
198     C- E-P over sea-ice + ice-free ocean [m/s]:
199     EmPmR(i,j,bi,bj) = EmPmR(i,j,bi,bj)*opFrac
200     & + ( EVAP(I2,3,myThid)
201     & - prcAtm(i,j) ) * conv_EmP * icFrac
202    
203     C- Net short wave (ice-free ocean) into the ocean (+=down)
204     Qsw(i,j,bi,bj) = opFrac*Qsw(i,j,bi,bj)
205     & + icFrac*SSR(I2,3,myThid)
206    
207 jmc 1.1 ENDIF
208     ENDDO
209     ENDDO
210 jmc 1.3
211     C-- end of If useThSIce / elseif aim_splitSIOsFx blocks
212 jmc 1.2 ENDIF
213    
214     IF ( aim_energPrecip ) THEN
215 jmc 1.3 C-- Ice free fraction: Add energy flux related to Precip. (snow, T_rain):
216 jmc 1.2 DO j=1,sNy
217     DO i=1,sNx
218     I2 = i+(j-1)*sNx
219     Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj)
220     & + EnPrec(I2,myThid)*prcAtm(i,j)
221     ENDDO
222     ENDDO
223 jmc 1.1 ENDIF
224    
225     DO j=1,sNy
226     DO i=1,sNx
227     C- Total Precip : convert units
228     prcAtm(i,j) = prcAtm(i,j) * conv_precip
229     C- Oceanic convention: Heat flux are > 0 upward ; reverse sign.
230     Qsw(i,j,bi,bj) = -Qsw(i,j,bi,bj)
231     Qnet(i,j,bi,bj)= -Qnet(i,j,bi,bj)
232     ENDDO
233     ENDDO
234    
235     #endif /* ALLOW_AIM */
236    
237     RETURN
238     END

  ViewVC Help
Powered by ViewVC 1.1.22