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

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

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


Revision 1.7 - (show annotations) (download)
Thu Jan 21 00:11:16 2010 UTC (14 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint64, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62b, checkpoint64a, checkpoint64c, checkpoint64b
Changes since 1.6: +34 -22 lines
little cleaning.

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_aim2dyn.F,v 1.6 2006/03/28 04:26:21 jmc Exp $
2 C $Name: $
3
4 #include "AIM_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: AIM_AIM2DYN
8 C !INTERFACE:
9 SUBROUTINE AIM_AIM2DYN(
10 I bi, bj, myTime, myIter, myThid )
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | S/R AIM_AIM2DYN
15 C | o Remap AIM outputs to dynamics conforming arrays.
16 C |==========================================================*
17 C | Currently AIM exports to the dynmaics
18 C | - PBL drag coefficient
19 C | - Net tendency for temperature
20 C | - Net tendency for water vapor
21 C | Exporting drag has the nice property that it is a scalar.
22 C | This means that the exchanges on the AIM exported fields
23 C | do not need special piaring on the cube. It may not be
24 C | a good idea in the long term as it makes assumptions
25 C | about the momentum schemes within AIM.
26 C *==========================================================*
27 C \ev
28 C-------
29 C Note: Except LSC tendency, all others need to be /dpFac.
30 C-------
31
32 C !USES:
33 IMPLICIT NONE
34
35 C == Global variables ===
36 C-- size for MITgcm & Physics package :
37 #include "AIM_SIZE.h"
38
39 #include "EEPARAMS.h"
40 #include "PARAMS.h"
41 #include "GRID.h"
42 #include "SURFACE.h"
43
44 #include "AIM2DYN.h"
45 #include "com_physvar.h"
46
47 C !INPUT/OUTPUT PARAMETERS:
48 C == Routine arguments ==
49 C bi,bj :: Tile index
50 C myTime :: Current time of simulation ( s )
51 C myIter :: Current iteration number in simulation
52 C myThid :: Number of this instance of the routine
53 INTEGER bi, bj
54 _RL myTime
55 INTEGER myIter, myThid
56 CEOP
57
58 #ifdef ALLOW_AIM
59 C !LOCAL VARIABLES:
60 C == Local variables ==
61 C i,j,k :: loop counters
62 C I2,Katm :: loop counters
63 C conv_T2theta :: conversion factor from (absolute) Temp. to Pot.Temp.
64 _RL conv_T2theta
65 INTEGER i,j,k
66 INTEGER I2, Katm
67 #ifdef ALLOW_DIAGNOSTICS
68 LOGICAL physTendDiag
69 LOGICAL DIAGNOSTICS_IS_ON
70 EXTERNAL DIAGNOSTICS_IS_ON
71 #endif
72
73 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
74
75 C-- Physics tendency term
76
77 #ifdef ALLOW_DIAGNOSTICS
78 physTendDiag = .FALSE.
79 IF (useDiagnostics) THEN
80 physTendDiag = DIAGNOSTICS_IS_ON( 'DIABT ', myThid )
81 & .OR. DIAGNOSTICS_IS_ON( 'DIABQ ', myThid )
82 ENDIF
83 #endif
84
85 C- Planetary boundary layer drag coeff.
86 DO j=1,sNy
87 DO i=1,sNx
88 I2 = i+(j-1)*sNx
89 aim_drag(i,j,bi,bj) = DRAG(I2,0,myThid)
90 ENDDO
91 ENDDO
92
93 DO k=1,Nr
94 Katm = _KD2KA( k )
95 conv_T2theta = (atm_po/rC(k))**atm_kappa
96
97 C- Add all tendencies (ignoring partial cell factor) for T & Q
98 C and convert Temp. tendency to Pot.Temp. tendency
99 DO j=1,sNy
100 DO i=1,sNx
101 I2 = i+(j-1)*sNx
102 C temperature tendency
103 aim_dTdt(i,j,k,bi,bj) = ( TT_CNV(I2,Katm,myThid)
104 & +TT_PBL(I2,Katm,myThid)
105 & +TT_RSW(I2,Katm,myThid)
106 & +TT_RLW(I2,Katm,myThid)
107 & +TT_LSC(I2,Katm,myThid)
108 & )*conv_T2theta
109 C water vapor tendency
110 aim_dSdt(i,j,k,bi,bj) = QT_CNV(I2,Katm,myThid)
111 & +QT_PBL(I2,Katm,myThid)
112 & +QT_LSC(I2,Katm,myThid)
113 ENDDO
114 ENDDO
115
116 #ifdef ALLOW_DIAGNOSTICS
117 IF ( physTendDiag ) THEN
118 CALL DIAGNOSTICS_FILL( aim_dTdt, 'DIABT ',
119 & k, Nr, 1,bi,bj, myThid )
120 CALL DIAGNOSTICS_FILL( aim_dSdt, 'DIABQ ',
121 & k, Nr, 1,bi,bj, myThid )
122 ENDIF
123 #endif /* ALLOW_DIAGNOSTICS */
124
125 C- Account for partial cell filling:
126 #ifdef NONLIN_FRSURF
127 IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN
128 IF ( select_rStar.GT.0 ) THEN
129 DO j=1,sNy
130 DO i=1,sNx
131 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
132 & *recip_hFacC(i,j,k,bi,bj)
133 & /rStarExpC(i,j,bi,bj)
134 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
135 & *recip_hFacC(i,j,k,bi,bj)
136 & /rStarExpC(i,j,bi,bj)
137 ENDDO
138 ENDDO
139 ELSE
140 DO j=1,sNy
141 DO i=1,sNx
142 IF ( k.EQ.ksurfC(i,j,bi,bj) ) THEN
143 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
144 & /hFac_surfC(i,j,bi,bj)
145 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
146 & /hFac_surfC(i,j,bi,bj)
147 ELSE
148 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
149 & *recip_hFacC(i,j,k,bi,bj)
150 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
151 & *recip_hFacC(i,j,k,bi,bj)
152 ENDIF
153 ENDDO
154 ENDDO
155 ENDIF
156 ELSE
157 #else /* ndef NONLIN_FRSURF */
158 IF (.TRUE.) THEN
159 #endif /* NONLIN_FRSURF */
160 DO j=1,sNy
161 DO i=1,sNx
162 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
163 & *recip_hFacC(i,j,k,bi,bj)
164 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
165 & *recip_hFacC(i,j,k,bi,bj)
166 ENDDO
167 ENDDO
168 ENDIF
169
170 C--- end of k loop.
171 ENDDO
172
173 #endif /* ALLOW_AIM */
174
175 RETURN
176 END

  ViewVC Help
Powered by ViewVC 1.1.22