/[MITgcm]/MITgcm/model/src/diags_oceanic_surf_flux.F
ViewVC logotype

Contents of /MITgcm/model/src/diags_oceanic_surf_flux.F

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


Revision 1.10 - (show annotations) (download)
Thu Sep 3 20:55:28 2009 UTC (14 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64b, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.9: +9 -124 lines
return to version 1.8, but uses (new) right type of S/R for diagnostic filling

1 C $Header: /u/gcmpack/MITgcm/model/src/diags_oceanic_surf_flux.F,v 1.9 2008/10/25 20:40:51 mlosch Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: DIAGS_OCEANIC_SURF_FLUX
9 C !INTERFACE:
10 SUBROUTINE DIAGS_OCEANIC_SURF_FLUX( myTime, myIter, myThid )
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE DIAGS_OCEANIC_SURF_FLUX
15 C | o Compute Diagnostics of Surface Fluxes (ocean only)
16 C *==========================================================*
17 C \ev
18
19 C !USES:
20 IMPLICIT NONE
21
22 C == Global variables ===
23 #include "SIZE.h"
24 #include "EEPARAMS.h"
25 #include "PARAMS.h"
26 #include "GRID.h"
27 #include "DYNVARS.h"
28 #include "SURFACE.h"
29 #include "FFIELDS.h"
30
31 C !INPUT/OUTPUT PARAMETERS:
32 C == Routine arguments ==
33 C myTime :: Current time in simulation
34 C myIter :: Current iteration number in simulation
35 C myThid :: Thread number for this instance of the routine.
36 _RL myTime
37 INTEGER myIter
38 INTEGER myThid
39 CEOP
40
41 #ifdef ALLOW_DIAGNOSTICS
42 C !LOCAL VARIABLES:
43 C i,j,bi,bj :: loop indices
44 C ks :: surface level index
45 LOGICAL DIAGNOSTICS_IS_ON
46 EXTERNAL DIAGNOSTICS_IS_ON
47 INTEGER i,j,bi,bj
48 INTEGER ks
49 _RL tmp1k(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
50 _RL tmpFac
51
52 C- Time Averages of surface fluxes
53 IF ( usingPCoords ) THEN
54 ks=Nr
55 ELSE
56 ks=1
57 ENDIF
58
59 C- taux (surface momentum flux [Pa=N/m2], positive <-> increase u)
60 CALL DIAGNOSTICS_SCALE_FILL_RS( fu,foFacMom,1,
61 & 'oceTAUX ',0, 1,0,1,1,myThid )
62
63 C- tauy (surface momentum flux [Pa=N/m2], positive <-> increase v)
64 CALL DIAGNOSTICS_SCALE_FILL_RS( fv,foFacMom,1,
65 & 'oceTAUY ',0, 1,0,1,1,myThid )
66
67 C- pLoad (Atmospheric pressure loading [Pa=N/m2])
68 CALL DIAGNOSTICS_FILL_RS( pLoad, 'atmPload',0,1,0,1,1,myThid )
69
70 C- sea-ice loading (expressed in Mass of ice+snow / area unit, [kg/m2])
71 CALL DIAGNOSTICS_FILL_RS( sIceLoad,'sIceLoad',0,1,0,1,1,myThid )
72
73 C- net Fresh Water flux into the ocean (+=down), [kg/m2/s]
74 tmpFac = -1. _d 0
75 CALL DIAGNOSTICS_SCALE_FILL_RS( EmPmR,tmpFac,1,
76 & 'oceFWflx',0, 1,0,1,1,myThid )
77
78 C- net Salt flux into the ocean (+=down), [psu.kg/m2/s ~ g/m2/s]
79 tmpFac = -1. _d 0
80 CALL DIAGNOSTICS_SCALE_FILL_RS( saltFlux,tmpFac,1,
81 & 'oceSflux',0, 1,0,1,1,myThid )
82
83 C- Qnet (= net heat flux into the ocean, +=down, [W/m2])
84 tmpFac = -1. _d 0
85 CALL DIAGNOSTICS_SCALE_FILL_RS( Qnet,tmpFac,1,
86 & 'oceQnet ',0, 1,0,1,1,myThid )
87
88 #ifdef SHORTWAVE_HEATING
89 C- Qsw (= net short-wave into the ocean, +=down, [W/m2])
90 tmpFac = -1. _d 0
91 CALL DIAGNOSTICS_SCALE_FILL_RS( Qsw,tmpFac,1,
92 & 'oceQsw ',0, 1,0,1,1,myThid )
93 #endif
94
95 C- oceFreez (= heating from freezing of sea-water, if allowFreezing=T)
96 tmpFac = HeatCapacity_Cp*rUnit2mass
97 CALL DIAGNOSTICS_SCALE_FILL( surfaceForcingTice,tmpFac,1,
98 & 'oceFreez',0, 1,0,1,1,myThid )
99
100 C- surForcT (=model surface forcing for Temperature [W/m2], >0 increases T
101 tmpFac = HeatCapacity_Cp*rUnit2mass
102 CALL DIAGNOSTICS_SCALE_FILL( surfaceForcingT,tmpFac,1,
103 & 'surForcT',0, 1,0,1,1,myThid )
104
105 C- surForcS (=model surface forcing for Salinity, [g/m2/s], >0 increases S
106 tmpFac = rUnit2mass
107 CALL DIAGNOSTICS_SCALE_FILL( surfaceForcingS,tmpFac,1,
108 & 'surForcS',0, 1,0,1,1,myThid )
109
110 C- TFLUX (=total heat flux, match heat-content variations, [W/m2])
111 IF ( DIAGNOSTICS_IS_ON('TFLUX ',myThid) ) THEN
112 DO bj = myByLo(myThid), myByHi(myThid)
113 DO bi = myBxLo(myThid), myBxHi(myThid)
114 DO j = 1,sNy
115 DO i = 1,sNx
116 tmp1k(i,j,bi,bj) =
117 #ifdef SHORTWAVE_HEATING
118 & -Qsw(i,j,bi,bj)+
119 #endif
120 & (surfaceForcingT(i,j,bi,bj)+surfaceForcingTice(i,j,bi,bj))
121 & *HeatCapacity_Cp*rUnit2mass
122 ENDDO
123 ENDDO
124 #ifdef NONLIN_FRSURF
125 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
126 & .AND. useRealFreshWaterFlux ) THEN
127 DO j=1,sNy
128 DO i=1,sNx
129 tmp1k(i,j,bi,bj) = tmp1k(i,j,bi,bj)
130 & + PmEpR(i,j,bi,bj)*theta(i,j,ks,bi,bj)*HeatCapacity_Cp
131 ENDDO
132 ENDDO
133 ENDIF
134 #endif /* NONLIN_FRSURF */
135 ENDDO
136 ENDDO
137 CALL DIAGNOSTICS_FILL( tmp1k,'TFLUX ',0,1,0,1,1,myThid )
138 ENDIF
139
140 C- SFLUX (=total salt flux, match salt-content variations [g/m2/s])
141 IF ( DIAGNOSTICS_IS_ON('SFLUX ',myThid) ) THEN
142 DO bj = myByLo(myThid), myByHi(myThid)
143 DO bi = myBxLo(myThid), myBxHi(myThid)
144 DO j = 1,sNy
145 DO i = 1,sNx
146 tmp1k(i,j,bi,bj) =
147 & surfaceForcingS(i,j,bi,bj)*rUnit2mass
148 ENDDO
149 ENDDO
150
151 #ifdef NONLIN_FRSURF
152 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
153 & .AND. useRealFreshWaterFlux ) THEN
154 DO j=1,sNy
155 DO i=1,sNx
156 tmp1k(i,j,bi,bj) = tmp1k(i,j,bi,bj)
157 & + PmEpR(i,j,bi,bj)*salt(i,j,ks,bi,bj)
158 ENDDO
159 ENDDO
160 ENDIF
161 #endif /* NONLIN_FRSURF */
162
163 ENDDO
164 ENDDO
165 CALL DIAGNOSTICS_FILL( tmp1k,'SFLUX ',0,1,0,1,1,myThid )
166 ENDIF
167 #endif /* ALLOW_DIAGNOSTICS */
168
169 RETURN
170 END

  ViewVC Help
Powered by ViewVC 1.1.22