/[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.6 - (show annotations) (download)
Tue Mar 28 04:26:21 2006 UTC (18 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58f_post, checkpoint58d_post, checkpoint62a, checkpoint58y_post, checkpoint58t_post, checkpoint58m_post, checkpoint60, checkpoint61, checkpoint62, checkpoint58w_post, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58e_post, checkpoint58r_post, checkpoint58n_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint61f, checkpoint58g_post, checkpoint58x_post, checkpoint61n, checkpoint58h_post, checkpoint58j_post, checkpoint61q, checkpoint61z, checkpoint61e, checkpoint58i_post, checkpoint58u_post, checkpoint58s_post, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61x, checkpoint61y
Changes since 1.5: +32 -19 lines
Scale LSC tendencies by hFac (get homogenous scaling across all AIM tendencies)
 and fix diabatic tendency diagnostics (DIABT,DIABQ) with p*

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

  ViewVC Help
Powered by ViewVC 1.1.22