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

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

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


Revision 1.23 - (show annotations) (download)
Wed Sep 11 20:19:11 2013 UTC (10 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64o, HEAD
Changes since 1.22: +10 -26 lines
- move bi,bj loops inside atm_store_my_data.F and store also wind-stress;
  update accordingly + simplify aim_do_physics.F

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_do_physics.F,v 1.22 2013/05/02 20:10:14 jmc Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: AIM_DO_PHYSICS
8 C !INTERFACE:
9 SUBROUTINE AIM_DO_PHYSICS( myTime, myIter, myThid )
10
11 C !DESCRIPTION: \bv
12 C *==================================================================*
13 C | S/R AIM_DO_PHYSICS
14 C *==================================================================*
15 C | Interface between atmospheric physics package and the
16 C | dynamical model.
17 C | Routine calls physics pacakge after setting surface BC.
18 C | Package should derive and set tendency terms
19 C | which can be included as external forcing terms in the dynamical
20 C | tendency routines. Packages should communicate this information
21 C | through common blocks.
22 C *==================================================================*
23 C \ev
24
25 C !USES:
26 IMPLICIT NONE
27
28 C -------------- Global variables ------------------------------------
29 C-- size for MITgcm & Physics package :
30 #include "AIM_SIZE.h"
31
32 C-- MITgcm
33 #include "EEPARAMS.h"
34 #include "PARAMS.h"
35 #include "DYNVARS.h"
36 #include "GRID.h"
37 #include "SURFACE.h"
38
39 C-- Physics package
40 #include "AIM_PARAMS.h"
41 #include "AIM_FFIELDS.h"
42 #include "AIM_GRID.h"
43 #include "com_physvar.h"
44 #include "com_forcing.h"
45 #include "AIM2DYN.h"
46
47 C !INPUT/OUTPUT PARAMETERS:
48 C == Routine arguments ==
49 C myTime :: Current time in simulation (s)
50 C myIter :: Current iteration number
51 C myThid :: My Thread Id. number
52 _RL myTime
53 INTEGER myIter
54 INTEGER myThid
55 CEOP
56
57 #ifdef ALLOW_AIM
58 C !FUNCTIONS:
59 C !LOCAL VARIABLES:
60 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61 C-- Local Variables originally (Speedy) in common bloc (com_forcing.h):
62 C-- COMMON /FORFIX/ Time invariant forcing fields (initialise in INFORC)
63 C phi0 :: surface geopotential
64 _RL phi0 (NGP)
65 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
66 C == Local variables ==
67 C bi,bj :: Tile indices
68 C i,j,k,I2 :: Loop counters
69 C tYear :: Fraction into year
70 C aim_sWght0 :: weight for time interpolation of surface BC
71 C aim_sWght1 :: 0/1 = time period before/after the current time
72 C prcAtm :: total precip from the atmosphere [kg/m2/s]
73 C snowPr :: snow precipitation [kg/m2/s]
74 INTEGER bi,bj
75 INTEGER i,j,k,I2
76 _RL tYear, yearLength
77 _RL aim_sWght0, aim_sWght1
78 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79 _RL snowPr(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80 #ifdef ALLOW_THSICE
81 _RL qPrcRn(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82 #endif
83
84 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
85
86 #ifdef ALLOW_AIM_CO2
87 CALL AIM_DO_CO2( myTime, myIter, myThid )
88 #endif
89
90 C-- Start loops on tile indices
91 DO bj=myByLo(myThid),myByHi(myThid)
92 DO bi=myBxLo(myThid),myBxHi(myThid)
93
94 C_jmc: Because AIM physics LSC is not applied in the stratosphere (top level),
95 C ==> move water wapor from the stratos to the surface level.
96 DO j = 1-OLy, sNy+OLy
97 DO i = 1-OLx, sNx+OLx
98 k = kSurfC(i,j,bi,bj)
99 IF (k.LE.Nr)
100 & salt(i,j,k,bi,bj) = salt(i,j,k,bi,bj)
101 & + salt(i,j,Nr,bi,bj)*drF(Nr)*recip_drF(k)
102 & *hFacC(i,j,Nr,bi,bj)*recip_hFacC(i,j,k,bi,bj)
103 salt(i,j,Nr,bi,bj) = 0.
104 ENDDO
105 ENDDO
106
107 #ifdef OLD_THSICE_CALL_SEQUENCE
108 #ifdef ALLOW_THSICE
109 IF ( useThSIce ) THEN
110 C- do sea-ice advection before setting any surface BC.
111 CALL THSICE_DO_ADVECT(
112 I bi, bj, myTime, myIter, myThid )
113 ENDIF
114 #endif /* ALLOW_THSICE */
115 #endif /* OLD_THSICE_CALL_SEQUENCE */
116
117 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
118
119 C- Physics package needs to know time of year as a fraction
120 yearLength = 86400.*360.
121 tYear = MOD(myTime/yearLength, 1. _d 0)
122
123 C-- Set surface Boundary Conditions for atmos. physics package:
124 C (Albedo, Soil moisture, Surf Temp, Land sea mask)
125 C includes some parts of S/R FORDATE from F.Molteni SPEDDY code (ver23)
126 CALL AIM_SURF_BC(
127 U tYear,
128 O aim_sWght0, aim_sWght1,
129 I bi, bj, myTime, myIter, myThid )
130
131 C-- Set surface geopotential: (g * orographic height)
132 DO j=1,sNy
133 DO i=1,sNx
134 I2 = i+(j-1)*sNx
135 PHI0(I2) = gravity*topoZ(i,j,bi,bj)
136 ENDDO
137 ENDDO
138
139 C-- Set topographic dependent FOROG var (originally in common SFLFIX);
140 C used to compute for wind stress over land
141
142 c_FM IF (IDAY.EQ.0) THEN
143 c_FM CALL SFLSET (PHIS0)
144 CALL SFLSET (PHI0, fOrogr(1,myThid), bi,bj,myThid)
145 c_FM ENDIF
146 c_FM CALL SOL_OZ (SOLC,TYEAR)
147
148 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
149
150 C- Compute atmospheric-physics tendencies (call the main AIM S/R)
151 CALL PHY_DRIVER( tYear, useDiagnostics,
152 I bi, bj, myTime, myIter, myThid )
153
154 CALL AIM_AIM2DYN( bi, bj, myTime, myIter, myThid )
155
156 #ifdef ALLOW_LAND
157 IF (useLand) THEN
158 C- prepare Surface flux over land for land package
159 CALL AIM_AIM2LAND( aim_landFr, bi, bj,
160 I myTime, myIter, myThid )
161
162 C- Step forward land model
163 CALL LAND_STEPFWD( aim_landFr, bi, bj,
164 I myTime, myIter, myThid )
165
166 C- Land diagnostics : write snap-shot & cumulate for TimeAve output
167 CALL LAND_DO_DIAGS( aim_landFr, bi, bj,
168 I myTime, myIter, myThid )
169
170 ENDIF
171 #endif /* ALLOW_LAND */
172
173 C- surface fluxes over ocean (ice-free & ice covered)
174 C used for diagnostics, thsice package and coupler
175 CALL AIM_AIM2SIOCE( aim_landFr, fmask1(1,3,myThid),
176 O prcAtm, snowPr,
177 I bi, bj, myTime, myIter, myThid )
178
179 #ifdef ALLOW_THSICE
180 IF ( useThSIce ) THEN
181 C- Step forward sea-ice model
182 DO j = 1-OLy, sNy+OLy
183 DO i = 1-OLx, sNx+OLx
184 qPrcRn(i,j) = 0.
185 ENDDO
186 ENDDO
187 CALL THSICE_STEP_FWD( bi, bj, 1, sNx, 1, sNy,
188 I prcAtm, snowPr, qPrcRn,
189 I myTime, myIter, myThid )
190 ENDIF
191 #endif /* ALLOW_THSICE */
192
193 C- AIM diagnostics : write snap-shot & cumulate for TimeAve output
194 CALL AIM_DIAGNOSTICS( bi, bj, myTime, myIter, myThid )
195
196 C-- end bi,bj loops.
197 ENDDO
198 ENDDO
199
200 #ifdef ALLOW_THSICE
201 IF ( useThSIce ) THEN
202
203 #ifndef OLD_THSICE_CALL_SEQUENCE
204 C-- Exchange fields that are advected by seaice dynamics
205 CALL THSICE_DO_EXCH( myThid )
206 C- do sea-ice advection after sea-ice thermodynamics
207 CALL THSICE_DO_ADVECT(
208 I 0, 0, myTime, myIter, myThid )
209 #endif /* ndef OLD_THSICE_CALL_SEQUENCE */
210
211 DO bj=myByLo(myThid),myByHi(myThid)
212 DO bi=myBxLo(myThid),myBxHi(myThid)
213 C- Slab Ocean : step forward ocean mixed-layer temp. & salinity
214 CALL THSICE_SLAB_OCEAN(
215 I aim_sWght0, aim_sWght1,
216 O dTsurf(1,2,myThid),
217 I bi, bj, myTime, myIter, myThid )
218 ENDDO
219 ENDDO
220
221 ENDIF
222 #endif /* ALLOW_THSICE */
223
224 C-- do exchanges for AIM related quantities:
225 _EXCH_XY_RL( aim_drag, myThid )
226
227 #ifdef OLD_THSICE_CALL_SEQUENCE
228 #ifdef ALLOW_THSICE
229 IF (useThSIce) THEN
230 C-- Exchange fields that are advected by seaice dynamics
231 CALL THSICE_DO_EXCH( myThid )
232 ENDIF
233 #endif
234 #endif /* OLD_THSICE_CALL_SEQUENCE */
235
236 #ifdef COMPONENT_MODULE
237 IF ( useCoupler ) THEN
238 CALL ATM_STORE_MY_DATA( myTime, myIter, myThid )
239 ENDIF
240 #endif /* COMPONENT_MODULE */
241
242 #endif /* ALLOW_AIM */
243
244 RETURN
245 END

  ViewVC Help
Powered by ViewVC 1.1.22