/[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.1 - (show annotations) (download)
Sun Apr 18 21:38:40 2004 UTC (20 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53b_pre, checkpoint52m_post, checkpoint53a_post, checkpoint53b_post, checkpoint53
AIM_AIM2SIOCE is a general (AIM)interface for ocean (ice-free and ice
 covered) and replaces S/R AIM_AIM2SICE (for sea-ice only).

1 C $Header: $
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,
14 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 #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 !INPUT/OUTPUT PARAMETERS:
50 C == Routine arguments ==
51 C land_frc :: land fraction [0-1]
52 C prcAtm :: total precip from the atmosphere [kg/m2/s]
53 C evpAtm :: evaporation to the atmosphere [kg/m2/s] (>0 if evaporate)
54 C flxSW :: net heat flux from the ice to the ocean
55 C bi,bj :: Tile index
56 C myTime :: Current time of simulation ( s )
57 C myIter :: Current iteration number in simulation
58 C myThid :: Number of this instance of the routine
59 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
60 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62 _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63 INTEGER bi, bj, myIter, myThid
64 _RL myTime
65 CEOP
66
67 #ifdef ALLOW_AIM
68 C == Local variables ==
69 C i,j,I2 :: loop counters
70 C conv_precip :: conversion factor for precip: from g/m2/s to kg/m2/s
71 C conv_EmP :: conversion factor for EmP : from g/m2/s to m/s
72 _RL conv_precip, conv_EmP
73 _RL icFrac, opFrac
74 INTEGER i,j,I2
75
76 C-- Initialisation :
77
78 C-- Atmospheric Physics Fluxes
79
80 c IF ( useLand ) THEN
81
82 C from g/m2/s to kg/m2/s :
83 conv_Precip = 1. _d -3
84 C from g/m2/s to m/s :
85 conv_EmP = conv_Precip / rhoConstFresh
86 #ifdef ALLOW_THSICE
87 IF (useThSIce) conv_EmP = conv_Precip / rhofw
88 #endif
89
90 DO j=1,sNy
91 DO i=1,sNx
92 I2 = i+(j-1)*sNx
93
94 C- Total Precip :
95 prcAtm(i,j) = ( PRECNV(I2,myThid)
96 & + PRECLS(I2,myThid) )
97
98 C- Net surface heat flux over ice-free ocean (+=down)
99 Qnet(i,j,bi,bj) =
100 & SSR(I2,2,myThid)
101 & - SLR(I2,2,myThid)
102 & - SHF(I2,2,myThid)
103 & - EVAP(I2,2,myThid)*ALHC
104
105 C- E-P over ice-free ocean [m/s]:
106 EmPmR(i,j,bi,bj) = ( EVAP(I2,2,myThid)
107 & - prcAtm(i,j) ) * conv_EmP
108
109 C- Net short wave (ice-free ocean) into the ocean (+=down)
110 flxSW(i,j) = Qsw(i,j,bi,bj)
111 Qsw(i,j,bi,bj) = SSR(I2,2,myThid)
112
113 ENDDO
114 ENDDO
115
116 IF ( aim_energPrecip ) THEN
117 C-- Add energy flux related to Precip. (snow, T_rain) over ice-free ocean
118 DO j=1,sNy
119 DO i=1,sNx
120 I2 = i+(j-1)*sNx
121 Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj)
122 & + EnPrec(I2,myThid)*prcAtm(i,j)
123 ENDDO
124 ENDDO
125 ENDIF
126
127 #ifdef ALLOW_THSICE
128 IF ( useThSIce ) THEN
129 DO j=1,sNy
130 DO i=1,sNx
131 I2 = i+(j-1)*sNx
132 C- Mixed-Layer Ocean:
133 IF (land_frc(i,j,bi,bj).EQ.1. _d 0) hOceMxL(i,j,bi,bj) = 0.
134
135 C- Evaporation over sea-ice:
136 evpAtm(i,j) = EVAP(I2,3,myThid)*conv_precip
137
138 C- short-wave downward heat flux (open ocean + ice-covered):
139 icFrac = iceMask(i,j,bi,bj)
140 opFrac = 1. _d 0 - icFrac
141 Qsw(i,j,bi,bj) = icFrac*flxSW(i,j) + opFrac*Qsw(i,j,bi,bj)
142
143 ENDDO
144 ENDDO
145 ENDIF
146
147 IF ( useThSIce .AND. aim_energPrecip ) THEN
148 C-- Add energy flux related to Precip. (snow, T_rain) over sea-ice
149 DO j=1,sNy
150 DO i=1,sNx
151 IF ( iceMask(i,j,bi,bj).GT.0. _d 0 ) THEN
152 I2 = i+(j-1)*sNx
153 IF ( EnPrec(I2,myThid).GE.0. _d 0 ) THEN
154 C- positive => add to surface heating
155 sHeating(i,j,bi,bj) = sHeating(i,j,bi,bj)
156 & + EnPrec(I2,myThid)*prcAtm(i,j)
157 ELSE
158 C- negative => make snow
159 snowPrc(i,j,bi,bj) = prcAtm(i,j)*conv_precip
160 ENDIF
161 ENDIF
162 ENDDO
163 ENDDO
164 ENDIF
165 #endif /* ALLOW_THSICE */
166
167 DO j=1,sNy
168 DO i=1,sNx
169 C- Total Precip : convert units
170 prcAtm(i,j) = prcAtm(i,j) * conv_precip
171 C- Oceanic convention: Heat flux are > 0 upward ; reverse sign.
172 Qsw(i,j,bi,bj) = -Qsw(i,j,bi,bj)
173 Qnet(i,j,bi,bj)= -Qnet(i,j,bi,bj)
174 ENDDO
175 ENDDO
176
177 #endif /* ALLOW_AIM */
178
179 RETURN
180 END

  ViewVC Help
Powered by ViewVC 1.1.22