/[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.6 - (show annotations) (download)
Wed Apr 27 20:21:42 2011 UTC (13 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62z, checkpoint62y, checkpoint62x, HEAD
Changes since 1.5: +4 -6 lines
fix for EmPmR units-change (from m/s to kg/m2/s) from Oct 1rst, 2007

1 C $Header: /u/gcmpack/MITgcm/pkg/timeave/timeave_surf_flux.F,v 1.5 2009/08/28 19:31:24 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)*theta(i,j,k,bi,bj)*HeatCapacity_Cp
82 ENDDO
83 ENDDO
84 ENDIF
85 #endif /* NONLIN_FRSURF */
86 CALL TIMEAVE_CUMUL_1T( tFluxtave, tmpFld, 1,
87 & deltaTclock, bi, bj, myThid)
88
89 C sFlux (=salt flux [psu.kg/m2/s], positive <-> increasing Theta)
90 DO j=1,sNy
91 DO i=1,sNx
92 tmpFld(i,j)=
93 & surfaceForcingS(i,j,bi,bj)*rUnit2mass
94 ENDDO
95 ENDDO
96 #ifdef NONLIN_FRSURF
97 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
98 & .AND. useRealFreshWaterFlux ) THEN
99 DO j=1,sNy
100 DO i=1,sNx
101 tmpFld(i,j) = tmpFld(i,j)
102 & + PmEpR(i,j,bi,bj)*salt(i,j,k,bi,bj)
103 ENDDO
104 ENDDO
105 ENDIF
106 #endif /* NONLIN_FRSURF */
107 CALL TIMEAVE_CUMUL_1T( sFluxtave, tmpFld, 1,
108 & deltaTclock, bi, bj, myThid)
109
110 #endif /* ALLOW_TIMEAVE */
111
112 RETURN
113 END

  ViewVC Help
Powered by ViewVC 1.1.22