/[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.13 - (show annotations) (download)
Wed Apr 4 02:47:16 2007 UTC (17 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint59a, checkpoint59c, checkpoint59b
Changes since 1.12: +17 -7 lines
an atempt to add sea-ice thickness diffusion in AIM set-up.

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_do_physics.F,v 1.12 2006/10/18 20:08:15 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( bi, bj, 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
46 C !INPUT/OUTPUT PARAMETERS:
47 C == Routine arguments ==
48 C bi,bj :: Tile indices
49 C myTime :: Current time in simulation (s)
50 C myIter :: Current iteration number
51 C myThid :: My Thread Id. number
52 INTEGER bi,bj
53 _RL myTime
54 INTEGER myIter
55 INTEGER myThid
56 CEOP
57
58 #ifdef ALLOW_AIM
59 C == Local variables ==
60 C i,j,k,I2 :: Loop counters
61 C tYear :: Fraction into year
62 C aim_sWght0 :: weight for time interpolation of surface BC
63 C aim_sWght1 :: 0/1 = time period before/after the current time
64 C prcAtm :: total precip from the atmosphere [kg/m2/s]
65 INTEGER i,j,k,I2
66 _RL tYear, yearLength
67 _RL aim_sWght0, aim_sWght1
68 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69
70 C_jmc: Because AIM physics LSC is not applied in the stratosphere (top level),
71 C ==> move water wapor from the stratos to the surface level.
72 DO j = 1-Oly, sNy+Oly
73 DO i = 1-Olx, sNx+Olx
74 k = ksurfC(i,j,bi,bj)
75 IF (k.LE.Nr)
76 & salt(i,j,k,bi,bj) = salt(i,j,k,bi,bj)
77 & + salt(i,j,Nr,bi,bj)*drF(Nr)*recip_drF(k)
78 & *hFacC(i,j,Nr,bi,bj)*recip_hFacC(i,j,k,bi,bj)
79 salt(i,j,Nr,bi,bj) = 0.
80 ENDDO
81 ENDDO
82
83 #ifdef ALLOW_THSICE
84 IF ( useThSIce ) THEN
85 C- do sea-ice advection before setting any surface BC.
86 CALL THSICE_DO_ADVECT(
87 I bi, bj, myTime, myIter, myThid )
88 ENDIF
89 #endif /* ALLOW_THSICE */
90
91 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
92
93 C- Physics package needs to know time of year as a fraction
94 yearLength = 86400.*360.
95 tYear = MOD(myTime/yearLength, 1. _d 0)
96
97 C-- Set surface Boundary Conditions for atmos. physics package:
98 C (Albedo, Soil moisture, Surf Temp, Land sea mask)
99 C includes some parts of S/R FORDATE from F.Molteni SPEDDY code (ver23)
100 CALL AIM_SURF_BC(
101 U tYear,
102 O aim_sWght0, aim_sWght1,
103 I bi, bj, myTime, myIter, myThid )
104
105 C-- Set surface geopotential: (g * orographic height)
106 DO j=1,sNy
107 DO i=1,sNx
108 I2 = i+(j-1)*sNx
109 PHI0(I2) = gravity*topoZ(i,j,bi,bj)
110 ENDDO
111 ENDDO
112
113 C-- Set topographic dependent FOROG var (originally in common SFLFIX);
114 C used to compute for wind stress over land
115
116 c_FM IF (IDAY.EQ.0) THEN
117 c_FM CALL SFLSET (PHIS0)
118 CALL SFLSET (PHI0, fOrogr(1,myThid), bi,bj,myThid)
119 c_FM ENDIF
120 c_FM CALL SOL_OZ (SOLC,TYEAR)
121
122 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
123
124 C- Compute atmospheric-physics tendencies (call the main AIM S/R)
125 CALL PHY_DRIVER( tYear, useDiagnostics,
126 I bi, bj, myTime, myIter, myThid )
127
128 CALL AIM_AIM2DYN( bi, bj, myTime, myIter, myThid )
129
130 #ifdef ALLOW_LAND
131 IF (useLand) THEN
132 C- prepare Surface flux over land for land package
133 CALL AIM_AIM2LAND( aim_landFr, bi, bj,
134 I myTime, myIter, myThid )
135
136 C- Step forward land model
137 CALL LAND_STEPFWD( aim_landFr, bi, bj,
138 I myTime, myIter, myThid )
139
140 C- Land diagnostics : write snap-shot & cumulate for TimeAve output
141 CALL LAND_DO_DIAGS( aim_landFr, bi, bj,
142 I myTime, myIter, myThid )
143
144 ENDIF
145 #endif /* ALLOW_LAND */
146
147 C- surface fluxes over ocean (ice-free & ice covered)
148 C used for diagnostics, thsice package and coupler
149 CALL AIM_AIM2SIOCE( aim_landFr, fmask1(1,3,myThid),
150 O prcAtm,
151 I bi, bj, myTime, myIter, myThid )
152
153 #ifdef ALLOW_THSICE
154 IF ( useThSIce ) THEN
155
156 C- Step forward sea-ice model
157 CALL THSICE_STEP_FWD( bi, bj, 1, sNx, 1, sNy,
158 I prcAtm,
159 I myTime, myIter, myThid )
160
161 C- Slab Ocean : step forward ocean mixed-layer temp. & salinity
162 CALL THSICE_SLAB_OCEAN(
163 I aim_sWght0, aim_sWght1,
164 O dTsurf(1,2,myThid),
165 I bi, bj, myTime, myIter, myThid )
166
167 CALL THSICE_AVE(
168 I bi, bj, myTime, myIter, myThid )
169
170 ENDIF
171 #endif /* ALLOW_THSICE */
172
173 #ifdef COMPONENT_MODULE
174 IF ( useCoupler ) THEN
175 CALL ATM_STORE_MY_DATA( bi, bj, myIter, myTime, myThid )
176 ENDIF
177 #endif /* COMPONENT_MODULE */
178
179 C- AIM diagnostics : write snap-shot & cumulate for TimeAve output
180 CALL AIM_DIAGNOSTICS( bi, bj, myTime, myIter, myThid )
181
182 #endif /* ALLOW_AIM */
183
184 RETURN
185 END

  ViewVC Help
Powered by ViewVC 1.1.22