/[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.10 - (show annotations) (download)
Thu Jan 26 00:18:54 2006 UTC (18 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint58d_post, checkpoint58a_post, checkpoint58e_post, checkpoint58c_post
Changes since 1.9: +5 -4 lines
add diagnostic for Donward LW radiation at the ground.

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

  ViewVC Help
Powered by ViewVC 1.1.22