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

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

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


Revision 1.2 - (hide annotations) (download)
Thu Apr 8 00:14:09 2004 UTC (20 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint53c_post, checkpoint53b_pre, checkpoint52m_post, checkpoint53a_post, checkpoint53b_post, checkpoint53, checkpoint53d_pre
Changes since 1.1: +28 -2 lines
allow to use ThSIce (with salb ocean) with AIM:
 - compute ice and surface temp. implicitly (aim_sice_impl alled from phy_driver)
 - call thermodynamic sea-ice model at the end of aim_do_physics.F

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/phy_suflux_post.F,v 1.1 2004/03/11 14:33:19 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: SUFLUX_POST
8     C !INTERFACE:
9     SUBROUTINE SUFLUX_POST(
10     I FMASK, EMISloc,
11     I TLAND, TSEA, TSICE, dTskin, SLRD,
12     I T0, Q0, CDENVV,
13     U DRAG, SHF, EVAP, SLRup,
14     O SLRU, TSFC, TSKIN,
15     I bi,bj,myThid)
16    
17     C !DESCRIPTION: \bv
18     C *==========================================================*
19     C | S/R SUFLUX_POST
20     C | o finish surface flux calculation
21     C *==========================================================*
22     C | o contain 2nd part of original S/R SUFLUX (Speedy code)
23     C *==========================================================*
24     C--
25     C-- SUBROUTINE SUFLUX (PSA,UA,VA,TA,QA,RH,PHI,
26     C-- & PHI0,FMASK,TLAND,TSEA,SWAV,SSR,SLRD,
27     C-- & USTR,VSTR,SHF,EVAP,SLRU,
28     C-- & TSFC,TSKIN,U0,V0,T0,Q0)
29     C--
30     C-- Purpose: Compute surface fluxes of momentum, energy and moisture,
31     C-- and define surface skin temperature from energy balance
32     C *==========================================================*
33     C \ev
34    
35     C !USES:
36     IMPLICIT NONE
37    
38     C Resolution parameters
39    
40     C-- size for MITgcm & Physics package :
41     #include "AIM_SIZE.h"
42    
43     #include "EEPARAMS.h"
44 jmc 1.2 #include "GRID.h"
45 jmc 1.1
46     C Physical constants + functions of sigma and latitude
47     #include "com_physcon.h"
48    
49     C Surface flux constants
50     #include "com_sflcon.h"
51    
52     C !INPUT/OUTPUT PARAMETERS:
53     C == Routine Arguments ==
54     C-- Input:
55     C FMASK :: fraction land - sea - sea-ice (2.5-dim)
56     C EMISloc:: longwave surface emissivity
57     C TLAND :: land-surface temperature (2-dim)
58     C TSEA :: sea-surface temperature (2-dim)
59     C TSICE :: sea-ice surface temperature (2-dim)
60     C dTskin :: temp. correction for daily-cycle heating [K]
61     C SLRD :: sfc lw radiation (downward flux)(2-dim)
62     C SSR :: sfc sw radiation (net flux) (2-dim)
63     C T0 :: near-surface air temperature (2-dim)
64     C Q0 :: near-surface sp. humidity [g/kg](2-dim)
65     C CDENVV :: sensible heat flux coefficient (1:land, 2:sea, 3:sea-ice)
66     C-- Output:
67     C DRAG :: surface Drag term (= Cd*Rho*|V|)(2-dim)
68     C SHF :: sensible heat flux (2-dim)
69     C EVAP :: evaporation [g/(m^2 s)] (2-dim)
70     C SLRU :: sfc lw radiation (upward flux) (2-dim)
71     C SLRup :: same, for each surface type (2-dim)
72     C TSFC :: surface temperature (clim.) (2-dim)
73     C TSKIN :: skin surface temperature (2-dim)
74     C-- Input:
75     C bi,bj :: tile index
76     C myThid :: Thread number for this instance of the routine
77     C--
78     _RL FMASK(NGP,3), EMISloc
79     _RL TLAND(NGP), TSEA(NGP), TSICE(NGP), dTskin(NGP), SLRD(NGP)
80     _RL T0(NGP), Q0(NGP), CDENVV(NGP,3)
81    
82     _RL DRAG(NGP,0:3), SHF(NGP,0:3), EVAP(NGP,0:3), SLRup(NGP,3)
83     _RL SLRU(NGP), TSFC(NGP), TSKIN(NGP)
84    
85     INTEGER bi,bj,myThid
86     CEOP
87    
88     #ifdef ALLOW_AIM
89    
90     C-- Local variables:
91 jmc 1.2 C J,i1,j1 :: Loop counters
92     C msgBuf :: Informational/error message buffer
93     INTEGER J,i1,j1
94     CHARACTER*(MAX_LEN_MBUF) msgBuf
95 jmc 1.1
96     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
97    
98     C-- 1. Extrapolation of wind, temp, hum. and density to the surface
99    
100     C-- 2. Computation of fluxes over land and sea
101    
102     C-- 3. Adjustment of skin temperature and fluxes over land
103     C-- based on energy balance (to be implemented)
104    
105     C 3.2 Sensible heat flux (from clim. TS over land)
106     C Note: needs to update SHF if land or sea-ice surf temp are computed
107     C implicitly ; recomputes SHF is consistent since SHF linear in TS
108    
109     DO J=1,NGP
110     SHF(J,1) = CDENVV(J,1)*CP*(TLAND(J)+dTskin(J)-T0(J))
111     c SHF(J,2) = CDENVV(J,2)*CP*(TSEA(J) -T0(J))
112     SHF(J,3) = CDENVV(J,3)*CP*(TSICE(J)-T0(J))
113     ENDDO
114    
115    
116     C-- 4. Weighted average of surface fluxes and temperatures
117     C-- according to land-sea mask
118    
119     DO J=1,NGP
120     c USTR(J,3) = USTR(J,2)+FMASK(J,1)*(USTR(J,1)-USTR(J,2))
121     c VSTR(J,3) = VSTR(J,2)+FMASK(J,1)*(VSTR(J,1)-VSTR(J,2))
122     c DRAG(J,0) = DRAG(J,2)+FMASK(J,1)*(DRAG(J,1)-DRAG(J,2))
123     c SHF(J,0) = SHF(J,2)+FMASK(J,1)*( SHF(J,1)- SHF(J,2))
124     c EVAP(J,0) = EVAP(J,2)+FMASK(J,1)*(EVAP(J,1)-EVAP(J,2))
125     c SLRU(J) = SLRup(J,2)+FMASK(J,1)*(SLRup(J,1)-SLRup(J,2))
126     DRAG(J,0) = (FMASK(J,1)*DRAG(J,1)+FMASK(J,2)*DRAG(J,2)
127     & +FMASK(J,3)*DRAG(J,3))
128     SHF (J,0) = (FMASK(J,1)*SHF(J,1) +FMASK(J,2)*SHF(J,2)
129     & +FMASK(J,3)*SHF(J,3) )
130     EVAP(J,0) = (FMASK(J,1)*EVAP(J,1)+FMASK(J,2)*EVAP(J,2)
131     & +FMASK(J,3)*EVAP(J,3))
132     SLRU(J) = (FMASK(J,1)*SLRup(J,1)+FMASK(J,2)*SLRup(J,2)
133     & +FMASK(J,3)*SLRup(J,3))
134     ENDDO
135    
136     DO J=1,NGP
137     c TSFC(J) = TSEA(J)+FMASK(J,1)*(TLAND(J)-TSEA(J))
138     TSFC(J) = (FMASK(J,1)*TLAND(J) + FMASK(J,2)*TSEA(J)
139     & + FMASK(J,3)*TSICE(J))
140     TSKIN(J) = TSFC(J)+FMASK(J,1)*dTskin(J)
141     ENDDO
142    
143     C- Compute Net LW surf flux (+=upward) for each surface type:
144     C (for diagnostic only)
145     DO J=1,NGP
146     SLRup(J,1)=EMISloc*SLRup(J,1)-SLRD(J)
147     SLRup(J,2)=EMISloc*SLRup(J,2)-SLRD(J)
148     SLRup(J,3)=EMISloc*SLRup(J,3)-SLRD(J)
149     ENDDO
150 jmc 1.2
151     C- Check that Temp is OK for LW Radiation scheme :
152     DO J=1,NGP
153     IF ( TSFC(J).LT.lwTemp1 .OR.
154     & TSFC(J).GT.lwTemp2 ) THEN
155     i1 = 1 + mod((J-1),sNx)
156     j1 = 1 + int((J-1)/sNx)
157     WRITE(msgBuf,'(A,1PE20.13,A,2I4)')
158     & 'SUFLUX_POST: TS=', TSFC(J),
159     & ' out of range ',lwTemp1,lwTemp2
160     CALL PRINT_ERROR( msgBuf , myThid)
161     WRITE(msgBuf,'(A,1P3E10.3,A,0P3F8.5)')
162     & 'SUFLUX_POST: T_Lnd,Sea,Sic=',TLAND(J),TSEA(J),TSICE(J),
163     & ' Mask:',FMASK(J,1),FMASK(J,2),FMASK(J,3)
164     CALL PRINT_ERROR( msgBuf , myThid)
165     WRITE(msgBuf,'(A,2I4,3I3,I6,2F9.3)')
166     & 'SUFLUX_POST: Pb in i,j,bi,bj,myThid,IJ,X,Y=',
167     & i1,j1,bi,bj,myThid,J,xC(i1,j1,bi,bj),yC(i1,j1,bi,bj)
168     CALL PRINT_ERROR( msgBuf , myThid)
169     STOP 'ABNORMAL END: S/R SUFLUX_POST'
170     ENDIF
171     ENDDO
172 jmc 1.1
173     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
174     #endif /* ALLOW_AIM */
175    
176     RETURN
177     END

  ViewVC Help
Powered by ViewVC 1.1.22