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

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

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


Revision 1.1 - (hide annotations) (download)
Thu Mar 11 14:33:18 2004 UTC (20 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint52l_post, checkpoint53b_pre, checkpoint52m_post, checkpoint53a_post, checkpoint53b_post, checkpoint53
a) Treat separately land / ocean / sea-ice surface fluxes
   to allow implicit computation of land & sea-ice surface temp.
b) add snow precipitation
c) other (little) modifications for new land formulation.

1 jmc 1.1 C $Header: $
2     C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5     #ifdef ALLOW_LAND
6     #include "LAND_OPTIONS.h"
7     #endif
8    
9     CBOP
10     C !ROUTINE: AIM_LAND_IMPL
11     C !INTERFACE:
12     SUBROUTINE AIM_LAND_IMPL(
13     I FMASK,
14     I dTskin, sFlx,
15     I Evp0, dEvp, Slr0, dSlr,
16     U Tsurf, EVAP, SLRU,
17     I bi, bj, myTime, myIter, myThid)
18    
19     C !DESCRIPTION: \bv
20     C *==========================================================*
21     C | S/R AIM_LAND_IMPL
22     C | o AIM Interface to the implicit part of the land model
23     C *==========================================================*
24     C \ev
25    
26     C !USES:
27     IMPLICIT NONE
28    
29     C == Global variables ===
30     C-- size for MITgcm & Physics package :
31     #include "AIM_SIZE.h"
32    
33     #include "EEPARAMS.h"
34     #include "PARAMS.h"
35    
36     #include "AIM_FFIELDS.h"
37     #include "com_physcon.h"
38     c #include "com_physvar.h"
39    
40     #ifdef ALLOW_LAND
41     #include "LAND_SIZE.h"
42     #include "LAND_PARAMS.h"
43     #include "LAND_VARS.h"
44     #endif
45    
46     C !INPUT/OUTPUT PARAMETERS:
47     C == Routine arguments ==
48     C FMASK :: land fraction [0-1]
49     C dTskin :: temp. correction for daily-cycle heating [K]
50     C sFlx :: net surface flux (+=down) function of surf. temp Ts:
51     C 0: Flux(Ts=0.oC) ; 1: Flux(Ts^n) ; 2: d.Flux/d.Ts(Ts^n)
52     C Evp0 :: evaporation computed over freezing surface (Ts=0.oC)
53     C dEvp :: evaporation derivative relative to surf. temp
54     C Slr0 :: upward long wave radiation over freezing surf.
55     C Tsurf :: surface temperature (2-dim)
56     C EVAP :: evaporation [g/(m^2 s)] (2-dim)
57     C SLRU :: sfc lw radiation (upward flux) (2-dim)
58     C bi,bj :: Tile index
59     C myTime :: Current time of simulation ( s )
60     C myIter :: Current iteration number in simulation
61     C myThid :: Number of this instance of the routine
62     _RL FMASK(NGP), dTskin(NGP), sFlx(NGP,0:2)
63     _RL Evp0(NGP), dEvp(NGP), Slr0(NGP), dSlr(NGP)
64     _RL Tsurf(NGP), EVAP(NGP), SLRU(NGP)
65     INTEGER bi, bj, myIter, myThid
66     _RL myTime
67     CEOP
68    
69     #ifdef ALLOW_AIM
70     #ifdef ALLOW_LAND
71     C == Local variables ==
72     C i,j, I2 :: loop counters
73     C dTsurf :: surf. temp change after 1 implicit time step [oC]
74     _RL dTsurf(NGP)
75     INTEGER i,j, I2
76    
77     C-- Physics tendency term
78    
79     IF ( land_impl_grT ) THEN
80    
81     DO j=1,sNy
82     DO i=1,sNx
83     I2 = i+(j-1)*sNx
84    
85     C- total surface downward heat flux :
86     land_HeatFLx(i,j,bi,bj) = sFlx(I2,1)
87    
88     C- initialize temp. changes and fresh water flux :
89     dTsurf(I2) = 0.
90     land_Pr_m_Ev(i,j,bi,bj) = 0. _d 0
91    
92     ENDDO
93     ENDDO
94    
95     CALL LAND_IMPL_TEMP(
96     I aim_landFr,
97     I dTskin, sFlx,
98     O dTsurf,
99     I bi, bj, myTime, myIter, myThid)
100    
101     C- Update Surf.Temp., Evap, Upward SW according to surf. temp. changes
102     DO J=1,NGP
103     IF ( dTsurf(J) .GT. 999. ) THEN
104     Tsurf(J) = tFreeze
105     EVAP(J) = Evp0(J)
106     SLRU(J) = Slr0(J)
107     ELSE
108     Tsurf(J) = Tsurf(J)+ dTsurf(J)
109     EVAP(J) = EVAP(J) + dTsurf(J)*dEvp(J)
110     SLRU(J) = SLRU(J) + dTsurf(J)*dSlr(J)
111     ENDIF
112     ENDDO
113    
114     C- end (if land_impl_grT)
115     ENDIF
116    
117     #endif /* ALLOW_LAND */
118     #endif /* ALLOW_AIM */
119    
120     RETURN
121     END

  ViewVC Help
Powered by ViewVC 1.1.22