/[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.5 - (show annotations) (download)
Thu Jul 8 15:51:19 2004 UTC (19 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57g_pre, checkpoint57s_post, checkpoint58b_post, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint57y_post, checkpoint54d_post, checkpoint54e_post, checkpoint57r_post, checkpoint57d_post, checkpoint57i_post, checkpoint58, checkpoint55, checkpoint57, checkpoint56, checkpoint57n_post, checkpoint58a_post, checkpoint57z_post, checkpoint54f_post, checkpoint55i_post, checkpoint57l_post, checkpoint57t_post, checkpoint55c_post, checkpoint57v_post, checkpoint57f_post, checkpoint57a_post, checkpoint57h_pre, checkpoint54b_post, checkpoint57h_post, checkpoint57y_pre, checkpoint55g_post, checkpoint57c_post, checkpoint55d_post, checkpoint55d_pre, checkpoint57c_pre, checkpoint55j_post, checkpoint55h_post, checkpoint57e_post, checkpoint55b_post, checkpoint55f_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, eckpoint57e_pre, checkpoint56a_post, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint56c_post, checkpoint57a_pre, checkpoint55a_post, checkpoint57o_post, checkpoint57k_post, checkpoint57w_post, checkpoint57x_post, checkpoint58c_post, checkpoint55e_post, checkpoint54c_post
Changes since 1.4: +75 -15 lines
o staggerTimeStep & NLFS: update physical pkg aim_v23

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_aim2dyn.F,v 1.4 2004/03/11 14:33: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 #include "DYNVARS.h"
37
38 #include "AIM2DYN.h"
39 #include "com_physvar.h"
40
41 C == Routine arguments ==
42 C bi,bj - Tile index
43 C myTime - Current time of simulation ( s )
44 C myIter - Current iteration number in simulation
45 C myThid - Number of this instance of the routine
46 INTEGER bi, bj, myIter, myThid
47 _RL myTime
48 CEndOfInterface
49
50 #ifdef ALLOW_AIM
51 C == Local variables ==
52 C i,j,k :: loop counters
53 C I2,Katm :: loop counters
54 C conv_T2theta :: conversion factor from (absolute) Temp. to Pot.Temp.
55 _RL conv_T2theta
56 INTEGER i,j,k
57 INTEGER I2, Katm
58
59 C-- Physics tendency term
60
61 C- Planetary boundary layer drag coeff.
62 DO j=1,sNy
63 DO i=1,sNx
64 I2 = i+(j-1)*sNx
65 aim_drag(i,j,bi,bj) = DRAG(I2,0,myThid)
66 ENDDO
67 ENDDO
68
69 DO k=1,Nr
70 Katm = _KD2KA( k )
71 conv_T2theta = (atm_po/rC(k))**atm_kappa
72
73 C- temp. & water vap. tendencies (ignoring partial cell factor)
74 DO j=1,sNy
75 DO i=1,sNx
76 I2 = i+(j-1)*sNx
77 C temperature tendency (except LSC, added later)
78 aim_dTdt(i,j,k,bi,bj) = TT_CNV(I2,Katm,myThid)
79 & +TT_PBL(I2,Katm,myThid)
80 & +TT_RSW(I2,Katm,myThid)
81 & +TT_RLW(I2,Katm,myThid)
82 C water vapor tendency (except LSC, added later)
83 aim_dSdt(i,j,k,bi,bj) = QT_CNV(I2,Katm,myThid)
84 & +QT_PBL(I2,Katm,myThid)
85 ENDDO
86 ENDDO
87
88 C- Account for partial cell filling:
89 #ifdef NONLIN_FRSURF
90 IF ( staggerTimeStep .AND. nonlinFreeSurf.GT.0 ) THEN
91 IF ( select_rStar.GT.0 ) THEN
92 DO j=1,sNy
93 DO i=1,sNx
94 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
95 & *recip_hFacC(i,j,k,bi,bj)
96 & /rStarExpC(i,j,bi,bj)
97 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
98 & *recip_hFacC(i,j,k,bi,bj)
99 & /rStarExpC(i,j,bi,bj)
100 ENDDO
101 ENDDO
102 ELSE
103 DO j=1,sNy
104 DO i=1,sNx
105 IF ( k.EQ.ksurfC(i,j,bi,bj) ) THEN
106 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
107 & /hFac_surfC(i,j,bi,bj)
108 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
109 & /hFac_surfC(i,j,bi,bj)
110 ELSE
111 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
112 & *recip_hFacC(i,j,k,bi,bj)
113 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
114 & *recip_hFacC(i,j,k,bi,bj)
115 ENDIF
116 ENDDO
117 ENDDO
118 ENDIF
119 ELSE
120 #else /* ndef NONLIN_FRSURF */
121 IF (.TRUE.) THEN
122 #endif /* NONLIN_FRSURF */
123 DO j=1,sNy
124 DO i=1,sNx
125 aim_dTdt(i,j,k,bi,bj) = aim_dTdt(i,j,k,bi,bj)
126 & *recip_hFacC(i,j,k,bi,bj)
127 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
128 & *recip_hFacC(i,j,k,bi,bj)
129 ENDDO
130 ENDDO
131 ENDIF
132
133 C- Net tendencies : Add LSC term & comvert to Pot.Temp.:
134 DO j=1,sNy
135 DO i=1,sNx
136 I2 = i+(j-1)*sNx
137 aim_dTdt(i,j,k,bi,bj) = ( aim_dTdt(i,j,k,bi,bj)
138 & +TT_LSC(I2,Katm,myThid)
139 & )*conv_T2theta
140 aim_dSdt(i,j,k,bi,bj) = aim_dSdt(i,j,k,bi,bj)
141 & +QT_LSC(I2,Katm,myThid)
142 ENDDO
143 ENDDO
144
145 C--- end of k loop.
146 ENDDO
147
148 #endif /* ALLOW_AIM */
149
150 RETURN
151 END

  ViewVC Help
Powered by ViewVC 1.1.22