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

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

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


Revision 1.5 - (show annotations) (download)
Fri Aug 28 19:31:24 2009 UTC (14 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.4: +19 -26 lines
fixed for #undef REAL4_IS_SLOW (when _RS is real*4)

1 C $Header: /u/gcmpack/MITgcm/pkg/timeave/timeave_surf_flux.F,v 1.4 2007/08/23 19:13:10 jmc Exp $
2 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 tmpFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
38
39 C- Time Averages of surface fluxes
40 IF ( usingPCoords ) THEN
41 k=Nr
42 ELSE
43 k=1
44 ENDIF
45
46 C- uFlux (surface momentum flux [Pa=N/m2], positive <-> increase u)
47 DO j=1,sNy
48 DO i=1,sNx
49 tmpFld(i,j)=fu(i,j,bi,bj)*foFacMom*_maskW(i,j,k,bi,bj)
50 ENDDO
51 ENDDO
52 CALL TIMEAVE_CUMUL_1T(uFluxtave,tmpFld,1,
53 & deltaTclock, bi, bj, myThid)
54
55 C- vFlux (surface momentum flux [Pa=N/m2], positive <-> increase v)
56 DO j=1,sNy
57 DO i=1,sNx
58 tmpFld(i,j)=fv(i,j,bi,bj)*foFacMom*_maskS(i,j,k,bi,bj)
59 ENDDO
60 ENDDO
61 CALL TIMEAVE_CUMUL_1T(vFluxtave,tmpFld,1,
62 & deltaTclock, bi, bj, myThid)
63
64 C tFlux (=Heat flux [W/m2], positive <-> increasing Theta)
65 DO j=1,sNy
66 DO i=1,sNx
67 tmpFld(i,j) =
68 #ifdef SHORTWAVE_HEATING
69 & -Qsw(i,j,bi,bj)+
70 #endif
71 & (surfaceForcingT(i,j,bi,bj)+surfaceForcingTice(I,J,bi,bj))
72 & *HeatCapacity_Cp*rUnit2mass
73 ENDDO
74 ENDDO
75 #ifdef NONLIN_FRSURF
76 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
77 & .AND. useRealFreshWaterFlux ) THEN
78 DO j=1,sNy
79 DO i=1,sNx
80 tmpFld(i,j) = tmpFld(i,j)
81 & + PmEpR(i,j,bi,bj)*rhoConstFresh
82 & *theta(i,j,k,bi,bj)*HeatCapacity_Cp
83 ENDDO
84 ENDDO
85 ENDIF
86 #endif /* NONLIN_FRSURF */
87 CALL TIMEAVE_CUMUL_1T( tFluxtave, tmpFld, 1,
88 & deltaTclock, bi, bj, myThid)
89
90 C sFlux (=salt flux [psu.kg/m2/s], positive <-> increasing Theta)
91 DO j=1,sNy
92 DO i=1,sNx
93 tmpFld(i,j)=
94 & surfaceForcingS(i,j,bi,bj)*rUnit2mass
95 ENDDO
96 ENDDO
97 #ifdef NONLIN_FRSURF
98 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
99 & .AND. useRealFreshWaterFlux ) THEN
100 DO j=1,sNy
101 DO i=1,sNx
102 tmpFld(i,j) = tmpFld(i,j)
103 & + PmEpR(i,j,bi,bj)*rhoConstFresh
104 & *salt(i,j,k,bi,bj)
105 ENDDO
106 ENDDO
107 ENDIF
108 #endif /* NONLIN_FRSURF */
109 CALL TIMEAVE_CUMUL_1T( sFluxtave, tmpFld, 1,
110 & deltaTclock, bi, bj, myThid)
111
112 #endif /* ALLOW_TIMEAVE */
113
114 RETURN
115 END

  ViewVC Help
Powered by ViewVC 1.1.22