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

Annotation of /MITgcm/model/src/calc_wsurf_tr.F

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


Revision 1.1 - (hide annotations) (download)
Fri Jan 5 01:35:00 2007 UTC (17 years, 5 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58x_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58y_post, checkpoint58v_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61l, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Second wave bis: correction of tracer source/sink due to Linear
Free surface

1 dfer 1.1 C $Header: $
2     C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: CALC_WSURF_TR
8     C !INTERFACE:
9     SUBROUTINE CALC_WSURF_TR(thetaFld, saltFld, wVelFld,
10     I myTime, myIter, myThid )
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | SUBROUTINE CALC_WSURF_TR
14     C | o Compute a correction for the source/sink of tracer
15     C | due to the linear free surface.
16     C | o The source/sink results from W*Tr not summing to
17     C | zero at the free surface.
18     C | o Here, we compute an area-weighted mean correction
19     C | to be applied in external_forcing.F
20     C *==========================================================*
21     C \ev
22    
23     C !USES:
24     IMPLICIT NONE
25     C == Global variables
26     #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "PARAMS.h"
29     #include "GRID.h"
30     #include "SURFACE.h"
31    
32     C !INPUT/OUTPUT PARAMETERS:
33     C == Routine arguments ==
34     C myTime :: Current time in simulation
35     C myIter :: Current iteration number in simulation
36     C myThid :: Thread number for this instance of the routine.
37     C thetaFld :: Potential Temperature field
38     C saltFld :: Salinity field
39     C wvelFld :: vertical velocity field
40     _RL myTime
41     INTEGER myIter
42     INTEGER myThid
43     _RL thetaFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
44     _RL saltFld (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
45     _RL wVelFld (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
46    
47     C !LOCAL VARIABLES:
48     C Local variables
49     C i,j,k,bi,bj :: loop counter
50     INTEGER i,j,bi,bj,ks
51     _RL wT_Mean, wS_Mean
52     _RL wT_Tile, wS_Tile
53     CEOP
54    
55     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
56    
57     TsurfCor=0.
58     SsurfCor=0.
59    
60     wT_Mean = 0.
61     wS_Mean = 0.
62    
63     DO bj=myByLo(myThid), myByHi(myThid)
64     DO bi=myBxLo(myThid), myBxHi(myThid)
65     wT_Tile = 0.
66     wS_Tile = 0.
67     DO j=1,sNy
68     DO i=1,sNx
69     ks = ksurfC(i,j,bi,bj)
70     IF (ks.LE.Nr) THEN
71     wT_Tile = wT_Tile
72     & + rA(i,j,bi,bj)*wVelFld(i,j,ks,bi,bj)
73     & *thetaFld(i,j,ks,bi,bj)
74     wS_Tile = wS_Tile
75     & + rA(i,j,bi,bj)*wVelFld(i,j,ks,bi,bj)
76     & *saltFld(i,j,ks,bi,bj)
77     ENDIF
78     ENDDO
79     ENDDO
80     wT_Mean = wT_Mean + wT_Tile
81     wS_Mean = wS_Mean + wS_Tile
82     C- end bi,bj loop.
83     ENDDO
84     ENDDO
85    
86     C-- Global diagnostic :
87     _GLOBAL_SUM_R8(wT_Mean,myThid)
88     _GLOBAL_SUM_R8(wS_Mean,myThid)
89     IF (globalArea.GT.0.) THEN
90     _BEGIN_MASTER( myThid )
91     TsurfCor = wT_Mean / globalArea
92     SsurfCor = wS_Mean / globalArea
93     _END_MASTER( myThid )
94     ENDIF
95     _BARRIER
96    
97     C-----
98    
99     RETURN
100     END

  ViewVC Help
Powered by ViewVC 1.1.22