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

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

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


Revision 1.1 - (hide annotations) (download)
Fri Nov 22 17:17:03 2002 UTC (21 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47a_post, checkpoint47b_post
new aim pkg: adapted from Franco Molteni SPEEDY code, ver23

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5    
6     SUBROUTINE AIM_DO_PHYSICS( bi, bj, myTime, myIter, myThid )
7    
8     C *==================================================================*
9     C | S/R AIM_DO_PHYSICS
10     C *==================================================================*
11     C | Interface between atmospheric physics package and the
12     C | dynamical model.
13     C | Routine calls physics pacakge after setting surface BC.
14     C | Package should derive and set tendency terms
15     C | which can be included as external forcing terms in the dynamical
16     C | tendency routines. Packages should communicate this information
17     C | through common blocks.
18     C *==================================================================*
19     IMPLICIT NONE
20    
21     C -------------- Global variables ------------------------------------
22     C-- size for MITgcm & Physics package :
23     #include "AIM_SIZE.h"
24    
25     C-- MITgcm
26     #include "EEPARAMS.h"
27     #include "PARAMS.h"
28     #include "DYNVARS.h"
29     #include "GRID.h"
30     #include "SURFACE.h"
31    
32     C-- Physics package
33     #include "AIM_FFIELDS.h"
34     #include "AIM_GRID.h"
35     #include "com_physvar.h"
36     #include "com_forcing.h"
37    
38     C == Routine arguments ==
39     C bi,bj - Tile index
40     C myTime - Current time of simulation ( s )
41     C myIter - Current iteration number in simulation
42     C myThid - Number of this instance of the routine
43     INTEGER bi, bj, myIter, myThid
44     _RL myTime
45    
46     #ifdef ALLOW_AIM
47     C == Local variables ==
48     C I,J,K,I2 - Loop counters
49     C tYear - Fraction into year
50     C Katm - Atmospheric K index
51     INTEGER I,J,K,I2
52     c INTEGER Katm
53     _RL tYear, yearLength
54    
55     C_jmc: Because AIM physics LSC is not applied in the stratosphere (top level),
56     C ==> move water wapor from the stratos to the surface level.
57     DO j = 1-Oly, sNy+Oly
58     DO i = 1-Olx, sNx+Olx
59     k = ksurfC(i,j,bi,bj)
60     IF (k.LE.Nr)
61     & salt(i,j,k,bi,bj) = salt(i,j,k,bi,bj)
62     & + salt(i,j,Nr,bi,bj)*drF(Nr)*recip_drF(k)
63     & *hFacC(i,j,Nr,bi,bj)*recip_hFacC(i,j,k,bi,bj)
64     salt(i,j,Nr,bi,bj) = 0.
65     ENDDO
66     ENDDO
67    
68     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
69    
70     c CALL FORDATE
71     C- extract parts of S/R FORDATE from Franco Molteni Physics :
72    
73     C- Physics package needs to know time of year as a fraction
74     yearLength = 86400.*360.
75     tYear = mod(myTime/yearLength, 1. _d 0)
76     c tYear = myTime/(86400.*360.) -
77     c & FLOAT(INT(myTime/(86400.*360.)))
78    
79     C- Load external data needed by physics package
80     C 1. Albedo (between 0-1)
81     C 2. Soil moisture (between 0-1)
82     C 3. Surface temperatures (in situ Temp. [K])
83     C 4. Snow depth - assume no snow for now
84     C 5. Sea ice - assume no sea ice for now
85     C 6. Land sea mask - infer from exact zeros in soil moisture dataset
86     C 7. Surface geopotential - to be done when orography is in
87     C dynamical kernel. Assume 0. for now.
88    
89     C Load in surface albedo data (in [0,1]) from aim_albedo to alb1 :
90     DO J=1,sNy
91     DO I=1,sNx
92     I2 = (sNx)*(J-1)+I
93     alb1(I2,myThid) = 0.
94     alb1(I2,myThid) = aim_albedo(I,J,bi,bj)
95     ENDDO
96     ENDDO
97     C Load in surface temperature data from aim_surfTemp to stl1 & sst1 :
98     DO J=1,sNy
99     DO I=1,sNx
100     I2 = (sNx)*(J-1)+I
101     sst1(I2,myThid) = 300.
102     stl1(I2,myThid) = 300.
103     sst1(I2,myThid) = aim_surfTemp(I,J,bi,bj)
104     stl1(I2,myThid) = aim_surfTemp(I,J,bi,bj)
105     ENDDO
106     ENDDO
107    
108     C Load in soil water availability (in [0,1]) from aim_soilWater to soilw1 :
109     DO J=1,sNy
110     DO I=1,sNx
111     I2 = (sNx)*(J-1)+I
112     soilw1(I2,myThid) = 0.
113     soilw1(I2,myThid) = aim_soilWater(I,J,bi,bj)
114     ENDDO
115     ENDDO
116     C Set snow depth, sea ice to zero for now
117     C Land-sea mask ( figure this out from where
118     C soil moisture is exactly zero ).
119     DO J=1,sNy
120     DO I=1,sNx
121     I2 = (sNx)*(J-1)+I
122     fMask1(I2,myThid) = 1.
123     IF ( soilw1(I2,myThid) .EQ. 0. ) fMask1(I2,myThid) = 0.
124     oice1(I2,myThid) = 0.
125     snow1(I2,myThid) = 0.
126     ENDDO
127     ENDDO
128     C open(77,file='lsmask',form='unformatted')
129     C write(77) fmask1
130     C close(77)
131    
132     C-- Set surface geopotential: (g * orographic height)
133     DO J=1,sNy
134     DO I=1,sNx
135     I2 = I+(J-1)*sNx
136     PHI0(I2) = gravity*topoZ(i,j,bi,bj)
137     ENDDO
138     ENDDO
139    
140     C-- Set topographic dependent FOROG var (originally in common SFLFIX);
141     C used to compute for wind stress over land
142    
143     c_FM IF (IDAY.EQ.0) THEN
144     c_FM CALL SFLSET (PHIS0)
145     CALL SFLSET (PHI0, fOrogr(1,myThid), bi,bj,myThid)
146     c_FM ENDIF
147     c_FM CALL SOL_OZ (SOLC,TYEAR)
148    
149     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
150    
151     C- Compute atmospheric-physics tendencies (call the main AIM S/R)
152     CALL PHY_DRIVER( tYear, myTime, myIter, bi, bj, myThid )
153    
154     C- AIM diagnostics : write snap-shot & cumulate for TimeAve output
155     CALL AIM_DIAGNOSTICS( bi, bj, myTime, myIter, myThid )
156    
157     CALL AIM_AIM2DYN( bi, bj, myTime, myIter, myThid )
158    
159     #endif /* ALLOW_AIM */
160    
161     RETURN
162     END

  ViewVC Help
Powered by ViewVC 1.1.22