/[MITgcm]/MITgcm/pkg/timeave/timeave_surf_flux.F
ViewVC logotype

Annotation of /MITgcm/pkg/timeave/timeave_surf_flux.F

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


Revision 1.2 - (hide annotations) (download)
Sun Jul 18 01:16:36 2004 UTC (19 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint55c_post, checkpoint54e_post, checkpoint55d_pre, checkpoint55b_post, checkpoint54d_post, checkpoint55, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint55e_post, checkpoint55a_post, checkpoint54c_post, checkpoint55d_post
Changes since 1.1: +4 -5 lines
replace surfaceTendency U,V,S,T,Tice by surfaceForcing U,V,S,T,Tice

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/timeave/timeave_surf_flux.F,v 1.1 2003/12/05 02:33:56 jmc Exp $
2 jmc 1.1 C $Name: $
3     #include "TIMEAVE_OPTIONS.h"
4    
5     SUBROUTINE TIMEAVE_SURF_FLUX(
6     I bi, bj, myTime, myIter, myThid)
7     C *==========================================================*
8     C | SUBROUTINE TIMEAVE_SURF_FLUX |
9     C | o Time averaging routine for surface (forcing) fluxes |
10     C *==========================================================*
11     IMPLICIT NONE
12    
13     C == Global variables ===
14     #include "SIZE.h"
15     #include "EEPARAMS.h"
16     #include "PARAMS.h"
17     #include "GRID.h"
18     #include "DYNVARS.h"
19     #include "SURFACE.h"
20     #include "FFIELDS.h"
21     #include "TIMEAVE_STATV.h"
22    
23     C == Routine arguments ==
24     C bi, bj :: current tile indices
25     C myTime :: Current time of simulation ( s )
26     C myIter :: Iteration number
27     C myThid :: Thread number for this instance of the routine.
28     INTEGER bi, bj
29     _RL myTime
30     INTEGER myIter
31     INTEGER myThid
32    
33     #ifdef ALLOW_TIMEAVE
34    
35     C == Local variables ==
36     INTEGER I, J, K
37     _RL DDTT
38     _RL tmpFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39    
40     C- Time Averages of surface fluxes
41     IF ( buoyancyRelation .EQ. 'OCEANICP' ) THEN
42     k=Nr
43     ELSE
44     k=1
45     ENDIF
46    
47     C- uFlux (surface momentum flux [Pa=N/m2], positive <-> increase u)
48     c DO j=1,sNy
49     c DO i=1,sNx
50     c tmpFld(i,j)=fu(i,j,bi,bj)*foFacMom*_maskW(i,j,k,bi,bj)
51     c ENDDO
52     c ENDDO
53     c CALL TIMEAVE_CUMUL_1T(uFluxtave,tmpFld,1,
54     c & deltaTclock, bi, bj, myThid)
55     DDTT = deltaTclock*foFacMom
56     CALL TIMEAVE_CUMULATE( uFluxtave, fu, 1,
57     & DDTT, bi, bj, myThid)
58    
59     C- vFlux (surface momentum flux [Pa=N/m2], positive <-> increase v)
60     c DO j=1,sNy
61     c DO i=1,sNx
62     c tmpFld(i,j)=fv(i,j,bi,bj)*foFacMom*_maskS(i,j,k,bi,bj)
63     c ENDDO
64     c ENDDO
65     c CALL TIMEAVE_CUMUL_1T(vFluxtave,tmpFld,1,
66     c & deltaTclock, bi, bj, myThid)
67     DDTT = deltaTclock*foFacMom
68     CALL TIMEAVE_CUMULATE( vFluxtave, fv, 1,
69     & DDTT, bi, bj, myThid)
70    
71     C tFlux (=Heat flux [W/m2], positive <-> increasing Theta)
72     DO j=1,sNy
73     DO i=1,sNx
74     tmpFld(i,j) =
75     #ifdef SHORTWAVE_HEATING
76     & -Qsw(i,j,bi,bj)+
77     #endif
78 jmc 1.2 & (surfaceForcingT(i,j,bi,bj)+surfaceForcingTice(I,J,bi,bj))
79 jmc 1.1 & *HeatCapacity_Cp*recip_horiVertRatio*rhoConst
80     ENDDO
81     ENDDO
82     #ifdef NONLIN_FRSURF
83     IF ( (nonlinFreeSurf.GT.0 .OR. buoyancyRelation.EQ.'OCEANICP')
84     & .AND. useRealFreshWaterFlux ) THEN
85     DO j=1,sNy
86     DO i=1,sNx
87     tmpFld(i,j) = tmpFld(i,j)
88     & + PmEpR(i,j,bi,bj)*rhoConstFresh
89     & *theta(i,j,k,bi,bj)*HeatCapacity_Cp
90     ENDDO
91     ENDDO
92     ENDIF
93     #endif /* NONLIN_FRSURF */
94     CALL TIMEAVE_CUMUL_1T( tFluxtave, tmpFld, 1,
95     & deltaTclock, bi, bj, myThid)
96    
97     C sFlux (=salt flux [psu.kg/m2/s], positive <-> increasing Theta)
98     DO j=1,sNy
99     DO i=1,sNx
100     tmpFld(i,j)=
101 jmc 1.2 & surfaceForcingS(i,j,bi,bj)*
102     & recip_horiVertRatio*rhoConst
103 jmc 1.1 ENDDO
104     ENDDO
105     #ifdef NONLIN_FRSURF
106     IF ( (nonlinFreeSurf.GT.0 .OR. buoyancyRelation.EQ.'OCEANICP')
107     & .AND. useRealFreshWaterFlux ) THEN
108     DO j=1,sNy
109     DO i=1,sNx
110     tmpFld(i,j) = tmpFld(i,j)
111     & + PmEpR(i,j,bi,bj)*rhoConstFresh
112     & *salt(i,j,k,bi,bj)
113     ENDDO
114     ENDDO
115     ENDIF
116     #endif /* NONLIN_FRSURF */
117     CALL TIMEAVE_CUMUL_1T( sFluxtave, tmpFld, 1,
118     & deltaTclock, bi, bj, myThid)
119    
120     #endif /* ALLOW_TIMEAVE */
121    
122     RETURN
123     END

  ViewVC Help
Powered by ViewVC 1.1.22